aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2014-09-27 16:20:56 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2014-09-27 16:20:56 -0700
commit9c4e33f085c40a4cbf221c5b76830fcf062880a2 (patch)
tree139af540ea9e48a55d0943e41dad0651bdeee1c7 /src/Text/Pandoc
parent5bab9574f615ef41bc0ae85c161e2a88a55bd86c (diff)
parent84b75a1c2a0067021031e5545ab50a521f966907 (diff)
downloadpandoc-9c4e33f085c40a4cbf221c5b76830fcf062880a2.tar.gz
Merge pull request #1589 from mszep/master
Add function to sanitize ConTeXt labels
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs24
1 files changed, 17 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index bbca7f858..ebdc4a3d3 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -36,6 +36,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Walk (query)
import Text.Printf ( printf )
import Data.List ( intercalate )
+import Data.Char ( ord )
import Control.Monad.State
import Text.Pandoc.Pretty
import Text.Pandoc.Templates ( renderTemplate' )
@@ -114,6 +115,13 @@ escapeCharForConTeXt opts ch =
stringToConTeXt :: WriterOptions -> String -> String
stringToConTeXt opts = concatMap (escapeCharForConTeXt opts)
+-- | Sanitize labels
+toLabel :: String -> String
+toLabel z = concatMap go z
+ where go x
+ | elem x "\\#[]\",{}%()|=" = "ux" ++ printf "%x" (ord x)
+ | otherwise = [x]
+
-- | Convert Elements to ConTeXt
elementToConTeXt :: WriterOptions -> Element -> State WriterState Doc
elementToConTeXt _ (Blk block) = blockToConTeXt block
@@ -286,15 +294,16 @@ inlineToConTeXt Space = return space
-- Handle HTML-like internal document references to sections
inlineToConTeXt (Link txt (('#' : ref), _)) = do
opts <- gets stOptions
- label <- inlineListToConTeXt txt
+ contents <- inlineListToConTeXt txt
+ let ref' = toLabel $ stringToConTeXt opts ref
return $ text "\\in"
<> braces (if writerNumberSections opts
- then label <+> text "(\\S"
- else label) -- prefix
+ then contents <+> text "(\\S"
+ else contents) -- prefix
<> braces (if writerNumberSections opts
then text ")"
else empty) -- suffix
- <> brackets (text ref)
+ <> brackets (text ref')
inlineToConTeXt (Link txt (src, _)) = do
let isAutolink = txt == [Str (unEscapeString src)]
@@ -302,13 +311,13 @@ inlineToConTeXt (Link txt (src, _)) = do
let next = stNextRef st
put $ st {stNextRef = next + 1}
let ref = "url" ++ show next
- label <- inlineListToConTeXt txt
+ contents <- inlineListToConTeXt txt
return $ "\\useURL"
<> brackets (text ref)
<> brackets (text $ escapeStringUsing [('#',"\\#"),('%',"\\%")] src)
<> (if isAutolink
then empty
- else brackets empty <> brackets label)
+ else brackets empty <> brackets contents)
<> "\\from"
<> brackets (text ref)
inlineToConTeXt (Image _ (src, _)) = do
@@ -337,6 +346,7 @@ sectionHeader (ident,classes,_) hdrLevel lst = do
st <- get
let opts = stOptions st
let level' = if writerChapters opts then hdrLevel - 1 else hdrLevel
+ let ident' = toLabel ident
let (section, chapter) = if "unnumbered" `elem` classes
then (text "subject", text "title")
else (text "section", text "chapter")
@@ -344,7 +354,7 @@ sectionHeader (ident,classes,_) hdrLevel lst = do
then char '\\'
<> text (concat (replicate (level' - 1) "sub"))
<> section
- <> (if (not . null) ident then brackets (text ident) else empty)
+ <> (if (not . null) ident' then brackets (text ident') else empty)
<> braces contents
<> blankline
else if level' == 0