ConTeXt writer: add function toLabel
This function can be used to sanitize reference labels so that they do not contain any of the illegal characters \#[]",{}%()|= . Currently only Links have their labels sanitized, because they are the only Elements that use passed labels.
This commit is contained in:
parent
4455905550
commit
84b75a1c2a
1 changed files with 17 additions and 7 deletions
|
@ -36,6 +36,7 @@ import Text.Pandoc.Options
|
||||||
import Text.Pandoc.Walk (query)
|
import Text.Pandoc.Walk (query)
|
||||||
import Text.Printf ( printf )
|
import Text.Printf ( printf )
|
||||||
import Data.List ( intercalate )
|
import Data.List ( intercalate )
|
||||||
|
import Data.Char ( ord )
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Text.Pandoc.Pretty
|
import Text.Pandoc.Pretty
|
||||||
import Text.Pandoc.Templates ( renderTemplate' )
|
import Text.Pandoc.Templates ( renderTemplate' )
|
||||||
|
@ -114,6 +115,13 @@ escapeCharForConTeXt opts ch =
|
||||||
stringToConTeXt :: WriterOptions -> String -> String
|
stringToConTeXt :: WriterOptions -> String -> String
|
||||||
stringToConTeXt opts = concatMap (escapeCharForConTeXt opts)
|
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
|
-- | Convert Elements to ConTeXt
|
||||||
elementToConTeXt :: WriterOptions -> Element -> State WriterState Doc
|
elementToConTeXt :: WriterOptions -> Element -> State WriterState Doc
|
||||||
elementToConTeXt _ (Blk block) = blockToConTeXt block
|
elementToConTeXt _ (Blk block) = blockToConTeXt block
|
||||||
|
@ -286,15 +294,16 @@ inlineToConTeXt Space = return space
|
||||||
-- Handle HTML-like internal document references to sections
|
-- Handle HTML-like internal document references to sections
|
||||||
inlineToConTeXt (Link txt (('#' : ref), _)) = do
|
inlineToConTeXt (Link txt (('#' : ref), _)) = do
|
||||||
opts <- gets stOptions
|
opts <- gets stOptions
|
||||||
label <- inlineListToConTeXt txt
|
contents <- inlineListToConTeXt txt
|
||||||
|
let ref' = toLabel $ stringToConTeXt opts ref
|
||||||
return $ text "\\in"
|
return $ text "\\in"
|
||||||
<> braces (if writerNumberSections opts
|
<> braces (if writerNumberSections opts
|
||||||
then label <+> text "(\\S"
|
then contents <+> text "(\\S"
|
||||||
else label) -- prefix
|
else contents) -- prefix
|
||||||
<> braces (if writerNumberSections opts
|
<> braces (if writerNumberSections opts
|
||||||
then text ")"
|
then text ")"
|
||||||
else empty) -- suffix
|
else empty) -- suffix
|
||||||
<> brackets (text ref)
|
<> brackets (text ref')
|
||||||
|
|
||||||
inlineToConTeXt (Link txt (src, _)) = do
|
inlineToConTeXt (Link txt (src, _)) = do
|
||||||
let isAutolink = txt == [Str (unEscapeString src)]
|
let isAutolink = txt == [Str (unEscapeString src)]
|
||||||
|
@ -302,13 +311,13 @@ inlineToConTeXt (Link txt (src, _)) = do
|
||||||
let next = stNextRef st
|
let next = stNextRef st
|
||||||
put $ st {stNextRef = next + 1}
|
put $ st {stNextRef = next + 1}
|
||||||
let ref = "url" ++ show next
|
let ref = "url" ++ show next
|
||||||
label <- inlineListToConTeXt txt
|
contents <- inlineListToConTeXt txt
|
||||||
return $ "\\useURL"
|
return $ "\\useURL"
|
||||||
<> brackets (text ref)
|
<> brackets (text ref)
|
||||||
<> brackets (text $ escapeStringUsing [('#',"\\#"),('%',"\\%")] src)
|
<> brackets (text $ escapeStringUsing [('#',"\\#"),('%',"\\%")] src)
|
||||||
<> (if isAutolink
|
<> (if isAutolink
|
||||||
then empty
|
then empty
|
||||||
else brackets empty <> brackets label)
|
else brackets empty <> brackets contents)
|
||||||
<> "\\from"
|
<> "\\from"
|
||||||
<> brackets (text ref)
|
<> brackets (text ref)
|
||||||
inlineToConTeXt (Image _ (src, _)) = do
|
inlineToConTeXt (Image _ (src, _)) = do
|
||||||
|
@ -337,6 +346,7 @@ sectionHeader (ident,classes,_) hdrLevel lst = do
|
||||||
st <- get
|
st <- get
|
||||||
let opts = stOptions st
|
let opts = stOptions st
|
||||||
let level' = if writerChapters opts then hdrLevel - 1 else hdrLevel
|
let level' = if writerChapters opts then hdrLevel - 1 else hdrLevel
|
||||||
|
let ident' = toLabel ident
|
||||||
let (section, chapter) = if "unnumbered" `elem` classes
|
let (section, chapter) = if "unnumbered" `elem` classes
|
||||||
then (text "subject", text "title")
|
then (text "subject", text "title")
|
||||||
else (text "section", text "chapter")
|
else (text "section", text "chapter")
|
||||||
|
@ -344,7 +354,7 @@ sectionHeader (ident,classes,_) hdrLevel lst = do
|
||||||
then char '\\'
|
then char '\\'
|
||||||
<> text (concat (replicate (level' - 1) "sub"))
|
<> text (concat (replicate (level' - 1) "sub"))
|
||||||
<> section
|
<> section
|
||||||
<> (if (not . null) ident then brackets (text ident) else empty)
|
<> (if (not . null) ident' then brackets (text ident') else empty)
|
||||||
<> braces contents
|
<> braces contents
|
||||||
<> blankline
|
<> blankline
|
||||||
else if level' == 0
|
else if level' == 0
|
||||||
|
|
Loading…
Reference in a new issue