aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorniszet <niszet0016@gmail.com>2020-10-02 01:55:16 +0900
committerGitHub <noreply@github.com>2020-10-01 09:55:16 -0700
commit7d97bf7a8cd37f7438b331f6799eeed6e4b74c3d (patch)
tree6971fe2c29c1075d09ad20e8a5e6979adde888fc
parent46dffbd8e5baebce4e6e278b8ed431ef1fd77d0e (diff)
downloadpandoc-7d97bf7a8cd37f7438b331f6799eeed6e4b74c3d.tar.gz
Syntax highlight for inline code of OpenDocument (#6711)
To implement Syntax highlighting for OpenDocument, inlineToOpenDocument in OpenDocument Writer is updated based on Docx Writer. This commit is only for inline Code because update of CodeBlock needs structual change of output document. Currently, styles are not generated automatically in styles.xml. To implement it, additional commit for ODT Writer is needed. Although styles are not included in styles.xml, output file can be shown in LibreOffice(7.0.0.3) like normal characters.
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs21
1 files changed, 18 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 401ae5ed9..5d742b5c6 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -19,7 +19,7 @@ import Control.Monad.State.Strict hiding (when)
import Data.Char (chr)
import Data.List (sortOn, sortBy, foldl')
import qualified Data.Map as Map
-import Data.Maybe (fromMaybe)
+import Data.Maybe (fromMaybe, isNothing)
import Data.Ord (comparing)
import qualified Data.Set as Set
import Data.Text (Text)
@@ -40,6 +40,8 @@ import Text.Pandoc.Writers.Shared
import qualified Text.Pandoc.Writers.AnnotatedTable as Ann
import Text.Pandoc.XML
import Text.Printf (printf)
+import Text.Pandoc.Highlighting (highlight)
+import Skylighting
-- | Auxiliary function to convert Plain block to Para.
plainToPara :: Block -> Block
@@ -563,7 +565,7 @@ inlineToOpenDocument o ils
SoftBreak
| writerWrapText o == WrapPreserve
-> return $ preformatted "\n"
- | otherwise ->return space
+ | otherwise -> return space
Span attr xs -> withLangFromAttr attr (inlinesToOpenDocument o xs)
LineBreak -> return $ selfClosingTag "text:line-break" []
Str s -> return $ handleSpaces $ escapeStringForXML s
@@ -575,7 +577,14 @@ inlineToOpenDocument o ils
Subscript l -> withTextStyle Sub $ inlinesToOpenDocument o l
SmallCaps l -> withTextStyle SmallC $ inlinesToOpenDocument o l
Quoted t l -> inQuotes t <$> inlinesToOpenDocument o l
- Code _ s -> inlinedCode $ preformatted s
+ Code attrs s -> if isNothing (writerHighlightStyle o)
+ then unhighlighted s
+ else case highlight (writerSyntaxMap o)
+ formatOpenDocument attrs s of
+ Right h -> return $ mconcat $ mconcat h
+ Left msg -> do
+ unless (T.null msg) $ report $ CouldNotHighlight msg
+ unhighlighted s
Math t s -> lift (texMathToInlines t s) >>=
inlinesToOpenDocument o
Cite _ l -> inlinesToOpenDocument o l
@@ -588,6 +597,12 @@ inlineToOpenDocument o ils
Image attr _ (s,t) -> mkImg attr s t
Note l -> mkNote l
where
+ formatOpenDocument :: FormatOptions -> [SourceLine] -> [[Doc Text]]
+ formatOpenDocument _fmtOpts = map (map toHlTok)
+ toHlTok :: Token -> Doc Text
+ toHlTok (toktype,tok) =
+ inTags False "text:span" [("text:style-name", (T.pack $ show toktype))] $ preformatted tok
+ unhighlighted s = inlinedCode $ preformatted s
preformatted s = handleSpaces $ escapeStringForXML s
inlinedCode s = return $ inTags False "text:span" [("text:style-name", "Source_Text")] s
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")