aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2019-10-07 21:22:50 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2019-10-07 21:23:50 -0700
commit8fb9a0d168517462860d6916c1f882958520988b (patch)
tree0ce884c8cebc80da5519d453c6794f70fc345daf /src
parentb235a187dc47e3d0afc8942f4e19c99527e1fca8 (diff)
downloadpandoc-8fb9a0d168517462860d6916c1f882958520988b.tar.gz
Remove derive_json_via_th flag; always use TH.
This cuts down on code duplication and reduces the chance for errors. See #4083.
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/App/CommandLineOptions.hs3
-rw-r--r--src/Text/Pandoc/App/Opt.hs14
-rw-r--r--src/Text/Pandoc/Extensions.hs18
-rw-r--r--src/Text/Pandoc/Filter.hs13
-rw-r--r--src/Text/Pandoc/Options.hs46
5 files changed, 0 insertions, 94 deletions
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index 82d88c1c7..98129d0fd 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -2,9 +2,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
-#ifdef DERIVE_JSON_VIA_TH
-{-# LANGUAGE TemplateHaskell #-}
-#endif
{- |
Module : Text.Pandoc.App.CommandLineOptions
Copyright : Copyright (C) 2006-2019 John MacFarlane
diff --git a/src/Text/Pandoc/App/Opt.hs b/src/Text/Pandoc/App/Opt.hs
index bc472d43c..f714586e4 100644
--- a/src/Text/Pandoc/App/Opt.hs
+++ b/src/Text/Pandoc/App/Opt.hs
@@ -2,9 +2,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
-#ifdef DERIVE_JSON_VIA_TH
{-# LANGUAGE TemplateHaskell #-}
-#endif
{- |
Module : Text.Pandoc.App.Opt
Copyright : Copyright (C) 2006-2019 John MacFarlane
@@ -36,11 +34,7 @@ import qualified Data.Text as T
import Data.Aeson (defaultOptions, Options(..), FromJSON(..), ToJSON(..),
Value(..))
import Data.Aeson.Types (typeMismatch)
-#ifdef DERIVE_JSON_VIA_TH
import Data.Aeson.TH (deriveJSON)
-#else
-import Data.Aeson (genericToEncoding)
-#endif
-- | The type of line-endings to be used when writing plain-text.
data LineEnding = LF | CRLF | Native deriving (Show, Generic)
@@ -203,16 +197,8 @@ defaultOpts = Opt
, optStripComments = False
}
-#ifdef DERIVE_JSON_VIA_TH
-- see https://github.com/jgm/pandoc/pull/4083
-- using generic deriving caused long compilation times
$(deriveJSON
defaultOptions{ fieldLabelModifier =
camelCaseToHyphenated . drop 3 } ''Opt)
-#else
-instance ToJSON Opt where
- toEncoding = genericToEncoding
- defaultOptions{ fieldLabelModifier =
- camelCaseToHyphenated . drop 3 }
-instance FromJSON Opt
-#endif
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index d85b26200..cdf4f159d 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -2,10 +2,8 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
-#ifdef DERIVE_JSON_VIA_TH
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
-#endif
{- |
Module : Text.Pandoc.Extensions
Copyright : Copyright (C) 2012-2019 John MacFarlane
@@ -41,13 +39,7 @@ import Data.Typeable (Typeable)
import GHC.Generics (Generic)
import Safe (readMay)
import Text.Parsec
-
-#ifdef DERIVE_JSON_VIA_TH
import Data.Aeson.TH (deriveJSON, defaultOptions)
-#else
-import Data.Aeson (FromJSON (..), ToJSON (..),
- defaultOptions, genericToEncoding)
-#endif
newtype Extensions = Extensions Integer
deriving (Show, Read, Eq, Ord, Data, Typeable, Generic)
@@ -538,15 +530,5 @@ parseFormatSpec = parse formatSpec ""
'+' -> (ext : extsToEnable, extsToDisable)
_ -> (extsToEnable, ext : extsToDisable)
-#ifdef DERIVE_JSON_VIA_TH
$(deriveJSON defaultOptions ''Extension)
$(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
diff --git a/src/Text/Pandoc/Filter.hs b/src/Text/Pandoc/Filter.hs
index 8375dda2a..a32c26fbd 100644
--- a/src/Text/Pandoc/Filter.hs
+++ b/src/Text/Pandoc/Filter.hs
@@ -1,9 +1,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}
-#ifdef DERIVE_JSON_VIA_TH
{-# LANGUAGE TemplateHaskell #-}
-#endif
{- |
Module : Text.Pandoc.Filter
Copyright : Copyright (C) 2006-2019 John MacFarlane
@@ -21,12 +19,7 @@ module Text.Pandoc.Filter
) where
import Prelude
-#ifdef DERIVE_JSON_VIA_TH
import Data.Aeson.TH (deriveJSON, defaultOptions)
-#else
-import Data.Aeson (FromJSON (..), ToJSON (..),
- defaultOptions, genericToEncoding)
-#endif
import Data.Foldable (foldrM)
import GHC.Generics (Generic)
import Text.Pandoc.Class (PandocIO)
@@ -59,10 +52,4 @@ expandFilterPath :: Filter -> PandocIO Filter
expandFilterPath (LuaFilter fp) = LuaFilter <$> Path.expandFilterPath fp
expandFilterPath (JSONFilter fp) = JSONFilter <$> Path.expandFilterPath fp
-#ifdef DERIVE_JSON_VIA_TH
$(deriveJSON defaultOptions ''Filter)
-#else
-instance ToJSON Filter where
- toEncoding = genericToEncoding defaultOptions
-instance FromJSON Filter
-#endif
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 0cc3f5ebe..d230291cb 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -2,9 +2,7 @@
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}
-#ifdef DERIVE_JSON_VIA_TH
{-# LANGUAGE TemplateHaskell #-}
-#endif
{- |
Module : Text.Pandoc.Options
Copyright : Copyright (C) 2012-2019 John MacFarlane
@@ -42,13 +40,7 @@ import Skylighting (SyntaxMap, defaultSyntaxMap)
import Text.Pandoc.Extensions
import Text.Pandoc.Highlighting (Style, pygments)
import Text.DocTemplates (Template)
-
-#ifdef DERIVE_JSON_VIA_TH
import Data.Aeson.TH (deriveJSON, defaultOptions)
-#else
-import Data.Aeson (FromJSON (..), ToJSON (..),
- defaultOptions, genericToEncoding)
-#endif
class HasSyntaxExtensions a where
getExtensions :: a -> Extensions
@@ -230,7 +222,6 @@ instance HasSyntaxExtensions WriterOptions where
isEnabled :: HasSyntaxExtensions a => Extension -> a -> Bool
isEnabled ext opts = ext `extensionEnabled` getExtensions opts
-#ifdef DERIVE_JSON_VIA_TH
$(deriveJSON defaultOptions ''ReaderOptions)
$(deriveJSON defaultOptions ''HTMLMathMethod)
$(deriveJSON defaultOptions ''CiteMethod)
@@ -240,40 +231,3 @@ $(deriveJSON defaultOptions ''TrackChanges)
$(deriveJSON defaultOptions ''WrapOption)
$(deriveJSON defaultOptions ''TopLevelDivision)
$(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