diff options
| author | John MacFarlane <jgm@berkeley.edu> | 2018-07-15 12:53:42 -0700 | 
|---|---|---|
| committer | John MacFarlane <jgm@berkeley.edu> | 2018-07-15 12:53:42 -0700 | 
| commit | 339a9e1b8b2aa34aab847d114a65d2d759bd25ed (patch) | |
| tree | 0efd9070274aad214e05f1e974a9c249ab75a1e6 /src/Text | |
| parent | 582b4afd0ee9e3ec16e95994e5456501fb10cb39 (diff) | |
| download | pandoc-339a9e1b8b2aa34aab847d114a65d2d759bd25ed.tar.gz | |
LaTeX reader:  be more forgiving in key/value option parsing.
We now allow arbitrary LaTeX values.
This helps with #4761. The `\maxwidth` is still not
propagated to the latex destination, but at least we don't
choke on parsing.
Diffstat (limited to 'src/Text')
| -rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 55 | 
1 files changed, 39 insertions, 16 deletions
| diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 0578e4836..504ac6db0 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -501,13 +501,17 @@ setpos spos (Tok _ tt txt) = Tok spos tt txt  anyControlSeq :: PandocMonad m => LP m Tok  anyControlSeq = satisfyTok isCtrlSeq -  where isCtrlSeq (Tok _ (CtrlSeq _) _) = True -        isCtrlSeq _                     = False + +isCtrlSeq :: Tok -> Bool +isCtrlSeq (Tok _ (CtrlSeq _) _) = True +isCtrlSeq _                     = False  anySymbol :: PandocMonad m => LP m Tok -anySymbol = satisfyTok isSym -  where isSym (Tok _ Symbol _) = True -        isSym _                = False +anySymbol = satisfyTok isSymbolTok + +isSymbolTok :: Tok -> Bool +isSymbolTok (Tok _ Symbol _) = True +isSymbolTok _                = False  spaces :: PandocMonad m => LP m ()  spaces = skipMany (satisfyTok (tokTypeIn [Comment, Spaces, Newline])) @@ -542,8 +546,10 @@ sp = whitespace <|> endline  whitespace :: PandocMonad m => LP m ()  whitespace = () <$ satisfyTok isSpaceTok -  where isSpaceTok (Tok _ Spaces _) = True -        isSpaceTok _                = False + +isSpaceTok :: Tok -> Bool +isSpaceTok (Tok _ Spaces _) = True +isSpaceTok _                = False  newlineTok :: PandocMonad m => LP m ()  newlineTok = () <$ satisfyTok isNewlineTok @@ -554,8 +560,10 @@ isNewlineTok _                 = False  comment :: PandocMonad m => LP m ()  comment = () <$ satisfyTok isCommentTok -  where isCommentTok (Tok _ Comment _) = True -        isCommentTok _                 = False + +isCommentTok :: Tok -> Bool +isCommentTok (Tok _ Comment _) = True +isCommentTok _                 = False  anyTok :: PandocMonad m => LP m Tok  anyTok = satisfyTok (const True) @@ -819,18 +827,25 @@ dolstinline = do  keyval :: PandocMonad m => LP m (String, String)  keyval = try $ do    Tok _ Word key <- satisfyTok isWordTok -  let isSpecSym (Tok _ Symbol t) = t /= "]" && t /= "," -      isSpecSym _                = False    optional sp -  val <- option [] $ do +  val <- option mempty $ do             symbol '='             optional sp -           braced <|> many1 (satisfyTok isWordTok <|> satisfyTok isSpecSym -                               <|> anyControlSeq) -  optional sp +           (untokenize <$> braced) <|> +             (mconcat <$> many1 ( +                 (untokenize . snd <$> withRaw braced) +                 <|> +                 (untokenize <$> (many1 +                      (satisfyTok +                         (\t -> case t of +                                Tok _ Symbol "]" -> False +                                Tok _ Symbol "," -> False +                                Tok _ Symbol "{" -> False +                                Tok _ Symbol "}" -> False +                                _                -> True))))))    optional (symbol ',')    optional sp -  return (T.unpack key, T.unpack . untokenize $ val) +  return (T.unpack key, T.unpack $ T.strip val)  keyvals :: PandocMonad m => LP m [(String, String)]  keyvals = try $ symbol '[' >> manyTill keyval (symbol ']') @@ -1644,8 +1659,16 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList    , ("foreignlanguage", foreignlanguage)    -- include    , ("input", include "input") +  -- plain tex stuff that should just be passed through as raw tex +  , ("ifdim", ifdim)    ] +ifdim :: PandocMonad m => LP m Inlines +ifdim = do +  contents <- manyTill anyTok (controlSeq "fi") +  return $ rawInline "latex" $ T.unpack $ +           "\\ifdim" <> untokenize contents <> "\\fi" +  makeUppercase :: Inlines -> Inlines  makeUppercase = fromList . walk (alterStr (map toUpper)) . toList | 
