ConTeXt writer: Add section labels and internal links as in HTML.
Add the ability to refer to internal links to the ConTeXt writer, just like the HTML writer can. The 'hierarchicalize' function generates unique names for sections, which can be used for references in ConTeXt, just as they can be in HTML. The ConTeXt writer adds these unique identifiers to each \section and does special processing of the Link target to see if it starts with a '#' (hash symbol), which is the tip-off that the link is an internal link.
This commit is contained in:
parent
83680430b3
commit
a5ee02c659
2 changed files with 77 additions and 27 deletions
12
README
12
README
|
@ -707,13 +707,13 @@ wrapping). Consider, for example:
|
|||
#22, for example, and #5.
|
||||
|
||||
|
||||
### Header identifiers in HTML ###
|
||||
### Header identifiers in HTML and ConTeXt ###
|
||||
|
||||
*Pandoc extension*.
|
||||
|
||||
Each header element in pandoc's HTML output is given a unique
|
||||
identifier. This identifier is based on the text of the header. To
|
||||
derive the identifier from the header text,
|
||||
Each header element in pandoc's HTML and ConTeXt output is given a
|
||||
unique identifier. This identifier is based on the text of the header.
|
||||
To derive the identifier from the header text,
|
||||
|
||||
- Remove all formatting, links, etc.
|
||||
- Remove all punctuation, except underscores, hyphens, and periods.
|
||||
|
@ -745,10 +745,10 @@ also make it easy to provide links from one section of a document to
|
|||
another. A link to this section, for example, might look like this:
|
||||
|
||||
See the section on
|
||||
[header identifiers](#header-identifiers-in-html).
|
||||
[header identifiers][#header-identifiers-in-html].
|
||||
|
||||
Note, however, that this method of providing links to sections works
|
||||
only in HTML.
|
||||
only in HTML and ConTeXt formats.
|
||||
|
||||
If the `--section-divs` option is specified, then each section will
|
||||
be wrapped in a `div` (or a `section`, if `--html5` was specified),
|
||||
|
|
|
@ -69,8 +69,8 @@ pandocToConTeXt options (Pandoc (Meta title authors date) blocks) = do
|
|||
datetext <- if null date
|
||||
then return ""
|
||||
else liftM (render colwidth) $ inlineListToConTeXt date
|
||||
body <- blockListToConTeXt blocks
|
||||
let main = render colwidth $ body
|
||||
body <- mapM (elementToConTeXt options) $ hierarchicalize blocks
|
||||
let main = (render colwidth . cat) body
|
||||
let context = writerVariables options ++
|
||||
[ ("toc", if writerTableOfContents options then "yes" else "")
|
||||
, ("body", main)
|
||||
|
@ -113,6 +113,14 @@ escapeCharForConTeXt ch =
|
|||
stringToConTeXt :: String -> String
|
||||
stringToConTeXt = concatMap escapeCharForConTeXt
|
||||
|
||||
-- | Convert Elements to ConTeXt
|
||||
elementToConTeXt :: WriterOptions -> Element -> State WriterState Doc
|
||||
elementToConTeXt _ (Blk block) = blockToConTeXt block
|
||||
elementToConTeXt opts (Sec level _ id' title' elements) = do
|
||||
header' <- sectionHeader id' level title'
|
||||
innerContents <- mapM (elementToConTeXt opts) elements
|
||||
return $ cat (header' : innerContents)
|
||||
|
||||
-- | Convert Pandoc block element to ConTeXt.
|
||||
blockToConTeXt :: Block
|
||||
-> State WriterState Doc
|
||||
|
@ -172,17 +180,8 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do
|
|||
blockToConTeXt (DefinitionList lst) =
|
||||
liftM vcat $ mapM defListItemToConTeXt lst
|
||||
blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
|
||||
blockToConTeXt (Header level lst) = do
|
||||
contents <- inlineListToConTeXt lst
|
||||
st <- get
|
||||
let opts = stOptions st
|
||||
let level' = if writerChapters opts then level - 1 else level
|
||||
return $ if level' >= 1 && level' <= 5
|
||||
then char '\\' <> text (concat (replicate (level' - 1) "sub")) <>
|
||||
text "section" <> char '{' <> contents <> char '}' <> blankline
|
||||
else if level' == 0
|
||||
then "\\chapter{" <> contents <> "}"
|
||||
else contents <> blankline
|
||||
-- If this is ever executed, provide a default for the reference identifier.
|
||||
blockToConTeXt (Header level lst) = sectionHeader "" level lst
|
||||
blockToConTeXt (Table caption aligns widths heads rows) = do
|
||||
let colDescriptor colWidth alignment = (case alignment of
|
||||
AlignLeft -> 'l'
|
||||
|
@ -274,20 +273,40 @@ inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr
|
|||
inlineToConTeXt Space = return space
|
||||
-- ConTeXT has its own way of printing links
|
||||
inlineToConTeXt (Link [Code _ str] (src, tit)) = inlineToConTeXt (Link [Str str] (src, tit))
|
||||
-- Handle HTML-like internal document references to sections
|
||||
inlineToConTeXt (Link txt (('#' : ref), _)) = do
|
||||
st <- get
|
||||
let opts = stOptions st
|
||||
let numberedSections = writerNumberSections opts
|
||||
label <- inlineListToConTeXt $ bottomUp hyphenateURL (normalize txt)
|
||||
let hasLabel = (not . isEmpty) label
|
||||
let label' = if hasLabel
|
||||
then label <+> text "("
|
||||
else if numberedSections
|
||||
then text "Section"
|
||||
else empty
|
||||
let label'' = braces $ if hasLabel
|
||||
then text ")"
|
||||
else empty
|
||||
return $ text "\\in"
|
||||
<> braces label'
|
||||
<> braces label''
|
||||
<> brackets (text ref)
|
||||
|
||||
-- Convert link's text, hyphenating URLs when they're seen (does deep list inspection)
|
||||
inlineToConTeXt (Link txt (src, _)) = do
|
||||
st <- get
|
||||
let next = stNextRef st
|
||||
put $ st {stNextRef = next + 1}
|
||||
let ref = "url" ++ show next
|
||||
let hyphenateURL (Str str) | isURI str =
|
||||
RawInline "context" ("\\hyphenatedurl{" ++ str ++ "}")
|
||||
hyphenateURL x = x
|
||||
label <- inlineListToConTeXt (bottomUp hyphenateURL $ normalize txt)
|
||||
return $ "\\useURL" <> brackets (text ref) <>
|
||||
brackets (text $ escapeStringUsing [('#',"\\#")] src) <>
|
||||
brackets empty <> brackets label <>
|
||||
"\\from" <> brackets (text ref)
|
||||
label <- inlineListToConTeXt $ bottomUp hyphenateURL (normalize txt)
|
||||
return $ "\\useURL"
|
||||
<> brackets (text ref)
|
||||
<> brackets (text $ escapeStringUsing [('#',"\\#")] src)
|
||||
<> brackets empty
|
||||
<> brackets label
|
||||
<> "\\from"
|
||||
<> brackets (text ref)
|
||||
inlineToConTeXt (Image _ (src, _)) = do
|
||||
let src' = if isURI src
|
||||
then src
|
||||
|
@ -302,3 +321,34 @@ inlineToConTeXt (Note contents) = do
|
|||
then text "\\footnote{" <> nest 2 contents' <> char '}'
|
||||
else text "\\startbuffer " <> nest 2 contents' <>
|
||||
text "\\stopbuffer\\footnote{\\getbuffer}"
|
||||
|
||||
-- | Craft the section header, inserting the secton reference, if supplied.
|
||||
sectionHeader :: [Char]
|
||||
-> Int
|
||||
-> [Inline]
|
||||
-> State WriterState Doc
|
||||
sectionHeader ident hdrLevel lst = do
|
||||
contents <- (inlineListToConTeXt . normalize) lst
|
||||
st <- get
|
||||
let opts = stOptions st
|
||||
let level' = if writerChapters opts then hdrLevel - 1 else hdrLevel
|
||||
return $ if level' >= 1 && level' <= 5
|
||||
then char '\\'
|
||||
<> text (concat (replicate (level' - 1) "sub"))
|
||||
<> text "section"
|
||||
<> (if (not . null) ident then brackets (text ident) else empty)
|
||||
<> braces contents
|
||||
<> blankline
|
||||
else if level' == 0
|
||||
then "\\chapter{" <> contents <> "}"
|
||||
else contents <> blankline
|
||||
|
||||
-- | Convert absolute URLs/URIs to ConTeXt raw inlines so that they are hyphenated.
|
||||
hyphenateURL :: Inline
|
||||
-> Inline
|
||||
hyphenateURL x =
|
||||
case x of
|
||||
(Str str) -> if isAbsoluteURI str
|
||||
then (RawInline "context" ("\\hyphenatedurl{" ++ str ++ "}"))
|
||||
else x
|
||||
_otherwise -> x
|
||||
|
|
Loading…
Reference in a new issue