diff options
-rw-r--r-- | src/Text/Pandoc/Highlighting.hs | 64 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 26 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 12 |
4 files changed, 48 insertions, 56 deletions
diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index c65d23f93..535f84ed2 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -29,57 +29,41 @@ Exports functions for syntax highlighting. -} module Text.Pandoc.Highlighting ( languages - , highlightHtml - , highlightLaTeX - , defaultHighlightingCss - , defaultLaTeXMacros , languagesByExtension + , highlight + , formatLaTeXInline + , formatLaTeXBlock + , styleToLaTeX + , formatHtmlInline + , formatHtmlBlock + , styleToHtml + , pygments ) where -import Text.Blaze import Text.Pandoc.Definition -import Text.Highlighting.Kate ( SourceLine, languages, highlightAs, formatAsHtml, - TokenType(..), formatAsLaTeX, FormatOption (..), defaultHighlightingCss, - defaultLaTeXMacros, languagesByExtension ) +import Text.Highlighting.Kate import Data.List (find) import Data.Maybe (fromMaybe) import Data.Char (toLower) -import qualified Text.Blaze.Html5.Attributes as A -highlight :: ([FormatOption] -> String -> [SourceLine] -> a) -- ^ Formatter - -> Bool -- ^ True if inline - -> Attr -- ^ Attributes of the Code or CodeBlock - -> String -- ^ Raw contents of the Code or CodeBlock - -> Maybe a -- ^ Maybe the formatted result -highlight formatter inline (_, classes, keyvals) rawCode = +lcLanguages :: [String] +lcLanguages = map (map toLower) languages + +highlight :: (FormatOptions -> [SourceLine] -> a) -- ^ Formatter + -> Attr -- ^ Attributes of the CodeBlock + -> String -- ^ Raw contents of the CodeBlock + -> Maybe a -- ^ Maybe the formatted result +highlight formatter (_, classes, keyvals) rawCode = let firstNum = case reads (fromMaybe "1" $ lookup "startFrom" keyvals) of ((n,_):_) -> n [] -> 1 - fmtOpts = [OptNumberFrom firstNum] ++ - [OptInline | inline] ++ - case find (`elem` ["number","numberLines","number-lines"]) classes of - Nothing -> [] - Just _ -> [OptNumberLines] - addBirdTracks = "literate" `elem` classes - lcLanguages = map (map toLower) languages - in case find (\c -> (map toLower c) `elem` lcLanguages) classes of + fmtOpts = defaultFormatOpts{ + startNumber = firstNum, + numberLines = any (`elem` + ["number","numberLines", "number-lines"]) classes } + lcclasses = map (map toLower) classes + in case find (`elem` lcLanguages) lcclasses of Nothing -> Nothing Just language -> Just - $ formatter fmtOpts language . - (if addBirdTracks - then map ((OtherTok,"> "):) - else id) + $ formatter fmtOpts $ highlightAs language rawCode -highlightHtml :: Bool -- ^ True if inline HTML - -> Attr -- ^ Attributes of the Code or CodeBlock - -> String -- ^ Raw contents of the Code or CodeBlock - -> Maybe Html -- ^ Maybe formatted Html -highlightHtml inline attr@(id',_,_) = fmap addId . highlight formatAsHtml inline attr - where addId = if null id' then id else (! A.id (toValue id')) - -highlightLaTeX :: Bool -- ^ True if inline - -> Attr -- ^ Attributes of the Code or CodeBlock - -> String -- ^ Raw contents of the Code or CodeBlock - -> Maybe String -- ^ Maybe formatted LaTeX -highlightLaTeX = highlight formatAsLaTeX - diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 9f8b921e7..150033f3f 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -35,7 +35,7 @@ import Text.Pandoc.Templates (renderTemplate) import Text.Pandoc.Readers.TeXMath import Data.List ( isPrefixOf, intercalate, isSuffixOf ) import Data.Char ( toLower ) -import Text.Pandoc.Highlighting (languages, languagesByExtension) +import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Pretty -- | Convert list of authors to a docbook <author> section diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 96fa5e906..1cee2b8e6 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -35,7 +35,8 @@ import Text.Pandoc.CharacterReferences ( decodeCharacterReferences ) import Text.Pandoc.Shared import Text.Pandoc.Templates import Text.Pandoc.Readers.TeXMath -import Text.Pandoc.Highlighting ( highlightHtml, defaultHighlightingCss ) +import Text.Pandoc.Highlighting ( highlight, pygments, styleToHtml, + formatHtmlInline, formatHtmlBlock ) import Text.Pandoc.XML (stripTags, escapeStringForXML) import Network.HTTP ( urlEncode ) import Numeric ( showHex ) @@ -153,7 +154,7 @@ pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do ("/*<![CDATA[*/\n" ++ s ++ "/*]]>*/\n") Nothing -> mempty else mempty - let newvars = [("highlighting-css", defaultHighlightingCss) | + let newvars = [("highlighting-css", renderHtml $ styleToHtml pygments) | stHighlighting st] ++ [("math", renderHtml math) | stMath st] return (tit, auths, date, toc, thebody, newvars) @@ -361,16 +362,21 @@ blockToHtml _ (RawBlock "html" str) = return $ preEscapedString str blockToHtml _ (RawBlock _ _) = return mempty blockToHtml _ (HorizontalRule) = return H.hr blockToHtml opts (CodeBlock (id',classes,keyvals) rawCode) = do - let classes' = if writerLiterateHaskell opts - then classes + let tolhs = writerLiterateHaskell opts && + any (\c -> map toLower c == "haskell") classes && + any (\c -> map toLower c == "literate") classes + classes' = if tolhs + then map (\c -> if map toLower c == "haskell" + then "literatehaskell" + else c) classes else filter (/= "literate") classes - case highlightHtml False (id',classes',keyvals) rawCode of + adjCode = if tolhs + then unlines . map ("> " ++) . lines $ rawCode + else rawCode + case highlight formatHtmlBlock (id',classes,keyvals) adjCode of Nothing -> let attrs = attrsToHtml opts (id', classes', keyvals) - addBird = if "literate" `elem` classes' - then unlines . map ("> " ++) . lines - else unlines . lines in return $ foldl (!) H.pre attrs $ H.code - $ toHtml $ addBird rawCode + $ toHtml adjCode Just h -> modify (\st -> st{ stHighlighting = True }) >> return h blockToHtml opts (BlockQuote blocks) = @@ -540,7 +546,7 @@ inlineToHtml opts inline = (Apostrophe) -> return $ strToHtml "’" (Emph lst) -> inlineListToHtml opts lst >>= return . H.em (Strong lst) -> inlineListToHtml opts lst >>= return . H.strong - (Code attr str) -> case highlightHtml True attr str of + (Code attr str) -> case highlight formatHtmlInline attr str of Nothing -> return $ foldl (!) H.code (attrsToHtml opts attr) $ strToHtml str diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index cb7df6b8a..117ecca51 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -41,7 +41,8 @@ import Data.Char ( toLower, isPunctuation ) import Control.Monad.State import Text.Pandoc.Pretty import System.FilePath (dropExtension) -import Text.Pandoc.Highlighting (highlightLaTeX, defaultLaTeXMacros) +import Text.Pandoc.Highlighting (highlight, pygments, styleToLaTeX, + formatLaTeXInline, formatLaTeXBlock) data WriterState = WriterState { stInNote :: Bool -- true if we're in a note @@ -60,7 +61,7 @@ data WriterState = , stLHS :: Bool -- true if document has literate haskell code , stBook :: Bool -- true if document uses book or memoir class , stCsquotes :: Bool -- true if document uses csquotes - , stHighlighting :: Bool -- true if document has highlighted code + , stHighlighting :: Bool -- true if document has highlighted code } -- | Convert Pandoc to LaTeX. @@ -131,7 +132,7 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do [ ("graphics", "yes") | stGraphics st ] ++ [ ("book-class", "yes") | stBook st] ++ [ ("listings", "yes") | writerListings options || stLHS st ] ++ - [ ("highlighting-macros", defaultLaTeXMacros) | stHighlighting st ] ++ + [ ("highlighting-macros", styleToLaTeX pygments) | stHighlighting st ] ++ citecontext return $ if writerStandalone options then renderTemplate context template @@ -160,6 +161,7 @@ stringToLaTeX isUrl = escapeStringUsing latexEscapes , ('\x2019', "'") , ('\x201C', "``") , ('\x201D', "''") + , ('\x2026', "\\ldots{}") ] -- | Puts contents into LaTeX command. @@ -231,7 +233,7 @@ blockToLaTeX (CodeBlock (_,classes,keyvalAttr) str) = do return $ flush ("\\begin{lstlisting}" <> printParams $$ text str $$ "\\end{lstlisting}") $$ cr highlightedCodeBlock = - case highlightLaTeX False ("",classes,keyvalAttr) str of + case highlight formatLaTeXBlock ("",classes,keyvalAttr) str of Nothing -> rawCodeBlock Just h -> modify (\st -> st{ stHighlighting = True }) >> return (text h) @@ -407,7 +409,7 @@ inlineToLaTeX (Code (_,classes,_) str) = do let chr = ((enumFromTo '!' '~') \\ str) !! 0 return $ text $ "\\lstinline" ++ [chr] ++ str ++ [chr] highlightCode = do - case highlightLaTeX True ("",classes,[]) str of + case highlight formatLaTeXInline ("",classes,[]) str of Nothing -> rawCode Just h -> modify (\st -> st{ stHighlighting = True }) >> return (text h) |