aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/ConTeXt.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2011-12-30 14:32:49 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2011-12-30 14:32:49 -0800
commit2c1569a0da04627b3c4a75c18fbb38d7776e68ed (patch)
treeee251e37dc24b3b0810c7292cb3d1a79d61707ae /src/Text/Pandoc/Writers/ConTeXt.hs
parente3dfb2646d950a6c468835cca5da759cf098ee75 (diff)
downloadpandoc-2c1569a0da04627b3c4a75c18fbb38d7776e68ed.tar.gz
Added support for internal links in ConTeXt writer.
Based on a patch by B. Scott Michel. Also simplified use of \hyphenateurl. We no longer try to go within an Inline list to find URLs. This is resource-heavy, and the main use case is autolinks, which can be readily recognized.
Diffstat (limited to 'src/Text/Pandoc/Writers/ConTeXt.hs')
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs45
1 files changed, 15 insertions, 30 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 9ea82268a..1427f78c8 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -31,7 +31,7 @@ Conversion of 'Pandoc' format into ConTeXt.
module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where
import Text.Pandoc.Definition
import Text.Pandoc.Shared
-import Text.Pandoc.Generic (queryWith, bottomUp)
+import Text.Pandoc.Generic (queryWith)
import Text.Printf ( printf )
import Data.List ( intercalate )
import Control.Monad.State
@@ -271,35 +271,29 @@ inlineToConTeXt (RawInline "tex" str) = return $ text str
inlineToConTeXt (RawInline _ _) = return empty
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))
+-- autolink
+inlineToConTeXt (Link [Code _ str] (src, tit)) = inlineToConTeXt (Link
+ [RawInline "context" "\\hyphenatedurl{", Str str, RawInline "context" "}"]
+ (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
+ opts <- gets stOptions
+ label <- inlineListToConTeXt txt
return $ text "\\in"
- <> braces label'
- <> braces label''
+ <> braces (if writerNumberSections opts
+ then label <+> text "(\\S"
+ else label) -- prefix
+ <> braces (if writerNumberSections opts
+ then text ")"
+ else empty) -- suffix
<> 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
- label <- inlineListToConTeXt $ bottomUp hyphenateURL (normalize txt)
+ label <- inlineListToConTeXt txt
return $ "\\useURL"
<> brackets (text ref)
<> brackets (text $ escapeStringUsing [('#',"\\#")] src)
@@ -328,7 +322,7 @@ sectionHeader :: [Char]
-> [Inline]
-> State WriterState Doc
sectionHeader ident hdrLevel lst = do
- contents <- (inlineListToConTeXt . normalize) lst
+ contents <- inlineListToConTeXt lst
st <- get
let opts = stOptions st
let level' = if writerChapters opts then hdrLevel - 1 else hdrLevel
@@ -343,12 +337,3 @@ sectionHeader ident hdrLevel lst = do
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