aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2025-08-10 16:26:59 +0200
committerJohn MacFarlane <[email protected]>2025-09-02 17:50:47 +0200
commit3a298067ae0fc022a2047e590d97602542a9e201 (patch)
tree57e3bfc6efd439e1bd2c9b993f126aa312192870 /src/Text
parent3e2c029a77397e50e5725218b1c26c21bb7b11cd (diff)
T.P.Highlighting: export `defaultStyle` [API Change]
This allows to be more explicit about using a default style, and providing a single point of truth for its value. The variable is an alias for `pygments`.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/App/Opt.hs3
-rw-r--r--src/Text/Pandoc/Highlighting.hs7
-rw-r--r--src/Text/Pandoc/Options.hs6
3 files changed, 11 insertions, 5 deletions
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index 94fabb95a..3b90901d0 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -36,6 +36,7 @@ import Data.Char (toLower)
import Data.Maybe (fromMaybe)
import GHC.Generics hiding (Meta)
import Text.Pandoc.Filter (Filter (..))
+import Text.Pandoc.Highlighting (defaultStyleName)
import Text.Pandoc.Logging (Verbosity (WARNING), LogMessage(..))
import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
TrackChanges (AcceptChanges),
@@ -773,7 +774,7 @@ defaultOpts = Opt
, optEmbedResources = False
, optLinkImages = False
, optHtmlQTags = False
- , optHighlightStyle = Just "pygments"
+ , optHighlightStyle = Just defaultStyleName
, optSyntaxDefinitions = []
, optTopLevelDivision = TopLevelDefault
, optHTMLMathMethod = PlainMath
diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs
index a748fe7eb..524e6dfba 100644
--- a/src/Text/Pandoc/Highlighting.hs
+++ b/src/Text/Pandoc/Highlighting.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Highlighting
- Copyright : Copyright (C) 2008-2024 John MacFarlane
+ Copyright : Copyright (C) 2008-2025 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <[email protected]>
@@ -31,6 +31,7 @@ module Text.Pandoc.Highlighting ( highlightingStyles
, styleToConTeXt
, formatANSI
-- * Styles
+ , defaultStyle
, pygments
, espresso
, zenburn
@@ -56,6 +57,10 @@ import Control.Monad.Except (throwError)
import System.FilePath (takeExtension)
import Text.Pandoc.Shared (safeRead)
+-- | The default highlighting style used by pandoc (pygments).
+defaultStyle :: Style
+defaultStyle = pygments
+
highlightingStyles :: [(T.Text, Style)]
highlightingStyles =
[("pygments", pygments),
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 43df5c27f..8e0046d0b 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -48,7 +48,7 @@ import Skylighting (SyntaxMap, defaultSyntaxMap)
import Text.DocTemplates (Context(..), Template)
import Text.Pandoc.Extensions
import Text.Pandoc.Chunks (PathTemplate)
-import Text.Pandoc.Highlighting (Style, pygments)
+import Text.Pandoc.Highlighting (Style, defaultStyle)
import Text.Pandoc.UTF8 (toStringLazy)
import Data.Aeson.TH (deriveJSON)
import Data.Aeson
@@ -115,7 +115,7 @@ instance FromJSON HTMLMathMethod where
mburl <- m .:? "url"
case method :: Text of
"plain" -> return PlainMath
- "webtex" -> return $ WebTeX $
+ "webtex" -> return $ WebTeX $
fromMaybe defaultWebTeXURL mburl
"gladtex" -> return GladTeX
"mathml" -> return MathML
@@ -375,7 +375,7 @@ instance Default WriterOptions where
, writerSlideLevel = Nothing
, writerTopLevelDivision = TopLevelDefault
, writerListings = False
- , writerHighlightStyle = Just pygments
+ , writerHighlightStyle = Just defaultStyle
, writerSetextHeaders = False
, writerListTables = False
, writerEpubSubdirectory = "EPUB"