{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE PatternGuards         #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE ViewPatterns          #-}
{- |
   Module      : Text.Pandoc.Readers.LaTeX
   Copyright   : Copyright (C) 2006-2021 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable

Conversion of LaTeX to 'Pandoc' document.

-}
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.Char (isDigit, isLetter, 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 System.FilePath (addExtension, replaceExtension, takeExtension)
import Text.Pandoc.BCP47 (renderLang)
import Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocPure (PandocPure)
import Text.Pandoc.Class.PandocMonad (PandocMonad (..), getResourcePath,
                                      readFileFromDirs, report,
                                      setResourcePath)
import Text.Pandoc.Error (PandocError (PandocParseError, PandocParsecError))
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.Readers.LaTeX.Types (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)

-- for debugging:
-- import Text.Pandoc.Extensions (getDefaultExtensions)
-- import Text.Pandoc.Class.PandocIO (runIOorExplode, PandocIO)
-- import Debug.Trace (traceShowId)

-- | Parse LaTeX from string and return 'Pandoc' document.
readLaTeX :: PandocMonad m
          => ReaderOptions -- ^ Reader options
          -> Text        -- ^ String to parse (assumes @'\n'@ line endings)
          -> m Pandoc
readLaTeX :: ReaderOptions -> Text -> m Pandoc
readLaTeX ReaderOptions
opts Text
ltx = do
  Either ParseError Pandoc
parsed <- ParsecT [Tok] LaTeXState m Pandoc
-> LaTeXState
-> SourceName
-> [Tok]
-> m (Either ParseError Pandoc)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a)
runParserT ParsecT [Tok] LaTeXState m Pandoc
forall (m :: * -> *). PandocMonad m => LP m Pandoc
parseLaTeX LaTeXState
forall a. Default a => a
def{ sOptions :: ReaderOptions
sOptions = ReaderOptions
opts } SourceName
"source"
               (SourceName -> Text -> [Tok]
tokenize SourceName
"source" (Text -> Text
crFilter Text
ltx))
  case Either ParseError Pandoc
parsed of
    Right Pandoc
result -> Pandoc -> m Pandoc
forall (m :: * -> *) a. Monad m => a -> m a
return Pandoc
result
    Left ParseError
e       -> PandocError -> m Pandoc
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> m Pandoc) -> PandocError -> m Pandoc
forall a b. (a -> b) -> a -> b
$ Text -> ParseError -> PandocError
PandocParsecError Text
ltx ParseError
e

parseLaTeX :: PandocMonad m => LP m Pandoc
parseLaTeX :: LP m Pandoc
parseLaTeX = do
  Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
  ParsecT [Tok] LaTeXState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  LaTeXState
st <- ParsecT [Tok] 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 (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 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') =
       -- handle the case where you have \part or \chapter
       (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 (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 (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


-- testParser :: LP PandocIO a -> Text -> IO a
-- testParser p t = do
--   res <- runIOorExplode (runParserT p defaultLaTeXState{
--             sOptions = def{ readerExtensions =
--               enableExtension Ext_raw_tex $
--                 getDefaultExtensions "latex" }} "source" (tokenize "source" t))
--   case res of
--        Left e  -> error (show e)
--        Right r -> return r


rawLaTeXBlock :: (PandocMonad m, HasMacros s, HasReaderOptions s)
              => ParserT Text s m Text
rawLaTeXBlock :: ParserT Text s m Text
rawLaTeXBlock = do
  ParsecT Text s m Char -> ParsecT Text 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 Text s m Char -> ParsecT Text s m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Text s m Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Text s m Char
-> ParsecT Text s m Char -> ParsecT Text s m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text s m Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter))
  Text
inp <- ParserT Text s m Text
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  let toks :: [Tok]
toks = SourceName -> Text -> [Tok]
tokenize SourceName
"source" Text
inp
  (Blocks, Text) -> Text
forall a b. (a, b) -> b
snd ((Blocks, Text) -> Text)
-> ParsecT Text s m (Blocks, Text) -> ParserT Text s m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ([Tok]
-> Bool
-> LP m Blocks
-> LP m Blocks
-> ParsecT Text s m (Blocks, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
[Tok] -> Bool -> LP m a -> LP m a -> ParserT Text s m (a, Text)
rawLaTeXParser [Tok]
toks Bool
False ((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
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
      ParsecT Text s m (Blocks, Text)
-> ParsecT Text s m (Blocks, Text)
-> ParsecT Text s m (Blocks, Text)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok]
-> Bool
-> LP m Blocks
-> LP m Blocks
-> ParsecT Text s m (Blocks, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
[Tok] -> Bool -> LP m a -> LP m a -> ParserT Text s m (a, Text)
rawLaTeXParser [Tok]
toks Bool
True
             (do [ParsecT [Tok] LaTeXState m Tok] -> ParsecT [Tok] 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 [Tok] LaTeXState m Tok)
-> [Text] -> [ParsecT [Tok] LaTeXState m Tok]
forall a b. (a -> b) -> [a] -> [b]
map Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq
                   [Text
"include", Text
"input", Text
"subfile", Text
"usepackage"])
                 ParsecT [Tok] LaTeXState m Inlines -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tok] 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 (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 Text s m (Blocks, Text)
-> ParsecT Text s m (Blocks, Text)
-> ParsecT Text s m (Blocks, Text)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok]
-> Bool
-> LP m Blocks
-> LP m Blocks
-> ParsecT Text s m (Blocks, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
[Tok] -> Bool -> LP m a -> LP m a -> ParserT Text s m (a, Text)
rawLaTeXParser [Tok]
toks Bool
True
           (LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
environment LP m Blocks -> LP m Blocks -> LP m Blocks
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 [Tok] LaTeXState m [Blocks] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks]
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 (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
beginOrEndCommand)))

-- See #4667 for motivation; sometimes people write macros
-- that just evaluate to a begin or end command, which blockCommand
-- won't accept.
beginOrEndCommand :: PandocMonad m => LP m Blocks
beginOrEndCommand :: LP m Blocks
beginOrEndCommand = 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
$ do
  Tok SourcePos
_ (CtrlSeq Text
name) Text
txt <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
  Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] 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 LP m Blocks
forall (m :: * -> *) a. MonadPlus m => m a
mzero
     else Blocks -> LP m Blocks
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
txt Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [Tok] -> Text
untokenize [Tok]
rawargs)

rawLaTeXInline :: (PandocMonad m, HasMacros s, HasReaderOptions s)
               => ParserT Text s m Text
rawLaTeXInline :: ParserT Text s m Text
rawLaTeXInline = do
  ParsecT Text s m Char -> ParsecT Text 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 Text s m Char -> ParsecT Text s m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Text s m Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Text s m Char
-> ParsecT Text s m Char -> ParsecT Text s m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text s m Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter))
  Text
inp <- ParserT Text s m Text
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  let toks :: [Tok]
toks = SourceName -> Text -> [Tok]
tokenize SourceName
"source" Text
inp
  Text
raw <- (Inlines, Text) -> Text
forall a b. (a, b) -> b
snd ((Inlines, Text) -> Text)
-> ParsecT Text s m (Inlines, Text) -> ParserT Text s m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
          (   [Tok]
-> Bool
-> LP m Inlines
-> LP m Inlines
-> ParsecT Text s m (Inlines, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
[Tok] -> Bool -> LP m a -> LP m a -> ParserT Text s m (a, Text)
rawLaTeXParser [Tok]
toks Bool
True
              (Inlines
forall a. Monoid a => a
mempty Inlines -> ParsecT [Tok] LaTeXState m [Tok] -> LP m Inlines
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 [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT [Tok] LaTeXState m Text -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *). PandocMonad m => LP m Text
rawopt ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced))
              LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlines
          ParsecT Text s m (Inlines, Text)
-> ParsecT Text s m (Inlines, Text)
-> ParsecT Text s m (Inlines, Text)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok]
-> Bool
-> LP m Inlines
-> LP m Inlines
-> ParsecT Text s m (Inlines, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
[Tok] -> Bool -> LP m a -> LP m a -> ParserT Text s m (a, Text)
rawLaTeXParser [Tok]
toks Bool
True (LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineEnvironment LP m Inlines -> LP m Inlines -> LP m Inlines
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
          )
  SourceName
finalbraces <- [SourceName] -> SourceName
forall a. Monoid a => [a] -> a
mconcat ([SourceName] -> SourceName)
-> ParsecT Text s m [SourceName] -> ParsecT Text s m SourceName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT Text s m SourceName -> ParsecT Text s m [SourceName]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (ParsecT Text s m SourceName -> ParsecT Text s m SourceName
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (SourceName -> ParsecT Text s m SourceName
forall s (m :: * -> *) u.
Stream s m Char =>
SourceName -> ParsecT s u m SourceName
string SourceName
"{}")) -- see #5439
  Text -> ParserT Text s m Text
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> ParserT Text s m Text) -> Text -> ParserT Text s m Text
forall a b. (a -> b) -> a -> b
$ Text
raw Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName -> Text
T.pack SourceName
finalbraces

