Remove derive_json_via_th flag; always use TH.
This cuts down on code duplication and reduces the chance for errors. See #4083.
This commit is contained in:
parent
b235a187dc
commit
8fb9a0d168
7 changed files with 1 additions and 104 deletions
10
pandoc.cabal
10
pandoc.cabal
|
@ -359,11 +359,6 @@ flag embed_data_files
|
||||||
Description: Embed data files in binary for relocatable executable.
|
Description: Embed data files in binary for relocatable executable.
|
||||||
Default: False
|
Default: False
|
||||||
|
|
||||||
flag derive_json_via_th
|
|
||||||
Description: Use Template Haskell instead of GHC Generics to derive ToJSON
|
|
||||||
and FromJSON instances.
|
|
||||||
Default: False
|
|
||||||
|
|
||||||
flag trypandoc
|
flag trypandoc
|
||||||
Description: Build trypandoc cgi executable.
|
Description: Build trypandoc cgi executable.
|
||||||
Default: False
|
Default: False
|
||||||
|
@ -441,9 +436,6 @@ library
|
||||||
cpp-options: -DEMBED_DATA_FILES
|
cpp-options: -DEMBED_DATA_FILES
|
||||||
build-depends: file-embed >= 0.0 && < 0.1
|
build-depends: file-embed >= 0.0 && < 0.1
|
||||||
other-modules: Text.Pandoc.Data
|
other-modules: Text.Pandoc.Data
|
||||||
if flag(derive_json_via_th)
|
|
||||||
cpp-options: -DDERIVE_JSON_VIA_TH
|
|
||||||
other-extensions: TemplateHaskell
|
|
||||||
if os(windows)
|
if os(windows)
|
||||||
cpp-options: -D_WINDOWS
|
cpp-options: -D_WINDOWS
|
||||||
ghc-options: -Wall -fno-warn-unused-do-bind
|
ghc-options: -Wall -fno-warn-unused-do-bind
|
||||||
|
@ -462,7 +454,7 @@ library
|
||||||
-fhide-source-paths
|
-fhide-source-paths
|
||||||
|
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
other-extensions: NoImplicitPrelude
|
other-extensions: NoImplicitPrelude, TemplateHaskell
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
|
|
||||||
exposed-modules: Text.Pandoc,
|
exposed-modules: Text.Pandoc,
|
||||||
|
|
|
@ -2,9 +2,6 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TupleSections #-}
|
{-# LANGUAGE TupleSections #-}
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
|
||||||
#endif
|
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.App.CommandLineOptions
|
Module : Text.Pandoc.App.CommandLineOptions
|
||||||
Copyright : Copyright (C) 2006-2019 John MacFarlane
|
Copyright : Copyright (C) 2006-2019 John MacFarlane
|
||||||
|
|
|
@ -2,9 +2,7 @@
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
#endif
|
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.App.Opt
|
Module : Text.Pandoc.App.Opt
|
||||||
Copyright : Copyright (C) 2006-2019 John MacFarlane
|
Copyright : Copyright (C) 2006-2019 John MacFarlane
|
||||||
|
@ -36,11 +34,7 @@ import qualified Data.Text as T
|
||||||
import Data.Aeson (defaultOptions, Options(..), FromJSON(..), ToJSON(..),
|
import Data.Aeson (defaultOptions, Options(..), FromJSON(..), ToJSON(..),
|
||||||
Value(..))
|
Value(..))
|
||||||
import Data.Aeson.Types (typeMismatch)
|
import Data.Aeson.Types (typeMismatch)
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
import Data.Aeson.TH (deriveJSON)
|
import Data.Aeson.TH (deriveJSON)
|
||||||
#else
|
|
||||||
import Data.Aeson (genericToEncoding)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
-- | The type of line-endings to be used when writing plain-text.
|
-- | The type of line-endings to be used when writing plain-text.
|
||||||
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
|
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
|
||||||
|
@ -203,16 +197,8 @@ defaultOpts = Opt
|
||||||
, optStripComments = False
|
, optStripComments = False
|
||||||
}
|
}
|
||||||
|
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
-- see https://github.com/jgm/pandoc/pull/4083
|
-- see https://github.com/jgm/pandoc/pull/4083
|
||||||
-- using generic deriving caused long compilation times
|
-- using generic deriving caused long compilation times
|
||||||
$(deriveJSON
|
$(deriveJSON
|
||||||
defaultOptions{ fieldLabelModifier =
|
defaultOptions{ fieldLabelModifier =
|
||||||
camelCaseToHyphenated . drop 3 } ''Opt)
|
camelCaseToHyphenated . drop 3 } ''Opt)
|
||||||
#else
|
|
||||||
instance ToJSON Opt where
|
|
||||||
toEncoding = genericToEncoding
|
|
||||||
defaultOptions{ fieldLabelModifier =
|
|
||||||
camelCaseToHyphenated . drop 3 }
|
|
||||||
instance FromJSON Opt
|
|
||||||
#endif
|
|
||||||
|
|
|
@ -2,10 +2,8 @@
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
{-# LANGUAGE DeriveDataTypeable #-}
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
#endif
|
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.Extensions
|
Module : Text.Pandoc.Extensions
|
||||||
Copyright : Copyright (C) 2012-2019 John MacFarlane
|
Copyright : Copyright (C) 2012-2019 John MacFarlane
|
||||||
|
@ -41,13 +39,7 @@ import Data.Typeable (Typeable)
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import Safe (readMay)
|
import Safe (readMay)
|
||||||
import Text.Parsec
|
import Text.Parsec
|
||||||
|
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
||||||
#else
|
|
||||||
import Data.Aeson (FromJSON (..), ToJSON (..),
|
|
||||||
defaultOptions, genericToEncoding)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
newtype Extensions = Extensions Integer
|
newtype Extensions = Extensions Integer
|
||||||
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
|
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
|
||||||
|
@ -538,15 +530,5 @@ parseFormatSpec = parse formatSpec ""
|
||||||
'+' -> (ext : extsToEnable, extsToDisable)
|
'+' -> (ext : extsToEnable, extsToDisable)
|
||||||
_ -> (extsToEnable, ext : extsToDisable)
|
_ -> (extsToEnable, ext : extsToDisable)
|
||||||
|
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
$(deriveJSON defaultOptions ''Extension)
|
$(deriveJSON defaultOptions ''Extension)
|
||||||
$(deriveJSON defaultOptions ''Extensions)
|
$(deriveJSON defaultOptions ''Extensions)
|
||||||
#else
|
|
||||||
instance ToJSON Extension where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON Extension
|
|
||||||
|
|
||||||
instance ToJSON Extensions where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON Extensions
|
|
||||||
#endif
|
|
||||||
|
|
|
@ -1,9 +1,7 @@
|
||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
#endif
|
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.Filter
|
Module : Text.Pandoc.Filter
|
||||||
Copyright : Copyright (C) 2006-2019 John MacFarlane
|
Copyright : Copyright (C) 2006-2019 John MacFarlane
|
||||||
|
@ -21,12 +19,7 @@ module Text.Pandoc.Filter
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Prelude
|
import Prelude
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
||||||
#else
|
|
||||||
import Data.Aeson (FromJSON (..), ToJSON (..),
|
|
||||||
defaultOptions, genericToEncoding)
|
|
||||||
#endif
|
|
||||||
import Data.Foldable (foldrM)
|
import Data.Foldable (foldrM)
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import Text.Pandoc.Class (PandocIO)
|
import Text.Pandoc.Class (PandocIO)
|
||||||
|
@ -59,10 +52,4 @@ expandFilterPath :: Filter -> PandocIO Filter
|
||||||
expandFilterPath (LuaFilter fp) = LuaFilter <$> Path.expandFilterPath fp
|
expandFilterPath (LuaFilter fp) = LuaFilter <$> Path.expandFilterPath fp
|
||||||
expandFilterPath (JSONFilter fp) = JSONFilter <$> Path.expandFilterPath fp
|
expandFilterPath (JSONFilter fp) = JSONFilter <$> Path.expandFilterPath fp
|
||||||
|
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
$(deriveJSON defaultOptions ''Filter)
|
$(deriveJSON defaultOptions ''Filter)
|
||||||
#else
|
|
||||||
instance ToJSON Filter where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON Filter
|
|
||||||
#endif
|
|
||||||
|
|
|
@ -2,9 +2,7 @@
|
||||||
{-# LANGUAGE DeriveDataTypeable #-}
|
{-# LANGUAGE DeriveDataTypeable #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE NoImplicitPrelude #-}
|
{-# LANGUAGE NoImplicitPrelude #-}
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
#endif
|
|
||||||
{- |
|
{- |
|
||||||
Module : Text.Pandoc.Options
|
Module : Text.Pandoc.Options
|
||||||
Copyright : Copyright (C) 2012-2019 John MacFarlane
|
Copyright : Copyright (C) 2012-2019 John MacFarlane
|
||||||
|
@ -42,13 +40,7 @@ import Skylighting (SyntaxMap, defaultSyntaxMap)
|
||||||
import Text.Pandoc.Extensions
|
import Text.Pandoc.Extensions
|
||||||
import Text.Pandoc.Highlighting (Style, pygments)
|
import Text.Pandoc.Highlighting (Style, pygments)
|
||||||
import Text.DocTemplates (Template)
|
import Text.DocTemplates (Template)
|
||||||
|
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
import Data.Aeson.TH (deriveJSON, defaultOptions)
|
||||||
#else
|
|
||||||
import Data.Aeson (FromJSON (..), ToJSON (..),
|
|
||||||
defaultOptions, genericToEncoding)
|
|
||||||
#endif
|
|
||||||
|
|
||||||
class HasSyntaxExtensions a where
|
class HasSyntaxExtensions a where
|
||||||
getExtensions :: a -> Extensions
|
getExtensions :: a -> Extensions
|
||||||
|
@ -230,7 +222,6 @@ instance HasSyntaxExtensions WriterOptions where
|
||||||
isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool
|
isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool
|
||||||
isEnabled ext opts = ext `extensionEnabled` getExtensions opts
|
isEnabled ext opts = ext `extensionEnabled` getExtensions opts
|
||||||
|
|
||||||
#ifdef DERIVE_JSON_VIA_TH
|
|
||||||
$(deriveJSON defaultOptions ''ReaderOptions)
|
$(deriveJSON defaultOptions ''ReaderOptions)
|
||||||
$(deriveJSON defaultOptions ''HTMLMathMethod)
|
$(deriveJSON defaultOptions ''HTMLMathMethod)
|
||||||
$(deriveJSON defaultOptions ''CiteMethod)
|
$(deriveJSON defaultOptions ''CiteMethod)
|
||||||
|
@ -240,40 +231,3 @@ $(deriveJSON defaultOptions ''TrackChanges)
|
||||||
$(deriveJSON defaultOptions ''WrapOption)
|
$(deriveJSON defaultOptions ''WrapOption)
|
||||||
$(deriveJSON defaultOptions ''TopLevelDivision)
|
$(deriveJSON defaultOptions ''TopLevelDivision)
|
||||||
$(deriveJSON defaultOptions ''ReferenceLocation)
|
$(deriveJSON defaultOptions ''ReferenceLocation)
|
||||||
#else
|
|
||||||
instance ToJSON CiteMethod where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON CiteMethod
|
|
||||||
|
|
||||||
instance ToJSON ReaderOptions where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON ReaderOptions
|
|
||||||
|
|
||||||
instance ToJSON ObfuscationMethod where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON ObfuscationMethod
|
|
||||||
|
|
||||||
instance ToJSON WrapOption where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON WrapOption
|
|
||||||
|
|
||||||
instance ToJSON HTMLMathMethod where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON HTMLMathMethod
|
|
||||||
|
|
||||||
instance ToJSON HTMLSlideVariant where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON HTMLSlideVariant
|
|
||||||
|
|
||||||
instance ToJSON TopLevelDivision where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON TopLevelDivision
|
|
||||||
|
|
||||||
instance ToJSON ReferenceLocation where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON ReferenceLocation
|
|
||||||
|
|
||||||
instance ToJSON TrackChanges where
|
|
||||||
toEncoding = genericToEncoding defaultOptions
|
|
||||||
instance FromJSON TrackChanges
|
|
||||||
#endif
|
|
||||||
|
|
|
@ -2,7 +2,6 @@ flags:
|
||||||
pandoc:
|
pandoc:
|
||||||
trypandoc: false
|
trypandoc: false
|
||||||
embed_data_files: true
|
embed_data_files: true
|
||||||
derive_json_via_th: false
|
|
||||||
static: false
|
static: false
|
||||||
pandoc-citeproc:
|
pandoc-citeproc:
|
||||||
bibutils: true
|
bibutils: true
|
||||||
|
|
Loading…
Add table
Reference in a new issue