Change JSON encodings of some types.
- For LineEnding use lowercase constructors, e.g. `crlf`, `native`. This was the original intent, but there was a bug in the implementation. - For HTMLSlideVariant use lowercase constructors. - For ReaderOptions use e.g. `default-image-extension` instead of `readerDefaultImageExtension` for field names. - For Extension, use e.g. `tex_math_dollars` instead of `Ext_tex_math_dollars` as constructor. - For Extensions, use an array of Extensions, instead of an object wrapping the tag `Extensions` and an integer. (The representation is not supposed to be part of the public API.) - For Opt, use field names like `tab-stop` instead of `optTabStop`.
This commit is contained in:
parent
d226a35c0a
commit
26a8de684e
4 changed files with 65 additions and 53 deletions
|
@ -460,36 +460,36 @@ filter.
|
|||
|
||||
Object fields:
|
||||
|
||||
`readerAbbreviations`
|
||||
`abbreviations`
|
||||
: set of known abbreviations (array of strings).
|
||||
|
||||
`readerColumns`
|
||||
`columns`
|
||||
: number of columns in terminal; an integer.
|
||||
|
||||
`readerDefaultImageExtension`
|
||||
default-image-extension`
|
||||
: default extension for images; a string.
|
||||
|
||||
`readerExtensions`
|
||||
`extensions`
|
||||
: integer representation of the syntax extensions bit
|
||||
field.
|
||||
|
||||
`readerIndentedCodeClasses`
|
||||
`indented-code-classes`
|
||||
: default classes for indented code blocks; array of
|
||||
strings.
|
||||
|
||||
`readerStandalone`
|
||||
`standalone`
|
||||
: whether the input was a standalone document with header;
|
||||
either `true` or `false`.
|
||||
|
||||
`readerStripComments`
|
||||
`strip-comments`
|
||||
: HTML comments are stripped instead of parsed as raw HTML;
|
||||
either `true` or `false`.
|
||||
|
||||
`readerTabStop`
|
||||
`tab-stop`
|
||||
: width (i.e. equivalent number of spaces) of tab stops;
|
||||
integer.
|
||||
|
||||
`readerTrackChanges`
|
||||
`track-changes`
|
||||
: track changes setting for docx; one of
|
||||
`"accept-changes"`, `"reject-changes"`, and
|
||||
`"all-changes"`.
|
||||
|
|
|
@ -29,7 +29,7 @@ import Control.Monad.Except (MonadIO, liftIO, throwError, (>=>), foldM)
|
|||
import Control.Monad.State.Strict (StateT, modify, gets)
|
||||
import System.FilePath ( addExtension, (</>), takeExtension, takeDirectory )
|
||||
import System.Directory ( canonicalizePath )
|
||||
import Data.Char (isLower, toLower)
|
||||
import Data.Char (toLower)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import GHC.Generics hiding (Meta)
|
||||
import Text.Pandoc.Filter (Filter (..))
|
||||
|
@ -43,8 +43,7 @@ import Text.Pandoc.Options (TopLevelDivision (TopLevelDefault),
|
|||
import Text.Pandoc.Class (readFileStrict, fileExists, setVerbosity, report,
|
||||
PandocMonad(lookupEnv), getUserDataDir)
|
||||
import Text.Pandoc.Error (PandocError (PandocParseError, PandocSomeError))
|
||||
import Text.Pandoc.Shared (camelCaseStrToHyphenated, defaultUserDataDir,
|
||||
findM, ordNub)
|
||||
import Text.Pandoc.Shared (defaultUserDataDir, findM, ordNub)
|
||||
import qualified Text.Pandoc.Parsing as P
|
||||
import Text.Pandoc.Readers.Metadata (yamlMap)
|
||||
import Text.Pandoc.Class.PandocPure
|
||||
|
@ -54,7 +53,7 @@ import Data.Default (def)
|
|||
import qualified Data.Text as T
|
||||
import qualified Data.Map as M
|
||||
import Text.Pandoc.Definition (Meta(..), MetaValue(..))
|
||||
import Data.Aeson (defaultOptions, Options(..), Result(..), fromJSON)
|
||||
import Data.Aeson (defaultOptions, Options(..), Result(..), fromJSON, camelTo2)
|
||||
import Data.Aeson.TH (deriveJSON)
|
||||
import Control.Applicative ((<|>))
|
||||
import Data.Yaml
|
||||
|
@ -62,6 +61,11 @@ import Data.Yaml
|
|||
-- | The type of line-endings to be used when writing plain-text.
|
||||
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
|
||||
|
||||
-- see https://github.com/jgm/pandoc/pull/4083
|
||||
-- using generic deriving caused long compilation times
|
||||
$(deriveJSON
|
||||
defaultOptions{ constructorTagModifier = map toLower } ''LineEnding)
|
||||
|
||||
-- | How to handle output blocks in ipynb.
|
||||
data IpynbOutput =
|
||||
IpynbOutputAll
|
||||
|
@ -69,6 +73,9 @@ data IpynbOutput =
|
|||
| IpynbOutputBest
|
||||
deriving (Show, Generic)
|
||||
|
||||
$(deriveJSON
|
||||
defaultOptions{ fieldLabelModifier = map toLower . drop 11 } ''IpynbOutput)
|
||||
|
||||
-- | Data structure for command line options.
|
||||
data Opt = Opt
|
||||
{ optTabStop :: Int -- ^ Number of spaces per tab
|
||||
|
@ -147,6 +154,9 @@ data Opt = Opt
|
|||
, optSandbox :: Bool
|
||||
} deriving (Generic, Show)
|
||||
|
||||
$(deriveJSON
|
||||
defaultOptions{ fieldLabelModifier = camelTo2 '-' . drop 3 } ''Opt)
|
||||
|
||||
instance FromJSON (Opt -> Opt) where
|
||||
parseJSON (Object m) =
|
||||
case fromJSON (Object m) of
|
||||
|
@ -714,14 +724,3 @@ cyclic :: Ord a => [[a]] -> Bool
|
|||
cyclic = any hasDuplicate
|
||||
where
|
||||
hasDuplicate xs = length (ordNub xs) /= length xs
|
||||
|
||||
-- see https://github.com/jgm/pandoc/pull/4083
|
||||
-- using generic deriving caused long compilation times
|
||||
$(deriveJSON
|
||||
defaultOptions{ fieldLabelModifier = drop 11 . map toLower } ''IpynbOutput)
|
||||
$(deriveJSON
|
||||
defaultOptions{ fieldLabelModifier = map toLower } ''LineEnding)
|
||||
$(deriveJSON
|
||||
defaultOptions{ fieldLabelModifier =
|
||||
camelCaseStrToHyphenated . dropWhile isLower
|
||||
} ''Opt)
|
||||
|
|
|
@ -40,31 +40,8 @@ import Data.Typeable (Typeable)
|
|||
import GHC.Generics (Generic)
|
||||
import Safe (readMay)
|
||||
import Text.Parsec
|
||||
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
||||
|
||||
newtype Extensions = Extensions Integer
|
||||
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
|
||||
|
||||
instance Semigroup Extensions where
|
||||
(Extensions a) <> (Extensions b) = Extensions (a .|. b)
|
||||
instance Monoid Extensions where
|
||||
mempty = Extensions 0
|
||||
mappend = (<>)
|
||||
|
||||
extensionsFromList :: [Extension] -> Extensions
|
||||
extensionsFromList = foldr enableExtension emptyExtensions
|
||||
|
||||
emptyExtensions :: Extensions
|
||||
emptyExtensions = Extensions 0
|
||||
|
||||
extensionEnabled :: Extension -> Extensions -> Bool
|
||||
extensionEnabled x (Extensions exts) = testBit exts (fromEnum x)
|
||||
|
||||
enableExtension :: Extension -> Extensions -> Extensions
|
||||
enableExtension x (Extensions exts) = Extensions (setBit exts (fromEnum x))
|
||||
|
||||
disableExtension :: Extension -> Extensions -> Extensions
|
||||
disableExtension x (Extensions exts) = Extensions (clearBit exts (fromEnum x))
|
||||
import Data.Aeson.TH (deriveJSON)
|
||||
import Data.Aeson
|
||||
|
||||
-- | Individually selectable syntax extensions.
|
||||
data Extension =
|
||||
|
@ -162,6 +139,40 @@ data Extension =
|
|||
| Ext_yaml_metadata_block -- ^ YAML metadata block
|
||||
deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable, Generic)
|
||||
|
||||
$(deriveJSON defaultOptions{ constructorTagModifier = drop 4 } ''Extension)
|
||||
|
||||
newtype Extensions = Extensions Integer
|
||||
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
|
||||
|
||||
instance Semigroup Extensions where
|
||||
(Extensions a) <> (Extensions b) = Extensions (a .|. b)
|
||||
instance Monoid Extensions where
|
||||
mempty = Extensions 0
|
||||
mappend = (<>)
|
||||
|
||||
instance FromJSON Extensions where
|
||||
parseJSON =
|
||||
return . foldr enableExtension emptyExtensions . fromJSON
|
||||
|
||||
instance ToJSON Extensions where
|
||||
toJSON exts = toJSON $
|
||||
[ext | ext <- [minBound..maxBound], extensionEnabled ext exts]
|
||||
|
||||
extensionsFromList :: [Extension] -> Extensions
|
||||
extensionsFromList = foldr enableExtension emptyExtensions
|
||||
|
||||
emptyExtensions :: Extensions
|
||||
emptyExtensions = Extensions 0
|
||||
|
||||
extensionEnabled :: Extension -> Extensions -> Bool
|
||||
extensionEnabled x (Extensions exts) = testBit exts (fromEnum x)
|
||||
|
||||
enableExtension :: Extension -> Extensions -> Extensions
|
||||
enableExtension x (Extensions exts) = Extensions (setBit exts (fromEnum x))
|
||||
|
||||
disableExtension :: Extension -> Extensions -> Extensions
|
||||
disableExtension x (Extensions exts) = Extensions (clearBit exts (fromEnum x))
|
||||
|
||||
-- | Extensions to be used with pandoc-flavored markdown.
|
||||
pandocExtensions :: Extensions
|
||||
pandocExtensions = extensionsFromList
|
||||
|
@ -618,5 +629,3 @@ parseFormatSpec = parse formatSpec ""
|
|||
'+' -> (ext : extsToEnable, extsToDisable)
|
||||
_ -> (extsToEnable, ext : extsToDisable)
|
||||
|
||||
$(deriveJSON defaultOptions ''Extension)
|
||||
$(deriveJSON defaultOptions ''Extensions)
|
||||
|
|
|
@ -37,6 +37,7 @@ import Control.Applicative ((<|>))
|
|||
import Data.Maybe (fromMaybe)
|
||||
import Data.Data (Data)
|
||||
import Data.Default
|
||||
import Data.Char (toLower)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Set as Set
|
||||
import Data.Typeable (Typeable)
|
||||
|
@ -371,6 +372,9 @@ defaultKaTeXURL :: Text
|
|||
defaultKaTeXURL = "https://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.11.1/"
|
||||
|
||||
-- Update documentation in doc/filters.md if this is changed.
|
||||
$(deriveJSON defaultOptions ''ReaderOptions)
|
||||
$(deriveJSON defaultOptions{ fieldLabelModifier =
|
||||
camelTo2 '-' . drop 6 }
|
||||
''ReaderOptions)
|
||||
|
||||
$(deriveJSON defaultOptions ''HTMLSlideVariant)
|
||||
$(deriveJSON defaultOptions{ constructorTagModifier = map toLower }
|
||||
''HTMLSlideVariant)
|
||||
|
|
Loading…
Reference in a new issue