aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-12-17 23:23:06 +0100
committerAlbert Krewinkel <[email protected]>2022-12-17 23:53:12 +0100
commit8f5af5a06c2c247e2bd47543a1faef017b62d240 (patch)
treed922f5574a573d3039dcc4a8966bb4baf806c4c6
parenta36f12119fe1a0b70a1a3ff65264e94373a490ce (diff)
ConTeXt writer: always use `\type` for inline code
Inline codes that contained curly braces where previously rendered with `\mono`; this led to unexpected results when the presentation of `\type` was customized, as those changes would not have been applied to code rendered with `\mono`.
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs26
-rw-r--r--test/Tests/Writers/ConTeXt.hs14
2 files changed, 29 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index a5940e1e4..9443988e0 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -540,11 +540,16 @@ inlineToConTeXt (Subscript lst) = do
inlineToConTeXt (SmallCaps lst) = do
contents <- inlineListToConTeXt lst
return $ braces $ "\\sc " <> contents
-inlineToConTeXt (Code _ str) | not (T.any (\c -> c == '{' || c == '}') str) =
- return $ "\\type" <> braces (literal str)
-inlineToConTeXt (Code _ str) = do
- opts <- gets stOptions
- return $ "\\mono" <> braces (literal $ stringToConTeXt opts str)
+inlineToConTeXt (Code _ str) =
+ return . literal $
+ case typeDelim str of
+ Just (open, close) ->
+ "\\type" <> (open `T.cons` str) `T.snoc` close
+ Nothing ->
+ "\\type[escape=yes]{" <>
+ (T.replace "{" "/BTEX\\letteropenbrace /ETEX" .
+ T.replace "}" "/BTEX\\letterclosebrace /ETEX" $
+ str) `T.snoc` '}'
inlineToConTeXt (Quoted SingleQuote lst) = do
contents <- inlineListToConTeXt lst
return $ "\\quote" <> braces contents
@@ -713,6 +718,17 @@ sectionLevelToText opts (_,classes,_) hdrLevel headingType = do
SectionHeading -> "sectionlevel"
NonSectionHeading -> ""
+-- | Finds a pair of symbols that can be used as delimiters.
+typeDelim :: Text -> Maybe (Char, Char)
+typeDelim t =
+ let delimChars = "{\"'`()-+=%,.:;"
+ go delims '}' = go delims '{'
+ go delims c = T.filter (/= c) delims
+ in case fmap fst . T.uncons $ T.foldl' go delimChars t of
+ Just '{' -> Just ('{', '}')
+ Just c -> Just (c, c)
+ Nothing -> Nothing
+
fromBCP47 :: PandocMonad m => Maybe Text -> WM m (Maybe Text)
fromBCP47 mbs = fromBCP47' <$> toLang mbs
diff --git a/test/Tests/Writers/ConTeXt.hs b/test/Tests/Writers/ConTeXt.hs
index 272c58df3..6f46c8e6f 100644
--- a/test/Tests/Writers/ConTeXt.hs
+++ b/test/Tests/Writers/ConTeXt.hs
@@ -9,6 +9,7 @@ import Tests.Helpers
import Text.Pandoc
import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder
+import qualified Data.Text as T
context :: (ToPandoc a) => a -> String
context = unpack . purely (writeConTeXt def) . toPandoc
@@ -44,16 +45,17 @@ infix 4 =:
tests :: [TestTree]
tests =
[ testGroup "inline code"
- [ "with '}'" =: code "}" =?> "\\mono{\\}}"
+ [ "with '}'" =: code "}" =?> "\\type\"}\""
, "without '}'" =: code "]" =?> "\\type{]}"
, "span with ID" =:
spanWith ("city", [], []) "Berlin" =?>
"\\reference[city]{}Berlin"
- , testProperty "code property" $ \s -> null s || '\n' `elem` s ||
- if '{' `elem` s || '}' `elem` s
- then context' (code $ pack s) == "\\mono{" ++
- context' (str $ pack s) ++ "}"
- else context' (code $ pack s) == "\\type{" ++ s ++ "}"
+ , testProperty "code property" $ \s ->
+ null s || '\n' `elem` s ||
+ case T.stripPrefix "\\type" (pack $ context' (code $ pack s))
+ >>= T.uncons of
+ Just (c, _) -> c `notElem` s
+ Nothing -> False
]
, testGroup "headers"
[ "level 1" =: