aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Extensions.hs
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/Text/Pandoc/Extensions.hs
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/Text/Pandoc/Extensions.hs')
-rw-r--r--src/Text/Pandoc/Extensions.hs18
1 files changed, 0 insertions, 18 deletions
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