inlineCommand :: PandocMonad m => ParserT Text ParserState m Inlines
inlineCommand :: ParserT Text ParserState m Inlines
inlineCommand = do
  ParsecT Text ParserState m Char -> ParsecT Text 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 Text ParserState m Char -> ParsecT Text ParserState m Char
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Char -> ParsecT Text ParserState m Char
forall s (m :: * -> *) u.
Stream s m Char =>
Char -> ParsecT s u m Char
char Char
'\\' ParsecT Text ParserState m Char
-> ParsecT Text ParserState m Char
-> ParsecT Text ParserState m Char
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ParsecT Text ParserState m Char
forall s (m :: * -> *) u. Stream s m Char => ParsecT s u m Char
letter))
  Text
inp <- ParsecT Text ParserState m Text
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  let toks :: [Tok]
toks = SourceName -> Text -> [Tok]
tokenize SourceName
"source" Text
inp
  (Inlines, Text) -> Inlines
forall a b. (a, b) -> a
fst ((Inlines, Text) -> Inlines)
-> ParsecT Text ParserState m (Inlines, Text)
-> ParserT Text ParserState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Tok]
-> Bool
-> LP m Inlines
-> LP m Inlines
-> ParsecT Text ParserState m (Inlines, Text)
forall (m :: * -> *) s a.
(PandocMonad m, HasMacros s, HasReaderOptions s) =>
[Tok] -> Bool -> LP m a -> LP m a -> ParserT Text s m (a, Text)
rawLaTeXParser [Tok]
toks Bool
True (LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineEnvironment LP m Inlines -> LP m Inlines -> LP m Inlines
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

-- inline elements:

word :: PandocMonad m => LP m Inlines
word :: LP m Inlines
word = Text -> Inlines
str (Text -> Inlines) -> (Tok -> Text) -> Tok -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tok -> Text
untoken (Tok -> Inlines) -> ParsecT [Tok] LaTeXState m Tok -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Tok -> Bool) -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => (Tok -> Bool) -> LP m Tok
satisfyTok Tok -> Bool
isWordTok

inlineGroup :: PandocMonad m => LP m Inlines
inlineGroup :: 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 (t :: * -> *) a. Foldable t => t a -> Bool
null Inlines
ils
     then Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
     else Inlines -> LP m Inlines
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
          -- we need the span so we can detitlecase bibtex entries;
          -- we need to know when something is {C}apitalized

doLHSverb :: PandocMonad m => LP m Inlines
doLHSverb :: 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 [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'|')

mkImage :: PandocMonad m => [(Text, Text)] -> Text -> LP m Inlines
mkImage :: [(Text, Text)] -> Text -> LP m Inlines
mkImage [(Text, Text)]
options (Text -> SourceName
T.unpack -> SourceName
src) = do
   let replaceTextwidth :: (a, Text) -> (a, Text)
replaceTextwidth (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
"%")
              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)
replaceTextwidth
             ([(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 (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 = Text -> Inlines
str Text
"image"
   Text
defaultExt <- (ReaderOptions -> Text) -> ParserT [Tok] LaTeXState m Text
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParserT s st m b
getOption ReaderOptions -> Text
readerDefaultImageExtension
   let exts' :: [SourceName]
exts' = [SourceName
".pdf", SourceName
".png", SourceName
".jpg", SourceName
".mps", SourceName
".jpeg", SourceName
".jbig2", SourceName
".jb2"]
   let exts :: [SourceName]
exts  = [SourceName]
exts' [SourceName] -> [SourceName] -> [SourceName]
forall a. [a] -> [a] -> [a]
++ (SourceName -> SourceName) -> [SourceName] -> [SourceName]
forall a b. (a -> b) -> [a] -> [b]
map ((Char -> Char) -> SourceName -> SourceName
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper) [SourceName]
exts'
   let findFile :: SourceName -> [SourceName] -> m SourceName
findFile SourceName
s [] = SourceName -> m SourceName
forall (m :: * -> *) a. Monad m => a -> m a
return SourceName
s
       findFile SourceName
s (SourceName
e:[SourceName]
es) = do
         let s' :: SourceName
s' = SourceName -> SourceName -> SourceName
addExtension SourceName
s SourceName
e
         Bool
exists <- SourceName -> m Bool
forall (m :: * -> *). PandocMonad m => SourceName -> m Bool
fileExists SourceName
s'
         if Bool
exists
            then SourceName -> m SourceName
forall (m :: * -> *) a. Monad m => a -> m a
return SourceName
s'
            else SourceName -> [SourceName] -> m SourceName
findFile SourceName
s [SourceName]
es
   SourceName
src' <- case SourceName -> SourceName
takeExtension SourceName
src of
               SourceName
"" | Bool -> Bool
not (Text -> Bool
T.null Text
defaultExt) -> SourceName -> ParsecT [Tok] LaTeXState m SourceName
forall (m :: * -> *) a. Monad m => a -> m a
return (SourceName -> ParsecT [Tok] LaTeXState m SourceName)
-> SourceName -> ParsecT [Tok] LaTeXState m SourceName
forall a b. (a -> b) -> a -> b
$ SourceName -> SourceName -> SourceName
addExtension SourceName
src (SourceName -> SourceName) -> SourceName -> SourceName
forall a b. (a -> b) -> a -> b
$ Text -> SourceName
T.unpack Text
defaultExt
                  | Bool
otherwise -> SourceName -> [SourceName] -> ParsecT [Tok] LaTeXState m SourceName
forall (m :: * -> *).
PandocMonad m =>
SourceName -> [SourceName] -> m SourceName
findFile SourceName
src [SourceName]
exts
               SourceName
_  -> SourceName -> ParsecT [Tok] LaTeXState m SourceName
forall (m :: * -> *) a. Monad m => a -> m a
return SourceName
src
   Inlines -> LP m Inlines
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 (SourceName -> Text
T.pack SourceName
src') Text
"" Inlines
alt

doxspace :: PandocMonad m => LP m Inlines
doxspace :: LP m Inlines
doxspace =
  (Inlines
space Inlines -> ParsecT [Tok] LaTeXState m Tok -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ((Tok -> Bool) -> ParsecT [Tok] 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 (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
forall a. Monoid a => a
mempty
  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


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 (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 :: 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 [Tok] 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 [Tok] LaTeXState m Tok -> LP m [Tok])
-> ParsecT [Tok] LaTeXState m Tok -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m Tok -> LP m [Tok])
-> ParsecT [Tok] LaTeXState m Tok -> LP m [Tok]
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'')
   LP m Inlines -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m Tok -> LP m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'“') (ParsecT [Tok] LaTeXState m Tok -> LP m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (ParsecT [Tok] LaTeXState m Tok -> LP m ())
-> ParsecT [Tok] LaTeXState m Tok -> LP m ()
forall a b. (a -> b) -> a -> b
$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'”')
   -- the following is used by babel for localized quotes:
   LP m Inlines -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m Tok] -> LP m [Tok]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'"', Char -> ParsecT [Tok] 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 [Tok] LaTeXState m Tok] -> LP m [Tok]
forall (t :: * -> *) (m :: * -> *) a.
(Traversable t, Monad m) =>
t (m a) -> m (t a)
sequence [Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'"', Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\''])

singleQuote :: PandocMonad m => LP m Inlines
singleQuote :: 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 [Tok] LaTeXState m Tok -> LP m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT [Tok] 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 [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'' ParsecT [Tok] LaTeXState m Tok -> LP m () -> LP m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                           ParsecT [Tok] 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 [Tok] 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 (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 [Tok] LaTeXState m Tok -> LP m [Tok]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Char -> ParsecT [Tok] 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 [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'’' ParsecT [Tok] LaTeXState m Tok -> LP m () -> LP m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                                  ParsecT [Tok] 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 [Tok] 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' :: (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 [Tok] 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 [Tok] LaTeXState m Extensions
-> ParsecT [Tok] LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReaderOptions -> Extensions)
-> ParsecT [Tok] LaTeXState m Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParserT s st m b
getOption ReaderOptions -> Extensions
readerExtensions
  if Bool
smart
     then do
       [Inlines]
ils <- LP m Inlines -> ParsecT [Tok] LaTeXState m [Inlines]
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 (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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> LP m Inlines
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 (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 :: Text -> LP m Inlines
lit = Inlines -> LP m Inlines
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Inlines -> LP m Inlines)
-> (Text -> Inlines) -> Text -> LP 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 :: 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 [Tok] LaTeXState m [Citation] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines
-> CitationMode -> Bool -> ParsecT [Tok] 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 (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 -- currently ignored
  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 [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m (Maybe Tok)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m Tok
 -> ParsecT [Tok] LaTeXState m (Maybe Tok))
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m (Maybe Tok)
forall a b. (a -> b) -> a -> b
$ SourceName -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => SourceName -> LP m Tok
symbolIn (SourceName
".:;?!" :: [Char])  -- currently ignored
  Blocks -> LP m Blocks
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' :: LP m Inlines
inlineCommand' = 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
$ do
  Tok SourcePos
_ (CtrlSeq Text
name) Text
cmd <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
  Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] 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 [Tok] LaTeXState m Text
-> ParsecT [Tok] 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 [Tok] LaTeXState m Text
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 [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp)
  Text
overlay <- Text
-> ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] 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 [Tok] 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]
ordNub [Text
name', Text
name] -- check non-starred as fallback
  let raw :: LP m Inlines
raw = do
       Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParserT s st m ()
guardEnabled Extension
Ext_raw_tex ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Inlines
rawInline Text
"latex" Text
rawcommand))
         LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> LP m Inlines
