Server: add abbreviations, defaultImageExtension, ...

... trackChanges, stripComments.
This commit is contained in:
John MacFarlane 2022-08-14 16:57:33 -07:00
parent 6625e9655e
commit 4e04947470
2 changed files with 31 additions and 10 deletions

View file

@ -799,6 +799,7 @@ executable pandoc-server
pandoc, pandoc,
aeson, aeson,
text, text,
containers,
data-default, data-default,
bytestring, bytestring,
base64 >= 0.4, base64 >= 0.4,

View file

@ -23,20 +23,26 @@ import Data.Char (isAlphaNum)
import Data.ByteString.Lazy (fromStrict, toStrict) import Data.ByteString.Lazy (fromStrict, toStrict)
import Data.ByteString.Base64 import Data.ByteString.Base64
import Data.Default import Data.Default
import Data.Set (Set)
import Skylighting (defaultSyntaxMap)
-- This is the data to be supplied by the JSON payload -- This is the data to be supplied by the JSON payload
-- of requests. Maybe values may be omitted and will be -- of requests. Maybe values may be omitted and will be
-- given default values. -- given default values.
data Params = Params data Params = Params
{ text :: Text { text: :: Text
, from :: Maybe Text , from: :: Maybe Text
, to :: Maybe Text , to: :: Maybe Text
, wrapText :: Maybe WrapOption , wrapText: :: Maybe WrapOption
, columns :: Maybe Int , columns: :: Maybe Int
, standalone :: Maybe Bool , standalone: :: Maybe Bool
, template :: Maybe Text , template: :: Maybe Text
, tabStop :: Maybe Int , tabStop: :: Maybe Int
, indentedCodeClasses :: Maybe [Text] , indentedCodeClasses: :: Maybe [Text]
, abbreviations: :: Maybe (Set Text)
, defaultImageExtension: :: Maybe Text
, trackChanges: :: Maybe TrackChanges
, stripComments: :: Maybe Bool
} deriving (Show) } deriving (Show)
instance Default Params where instance Default Params where
@ -50,6 +56,10 @@ instance Default Params where
, template = Nothing , template = Nothing
, tabStop = Nothing , tabStop = Nothing
, indentedCodeClasses = Nothing , indentedCodeClasses = Nothing
, abbreviations = Nothing
, defaultImageExtension = Nothing
, trackChanges = Nothing
, stripComments = Nothing
} }
-- Automatically derive code to convert to/from JSON. -- Automatically derive code to convert to/from JSON.
@ -117,11 +127,21 @@ server = convert
, readerTabStop = fromMaybe 4 (tabStop params) , readerTabStop = fromMaybe 4 (tabStop params)
, readerIndentedCodeClasses = fromMaybe [] , readerIndentedCodeClasses = fromMaybe []
(indentedCodeClasses params) (indentedCodeClasses params)
, readerAbbreviations =
fromMaybe mempty (abbreviations params)
, readerDefaultImageExtension =
fromMaybe mempty (defaultImageExtension params)
, readerTrackChanges =
fromMaybe AcceptChanges (trackChanges params)
, readerStripComments =
fromMaybe False (stripComments params)
} }
let writeropts = def{ writerExtensions = writerExts let writeropts = def{ writerExtensions = writerExts
, writerTabStop = fromMaybe 4 (tabStop params)
, writerWrapText = fromMaybe WrapAuto (wrapText params) , writerWrapText = fromMaybe WrapAuto (wrapText params)
, writerColumns = fromMaybe 72 (columns params) , writerColumns = fromMaybe 72 (columns params)
, writerTemplate = mbTemplate } , writerTemplate = mbTemplate
, writerSyntaxMap = defaultSyntaxMap }
let reader = case readerSpec of let reader = case readerSpec of
TextReader r -> r readeropts TextReader r -> r readeropts
ByteStringReader r -> \t -> do ByteStringReader r -> \t -> do