diff options
author | John MacFarlane <jgm@berkeley.edu> | 2011-01-26 20:44:25 -0800 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2011-01-26 20:44:25 -0800 |
commit | f8dca6ccbc4ce927ee035c3e60729c040b2280a0 (patch) | |
tree | 8146ceff33aa064450e368ef6cd515d50f278294 /src/Text/Pandoc/Writers | |
parent | 703c421c9e8684bb20aa091223ca5e532b6bb867 (diff) | |
download | pandoc-f8dca6ccbc4ce927ee035c3e60729c040b2280a0.tar.gz |
Add support for attributes in inline Code.
Additional related changes:
* URLs in Code in autolinks now use class "url".
* Require highlighting-kate 0.2.8.2, which omits the final <br/> tag,
essential for inline code.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 17 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Man.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 48 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/MediaWiki.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Org.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Textile.hs | 6 |
13 files changed, 75 insertions, 59 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index b6f5352c6..0f6e00a3b 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -245,9 +245,9 @@ inlineToConTeXt (Subscript lst) = do inlineToConTeXt (SmallCaps lst) = do contents <- inlineListToConTeXt lst return $ braces $ "\\sc " <> contents -inlineToConTeXt (Code str) | not ('{' `elem` str || '}' `elem` str) = +inlineToConTeXt (Code _ str) | not ('{' `elem` str || '}' `elem` str) = return $ "\\type" <> braces (text str) -inlineToConTeXt (Code str) = +inlineToConTeXt (Code _ str) = return $ "\\mono" <> braces (text $ stringToConTeXt str) inlineToConTeXt (Quoted SingleQuote lst) = do contents <- inlineListToConTeXt lst @@ -270,7 +270,7 @@ inlineToConTeXt (RawInline "tex" str) = return $ text str inlineToConTeXt (RawInline _ _) = return empty inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr inlineToConTeXt Space = return space -inlineToConTeXt (Link [Code str] (src, tit)) = -- since ConTeXt has its own +inlineToConTeXt (Link [Code _ str] (src, tit)) = -- since ConTeXt has its own inlineToConTeXt (Link [Str str] (src, tit)) -- way of printing links... inlineToConTeXt (Link txt (src, _)) = do st <- get diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index aac4002f5..9d09d46e3 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -258,7 +258,7 @@ inlineToDocbook _ Apostrophe = char '\'' inlineToDocbook _ Ellipses = text "…" inlineToDocbook _ EmDash = text "—" inlineToDocbook _ EnDash = text "–" -inlineToDocbook _ (Code str) = +inlineToDocbook _ (Code _ str) = inTagsSimple "literal" $ text (escapeStringForXML str) inlineToDocbook opts (Math _ str) = inlinesToDocbook opts $ readTeXMath str inlineToDocbook _ (RawInline _ _) = empty @@ -269,10 +269,10 @@ inlineToDocbook opts (Link txt (src, _)) = then let src' = drop 7 src emailLink = inTagsSimple "email" $ text $ escapeStringForXML $ src' - in if txt == [Code src'] - then emailLink - else inlinesToDocbook opts txt <+> char '(' <> emailLink <> - char ')' + in case txt of + [Code _ s] | s == src' -> emailLink + _ -> inlinesToDocbook opts txt <+> + char '(' <> emailLink <> char ')' else (if isPrefixOf "#" src then inTags False "link" [("linkend", drop 1 src)] else inTags False "ulink" [("url", src)]) $ diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 94dec864e..3b40515da 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -298,6 +298,12 @@ obfuscateChar char = obfuscateString :: String -> String obfuscateString = concatMap obfuscateChar . decodeCharacterReferences +attrsToHtml :: WriterOptions -> Attr -> [HtmlAttr] +attrsToHtml opts (id',classes',keyvals) = + [theclass (unwords classes') | not (null classes')] ++ + [prefixedId opts id' | not (null id')] ++ + map (\(x,y) -> strAttr x y) keyvals + -- | Convert Pandoc block element to HTML. blockToHtml :: WriterOptions -> Block -> State WriterState Html blockToHtml _ Null = return $ noHtml @@ -322,9 +328,7 @@ blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do Left _ -> -- change leading newlines into <br /> tags, because some -- browsers ignore leading newlines in pre blocks let (leadingBreaks, rawCode') = span (=='\n') rawCode - attrs = [theclass (unwords classes') | not (null classes')] ++ - [prefixedId opts id' | not (null id')] ++ - map (\(x,y) -> strAttr x y) keyvals + attrs = attrsToHtml opts (id', classes', keyvals) addBird = if "literate" `elem` classes' then unlines . map ("> " ++) . lines else unlines . lines @@ -479,7 +483,10 @@ inlineToHtml opts inline = (Apostrophe) -> return $ stringToHtml "’" (Emph lst) -> inlineListToHtml opts lst >>= return . emphasize (Strong lst) -> inlineListToHtml opts lst >>= return . strong - (Code str) -> return $ thecode << str + (Code attr str) -> return $ thecode ! (attrsToHtml opts attr) << str' + where str' = case highlightHtml attr str of + Left _ -> stringToHtml str + Right h -> h (Strikeout lst) -> inlineListToHtml opts lst >>= return . (thespan ! [thestyle "text-decoration: line-through;"]) (SmallCaps lst) -> inlineListToHtml opts lst >>= @@ -547,7 +554,7 @@ inlineToHtml opts inline = _ -> return noHtml (RawInline "html" str) -> return $ primHtml str (RawInline _ _) -> return noHtml - (Link [Code str] (s,_)) | "mailto:" `isPrefixOf` s -> + (Link [Code _ str] (s,_)) | "mailto:" `isPrefixOf` s -> return $ obfuscateLink opts str s (Link txt (s,_)) | "mailto:" `isPrefixOf` s -> do linkText <- inlineListToHtml opts txt diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 101ae628a..d2f8553e3 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -150,7 +150,7 @@ inCmd cmd contents = char '\\' <> text cmd <> braces contents -- (because it's illegal to have verbatim inside some command arguments) deVerb :: [Inline] -> [Inline] deVerb [] = [] -deVerb ((Code str):rest) = +deVerb ((Code _ str):rest) = (RawInline "latex" $ "\\texttt{" ++ stringToLaTeX str ++ "}"):(deVerb rest) deVerb (other:rest) = other:(deVerb rest) @@ -331,7 +331,7 @@ inlineToLaTeX (Cite cits lst) = do Biblatex -> citationsToBiblatex cits _ -> inlineListToLaTeX lst -inlineToLaTeX (Code str) = do +inlineToLaTeX (Code _ str) = do st <- get when (stInNote st) $ modify $ \s -> s{ stVerbInNote = True } let chr = ((enumFromTo '!' '~') \\ str) !! 0 @@ -368,7 +368,7 @@ inlineToLaTeX (LineBreak) = return "\\\\" inlineToLaTeX Space = return space inlineToLaTeX (Link txt (src, _)) = case txt of - [Code x] | x == src -> -- autolink + [Code _ x] | x == src -> -- autolink do modify $ \s -> s{ stUrl = True } return $ text $ "\\url{" ++ x ++ "}" _ -> do contents <- inlineListToLaTeX $ deVerb txt diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index c3e4ea3bb..78b9274d6 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -307,7 +307,7 @@ inlineToMan _ EmDash = return $ text "\\[em]" inlineToMan _ EnDash = return $ text "\\[en]" inlineToMan _ Apostrophe = return $ char '\'' inlineToMan _ Ellipses = return $ text "\\&..." -inlineToMan _ (Code str) = +inlineToMan _ (Code _ str) = return $ text $ "\\f[C]" ++ escapeCode str ++ "\\f[]" inlineToMan _ (Str str) = return $ text $ escapeString str inlineToMan opts (Math InlineMath str) = inlineListToMan opts $ readTeXMath str @@ -322,9 +322,10 @@ inlineToMan _ Space = return space inlineToMan opts (Link txt (src, _)) = do linktext <- inlineListToMan opts txt let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src - return $ if txt == [Code srcSuffix] - then char '<' <> text srcSuffix <> char '>' - else linktext <> text " (" <> text src <> char ')' + return $ case txt of + [Code _ s] + | s == srcSuffix -> char '<' <> text srcSuffix <> char '>' + _ -> linktext <> text " (" <> text src <> char ')' inlineToMan opts (Image alternate (source, tit)) = do let txt = if (null alternate) || (alternate == [Str ""]) || (alternate == [Str source]) -- to prevent autolinks diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index d1b16b34e..5e12c4aca 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -73,7 +73,7 @@ plainify = bottomUp go go (Superscript xs) = SmallCaps xs go (Subscript xs) = SmallCaps xs go (SmallCaps xs) = SmallCaps xs - go (Code s) = Str s + go (Code _ s) = Str s go (Math _ s) = Str s go (RawInline _ _) = Str "" go (Link xs _) = SmallCaps xs @@ -171,6 +171,22 @@ elementToListItem (Sec _ _ _ headerText subsecs) = [Plain headerText] ++ then [] else [BulletList $ map elementToListItem subsecs] +attrsToMarkdown :: Attr -> Doc +attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys] + where attribId = case attribs of + ([],_,_) -> empty + (i,_,_) -> "#" <> text i + attribClasses = case attribs of + (_,[],_) -> empty + (_,cs,_) -> hsep $ + map (text . ('.':)) + cs + attribKeys = case attribs of + (_,_,[]) -> empty + (_,_,ks) -> hsep $ + map (\(k,v) -> text k + <> "=\"" <> text v <> "\"") ks + -- | Ordered list start parser for use in Para below. olMarker :: GenParser Char ParserState Char olMarker = do (start, style', delim) <- anyOrderedListMarker @@ -233,26 +249,13 @@ blockToMarkdown opts (CodeBlock (_,classes,_) str) writerLiterateHaskell opts = return $ prefixed "> " (text str) <> blankline blockToMarkdown opts (CodeBlock attribs str) = return $ - if writerStrictMarkdown opts || attribs == ([],[],[]) + if writerStrictMarkdown opts || attribs == nullAttr then nest (writerTabStop opts) (text str) <> blankline else -- use delimited code block flush (tildes <> space <> attrs <> cr <> text str <> cr <> tildes) <> blankline where tildes = text "~~~~" - attrs = braces $ hsep [attribId, attribClasses, attribKeys] - attribId = case attribs of - ([],_,_) -> empty - (i,_,_) -> "#" <> text i - attribClasses = case attribs of - (_,[],_) -> empty - (_,cs,_) -> hsep $ - map (text . ('.':)) - cs - attribKeys = case attribs of - (_,_,[]) -> empty - (_,_,ks) -> hsep $ - map (\(k,v) -> text k - <> "=\"" <> text v <> "\"") ks + attrs = attrsToMarkdown attribs blockToMarkdown opts (BlockQuote blocks) = do st <- get -- if we're writing literate haskell, put a space before the bird tracks @@ -423,14 +426,17 @@ inlineToMarkdown _ EmDash = return "\8212" inlineToMarkdown _ EnDash = return "\8211" inlineToMarkdown _ Apostrophe = return "\8217" inlineToMarkdown _ Ellipses = return "\8230" -inlineToMarkdown _ (Code str) = +inlineToMarkdown opts (Code attr str) = let tickGroups = filter (\s -> '`' `elem` s) $ group str longest = if null tickGroups then 0 else maximum $ map length tickGroups marker = replicate (longest + 1) '`' - spacer = if (longest == 0) then "" else " " in - return $ text (marker ++ spacer ++ str ++ spacer ++ marker) + spacer = if (longest == 0) then "" else " " + attrs = if writerStrictMarkdown opts || attr == nullAttr + then empty + else attrsToMarkdown attr + in return $ text (marker ++ spacer ++ str ++ spacer ++ marker) <> attrs inlineToMarkdown _ (Str str) = do st <- get if stPlain st @@ -485,7 +491,9 @@ inlineToMarkdown opts (Link txt (src', tit)) = do let src = unescapeURI src' let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src let useRefLinks = writerReferenceLinks opts - let useAuto = null tit && txt == [Code srcSuffix] + let useAuto = case (tit,txt) of + ("", [Code _ s]) | s == srcSuffix -> True + _ -> False ref <- if useRefLinks then getReference txt (src, tit) else return [] reftext <- inlineListToMarkdown opts ref return $ if useAuto diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 1400b5846..a7c7fc482 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -362,7 +362,7 @@ inlineToMediaWiki _ Apostrophe = return "’" inlineToMediaWiki _ Ellipses = return "…" -inlineToMediaWiki _ (Code str) = +inlineToMediaWiki _ (Code _ str) = return $ "<tt>" ++ (escapeString str) ++ "</tt>" inlineToMediaWiki _ (Str str) = return $ escapeString str @@ -380,12 +380,12 @@ inlineToMediaWiki _ Space = return " " inlineToMediaWiki opts (Link txt (src, _)) = do label <- inlineListToMediaWiki opts txt - if txt == [Code src] -- autolink - then return src - else if isURI src - then return $ "[" ++ src ++ " " ++ label ++ "]" - else return $ "[[" ++ src' ++ "|" ++ label ++ "]]" - where src' = case src of + case txt of + [Code _ s] | s == src -> return src + _ -> if isURI src + then return $ "[" ++ src ++ " " ++ label ++ "]" + else return $ "[[" ++ src' ++ "|" ++ label ++ "]]" + where src' = case src of '/':xs -> xs -- with leading / it's a _ -> src -- link to a help page inlineToMediaWiki opts (Image alt (source, tit)) = do diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 59980a30c..b9444aac7 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -362,7 +362,7 @@ inlineToOpenDocument o ils | Subscript l <- ils = withTextStyle Sub $ inlinesToOpenDocument o l | SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l | Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l - | Code s <- ils = preformatted s + | Code _ s <- ils = preformatted s | Math _ s <- ils = inlinesToOpenDocument o (readTeXMath s) | Cite _ l <- ils = inlinesToOpenDocument o l | RawInline "opendocument" s <- ils = preformatted s diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 8f3ff6f3e..f7f314428 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -253,7 +253,7 @@ inlineToOrg EmDash = return "---" inlineToOrg EnDash = return "--" inlineToOrg Apostrophe = return "'" inlineToOrg Ellipses = return "..." -inlineToOrg (Code str) = return $ "=" <> text str <> "=" +inlineToOrg (Code _ str) = return $ "=" <> text str <> "=" inlineToOrg (Str str) = return $ text $ escapeString str inlineToOrg (Math t str) = do modify $ \st -> st{ stHasMath = True } @@ -266,7 +266,7 @@ inlineToOrg (LineBreak) = return cr -- there's no line break in Org inlineToOrg Space = return space inlineToOrg (Link txt (src, _)) = do case txt of - [Code x] | x == src -> -- autolink + [Code _ x] | x == src -> -- autolink do modify $ \s -> s{ stLinks = True } return $ "[[" <> text x <> "]]" _ -> do contents <- inlineListToOrg txt diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 1d1f79d57..d4adaa929 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -285,7 +285,7 @@ inlineToRST EmDash = return $ char '\8212' inlineToRST EnDash = return $ char '\8211' inlineToRST Apostrophe = return $ char '\8217' inlineToRST Ellipses = return $ char '\8230' -inlineToRST (Code str) = return $ "``" <> text str <> "``" +inlineToRST (Code _ str) = return $ "``" <> text str <> "``" inlineToRST (Str str) = return $ text $ escapeString str inlineToRST (Math t str) = do modify $ \st -> st{ stHasMath = True } @@ -295,8 +295,8 @@ inlineToRST (Math t str) = do inlineToRST (RawInline _ _) = return empty inlineToRST (LineBreak) = return cr -- there's no line break in RST inlineToRST Space = return space -inlineToRST (Link [Code str] (src, _)) | src == str || - src == "mailto:" ++ str = do +inlineToRST (Link [Code _ str] (src, _)) | src == str || + src == "mailto:" ++ str = do let srcSuffix = if isPrefixOf "mailto:" src then drop 7 src else src return $ text $ unescapeURI srcSuffix inlineToRST (Link txt (src', tit)) = do diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 31a28101c..63954cebf 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -265,7 +265,7 @@ inlineToRTF Apostrophe = "\\u8217'" inlineToRTF Ellipses = "\\u8230?" inlineToRTF EmDash = "\\u8212-" inlineToRTF EnDash = "\\u8211-" -inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}" +inlineToRTF (Code _ str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}" inlineToRTF (Str str) = stringToRTF str inlineToRTF (Math _ str) = inlineListToRTF $ readTeXMath str inlineToRTF (Cite _ lst) = inlineListToRTF lst diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 037d7bdbe..c8638cdd7 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -372,7 +372,7 @@ inlineToTexinfo (Subscript lst) = do inlineToTexinfo (SmallCaps lst) = inlineListToTexinfo lst >>= return . inCmd "sc" -inlineToTexinfo (Code str) = do +inlineToTexinfo (Code _ str) = do return $ text $ "@code{" ++ stringToTexinfo str ++ "}" inlineToTexinfo (Quoted SingleQuote lst) = do @@ -400,7 +400,7 @@ inlineToTexinfo Space = return $ char ' ' inlineToTexinfo (Link txt (src, _)) = do case txt of - [Code x] | x == src -> -- autolink + [Code _ x] | x == src -> -- autolink do return $ text $ "@url{" ++ x ++ "}" _ -> do contents <- inlineListToTexinfo txt let src1 = stringToTexinfo src diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 9bfff0dba..6614ec28e 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -378,7 +378,7 @@ inlineToTextile _ Apostrophe = return "'" inlineToTextile _ Ellipses = return "..." -inlineToTextile _ (Code str) = +inlineToTextile _ (Code _ str) = return $ if '@' `elem` str then "<tt>" ++ escapeStringForXML str ++ "</tt>" else "@" ++ str ++ "@" @@ -399,8 +399,8 @@ inlineToTextile _ Space = return " " inlineToTextile opts (Link txt (src, _)) = do label <- case txt of - [Code s] -> return s - _ -> inlineListToTextile opts txt + [Code _ s] -> return s + _ -> inlineListToTextile opts txt return $ "\"" ++ label ++ "\":" ++ src inlineToTextile opts (Image alt (source, tit)) = do |