forall a (m :: * -> *) s u.
(Monoid a, PandocMonad m) =>
Text -> ParserT s u m a
ignore Text
rawcommand
  LP m Inlines -> [Text] -> Map Text (LP m Inlines) -> LP m Inlines
forall k v. Ord k => v -> [k] -> Map k v -> v
lookupListDefault LP m Inlines
raw [Text]
names Map Text (LP m Inlines)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Inlines)
inlineCommands

tok :: PandocMonad m => LP m Inlines
tok :: 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
. Text -> Text -> [Text]
T.splitOn Text
"\\"
  where
    isEscapable :: Char -> Bool
isEscapable Char
c = Char
c Char -> Text -> Bool
`elemText` 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 :: 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", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
ttfamily)
    , (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
"alert", LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts LP m () -> LP m Inlines -> LP m Inlines
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) -- beamer
    , (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
"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 [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] 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 [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] 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 [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m (Inlines -> Inlines)
-> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
    -- old TeX commands
    , (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", Text -> Inlines
code (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify ([Inline] -> Text) -> (Inlines -> [Inline]) -> Inlines -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList (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) -- textcase
    , (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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> Inlines
note (Blocks -> Inlines)
-> ParsecT [Tok] LaTeXState m Blocks -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Blocks
-> ParsecT [Tok] LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT [Tok] 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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> Inlines
note (Blocks -> Inlines)
-> ParsecT [Tok] LaTeXState m Blocks -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Blocks
-> ParsecT [Tok] LaTeXState m Blocks
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT [Tok] LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block)
    , (Text
"passthrough", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok) -- \passthrough macro used by latex writer
                           -- for listings
    , (Text
"includegraphics", do [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] 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 [Tok] LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
                             [Tok]
src <- ParsecT [Tok] 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)
    -- hyperref
    , (Text
"url", (\Text
url -> Text -> Text -> Inlines -> Inlines
link 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 [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
                    ParsecT [Tok] 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 [Tok] LaTeXState m [Tok] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl)
    , (Text
"href", do [Tok]
url <- ParsecT [Tok] 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)
    -- hyphenat
    , (Text
"nohyphens", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok)
    , (Text
"textnhtt", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
ttfamily)
    , (Text
"nhttfamily", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
ttfamily)
    -- LaTeX colors
    , (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")
    -- xspace
    , (Text
"xspace", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doxspace)
    -- etoolbox
    , (Text
"ifstrequal", LP m Inlines
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
ifstrequal)
    , (Text
"newtoggle", ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> LP m Inlines) -> LP m Inlines
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 [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> LP m Inlines) -> LP m Inlines
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 [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> LP m Inlines) -> LP m Inlines
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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline)
    -- include
    , (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")
    -- soul package
    , (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)
    -- ulem package
    , (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)
    -- plain tex stuff that should just be passed through as raw tex
    , (Text
"ifdim", LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
ifdim)
    ]

lettrine :: PandocMonad m => LP m Inlines
lettrine :: LP m Inlines
lettrine = do
  ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m (Maybe Text)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT [Tok] 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 (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 :: LP m Inlines
ifdim = do
  [Tok]
contents <- ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] 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 [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok (Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"fi")
  Inlines -> LP m Inlines
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

hyperlink :: PandocMonad m => LP m Inlines
hyperlink :: LP m Inlines
hyperlink = 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
$ do
  Text
src <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  Inlines
lab <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
  Inlines -> LP m Inlines
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 -> 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 :: LP m Inlines
hyperref = 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
$ 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracketedToks ParsecT [Tok] LaTeXState m [Tok]
-> LP m () -> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp))
       ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracedUrl)
  Text -> Text -> Inlines -> Inlines
link Text
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

hypertargetBlock :: PandocMonad m => LP m Blocks
hypertargetBlock :: LP m Blocks
hypertargetBlock = 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
$ do
  Text
ref <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  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
  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 -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
bs
       [Block]
_                        -> Blocks -> LP m Blocks
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
ref, [], []) Blocks
bs

hypertargetInline :: PandocMonad m => LP m Inlines
hypertargetInline :: LP m Inlines
hypertargetInline = 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
$ do
  Text
ref <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  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
  Inlines -> LP m Inlines
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 (Text
ref, [], []) Inlines
ils

newToggle :: (Monoid a, PandocMonad m) => [Tok] -> LP m a
newToggle :: [Tok] -> LP m a
newToggle [Tok]
name = do
  (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st ->
    LaTeXState
st{ sToggles :: Map Text Bool
sToggles = Text -> Bool -> Map Text Bool -> Map Text Bool
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert ([Tok] -> Text
untokenize [Tok]
name) Bool
False (LaTeXState -> Map Text Bool
sToggles LaTeXState
st) }
  a -> LP 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 :: Bool -> [Tok] -> LP m a
setToggle Bool
on [Tok]
name = do
  (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st ->
    LaTeXState
st{ sToggles :: Map Text Bool
sToggles = (Bool -> Bool) -> Text -> Map Text Bool -> Map Text Bool
forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
M.adjust (Bool -> Bool -> Bool
forall a b. a -> b -> a
const Bool
on) ([Tok] -> Text
untokenize [Tok]
name) (LaTeXState -> Map Text Bool
sToggles LaTeXState
st) }
  a -> LP m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
forall a. Monoid a => a
mempty

ifToggle :: PandocMonad m => LP m ()
ifToggle :: 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]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
  [Tok]
no <- 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 [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m (Map Text Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  [Tok]
inp <- LP m [Tok]
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  -> [Tok] -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok]
yes [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
inp)
                Just Bool
False -> [Tok] -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok]
no  [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++ [Tok]
inp)
                Maybe Bool
Nothing    -> do
                  SourcePos
pos <- ParsecT [Tok] 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 (m :: * -> *) a. Monad m => a -> m a
return ()

ifstrequal :: (PandocMonad m, Monoid a) => LP m a
ifstrequal :: 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]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  [Tok]
ifnotequal <- LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  if Inlines
str1 Inlines -> Inlines -> Bool
forall a. Eq a => a -> a -> Bool
== Inlines
str2
     then LP m [Tok]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput LP m [Tok]
-> ([Tok] -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Tok] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok] -> ParsecT [Tok] LaTeXState m ())
-> ([Tok] -> [Tok]) -> [Tok] -> ParsecT [Tok] LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Tok]
ifequal [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++)
     else LP m [Tok]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput LP m [Tok]
