aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers
diff options
context:
space:
mode:
authorVasily Alferov <ya-ikmik2012@yandex.ru>2019-07-14 02:55:41 +0300
committerJohn MacFarlane <jgm@berkeley.edu>2019-07-13 16:55:41 -0700
commitf6c92c7523a4070f13fbf193ef80ad7ac63f6693 (patch)
tree5e4afc7c98d7368780df2d868e0d0cf11cd7e048 /src/Text/Pandoc/Readers
parent7bc9eab8465e16a13768834e49f124a3efbf29f4 (diff)
downloadpandoc-f6c92c7523a4070f13fbf193ef80ad7ac63f6693.tar.gz
Fix #4499: add mbox and hbox handling to LaTeX reader (#5586)
When `+raw_tex` is enabled, these are passed through literally. Otherwise, they are handled in a way that emulates LaTeX's behavior.
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs12
1 files changed, 11 insertions, 1 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 0202c1fc4..73780a8b8 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -29,7 +29,7 @@ import Prelude
import Control.Applicative (many, optional, (<|>))
import Control.Monad
import Control.Monad.Except (throwError)
-import Data.Char (isDigit, isLetter, toLower, toUpper)
+import Data.Char (isDigit, isLetter, toLower, toUpper, chr)
import Data.Default
import Data.List (intercalate, isPrefixOf)
import qualified Data.Map as M
@@ -893,6 +893,8 @@ inlineCommands = M.union inlineLanguageCommands $ 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
+ , ("mbox", rawInlineOr "mbox" $ processHBox <$> tok)
+ , ("hbox", rawInlineOr "hbox" $ processHBox <$> tok)
, ("lettrine", optional opt >> extractSpaces (spanWith ("",["lettrine"],[])) <$> tok)
, ("(", mathInline . toksToString <$> manyTill anyTok (controlSeq ")"))
, ("[", mathDisplay . toksToString <$> manyTill anyTok (controlSeq "]"))
@@ -1287,6 +1289,14 @@ rawInlineOr name' fallback = do
then rawInline "latex" <$> getRawCommand name' ("\\" <> name')
else fallback
+processHBox :: Inlines -> Inlines
+processHBox = walk convert
+ where
+ convert Space = Str [chr 160] -- non-breakable space
+ convert SoftBreak = Str [chr 160] -- non-breakable space
+ convert LineBreak = Str ""
+ convert x = x
+
getRawCommand :: PandocMonad m => Text -> Text -> LP m String
getRawCommand name txt = do
(_, rawargs) <- withRaw $