diff options
-rw-r--r-- | CONTRIBUTING.md | 2 | ||||
-rw-r--r-- | pandoc.cabal | 8 | ||||
-rw-r--r-- | pandoc.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Highlighting.hs | 36 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 4 | ||||
-rw-r--r-- | stack.yaml | 3 | ||||
-rw-r--r-- | tests/lhs-test.latex | 4 |
8 files changed, 44 insertions, 30 deletions
diff --git a/CONTRIBUTING.md b/CONTRIBUTING.md index 0f6fa03f1..d9c95702e 100644 --- a/CONTRIBUTING.md +++ b/CONTRIBUTING.md @@ -248,7 +248,7 @@ The library is structured as follows: cabal flag is used. It is generated from `src/Text/Pandoc/Data.hsb` using the preprocessor [hsb2hs]. - `Text.Pandoc.Highlighting` contains the interface to the - highlighting-kate library, which is used for code syntax highlighting. + skylighting library, which is used for code syntax highlighting. - `Text.Pandoc.ImageSize` is a utility module containing functions for calculating image sizes from the contents of image files. - `Text.Pandoc.MIME` contains functions for associating MIME types diff --git a/pandoc.cabal b/pandoc.cabal index 3054838be..958a5f70d 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -275,7 +275,7 @@ Library tagsoup >= 0.13.7 && < 0.15, base64-bytestring >= 0.1 && < 1.1, zlib >= 0.5 && < 0.7, - highlighting-kate >= 0.6.2 && < 0.7, + skylighting >= 0.1.0.1 && < 0.2, data-default >= 0.4 && < 0.8, temporary >= 1.1 && < 1.3, blaze-html >= 0.5 && < 0.9, @@ -431,7 +431,7 @@ Executable pandoc text >= 0.11 && < 1.3, bytestring >= 0.9 && < 0.11, extensible-exceptions >= 0.1 && < 0.2, - highlighting-kate >= 0.6.2 && < 0.7, + skylighting >= 0.1.0.1 && < 0.2, aeson >= 0.7.0.5 && < 1.1, yaml >= 0.8.8.2 && < 0.9, containers >= 0.1 && < 0.6, @@ -468,7 +468,7 @@ Executable trypandoc Other-Modules: Prelude default-language: Haskell2010 if flag(trypandoc) - Build-Depends: base, aeson, pandoc, highlighting-kate, + Build-Depends: base, aeson, pandoc, skylighting, text, wai-extra, wai >= 0.3, http-types Buildable: True else @@ -506,7 +506,7 @@ Test-Suite test-pandoc directory >= 1 && < 1.4, filepath >= 1.1 && < 1.5, process >= 1 && < 1.5, - highlighting-kate >= 0.6.2 && < 0.7, + skylighting >= 0.1.0.1 && < 0.2, Diff >= 0.2 && < 0.4, test-framework >= 0.3 && < 0.9, test-framework-hunit >= 0.2 && < 0.4, @@ -42,7 +42,7 @@ import Text.Pandoc.MediaBag ( mediaDirectory, extractMediaBag, MediaBag ) import Text.Pandoc.XML ( toEntities ) import Text.Pandoc.SelfContained ( makeSelfContained ) import Text.Pandoc.Process (pipeProcess) -import Text.Highlighting.Kate ( languages, Style, tango, pygments, +import Skylighting ( defaultSyntaxMap, Syntax(..), Style, tango, pygments, espresso, zenburn, kate, haddock, monochrome ) import System.Environment ( getArgs, getProgName, getEnvironment ) import System.Exit ( ExitCode (..), exitSuccess ) @@ -92,7 +92,7 @@ copyrightMessage = intercalate "\n" [ compileInfo :: String compileInfo = "\nCompiled with pandoc-types " ++ VERSION_pandoc_types ++ ", texmath " ++ - VERSION_texmath ++ ", highlighting-kate " ++ VERSION_highlighting_kate + VERSION_texmath ++ ", skylighting " ++ VERSION_skylighting -- | Converts a list of strings into a single string with the items printed as -- comma separated words in lines with a maximum line length. @@ -950,8 +950,11 @@ options = , Option "" ["list-highlight-languages"] (NoArg (\_ -> do - let langs = [map toLower l | l <- languages, - l /= "Alert" && l /= "Alert_indent"] + let langs = [ T.unpack (T.toLower (sShortname s)) + | s <- M.elems defaultSyntaxMap + , sShortname s `notElem` + [T.pack "Alert", T.pack "Alert_indent"] + ] mapM_ (UTF8.hPutStrLn stdout) langs exitSuccess )) "" diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index 1b9e92ae2..18157afce 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -50,15 +50,20 @@ module Text.Pandoc.Highlighting ( languages ) where import Text.Pandoc.Definition import Text.Pandoc.Shared (safeRead) -import Text.Highlighting.Kate -import Data.List (find) +import Skylighting import Data.Maybe (fromMaybe) import Data.Char (toLower) import qualified Data.Map as M import Control.Applicative ((<|>)) +import Control.Monad +import qualified Data.Text as T -lcLanguages :: [String] -lcLanguages = map (map toLower) languages +languages :: [String] +languages = [T.unpack (T.toLower (sName s)) | s <- M.elems defaultSyntaxMap] + +languagesByExtension :: String -> [String] +languagesByExtension ext = + [T.unpack (T.toLower (sName s)) | s <- syntaxesByExtension defaultSyntaxMap ext] highlight :: (FormatOptions -> [SourceLine] -> a) -- ^ Formatter -> Attr -- ^ Attributes of the CodeBlock @@ -70,19 +75,24 @@ highlight formatter (_, classes, keyvals) rawCode = startNumber = firstNum, numberLines = any (`elem` ["number","numberLines", "number-lines"]) classes } - lcclasses = map (map toLower) - (classes ++ concatMap languagesByExtension classes) - in case find (`elem` lcLanguages) lcclasses of + tokenizeOpts = TokenizerConfig{ syntaxMap = defaultSyntaxMap + , traceOutput = False } + classes' = map T.pack classes + rawCode' = T.pack rawCode + in case msum (map (\l -> lookupSyntax l defaultSyntaxMap) classes') of Nothing | numberLines fmtOpts -> Just $ formatter fmtOpts{ codeClasses = [], - containerClasses = classes } - $ map (\ln -> [(NormalTok, ln)]) $ lines rawCode + containerClasses = classes' } + $ map (\ln -> [(NormalTok, ln)]) $ T.lines rawCode' | otherwise -> Nothing - Just language -> Just - $ formatter fmtOpts{ codeClasses = [language], - containerClasses = classes } - $ highlightAs language rawCode + Just syntax -> + case tokenize tokenizeOpts syntax rawCode' of + Right slines -> Just $ + formatter fmtOpts{ codeClasses = + [T.toLower (sShortname syntax)], + containerClasses = classes' } slines + Left _ -> Nothing -- Functions for correlating latex listings package's language names -- with highlighting-kate language names: diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a8f82c0ec..3fc5d22a2 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -49,19 +49,19 @@ import Text.Pandoc.Options import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Highlighting ( highlight ) import Text.Pandoc.Walk -import Text.Highlighting.Kate.Types () import Text.XML.Light as XML import Text.TeXMath import Text.Pandoc.Readers.Docx.StyleMap import Text.Pandoc.Readers.Docx.Util (elemName) import Control.Monad.Reader import Control.Monad.State -import Text.Highlighting.Kate +import Skylighting import Data.Unique (hashUnique, newUnique) import System.Random (randomRIO) import Text.Printf (printf) import qualified Control.Exception as E import Data.Monoid ((<>)) +import qualified Data.Text as T import Text.Pandoc.MIME (MimeType, getMimeType, getMimeTypeDef, extensionFromMimeType) import Control.Applicative ((<|>)) @@ -1127,7 +1127,7 @@ inlineToOpenXML' opts (Code attrs str) = do toHlTok (toktype,tok) = mknode "w:r" [] [ mknode "w:rPr" [] [ rCustomStyle (show toktype) ] - , mknode "w:t" [("xml:space","preserve")] tok ] + , mknode "w:t" [("xml:space","preserve")] (T.unpack tok) ] withTextProp (rCustomStyle "VerbatimChar") $ if writerHighlight opts then case highlight formatOpenXML attrs str of diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 81109e111..88934eb44 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -508,7 +508,7 @@ blockToLaTeX (CodeBlock (identifier,classes,keyvalAttr) str) = do case highlight formatLaTeXBlock ("",classes,keyvalAttr) str of Nothing -> rawCodeBlock Just h -> modify (\st -> st{ stHighlighting = True }) >> - return (flush $ linkAnchor $$ text h) + return (flush $ linkAnchor $$ text (T.unpack h)) case () of _ | isEnabled Ext_literate_haskell opts && "haskell" `elem` classes && "literate" `elem` classes -> lhsCodeBlock @@ -916,7 +916,7 @@ inlineToLaTeX (Code (_,classes,_) str) = do case highlight formatLaTeXInline ("",classes,[]) str of Nothing -> rawCode Just h -> modify (\st -> st{ stHighlighting = True }) >> - return (text h) + return (text (T.unpack h)) rawCode = liftM (text . (\s -> "\\texttt{" ++ escapeSpaces s ++ "}")) $ stringToLaTeX CodeString str where diff --git a/stack.yaml b/stack.yaml index b3fac5247..b7cf3f51a 100644 --- a/stack.yaml +++ b/stack.yaml @@ -11,4 +11,5 @@ extra-deps: - texmath-0.9 - doctemplates-0.1.0.2 - pandoc-types-1.17.0.4 -resolver: lts-7.9 +- skylighting-0.1.0.1 +resolver: lts-7.14 diff --git a/tests/lhs-test.latex b/tests/lhs-test.latex index ac985e287..8234fce8f 100644 --- a/tests/lhs-test.latex +++ b/tests/lhs-test.latex @@ -101,8 +101,8 @@ return a single value: \begin{Shaded} \begin{Highlighting}[] -\OtherTok{unsplit ::} \NormalTok{(}\DataTypeTok{Arrow} \NormalTok{a) }\OtherTok{=>} \NormalTok{(b }\OtherTok{->} \NormalTok{c }\OtherTok{->} \NormalTok{d) }\OtherTok{->} \NormalTok{a (b, c) d} -\NormalTok{unsplit }\FunctionTok{=} \NormalTok{arr }\FunctionTok{.} \NormalTok{uncurry} +\OtherTok{unsplit ::}\NormalTok{ (}\DataTypeTok{Arrow}\NormalTok{ a) }\OtherTok{=>}\NormalTok{ (b }\OtherTok{->}\NormalTok{ c }\OtherTok{->}\NormalTok{ d) }\OtherTok{->}\NormalTok{ a (b, c) d} +\NormalTok{unsplit }\FunctionTok{=}\NormalTok{ arr }\FunctionTok{.}\NormalTok{ uncurry} \CommentTok{-- arr (\textbackslash{}op (x,y) -> x `op` y)} \end{Highlighting} \end{Shaded} |