aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2016-12-23 17:31:10 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2016-12-23 18:07:49 -0700
commit9d781b145449933369a02145eeb18cc2857480ed (patch)
treebadd31c411b28de1485f3b7f2c38840e8aec37e9 /src/Text
parentbfb6b61084ab6046db2105ebb42935543ee4d528 (diff)
downloadpandoc-9d781b145449933369a02145eeb18cc2857480ed.tar.gz
Updates to use skylighting rather than highlighting-kate.
So far this just reproduces capacity. Later we'll be able to add features like warning messages, dynamic loading of xml syntax definitions, and dynamic loading of themes.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Highlighting.hs36
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs4
3 files changed, 28 insertions, 18 deletions
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