-> ([Tok] -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Tok] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok] -> ParsecT [Tok] LaTeXState m ())
-> ([Tok] -> [Tok]) -> [Tok] -> ParsecT [Tok] LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([Tok]
ifnotequal [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++)
  a -> LP 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 :: 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

ttfamily :: PandocMonad m => LP m Inlines
ttfamily :: LP m Inlines
ttfamily = Text -> Inlines
code (Text -> Inlines) -> (Inlines -> Text) -> Inlines -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Inline] -> Text
forall a. Walkable Inline a => a -> Text
stringify ([Inline] -> Text) -> (Inlines -> [Inline]) -> Inlines -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
toList (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 -- non-breakable space
    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 -- non-breakable space
    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"
      -- \ignore{} is used conventionally in literate haskell for definitions
      -- that are to be processed by the compiler but not printed.
   , 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 :: 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 k a. Ord k => [k] -> Map k a -> Maybe a
lookupList
  where lookupList :: [k] -> Map k a -> Maybe a
lookupList [k]
l Map k 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
$ (k -> Maybe a) -> [k] -> [Maybe a]
forall a b. (a -> b) -> [a] -> [b]
map (k -> Map k a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
`M.lookup` Map k a
m) [k]
l

inline :: PandocMonad m => LP m Inlines
inline :: LP m Inlines
inline = do
  Tok SourcePos
pos TokType
toktype Text
t <- ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok
  let symbolAsString :: LP m Inlines
symbolAsString = Text -> Inlines
str (Text -> Inlines) -> (Tok -> Text) -> Tok -> Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tok -> Text
untoken (Tok -> Inlines) -> ParsecT [Tok] LaTeXState m Tok -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anySymbol
  let unescapedSymbolAsString :: LP m Inlines
unescapedSymbolAsString =
        do Text
s <- Tok -> Text
untoken (Tok -> Text)
-> ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anySymbol
           LogMessage -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
ParsingUnescaped Text
s SourcePos
pos
           Inlines -> LP m Inlines
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
s
  case TokType
toktype of
    TokType
Comment     -> Inlines
forall a. Monoid a => a
mempty Inlines -> ParsecT [Tok] LaTeXState m () -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
comment
    TokType
Spaces      -> Inlines
space Inlines -> ParsecT [Tok] LaTeXState m () -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
whitespace
    TokType
Newline     -> Inlines
softbreak Inlines -> ParsecT [Tok] LaTeXState m () -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
endline
    TokType
Word        -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
word
    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 [Tok] LaTeXState m Char -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 [Tok] LaTeXState m Char -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Char
forall (m :: * -> *). PandocMonad m => LP m Char
primEscape
    TokType
Symbol      ->
      case Text
t of
        Text
"-"     -> Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'-' ParsecT [Tok] LaTeXState m Tok -> LP m Inlines -> LP m Inlines
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 -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'-' ParsecT [Tok] LaTeXState m Tok -> LP m Inlines -> LP m Inlines
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 -> ParsecT [Tok] LaTeXState m Tok -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'-'))
        Text
"'"     -> Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'' ParsecT [Tok] LaTeXState m Tok -> LP m Inlines -> LP m Inlines
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 -> ParsecT [Tok] LaTeXState m Tok -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'\'')
        Text
"~"     -> Text -> Inlines
str Text
"\160" Inlines -> ParsecT [Tok] LaTeXState m Tok -> LP m Inlines
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'~'
        Text
