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