aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/LaTeX
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Inline.hs10
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Macro.hs117
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Math.hs14
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Parsing.hs79
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/SIunitx.hs6
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Table.hs4
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Types.hs6
7 files changed, 172 insertions, 64 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
index 7b8bca4af..5938096fd 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
@@ -35,7 +35,7 @@ import Text.Pandoc.Readers.LaTeX.Parsing
import Text.Pandoc.Extensions (extensionEnabled, Extension(..))
import Text.Pandoc.Parsing (getOption, updateState, getState, notFollowedBy,
manyTill, getInput, setInput, incSourceColumn,
- option, many1, try)
+ option, many1)
import Data.Char (isDigit)
import Text.Pandoc.Highlighting (fromListingsLanguage,)
import Data.Maybe (maybeToList, fromMaybe)
@@ -56,8 +56,7 @@ dolabel = do
let refstr = untokenize v
updateState $ \st ->
st{ sLastLabel = Just refstr }
- return $ spanWith (refstr,[],[("label", refstr)])
- $ inBrackets $ str $ untokenize v
+ return $ spanWith (refstr,[],[("label", refstr)]) mempty
doref :: PandocMonad m => Text -> LP m Inlines
doref cls = do
@@ -160,8 +159,8 @@ romanNumeralArg = spaces *> (parser <|> inBraces)
accentWith :: PandocMonad m
=> LP m Inlines -> Char -> Maybe Char -> LP m Inlines
-accentWith tok combiningAccent fallBack = try $ do
- ils <- tok
+accentWith tok combiningAccent fallBack = do
+ ils <- option mempty tok
case toList ils of
(Str (T.uncons -> Just (x, xs)) : ys) -> return $ fromList $
-- try to normalize to the combined character:
@@ -339,6 +338,7 @@ refCommands = M.fromList
, ("cref", rawInlineOr "cref" $ doref "ref") -- from cleveref.sty
, ("vref", rawInlineOr "vref" $ doref "ref+page") -- from varioref.sty
, ("eqref", rawInlineOr "eqref" $ doref "eqref") -- from amsmath.sty
+ , ("autoref", rawInlineOr "autoref" $ doref "autoref") -- from hyperref.sty
]
acronymCommands :: PandocMonad m => M.Map Text (LP m Inlines)
diff --git a/src/Text/Pandoc/Readers/LaTeX/Macro.hs b/src/Text/Pandoc/Readers/LaTeX/Macro.hs
index 5495a8e74..d40277eb5 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Macro.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Macro.hs
@@ -15,6 +15,8 @@ import Control.Applicative ((<|>), optional)
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
+import qualified Data.List.NonEmpty as NonEmpty
+import Data.List.NonEmpty (NonEmpty(..))
macroDef :: (PandocMonad m, Monoid a) => (Text -> a) -> LP m a
macroDef constructor = do
@@ -23,51 +25,91 @@ macroDef constructor = do
guardDisabled Ext_latex_macros)
<|> return mempty
where commandDef = do
- nameMacroPairs <- newcommand <|> letmacro <|> defmacro <|> newif
+ nameMacroPairs <- newcommand <|>
+ checkGlobal (letmacro <|> edefmacro <|> defmacro <|> newif)
guardDisabled Ext_latex_macros <|>
- mapM_ (\(name, macro') ->
- updateState (\s -> s{ sMacros = M.insert name macro'
- (sMacros s) })) nameMacroPairs
+ mapM_ insertMacro nameMacroPairs
environmentDef = do
mbenv <- newenvironment
case mbenv of
Nothing -> return ()
Just (name, macro1, macro2) ->
guardDisabled Ext_latex_macros <|>
- do updateState $ \s -> s{ sMacros =
- M.insert name macro1 (sMacros s) }
- updateState $ \s -> s{ sMacros =
- M.insert ("end" <> name) macro2 (sMacros s) }
+ do insertMacro (name, macro1)
+ insertMacro ("end" <> name, macro2)
-- @\newenvironment{envname}[n-args][default]{begin}{end}@
-- is equivalent to
-- @\newcommand{\envname}[n-args][default]{begin}@
-- @\newcommand{\endenvname}@
+insertMacro :: PandocMonad m => (Text, Macro) -> LP m ()
+insertMacro (name, macro'@(Macro GlobalScope _ _ _ _)) =
+ updateState $ \s ->
+ s{ sMacros = NonEmpty.map (M.insert name macro') (sMacros s) }
+insertMacro (name, macro'@(Macro GroupScope _ _ _ _)) =
+ updateState $ \s ->
+ s{ sMacros = M.insert name macro' (NonEmpty.head (sMacros s)) :|
+ NonEmpty.tail (sMacros s) }
+
+lookupMacro :: PandocMonad m => Text -> LP m Macro
+lookupMacro name = do
+ macros :| _ <- sMacros <$> getState
+ case M.lookup name macros of
+ Just m -> return m
+ Nothing -> fail "Macro not found"
+
letmacro :: PandocMonad m => LP m [(Text, Macro)]
letmacro = do
controlSeq "let"
- (name, contents) <- withVerbatimMode $ do
+ withVerbatimMode $ do
Tok _ (CtrlSeq name) _ <- anyControlSeq
optional $ symbol '='
spaces
-- we first parse in verbatim mode, and then expand macros,
-- because we don't want \let\foo\bar to turn into
-- \let\foo hello if we have previously \def\bar{hello}
+ target <- anyControlSeq <|> singleChar
+ case target of
+ (Tok _ (CtrlSeq name') _) ->
+ (do m <- lookupMacro name'
+ pure [(name, m)])
+ <|> pure [(name,
+ Macro GroupScope ExpandWhenDefined [] Nothing [target])]
+ _ -> pure [(name, Macro GroupScope ExpandWhenDefined [] Nothing [target])]
+
+checkGlobal :: PandocMonad m => LP m [(Text, Macro)] -> LP m [(Text, Macro)]
+checkGlobal p =
+ (controlSeq "global" *>
+ (map (\(n, Macro _ expand arg optarg contents) ->
+ (n, Macro GlobalScope expand arg optarg contents)) <$> p))
+ <|> p
+
+edefmacro :: PandocMonad m => LP m [(Text, Macro)]
+edefmacro = do
+ scope <- (GroupScope <$ controlSeq "edef")
+ <|> (GlobalScope <$ controlSeq "xdef")
+ (name, contents) <- withVerbatimMode $ do
+ Tok _ (CtrlSeq name) _ <- anyControlSeq
+ -- we first parse in verbatim mode, and then expand macros,
+ -- because we don't want \let\foo\bar to turn into
+ -- \let\foo hello if we have previously \def\bar{hello}
contents <- bracedOrToken
return (name, contents)
- contents' <- doMacros' 0 contents
- return [(name, Macro ExpandWhenDefined [] Nothing contents')]
+ -- expand macros
+ contents' <- parseFromToks (many anyTok) contents
+ return [(name, Macro scope ExpandWhenDefined [] Nothing contents')]
defmacro :: PandocMonad m => LP m [(Text, Macro)]
defmacro = do
-- we use withVerbatimMode, because macros are to be expanded
-- at point of use, not point of definition
- controlSeq "def"
+ scope <- (GroupScope <$ controlSeq "def")
+ <|> (GlobalScope <$ controlSeq "gdef")
withVerbatimMode $ do
Tok _ (CtrlSeq name) _ <- anyControlSeq
argspecs <- many (argspecArg <|> argspecPattern)
contents <- bracedOrToken
- return [(name, Macro ExpandWhenUsed argspecs Nothing contents)]
+ return [(name, Macro scope ExpandWhenUsed argspecs Nothing contents)]
-- \newif\iffoo' defines:
-- \iffoo to be \iffalse
@@ -82,16 +124,16 @@ newif = do
-- \def\footrue{\def\iffoo\iftrue}
-- \def\foofalse{\def\iffoo\iffalse}
let base = T.drop 2 name
- return [ (name, Macro ExpandWhenUsed [] Nothing
+ return [ (name, Macro GroupScope ExpandWhenUsed [] Nothing
[Tok pos (CtrlSeq "iffalse") "\\iffalse"])
, (base <> "true",
- Macro ExpandWhenUsed [] Nothing
+ Macro GroupScope ExpandWhenUsed [] Nothing
[ Tok pos (CtrlSeq "def") "\\def"
, Tok pos (CtrlSeq name) ("\\" <> name)
, Tok pos (CtrlSeq "iftrue") "\\iftrue"
])
, (base <> "false",
- Macro ExpandWhenUsed [] Nothing
+ Macro GroupScope ExpandWhenUsed [] Nothing
[ Tok pos (CtrlSeq "def") "\\def"
, Tok pos (CtrlSeq name) ("\\" <> name)
, Tok pos (CtrlSeq "iffalse") "\\iffalse"
@@ -138,14 +180,13 @@ newcommand = do
: (contents' ++
[ Tok pos Symbol "}", Tok pos Symbol "}" ])
_ -> contents'
- macros <- sMacros <$> getState
- case M.lookup name macros of
- Just macro
- | mtype == "newcommand" -> do
- report $ MacroAlreadyDefined txt pos
- return [(name, macro)]
- | mtype == "providecommand" -> return [(name, macro)]
- _ -> return [(name, Macro ExpandWhenUsed argspecs optarg contents)]
+ let macro = Macro GroupScope ExpandWhenUsed argspecs optarg contents
+ (do lookupMacro name
+ case mtype of
+ "providecommand" -> return []
+ "renewcommand" -> return [(name, macro)]
+ _ -> [] <$ report (MacroAlreadyDefined txt pos))
+ <|> pure [(name, macro)]
newenvironment :: PandocMonad m => LP m (Maybe (Text, Macro, Macro))
newenvironment = do
@@ -164,17 +205,23 @@ newenvironment = do
let argspecs = map (\i -> ArgNum i) [1..numargs]
startcontents <- spaces >> bracedOrToken
endcontents <- spaces >> bracedOrToken
- macros <- sMacros <$> getState
- case M.lookup name macros of
- Just _
- | mtype == "newenvironment" -> do
- report $ MacroAlreadyDefined name pos
- return Nothing
- | mtype == "provideenvironment" ->
- return Nothing
- _ -> return $ Just (name,
- Macro ExpandWhenUsed argspecs optarg startcontents,
- Macro ExpandWhenUsed [] Nothing endcontents)
+ -- we need the environment to be in a group so macros defined
+ -- inside behave correctly:
+ let bg = Tok pos (CtrlSeq "bgroup") "\\bgroup "
+ let eg = Tok pos (CtrlSeq "egroup") "\\egroup "
+ let result = (name,
+ Macro GroupScope ExpandWhenUsed argspecs optarg
+ (bg:startcontents),
+ Macro GroupScope ExpandWhenUsed [] Nothing
+ (endcontents ++ [eg]))
+ (do lookupMacro name
+ case mtype of
+ "provideenvironment" -> return Nothing
+ "renewenvironment" -> return (Just result)
+ _ -> do
+ report $ MacroAlreadyDefined name pos
+ return Nothing)
+ <|> return (Just result)
bracketedNum :: PandocMonad m => LP m Int
bracketedNum = do
diff --git a/src/Text/Pandoc/Readers/LaTeX/Math.hs b/src/Text/Pandoc/Readers/LaTeX/Math.hs
index 5b49a0376..01edce7ed 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Math.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Math.hs
@@ -142,14 +142,15 @@ newtheorem inline = do
theoremEnvironment :: PandocMonad m
=> LP m Blocks -> LP m Inlines -> Text -> LP m Blocks
theoremEnvironment blocks opt name = do
+ resetCaption
tmap <- sTheoremMap <$> getState
case M.lookup name tmap of
Nothing -> mzero
Just tspec -> do
optTitle <- option mempty $ (\x -> space <> "(" <> x <> ")") <$> opt
- mblabel <- option Nothing $ Just . untokenize <$>
- try (spaces >> controlSeq "label" >> spaces >> braced)
bs <- env name blocks
+ mblabel <- sLastLabel <$> getState
+
number <-
if theoremNumber tspec
then do
@@ -169,9 +170,7 @@ theoremEnvironment blocks opt name = do
Just ident ->
updateState $ \s ->
s{ sLabels = M.insert ident
- (B.toList $
- theoremName tspec <> "\160" <>
- str (renderDottedNum num)) (sLabels s) }
+ (B.toList $ str (renderDottedNum num)) (sLabels s) }
Nothing -> return ()
return $ space <> B.text (renderDottedNum num)
else return mempty
@@ -181,13 +180,14 @@ theoremEnvironment blocks opt name = do
RemarkStyle -> B.emph
let title = titleEmph (theoremName tspec <> number)
<> optTitle <> "." <> space
- return $ divWith (fromMaybe "" mblabel, [name], []) $ addTitle title
+ return $ divWith (fromMaybe "" mblabel, [name], [])
+ $ addTitle title
+ $ maybe id removeLabel mblabel
$ case theoremStyle tspec of
PlainStyle -> walk italicize bs
_ -> bs
-
proof :: PandocMonad m => LP m Blocks -> LP m Inlines -> LP m Blocks
proof blocks opt = do
title <- option (B.text "Proof") opt
diff --git a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
index 9dac4d6ef..9eb4a0cbc 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Parsing.hs
@@ -45,6 +45,7 @@ module Text.Pandoc.Readers.LaTeX.Parsing
, isNewlineTok
, isWordTok
, isArgTok
+ , infile
, spaces
, spaces1
, tokTypeIn
@@ -89,6 +90,7 @@ module Text.Pandoc.Readers.LaTeX.Parsing
, resetCaption
, env
, addMeta
+ , removeLabel
) where
import Control.Applicative (many, (<|>))
@@ -102,6 +104,9 @@ import qualified Data.IntMap as IntMap
import qualified Data.Map as M
import qualified Data.Set as Set
import Data.Text (Text)
+import Data.Maybe (fromMaybe)
+import Data.List.NonEmpty (NonEmpty(..))
+import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Text as T
import Text.Pandoc.Builder
import Text.Pandoc.Class.PandocMonad (PandocMonad, report)
@@ -115,6 +120,7 @@ import Text.Pandoc.Readers.LaTeX.Types (ExpansionPoint (..), Macro (..),
ArgSpec (..), Tok (..), TokType (..))
import Text.Pandoc.Shared
import Text.Parsec.Pos
+import Text.Pandoc.Walk
newtype DottedNum = DottedNum [Int]
deriving (Show, Eq)
@@ -146,7 +152,7 @@ data TheoremSpec =
data LaTeXState = LaTeXState{ sOptions :: ReaderOptions
, sMeta :: Meta
, sQuoteContext :: QuoteContext
- , sMacros :: M.Map Text Macro
+ , sMacros :: NonEmpty (M.Map Text Macro)
, sContainers :: [Text]
, sLogMessages :: [LogMessage]
, sIdentifiers :: Set.Set Text
@@ -173,7 +179,7 @@ defaultLaTeXState :: LaTeXState
defaultLaTeXState = LaTeXState{ sOptions = def
, sMeta = nullMeta
, sQuoteContext = NoQuote
- , sMacros = M.empty
+ , sMacros = M.empty :| []
, sContainers = []
, sLogMessages = []
, sIdentifiers = Set.empty
@@ -220,8 +226,9 @@ instance HasIncludeFiles LaTeXState where
dropLatestIncludeFile s = s { sContainers = drop 1 $ sContainers s }
instance HasMacros LaTeXState where
- extractMacros st = sMacros st
- updateMacros f st = st{ sMacros = f (sMacros st) }
+ extractMacros st = NonEmpty.head $ sMacros st
+ updateMacros f st = st{ sMacros = f (NonEmpty.head (sMacros st))
+ :| NonEmpty.tail (sMacros st) }
instance HasReaderOptions LaTeXState where
extractReaderOptions = sOptions
@@ -254,7 +261,7 @@ rawLaTeXParser :: (PandocMonad m, HasMacros s, HasReaderOptions s, Show a)
rawLaTeXParser toks retokenize parser valParser = do
pstate <- getState
let lstate = def{ sOptions = extractReaderOptions pstate }
- let lstate' = lstate { sMacros = extractMacros pstate }
+ let lstate' = lstate { sMacros = extractMacros pstate :| [] }
let setStartPos = case toks of
Tok pos _ _ : _ -> setPosition pos
_ -> return ()
@@ -267,14 +274,14 @@ rawLaTeXParser toks retokenize parser valParser = do
Right (endpos, toks') -> do
res <- lift $ runParserT (do when retokenize $ do
-- retokenize, applying macros
- ts <- many (satisfyTok (const True))
+ ts <- many anyTok
setInput ts
rawparser)
lstate' "chunk" toks'
case res of
Left _ -> mzero
Right ((val, raw), st) -> do
- updateState (updateMacros (sMacros st <>))
+ updateState (updateMacros ((NonEmpty.head (sMacros st)) <>))
let skipTilPos stopPos = do
anyChar
pos <- getPosition
@@ -296,10 +303,10 @@ rawLaTeXParser toks retokenize parser valParser = do
applyMacros :: (PandocMonad m, HasMacros s, HasReaderOptions s)
=> Text -> ParserT Sources s m Text
applyMacros s = (guardDisabled Ext_latex_macros >> return s) <|>
- do let retokenize = untokenize <$> many (satisfyTok (const True))
+ do let retokenize = untokenize <$> many anyTok
pstate <- getState
let lstate = def{ sOptions = extractReaderOptions pstate
- , sMacros = extractMacros pstate }
+ , sMacros = extractMacros pstate :| [] }
res <- runParserT retokenize lstate "math" (tokenize "math" s)
case res of
Left e -> Prelude.fail (show e)
@@ -552,10 +559,10 @@ doMacros' n inp =
handleMacros n' spos name ts = do
when (n' > 20) -- detect macro expansion loops
$ throwError $ PandocMacroLoop name
- macros <- sMacros <$> getState
+ (macros :| _ ) <- sMacros <$> getState
case M.lookup name macros of
Nothing -> trySpecialMacro name ts
- Just (Macro expansionPoint argspecs optarg newtoks) -> do
+ Just (Macro _scope expansionPoint argspecs optarg newtoks) -> do
let getargs' = do
args <-
(case expansionPoint of
@@ -642,6 +649,9 @@ isArgTok :: Tok -> Bool
isArgTok (Tok _ (Arg _) _) = True
isArgTok _ = False
+infile :: PandocMonad m => SourceName -> LP m Tok
+infile reference = satisfyTok (\(Tok source _ _) -> (sourceName source) == reference)
+
spaces :: PandocMonad m => LP m ()
spaces = skipMany (satisfyTok (tokTypeIn [Comment, Spaces, Newline]))
@@ -745,10 +755,22 @@ primEscape = do
bgroup :: PandocMonad m => LP m Tok
bgroup = try $ do
optional sp
- symbol '{' <|> controlSeq "bgroup" <|> controlSeq "begingroup"
+ t <- symbol '{' <|> controlSeq "bgroup" <|> controlSeq "begingroup"
+ -- Add a copy of the macro table to the top of the macro stack,
+ -- private for this group. We inherit all the macros defined in
+ -- the parent group.
+ updateState $ \s -> s{ sMacros = NonEmpty.cons (NonEmpty.head (sMacros s))
+ (sMacros s) }
+ return t
+
egroup :: PandocMonad m => LP m Tok
-egroup = symbol '}' <|> controlSeq "egroup" <|> controlSeq "endgroup"
+egroup = do
+ t <- symbol '}' <|> controlSeq "egroup" <|> controlSeq "endgroup"
+ -- remove the group's macro table from the stack
+ updateState $ \s -> s{ sMacros = fromMaybe (sMacros s) $
+ NonEmpty.nonEmpty (NonEmpty.tail (sMacros s)) }
+ return t
grouped :: (PandocMonad m, Monoid a) => LP m a -> LP m a
grouped parser = try $ do
@@ -921,6 +943,9 @@ getRawCommand name txt = do
void $ count 4 braced
"def" ->
void $ manyTill anyTok braced
+ "vadjust" ->
+ void (manyTill anyTok braced) <|>
+ void (satisfyTok isPreTok) -- see #7531
_ | isFontSizeCommand name -> return ()
| otherwise -> do
skipopts
@@ -928,6 +953,10 @@ getRawCommand name txt = do
void $ many braced
return $ txt <> untokenize rawargs
+isPreTok :: Tok -> Bool
+isPreTok (Tok _ Word "pre") = True
+isPreTok _ = False
+
isDigitTok :: Tok -> Bool
isDigitTok (Tok _ Word t) = T.all isDigit t
isDigitTok _ = False
@@ -1017,7 +1046,16 @@ resetCaption = updateState $ \st -> st{ sCaption = Nothing
, sLastLabel = Nothing }
env :: PandocMonad m => Text -> LP m a -> LP m a
-env name p = p <* end_ name
+env name p = do
+ -- environments are groups as far as macros are concerned,
+ -- so we need a local copy of the macro table (see above, bgroup, egroup):
+ updateState $ \s -> s{ sMacros = NonEmpty.cons (NonEmpty.head (sMacros s))
+ (sMacros s) }
+ result <- p
+ updateState $ \s -> s{ sMacros = fromMaybe (sMacros s) $
+ NonEmpty.nonEmpty (NonEmpty.tail (sMacros s)) }
+ end_ name
+ return result
tokWith :: PandocMonad m => LP m Inlines -> LP m Inlines
tokWith inlineParser = try $ spaces >>
@@ -1031,3 +1069,16 @@ tokWith inlineParser = try $ spaces >>
addMeta :: PandocMonad m => ToMetaValue a => Text -> a -> LP m ()
addMeta field val = updateState $ \st ->
st{ sMeta = addMetaField field val $ sMeta st }
+
+-- remove label spans to avoid duplicated identifier
+removeLabel :: Walkable [Inline] a => Text -> a -> a
+removeLabel lbl = walk go
+ where
+ go (Span (_,_,kvs) _ : rest)
+ | Just lbl' <- lookup "label" kvs
+ , lbl' == lbl = go (dropWhile isSpaceOrSoftBreak rest)
+ go (x:xs) = x : go xs
+ go [] = []
+ isSpaceOrSoftBreak Space = True
+ isSpaceOrSoftBreak SoftBreak = True
+ isSpaceOrSoftBreak _ = False
diff --git a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
index b8bf0ce7f..e4738a763 100644
--- a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
@@ -23,11 +23,15 @@ siunitxCommands :: PandocMonad m
=> LP m Inlines -> M.Map Text (LP m Inlines)
siunitxCommands tok = M.fromList
[ ("si", dosi tok)
+ , ("unit", dosi tok) -- v3 version of si
, ("SI", doSI tok)
+ , ("qty", doSI tok) -- v3 version of SI
, ("SIrange", doSIrange True tok)
+ , ("qtyrange", doSIrange True tok) -- v3 version of SIrange
+ , ("SIlist", doSIlist tok)
+ , ("qtylist", doSIlist tok) -- v3 version of SIlist
, ("numrange", doSIrange False tok)
, ("numlist", doSInumlist)
- , ("SIlist", doSIlist tok)
, ("num", doSInum)
, ("ang", doSIang)
]
diff --git a/src/Text/Pandoc/Readers/LaTeX/Table.hs b/src/Text/Pandoc/Readers/LaTeX/Table.hs
index f56728fe1..7d5c4f265 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Table.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Table.hs
@@ -368,7 +368,9 @@ addTableCaption = walkM go
((_,classes,kvs), Just ident) ->
(ident,classes,kvs)
_ -> attr
- return $ addAttrDiv attr' $ Table nullAttr capt spec th tb tf
+ return $ addAttrDiv attr'
+ $ maybe id removeLabel mblabel
+ $ Table nullAttr capt spec th tb tf
go x = return x
-- TODO: For now we add a Div to contain table attributes, since
diff --git a/src/Text/Pandoc/Readers/LaTeX/Types.hs b/src/Text/Pandoc/Readers/LaTeX/Types.hs
index c20b72bc5..a4eae56db 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Types.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Types.hs
@@ -15,6 +15,7 @@ module Text.Pandoc.Readers.LaTeX.Types ( Tok(..)
, Macro(..)
, ArgSpec(..)
, ExpansionPoint(..)
+ , MacroScope(..)
, SourcePos
)
where
@@ -43,7 +44,10 @@ tokToText (Tok _ _ t) = t
data ExpansionPoint = ExpandWhenDefined | ExpandWhenUsed
deriving (Eq, Ord, Show)
-data Macro = Macro ExpansionPoint [ArgSpec] (Maybe [Tok]) [Tok]
+data MacroScope = GlobalScope | GroupScope
+ deriving (Eq, Ord, Show)
+
+data Macro = Macro MacroScope ExpansionPoint [ArgSpec] (Maybe [Tok]) [Tok]
deriving Show
data ArgSpec = ArgNum Int | Pattern [Tok]