[commit: ghc] wip/nfs-locking: Drop DeriveDataTypeable extension (fda4673)
git at git.haskell.org
git at git.haskell.org
Fri Oct 27 01:00:53 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nfs-locking
Link : http://ghc.haskell.org/trac/ghc/changeset/fda46732212cd1f052734ac796dafb3b3f7526a8/ghc
>---------------------------------------------------------------
commit fda46732212cd1f052734ac796dafb3b3f7526a8
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date: Sun May 15 01:03:32 2016 +0100
Drop DeriveDataTypeable extension
>---------------------------------------------------------------
fda46732212cd1f052734ac796dafb3b3f7526a8
hadrian.cabal | 3 +--
src/Oracles/ArgsHash.hs | 2 +-
src/Oracles/Config.hs | 2 +-
src/Oracles/Dependencies.hs | 2 +-
src/Oracles/LookupInPath.hs | 2 +-
src/Oracles/ModuleFiles.hs | 2 +-
src/Oracles/PackageData.hs | 2 +-
src/Oracles/PackageDeps.hs | 2 +-
src/Oracles/WindowsPath.hs | 2 +-
src/Package.hs | 2 +-
src/Settings/Builders/GhcCabal.hs | 2 +-
11 files changed, 11 insertions(+), 12 deletions(-)
diff --git a/hadrian.cabal b/hadrian.cabal
index 5c13f7a..7f03057 100644
--- a/hadrian.cabal
+++ b/hadrian.cabal
@@ -112,8 +112,7 @@ executable hadrian
default-language: Haskell2010
default-extensions: RecordWildCards
- other-extensions: DeriveDataTypeable
- , DeriveGeneric
+ other-extensions: DeriveGeneric
, FlexibleInstances
, GeneralizedNewtypeDeriving
, LambdaCase
diff --git a/src/Oracles/ArgsHash.hs b/src/Oracles/ArgsHash.hs
index d3bfd61..c26efd4 100644
--- a/src/Oracles/ArgsHash.hs
+++ b/src/Oracles/ArgsHash.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.ArgsHash (checkArgsHash, argsHashOracle) where
import Base
diff --git a/src/Oracles/Config.hs b/src/Oracles/Config.hs
index 7801208..95facc8 100644
--- a/src/Oracles/Config.hs
+++ b/src/Oracles/Config.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.Config (askConfig, askConfigWithDefault, configOracle) where
import Base
diff --git a/src/Oracles/Dependencies.hs b/src/Oracles/Dependencies.hs
index aa54d86..08b3afa 100644
--- a/src/Oracles/Dependencies.hs
+++ b/src/Oracles/Dependencies.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.Dependencies (dependencies, dependenciesOracle) where
import Control.Monad.Trans.Maybe
diff --git a/src/Oracles/LookupInPath.hs b/src/Oracles/LookupInPath.hs
index 0ea03fd..18c990b 100644
--- a/src/Oracles/LookupInPath.hs
+++ b/src/Oracles/LookupInPath.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.LookupInPath (lookupInPath, lookupInPathOracle) where
import System.Directory
diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs
index 233cdc0..f2b03f3 100644
--- a/src/Oracles/ModuleFiles.hs
+++ b/src/Oracles/ModuleFiles.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.ModuleFiles (
decodeModule, encodeModule, findGenerator, haskellSources, moduleFilesOracle
) where
diff --git a/src/Oracles/PackageData.hs b/src/Oracles/PackageData.hs
index dba1192..6a01692 100644
--- a/src/Oracles/PackageData.hs
+++ b/src/Oracles/PackageData.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.PackageData (
PackageData (..), PackageDataList (..),
pkgData, pkgDataList, packageDataOracle
diff --git a/src/Oracles/PackageDeps.hs b/src/Oracles/PackageDeps.hs
index 7983c7f..c70b959 100644
--- a/src/Oracles/PackageDeps.hs
+++ b/src/Oracles/PackageDeps.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.PackageDeps (packageDeps, packageDepsOracle) where
import qualified Data.HashMap.Strict as Map
diff --git a/src/Oracles/WindowsPath.hs b/src/Oracles/WindowsPath.hs
index e252bba..2a3336d 100644
--- a/src/Oracles/WindowsPath.hs
+++ b/src/Oracles/WindowsPath.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Oracles.WindowsPath (
fixAbsolutePathOnWindows, topDirectory, windowsPathOracle
) where
diff --git a/src/Package.hs b/src/Package.hs
index 1fc1ac9..7517d87 100644
--- a/src/Package.hs
+++ b/src/Package.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving, DeriveDataTypeable #-}
+{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-}
module Package (
Package (..), PackageName (..), PackageType (..),
diff --git a/src/Settings/Builders/GhcCabal.hs b/src/Settings/Builders/GhcCabal.hs
index faeb99d..9df0fdb 100644
--- a/src/Settings/Builders/GhcCabal.hs
+++ b/src/Settings/Builders/GhcCabal.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Settings.Builders.GhcCabal (
ghcCabalBuilderArgs, ghcCabalHsColourBuilderArgs, bootPackageDbArgs,
PackageDbKey (..), cppArgs, needDll0
More information about the ghc-commits
mailing list