"`"     -> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
doubleQuote LP m Inlines -> LP m Inlines -> LP m Inlines
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 (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 (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 (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 (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 (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 (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
unescapedSymbolAsString
        Text
"|"     -> (Extension -> ParsecT [Tok] LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParserT s st m ()
guardEnabled Extension
Ext_literate_haskell ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
                    Char -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Char -> LP m Tok
symbol Char
'|' ParsecT [Tok] LaTeXState m Tok -> LP m Inlines -> LP m Inlines
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 (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 (m :: * -> *) a. MonadPlus m => m a
mzero
        Text
"}"     -> LP m Inlines
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 (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 (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineEnvironment
                  LP m Inlines -> LP m Inlines -> LP m Inlines
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inlineGroup
    TokType
_           -> LP m Inlines
forall (m :: * -> *) a. MonadPlus m => m a
mzero

inlines :: PandocMonad m => LP m Inlines
inlines :: LP m Inlines
inlines = [Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tok] LaTeXState m [Inlines] -> LP m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Inlines -> ParsecT [Tok] LaTeXState m [Inlines]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline

opt :: PandocMonad m => LP m Inlines
opt :: LP m Inlines
opt = do
  [Tok]
toks <- ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
bracketedToks ParsecT [Tok] LaTeXState m [Tok]
-> LP m () -> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
sp)
  -- now parse the toks as inlines
  LaTeXState
st <- ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Either ParseError Inlines
parsed <- ParsecT [Tok] LaTeXState (ParsecT [Tok] LaTeXState m) Inlines
-> LaTeXState
-> SourceName
-> [Tok]
-> ParsecT [Tok] LaTeXState m (Either ParseError Inlines)
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> u -> SourceName -> s -> m (Either ParseError a)
runParserT ([Inlines] -> Inlines
forall a. Monoid a => [a] -> a
mconcat ([Inlines] -> Inlines)
-> ParsecT [Tok] LaTeXState (ParsecT [Tok] LaTeXState m) [Inlines]
-> ParsecT [Tok] LaTeXState (ParsecT [Tok] LaTeXState m) Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState (ParsecT [Tok] LaTeXState m) Inlines
-> ParsecT [Tok] LaTeXState (ParsecT [Tok] LaTeXState m) [Inlines]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT [Tok] LaTeXState (ParsecT [Tok] LaTeXState m) Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
inline) LaTeXState
st SourceName
"bracketed option" [Tok]
toks
  case Either ParseError Inlines
parsed of
    Right Inlines
result -> Inlines -> LP m Inlines
forall (m :: * -> *) a. Monad m => a -> m a
return Inlines
result
    Left ParseError
e       -> PandocError -> LP m Inlines
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
$ Text -> ParseError -> PandocError
PandocParsecError ([Tok] -> Text
untokenize [Tok]
toks) ParseError
e

-- block elements:

preamble :: PandocMonad m => LP m Blocks
preamble :: LP m Blocks
preamble = [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT [Tok] LaTeXState m [Blocks] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many LP m Blocks
preambleBlock
  where preambleBlock :: LP m Blocks
preambleBlock =  (Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1)
                     LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (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 (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
filecontents
                     LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Blocks
forall a. Monoid a => a
mempty Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand)
                     LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m [Tok] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced)
                     LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (do ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] 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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => Text -> LP m ()
begin_ Text
"document")
                             LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok
                             Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty)

rule :: PandocMonad m => LP m Blocks
rule :: 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 [Tok] LaTeXState m Inlines
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
  Inlines
_thickness <- ParsecT [Tok] LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
  -- 0-width rules are used to fix spacing issues:
  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 (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
    Maybe Double
_ -> Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
horizontalRule

paragraph :: PandocMonad m => LP m Blocks
paragraph :: 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 [Tok] LaTeXState m [Inlines]
-> ParsecT [Tok] LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Inlines
-> ParsecT [Tok] 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 [Tok] 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 (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty
     else Blocks -> LP m Blocks
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 :: Text -> LP m Blocks -> LP m Blocks
rawBlockOr Text
name LP m Blocks
fallback = do
  -- if raw_tex allowed, don't process
  Bool
parseRaw <- Extension -> Extensions -> Bool
extensionEnabled Extension
Ext_raw_tex (Extensions -> Bool)
-> ParsecT [Tok] LaTeXState m Extensions
-> ParsecT [Tok] LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (ReaderOptions -> Extensions)
-> ParsecT [Tok] LaTeXState m Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParserT s st m b
getOption ReaderOptions -> Extensions
readerExtensions
  if Bool
parseRaw
     then Text -> Text -> Blocks
rawBlock Text
"latex" (Text -> Blocks) -> ParsecT [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ParsecT [Tok] 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 :: LP m Blocks
doSubfile = do
  ParsecT [Tok] LaTeXState m Inlines -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tok] LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
  SourceName
f <- Text -> SourceName
T.unpack (Text -> SourceName) -> ([Tok] -> Text) -> [Tok] -> SourceName
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] -> SourceName)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m SourceName
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  [Tok]
oldToks <- ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput
  [Tok] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput []
  SourceName -> SourceName -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *).
PandocMonad m =>
SourceName -> SourceName -> LP m ()
insertIncluded SourceName
".tex" SourceName
f
  Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
  ParsecT [Tok] LaTeXState m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  [Tok] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput [Tok]
oldToks
  Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
bs

include :: (PandocMonad m, Monoid a) => Text -> LP m a
include :: Text -> LP m a
include Text
name = do
  ParsecT [Tok] LaTeXState m Inlines -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tok] LaTeXState m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt
  [SourceName]
fs <- (Text -> SourceName) -> [Text] -> [SourceName]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> SourceName
T.unpack (Text -> SourceName) -> (Text -> Text) -> Text -> SourceName
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] -> [SourceName])
-> ([Tok] -> [Text]) -> [Tok] -> [SourceName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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] -> [SourceName])
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [SourceName]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  let defaultExt :: SourceName
defaultExt | Text
name Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"usepackage" = SourceName
".sty"
                 | Bool
otherwise            = SourceName
".tex"
  (SourceName -> ParsecT [Tok] LaTeXState m ())
-> [SourceName] -> ParsecT [Tok] LaTeXState m ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ (SourceName -> SourceName -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *).
PandocMonad m =>
SourceName -> SourceName -> LP m ()
insertIncluded SourceName
defaultExt) [SourceName]
fs
  a -> LP 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 :: SourceName -> LP m (Maybe Text)
readFileFromTexinputs SourceName
fp = do
  Map Text Text
fileContentsMap <- LaTeXState -> Map Text Text
sFileContents (LaTeXState -> Map Text Text)
-> ParsecT [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m (Map Text Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 (SourceName -> Text
T.pack SourceName
fp) Map Text Text
fileContentsMap of
    Just Text
t -> Maybe Text -> LP m (Maybe Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
t)
    Maybe Text
Nothing -> do
      [SourceName]
dirs <- (Text -> SourceName) -> [Text] -> [SourceName]
forall a b. (a -> b) -> [a] -> [b]
map Text -> SourceName
T.unpack ([Text] -> [SourceName])
-> (Maybe Text -> [Text]) -> Maybe Text -> [SourceName]
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
':') (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 -> [SourceName])
-> LP m (Maybe Text) -> ParsecT [Tok] LaTeXState m [SourceName]
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"
      [SourceName] -> SourceName -> LP m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
[SourceName] -> SourceName -> m (Maybe Text)
readFileFromDirs [SourceName]
dirs SourceName
fp

insertIncluded :: PandocMonad m
               => FilePath
               -> FilePath
               -> LP m ()
insertIncluded :: SourceName -> SourceName -> LP m ()
insertIncluded SourceName
defaultExtension SourceName
f' = do
  let f :: SourceName
f = case SourceName -> SourceName
takeExtension SourceName
f' of
                SourceName
".tex" -> SourceName
f'
                SourceName
".sty" -> SourceName
f'
                SourceName
_      -> SourceName -> SourceName -> SourceName
addExtension SourceName
f' SourceName
defaultExtension
  SourcePos
pos <- ParsecT [Tok] 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 [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> LP m () -> LP m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (SourceName -> Text
T.pack SourceName
f Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
containers) (LP m () -> LP m ()) -> LP m () -> LP m ()
forall a b. (a -> b) -> a -> b
$
    PandocError -> LP m ()
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError (PandocError -> LP m ()) -> PandocError -> LP m ()
forall a b. (a -> b) -> a -> b
$ Text -> PandocError
PandocParseError (Text -> PandocError) -> Text -> PandocError
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ SourceName
"Include file loop at " SourceName -> SourceName -> SourceName
forall a. [a] -> [a] -> [a]
++ SourcePos -> SourceName
forall a. Show a => a -> SourceName
show SourcePos
pos
  (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
$ Text -> LaTeXState -> LaTeXState
forall st. HasIncludeFiles st => Text -> st -> st
addIncludeFile (Text -> LaTeXState -> LaTeXState)
-> Text -> LaTeXState -> LaTeXState
forall a b. (a -> b) -> a -> b
$ SourceName -> Text
T.pack SourceName
f
  Maybe Text
mbcontents <- SourceName -> LP m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
SourceName -> LP m (Maybe Text)
readFileFromTexinputs SourceName
f
  Text
contents <- case Maybe Text
mbcontents of
                   Just Text
s -> Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
s
                   Maybe Text
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
CouldNotLoadIncludeFile (SourceName -> Text
T.pack SourceName
f) SourcePos
pos
                     Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
  ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) s u. Monad m => ParsecT s u m s
getInput ParsecT [Tok] LaTeXState m [Tok] -> ([Tok] -> LP m ()) -> LP m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [Tok] -> LP m ()
forall (m :: * -> *) s u. Monad m => s -> ParsecT s u m ()
setInput ([Tok] -> LP m ()) -> ([Tok] -> [Tok]) -> [Tok] -> LP m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceName -> Text -> [Tok]
tokenize SourceName
f Text
contents [Tok] -> [Tok] -> [Tok]
forall a. [a] -> [a] -> [a]
++)
  (LaTeXState -> LaTeXState) -> LP m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState LaTeXState -> LaTeXState
forall st. HasIncludeFiles st => st -> st
dropLatestIncludeFile

authors :: PandocMonad m => LP m ()
authors :: LP m ()
authors = 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
$ do
  LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
bgroup
  let oneAuthor :: ParsecT [Tok] 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 [Tok] LaTeXState m [Blocks]
-> ParsecT [Tok] LaTeXState m Inlines
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Blocks
-> ParsecT [Tok] 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 [Tok] LaTeXState m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block
  [Inlines]
auths <- ParsecT [Tok] LaTeXState m Inlines
-> LP m Tok -> ParsecT [Tok] 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 [Tok] 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] -> LP 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 :: LP m Blocks
looseItem = do
  Bool
inListItem <- LaTeXState -> Bool
sInListItem (LaTeXState -> Bool)
-> ParsecT [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Bool -> Bool
not Bool
inListItem
  ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty

epigraph :: PandocMonad m => LP m Blocks
epigraph :: 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 (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 :: 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 [Tok] LaTeXState m Text
-> ParsecT [Tok] 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 [Tok] LaTeXState m Text
 -> ParsecT [Tok] LaTeXState m Text)
-> ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m Text
forall a b. (a -> b) -> a -> b
$
          ParsecT [Tok] LaTeXState m Text -> ParsecT [Tok] 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 [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"label"
               ParsecT [Tok] LaTeXState m Tok -> LP m () -> LP m ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces LP m ()
-> ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 :: Bool
sHasChapters = Bool
True }
  Bool -> LP m () -> LP m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Text
"unnumbered" Text -> [Text] -> 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 [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m DottedNum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
    Bool
hasChapters <- LaTeXState -> Bool
sHasChapters (LaTeXState -> Bool)
-> ParsecT [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 :: DottedNum
sLastHeaderNum = DottedNum
num
                           , sLabels :: Map Text [Inline]
sLabels = Text -> [Inline] -> Map Text [Inline] -> Map Text [Inline]
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
lab
                              [Text -> Inline
Str (DottedNum -> Text
renderDottedNum DottedNum
num)]
                              (LaTeXState -> Map Text [Inline]
sLabels LaTeXState
st) }
  Attr
attr' <- Attr -> Inlines -> ParserT [Tok] LaTeXState m Attr
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st, HasLogMessages st,
 HasIdentifierList st) =>
Attr -> Inlines -> ParserT s st m Attr
registerHeader (Text
lab, [Text]
classes, [(Text, Text)]
kvs) Inlines
contents
  Blocks -> LP m Blocks
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 :: LP m Blocks
blockCommand = 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
$ do
  Tok SourcePos
_ (CtrlSeq Text
name) Text
txt <- LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyControlSeq
  Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] 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 [Tok] LaTeXState m Text
-> ParsecT [Tok] 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 [Tok] LaTeXState m Text
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 [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] 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]
ordNub [Text
name', Text
name]
  let rawDefiniteBlock :: LP m Blocks
rawDefiniteBlock = do
        Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> Bool
isBlockCommand Text
name
        Text
rawcontents <- Text -> Text -> ParsecT [Tok] 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 [Tok] LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParserT s st m ()
guardEnabled Extension
Ext_raw_tex ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
rawBlock Text
"latex" Text
rawcontents))
          LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> LP m Blocks
forall a (m :: * -> *) s u.
(Monoid a, PandocMonad m) =>
Text -> ParserT s u m a
ignore Text
rawcontents
  -- heuristic:  if it could be either block or inline, we
  -- treat it if block if we have a sequence of block
  -- commands followed by a newline.  But we stop if we
  -- hit a \startXXX, since this might start a raw ConTeXt
  -- environment (this is important because this parser is
  -- used by the Markdown reader).
  let startCommand :: ParsecT [Tok] LaTeXState m ()
startCommand = ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] 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 [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text
"start" Text -> Text -> Bool
`T.isPrefixOf` Text
n
  let rawMaybeBlock :: LP m Blocks
rawMaybeBlock = 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
$ do
        Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParserT s st m ()
guardEnabled Extension
Ext_raw_tex ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>>
                    Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Text -> Text -> Blocks
rawBlock Text
"latex" Text
rawcontents))
                   LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> LP m Blocks
forall a (m :: * -> *) s u.
(Monoid a, PandocMonad m) =>
Text -> ParserT s u m a
ignore Text
rawcontents
        [Blocks]
rest <- LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks])
-> LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks]
forall a b. (a -> b) -> a -> b
$ ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] 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 [Tok] LaTeXState m ()
startCommand ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blockCommand
        ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead (ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
blankline ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ParsecT [Tok] LaTeXState m ()
startCommand
        Blocks -> LP m Blocks
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
curr Blocks -> Blocks -> Blocks
forall a. Semigroup a => a -> a -> a
<> [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat [Blocks]
rest
  let raw :: LP m Blocks
raw = LP m Blocks
rawDefiniteBlock LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> LP m Blocks
rawMaybeBlock
  LP m Blocks -> [Text] -> Map Text (LP m Blocks) -> LP m Blocks
forall k v. Ord k => v -> [k] -> Map k v -> v
lookupListDefault LP m Blocks
raw [Text]
names Map Text (LP m Blocks)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
blockCommands

closing :: PandocMonad m => LP m Blocks
closing :: LP m Blocks
closing = do
  Inlines
contents <- LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
tok
  LaTeXState
st <- ParsecT [Tok] 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 (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 :: LP m Blocks
parbox = 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
$ do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced -- size
  Bool
oldInTableCell <- LaTeXState -> Bool
sInTableCell (LaTeXState -> Bool)
-> ParsecT [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  -- see #5711
  (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 :: Bool
sInTableCell = Bool
False }
  Blocks
res <- 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
  (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 :: Bool
sInTableCell = Bool
oldInTableCell }
  Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
res

blockCommands :: PandocMonad m => M.Map Text (LP m Blocks)
blockCommands :: 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"title")
                         ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Blocks -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
authors))
   -- -- in letter class, temp. store address & sig as title, author
   , (Text
"address", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
authors))
   , (Text
"date", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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)
   -- KOMA-Script metadata commands
   , (Text
"extratitle", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Inlines -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"dedication"))
   -- sectioning
   , (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 Attr
nullAttr (-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)
   -- beamer slides
   , (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)
   -- letters
   , (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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
closing)
   -- memoir
   , (Text
"plainbreak", LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced LP m [Tok] -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
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 (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 (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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
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 (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 (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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Blocks -> LP m Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
   , (Text
"pfbreak", Blocks -> LP m Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
   , (Text
"pfbreak*", Blocks -> LP m Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
   --
   , (Text
"hrule", Blocks -> LP m Blocks
forall (f :: * -> *) a. Applicative f => a -> f a
pure Blocks
horizontalRule)
   , (Text
"strut", Blocks -> LP m Blocks
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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m [Tok] -> LP m [Tok]
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 (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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ LP m Inlines -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m [Tok] -> LP m [Tok]
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         Text -> [Inlines] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"bibliography" ([Inlines] -> ParsecT [Tok] LaTeXState m ())
-> ([Tok] -> [Inlines]) -> [Tok] -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ (ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m [Tok] -> LP m [Tok]
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>=
         Text -> [Inlines] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a.
(PandocMonad m, ToMetaValue a) =>
Text -> a -> LP m ()
addMeta Text
"bibliography" ([Inlines] -> ParsecT [Tok] LaTeXState m ())
-> ([Tok] -> [Inlines]) -> [Tok] -> ParsecT [Tok] 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok)
   -- includes
   , (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)
   -- polyglossia
   , (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)
   -- hyperlink
   , (Text
"hypertarget", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
hypertargetBlock)
   -- LaTeX colors
   , (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")
   -- csquotes
   , (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 (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 (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 (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 (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)
   -- include
   , (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 -> 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
"usepackage")
   -- preamble
   , (Text
"PackageError", Blocks
forall a. Monoid a => a
mempty Blocks -> LP m [Tok] -> LP m Blocks
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 (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 (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced))
   -- epigraph package
   , (Text
"epigraph", LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
epigraph)
   ]


environments :: PandocMonad m => M.Map Text (LP m Blocks)
environments :: 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 [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m ()
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m ()
skipMany ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok)
   , (Text
"abstract", Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
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 [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Text -> Blocks -> ParsecT [Tok] 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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m (Maybe [Tok])
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Inlines -> LP m Inlines
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 (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 [Tok] LaTeXState m [Blocks] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT [Tok] LaTeXState m [Blocks]
-> ParsecT [Tok] LaTeXState m [Blocks]
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
listenv Text
"itemize" (LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks]
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 [Tok] LaTeXState m [(Inlines, [Blocks])] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT [Tok] LaTeXState m [(Inlines, [Blocks])]
-> ParsecT [Tok] LaTeXState m [(Inlines, [Blocks])]
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
listenv Text
"description" (ParsecT [Tok] LaTeXState m (Inlines, [Blocks])
-> ParsecT [Tok] LaTeXState m [(Inlines, [Blocks])]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT [Tok] 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 [Tok] LaTeXState m ()
forall s (m :: * -> *) a st.
(Stream s m a, HasReaderOptions st) =>
Extension -> ParserT s st m ()
guardEnabled Extension
Ext_literate_haskell ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*>
       (Attr -> Text -> Blocks
codeBlockWith (Text
"",[Text
"haskell",Text
"literate"],[]) (Text -> Blocks) -> ParsecT [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT [Tok] 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 [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"comment")
   , (Text
"verbatim", Text -> Blocks
codeBlock (Text -> Blocks) -> ParsecT [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT [Tok] 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 [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] LaTeXState m Attr
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] 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 [Tok] LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
                       Attr -> Text -> Blocks
codeBlockWith Attr
attr (Text -> Blocks) -> ParsecT [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT [Tok] 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")
   -- amsthm
   , (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)
   -- etoolbox
   , (Text
"ifstrequal", LP m Blocks
forall (m :: * -> *) a. (PandocMonad m, Monoid a) => LP m a
ifstrequal)
   , (Text
"newtoggle", ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> LP m Blocks) -> LP m Blocks
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 [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> LP m Blocks) -> LP m Blocks
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 [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ([Tok] -> LP m Blocks) -> LP m Blocks
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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
ifToggle ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block)
   ]

filecontents :: PandocMonad m => LP m Blocks
filecontents :: LP m Blocks
filecontents = 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
$ do
  Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"begin"
  Text
name <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  Bool -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (Bool -> ParsecT [Tok] LaTeXState m ())
-> Bool -> ParsecT [Tok] 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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  Text
fp <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  Text
txt <- Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
name
  (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st ->
    LaTeXState
st{ sFileContents :: Map Text Text
sFileContents = Text -> Text -> Map Text Text -> Map Text Text
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
fp Text
txt (LaTeXState -> Map Text Text
sFileContents LaTeXState
st) }
  Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty

environment :: PandocMonad m => LP m Blocks
environment :: LP m Blocks
environment = 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
$ do
  Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"begin"
  Text
name <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  LP m Blocks -> Text -> Map Text (LP m Blocks) -> LP m Blocks
forall k a. Ord k => a -> k -> Map k a -> a
M.findWithDefault LP m Blocks
forall (m :: * -> *) a. MonadPlus m => m a
mzero Text
name Map Text (LP m Blocks)
forall (m :: * -> *). PandocMonad m => Map Text (LP m Blocks)
environments LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|>
    LP m Blocks -> LP m Inlines -> Text -> LP m Blocks
forall (m :: * -> *).
PandocMonad m =>
LP m Blocks -> LP m Inlines -> Text -> LP m Blocks
theoremEnvironment LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Inlines
forall (m :: * -> *). PandocMonad m => LP m Inlines
opt Text
name LP m Blocks -> LP m Blocks -> LP m Blocks
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 LP m Blocks
forall (m :: * -> *) a. MonadPlus m => m a
mzero
       else LP m Blocks -> LP m Blocks
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawEnv Text
name) LP m Blocks -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Text -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Text -> LP m Blocks
rawVerbEnv Text
name

rawEnv :: PandocMonad m => Text -> LP m Blocks
rawEnv :: Text -> LP m Blocks
rawEnv Text
name = do
  Extensions
exts <- (ReaderOptions -> Extensions)
-> ParserT [Tok] LaTeXState m Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParserT s st 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 [Tok] LaTeXState m [Text]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m Text
-> ParsecT [Tok] LaTeXState m [Text]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many ParsecT [Tok] 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 [Tok] 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 (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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent Text
beginCommand SourcePos
pos1
       SourcePos
pos2 <- ParsecT [Tok] LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
       LogMessage -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] 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 (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 :: Text -> LP m Blocks
rawVerbEnv Text
name = do
  SourcePos
pos <- ParsecT [Tok] 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)
-> ParserT [Tok] LaTeXState m Extensions
forall st s (m :: * -> *) t b.
(HasReaderOptions st, Stream s m t) =>
(ReaderOptions -> b) -> ParserT s st 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 (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 [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
SkippedContent Text
raw' SourcePos
pos
       Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return Blocks
forall a. Monoid a => a
mempty

fancyverbEnv :: PandocMonad m => Text -> LP m Blocks
fancyverbEnv :: Text -> LP m Blocks
fancyverbEnv Text
name = do
  [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
name

obeylines :: PandocMonad m => LP m Blocks
obeylines :: 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 [Tok] LaTeXState m Inlines -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> ParsecT [Tok] LaTeXState m Inlines
-> ParsecT [Tok] LaTeXState m Inlines
forall (m :: * -> *) a. PandocMonad m => Text -> LP m a -> LP m a
env Text
"obeylines" ParsecT [Tok] 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 :: 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 [Tok] LaTeXState m Text -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *). PandocMonad m => Text -> LP m Text
verbEnv Text
"minted"

mintedAttr :: PandocMonad m => LP m Attr
mintedAttr :: LP m Attr
mintedAttr = do
  [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] 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 [Tok] LaTeXState m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => LP m [(Text, Text)]
keyvals
  Text
lang <- [Tok] -> Text
untokenize ([Tok] -> Text)
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 (m :: * -> *) a. Monad m => a -> m a
return (Text
"",[Text]
classes,[(Text, Text)]
kvs)

inputMinted :: PandocMonad m => LP m Blocks
inputMinted :: LP m Blocks
inputMinted = do
  SourcePos
pos <- ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  Maybe Text
mbCode <- SourceName -> LP m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
SourceName -> LP m (Maybe Text)
readFileFromTexinputs (Text -> SourceName
T.unpack Text
f)
  Text
rawcode <- case Maybe Text
mbCode of
                  Just Text
s -> Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
s
                  Maybe Text
Nothing -> do
                    LogMessage -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
CouldNotLoadIncludeFile Text
f SourcePos
pos
                    Text -> ParsecT [Tok] LaTeXState m Text
forall (m :: * -> *) a. Monad m => a -> m a
return Text
""
  Blocks -> LP m Blocks
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 :: LP m Blocks
letterContents = do
  Blocks
bs <- LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks
  LaTeXState
st <- ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  -- add signature (author) and address (title)
  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 (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 -- sig added by \closing

figure :: PandocMonad m => LP m Blocks
figure :: LP m Blocks
figure = 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
$ do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
resetCaption
  LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks LP m Blocks -> (Blocks -> LP m Blocks) -> LP m Blocks
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Blocks -> LP m Blocks
forall (m :: * -> *). PandocMonad m => Blocks -> LP m Blocks
addImageCaption

addImageCaption :: PandocMonad m => Blocks -> LP m Blocks
addImageCaption :: Blocks -> LP m Blocks
addImageCaption = (Inline -> ParsecT [Tok] 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
walkM Inline -> ParsecT [Tok] LaTeXState m Inline
forall (m :: * -> *).
Monad m =>
Inline -> ParsecT [Tok] LaTeXState m Inline
go
  where go :: Inline -> ParsecT [Tok] LaTeXState m Inline
go (Image attr :: Attr
attr@(Text
_, [Text]
cls, [(Text, Text)]
kvs) [Inline]
alt (Text
src,Text
tit))
            | Bool -> Bool
not (Text
"fig:" Text -> Text -> Bool
`T.isPrefixOf` Text
tit) = do
          LaTeXState
st <- ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
          let ([Inline]
alt', Text
tit') = case LaTeXState -> Maybe Inlines
sCaption LaTeXState
st of
                               Just Inlines
ils -> (Inlines -> [Inline]
forall a. Many a -> [a]
toList Inlines
ils, Text
"fig:" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
tit)
                               Maybe Inlines
Nothing  -> ([Inline]
alt, Text
tit)
              attr' :: Attr
attr' = case LaTeXState -> Maybe Text
sLastLabel LaTeXState
st of
                        Just Text
lab -> (Text
lab, [Text]
cls, [(Text, Text)]
kvs)
                        Maybe Text
Nothing  -> Attr
attr
          case Attr
attr' of
               (Text
"", [Text]
_, [(Text, Text)]
_)    -> () -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
               (Text
ident, [Text]
_, [(Text, Text)]
_) -> do
                  DottedNum
num <- (LaTeXState -> DottedNum) -> LP m DottedNum
forall (m :: * -> *).
Monad m =>
(LaTeXState -> DottedNum) -> LP m DottedNum
getNextNumber LaTeXState -> DottedNum
sLastFigureNum
                  LaTeXState -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => u -> ParsecT s u m ()
setState
                    LaTeXState
st{ sLastFigureNum :: DottedNum
sLastFigureNum = DottedNum
num
                      , sLabels :: Map Text [Inline]
sLabels = Text -> [Inline] -> Map Text [Inline] -> Map Text [Inline]
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
ident
                                 [Text -> Inline
Str (DottedNum -> Text
renderDottedNum DottedNum
num)] (LaTeXState -> Map Text [Inline]
sLabels LaTeXState
st) }
          Inline -> ParsecT [Tok] LaTeXState m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return (Inline -> ParsecT [Tok] LaTeXState m Inline)
-> Inline -> ParsecT [Tok] LaTeXState m Inline
forall a b. (a -> b) -> a -> b
$ Attr -> [Inline] -> (Text, Text) -> Inline
Image Attr
attr' [Inline]
alt' (Text
src, Text
tit')
        go Inline
x = Inline -> ParsecT [Tok] LaTeXState m Inline
forall (m :: * -> *) a. Monad m => a -> m a
return Inline
x

coloredBlock :: PandocMonad m => Text -> LP m Blocks
coloredBlock :: Text -> LP m Blocks
coloredBlock Text
stylename = 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
$ do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts
  [Tok]
color <- LP m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  ParsecT [Tok] 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 [Tok] LaTeXState m Inlines
-> ParsecT [Tok] LaTeXState m Inlines
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped ParsecT [Tok] 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) -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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

graphicsPath :: PandocMonad m => LP m Blocks
graphicsPath :: LP m Blocks
graphicsPath = do
  [SourceName]
ps <- ([Tok] -> SourceName) -> [[Tok]] -> [SourceName]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> SourceName
T.unpack (Text -> SourceName) -> ([Tok] -> Text) -> [Tok] -> SourceName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Tok] -> Text
untokenize) ([[Tok]] -> [SourceName])
-> ParsecT [Tok] LaTeXState m [[Tok]]
-> ParsecT [Tok] LaTeXState m [SourceName]
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 [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m [[Tok]]
-> ParsecT [Tok] LaTeXState m [[Tok]]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m [Tok]
-> LP m Tok -> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces) LP m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
egroup)
  ParsecT [Tok] LaTeXState m [SourceName]
forall (m :: * -> *). PandocMonad m => m [SourceName]
getResourcePath ParsecT [Tok] LaTeXState m [SourceName]
-> ([SourceName] -> ParsecT [Tok] LaTeXState m ())
-> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= [SourceName] -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => [SourceName] -> m ()
setResourcePath ([SourceName] -> ParsecT [Tok] LaTeXState m ())
-> ([SourceName] -> [SourceName])
-> [SourceName]
-> ParsecT [Tok] LaTeXState m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([SourceName] -> [SourceName] -> [SourceName]
forall a. Semigroup a => a -> a -> a
<> [SourceName]
ps)
  Blocks -> LP m Blocks
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
. SourceName -> Text
T.pack (SourceName -> Text) -> (Text -> SourceName) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceName -> SourceName -> SourceName)
-> SourceName -> SourceName -> SourceName
forall a b c. (a -> b -> c) -> b -> a -> c
flip SourceName -> SourceName -> SourceName
replaceExtension SourceName
"bib" (SourceName -> SourceName)
-> (Text -> SourceName) -> Text -> SourceName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> SourceName
T.unpack (Text -> SourceName) -> (Text -> Text) -> Text -> SourceName
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 :: LP m Blocks
inputListing = do
  SourcePos
pos <- ParsecT [Tok] LaTeXState m SourcePos
forall (m :: * -> *) s u. Monad m => ParsecT s u m SourcePos
getPosition
  [(Text, Text)]
options <- [(Text, Text)]
-> ParsecT [Tok] LaTeXState m [(Text, Text)]
-> ParsecT [Tok] 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 [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  Maybe Text
mbCode <- SourceName -> LP m (Maybe Text)
forall (m :: * -> *).
PandocMonad m =>
SourceName -> LP m (Maybe Text)
readFileFromTexinputs (Text -> SourceName
T.unpack Text
f)
  [Text]
codeLines <- case Maybe Text
mbCode of
                      Just Text
s -> [Text] -> ParsecT [Tok] LaTeXState m [Text]
forall (m :: * -> *) a. Monad m => a -> m a
return ([Text] -> ParsecT [Tok] LaTeXState m [Text])
-> [Text] -> ParsecT [Tok] LaTeXState m [Text]
forall a b. (a -> b) -> a -> b
$ Text -> [Text]
T.lines Text
s
                      Maybe Text
Nothing -> do
                        LogMessage -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LogMessage -> m ()
report (LogMessage -> ParsecT [Tok] LaTeXState m ())
-> LogMessage -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ Text -> SourcePos -> LogMessage
CouldNotLoadIncludeFile Text
f SourcePos
pos
                        [Text] -> ParsecT [Tok] LaTeXState m [Text]
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 (Text -> [Text]
languagesByExtension (SourceName -> Text
T.pack (SourceName -> Text) -> SourceName -> Text
forall a b. (a -> b) -> a -> b
$ SourceName -> SourceName
takeExtension (SourceName -> SourceName) -> SourceName -> SourceName
forall a b. (a -> b) -> a -> b
$ Text -> SourceName
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 (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 (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 (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 (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

-- lists

item :: PandocMonad m => LP m Blocks
item :: LP m Blocks
item = LP m Blocks -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks ParsecT [Tok] LaTeXState m ()
-> ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Text -> ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"item" ParsecT [Tok] LaTeXState m Tok
-> ParsecT [Tok] LaTeXState m () -> ParsecT [Tok] LaTeXState m ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
skipopts ParsecT [Tok] LaTeXState m () -> LP m Blocks -> LP m Blocks
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks

descItem :: PandocMonad m => LP m (Inlines, [Blocks])
descItem :: LP m (Inlines, [Blocks])
descItem = do
  LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
blocks -- skip blocks before item
  Text -> LP m Tok
forall (m :: * -> *). PandocMonad m => Text -> LP m Tok
controlSeq Text
"item"
  LP 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 (m :: * -> *) a. Monad m => a -> m a
return (Inlines
ils, [Blocks
bs])

listenv :: PandocMonad m => Text -> LP m a -> LP m a
listenv :: 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 [Tok] LaTeXState m LaTeXState
-> ParsecT [Tok] LaTeXState m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecT [Tok] LaTeXState m LaTeXState
forall (m :: * -> *) s u. Monad m => ParsecT s u m u
getState
  (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInListItem :: Bool
sInListItem = Bool
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 [Tok] LaTeXState m ()
forall (m :: * -> *) u s. Monad m => (u -> u) -> ParsecT s u m ()
updateState ((LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ())
-> (LaTeXState -> LaTeXState) -> ParsecT [Tok] LaTeXState m ()
forall a b. (a -> b) -> a -> b
$ \LaTeXState
st -> LaTeXState
st{ sInListItem :: Bool
sInListItem = Bool
oldInListItem }
  a -> LP m a
forall (m :: * -> *) a. Monad m => a -> m a
return a
res

orderedList' :: PandocMonad m => LP m Blocks
orderedList' :: LP m Blocks
orderedList' = 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
$ do
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
  let markerSpec :: ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Tok -> LP m Tok -> ParsecT [Tok] 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
-> SourceName
-> Text
-> Either ParseError ListAttributes
forall s t u a.
Stream s Identity t =>
Parsec s u a -> u -> SourceName -> s -> Either ParseError a
runParser Parsec Text ParserState ListAttributes
forall s (m :: * -> *).
Stream s m Char =>
ParserT s ParserState m ListAttributes
anyOrderedListMarker ParserState
forall a. Default a => a
def SourceName
"option" Text
ts of
             Right ListAttributes
r -> ListAttributes -> ParsecT [Tok] LaTeXState m ListAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return ListAttributes
r
             Left ParseError
_  -> do
               SourcePos
pos <- ParsecT [Tok] 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 [Tok] LaTeXState m ListAttributes
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
1, ListNumberStyle
DefaultStyle, ListNumberDelim
DefaultDelim)
  (Int
_, ListNumberStyle
style, ListNumberDelim
delim) <- ListAttributes
-> ParsecT [Tok] LaTeXState m ListAttributes
-> ParsecT [Tok] 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 [Tok] LaTeXState m ListAttributes
markerSpec
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
  ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ParsecT [Tok] LaTeXState m [Tok]
 -> ParsecT [Tok] LaTeXState m (Maybe [Tok]))
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m (Maybe [Tok])
forall a b. (a -> b) -> a -> b
$ ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tok] LaTeXState m [Tok]
 -> ParsecT [Tok] LaTeXState m [Tok])
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *) a.
(PandocMonad m, Monoid a) =>
LP m a -> LP m a
grouped (Int -> LP m Tok -> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok])
-> LP m Tok -> ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m [Tok]
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT [Tok] LaTeXState m [Tok]
forall (m :: * -> *). PandocMonad m => LP m [Tok]
braced
  LP m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces
  Int
start <- Int
-> ParsecT [Tok] LaTeXState m Int -> ParsecT [Tok] 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 [Tok] LaTeXState m Int -> ParsecT [Tok] LaTeXState m Int)
-> ParsecT [Tok] LaTeXState m Int -> ParsecT [Tok] LaTeXState m Int
forall a b. (a -> b) -> a -> b
$ ParsecT [Tok] LaTeXState m Int -> ParsecT [Tok] LaTeXState m Int
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT [Tok] LaTeXState m Int -> ParsecT [Tok] LaTeXState m Int)
-> ParsecT [Tok] LaTeXState m Int -> ParsecT [Tok] LaTeXState m Int
forall a b. (a -> b) -> a -> b
$ do SourcePos
pos <- ParsecT [Tok] 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 -> SourceName -> 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 [Tok] LaTeXState m [Tok]
-> ParsecT [Tok] LaTeXState m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT [Tok] 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 [Tok] LaTeXState m Int
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 [Tok] LaTeXState m Int
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" (LP m Blocks -> LP m [Blocks]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
item)
  Blocks -> LP m Blocks
forall (m :: * -> *) a. Monad m => a -> m a
return (Blocks -> LP m Blocks) -> Blocks -> LP 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 :: LP m Blocks
block = do
  Tok SourcePos
_ TokType
toktype Text
_ <- ParsecT [Tok] LaTeXState m Tok -> ParsecT [Tok] LaTeXState m Tok
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m a
lookAhead ParsecT [Tok] LaTeXState m Tok
forall (m :: * -> *). PandocMonad m => LP m Tok
anyTok
  Blocks
res <- (case TokType
toktype of
            TokType
Newline           -> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1
            TokType
Spaces            -> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] LaTeXState m ()
forall (m :: * -> *). PandocMonad m => LP m ()
spaces1
            TokType
Comment           -> Blocks
forall a. Monoid a => a
mempty Blocks -> ParsecT [Tok] LaTeXState m () -> LP m Blocks
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT [Tok] 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 (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 (m :: * -> *) a. MonadPlus m => m a
mzero)
          LP m Blocks -> LP m Blocks -> LP m Blocks
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 (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 [Tok] 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 (m :: * -> *) a. Monad m => a -> m a
return Blocks
res

blocks :: PandocMonad m => LP m Blocks
blocks :: LP m Blocks
blocks = [Blocks] -> Blocks
forall a. Monoid a => [a] -> a
mconcat ([Blocks] -> Blocks)
-> ParsecT [Tok] LaTeXState m [Blocks] -> LP m Blocks
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LP m Blocks -> ParsecT [Tok] LaTeXState m [Blocks]
forall (f :: * -> *) a. Alternative f => f a -> f [a]
many LP m Blocks
forall (m :: * -> *). PandocMonad m => LP m Blocks
block