[commit: ghc] master: Remove redundant language extensions (18759cc)

git at git.haskell.org git at git.haskell.org
Fri Sep 11 23:22:46 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/18759cc42636628f136d43d545bd21f26064179e/ghc

>---------------------------------------------------------------

commit 18759cc42636628f136d43d545bd21f26064179e
Author: Jan Stolarek <jan.stolarek at p.lodz.pl>
Date:   Fri Sep 11 23:44:42 2015 +0200

    Remove redundant language extensions


>---------------------------------------------------------------

18759cc42636628f136d43d545bd21f26064179e
 compiler/basicTypes/MkId.hs   | 2 +-
 compiler/iface/TcIface.hs     | 2 +-
 compiler/typecheck/FamInst.hs | 2 +-
 compiler/types/TypeRep.hs     | 2 +-
 4 files changed, 4 insertions(+), 4 deletions(-)

diff --git a/compiler/basicTypes/MkId.hs b/compiler/basicTypes/MkId.hs
index 698c865..6f812de 100644
--- a/compiler/basicTypes/MkId.hs
+++ b/compiler/basicTypes/MkId.hs
@@ -12,7 +12,7 @@ have a standard form, namely:
 - primitive operations
 -}
 
-{-# LANGUAGE CPP, DataKinds #-}
+{-# LANGUAGE CPP #-}
 
 module MkId (
         mkDictFunId, mkDictFunTy, mkDictSelId, mkDictSelRhs,
diff --git a/compiler/iface/TcIface.hs b/compiler/iface/TcIface.hs
index b601dc6..5189b3c 100644
--- a/compiler/iface/TcIface.hs
+++ b/compiler/iface/TcIface.hs
@@ -6,7 +6,7 @@
 Type checking of type signatures in interface files
 -}
 
-{-# LANGUAGE CPP, DataKinds #-}
+{-# LANGUAGE CPP #-}
 
 module TcIface (
         tcLookupImported_maybe,
diff --git a/compiler/typecheck/FamInst.hs b/compiler/typecheck/FamInst.hs
index 978e92e..b598f2a 100644
--- a/compiler/typecheck/FamInst.hs
+++ b/compiler/typecheck/FamInst.hs
@@ -1,6 +1,6 @@
 -- The @FamInst@ type: family instance heads
 
-{-# LANGUAGE CPP, GADTs, DataKinds #-}
+{-# LANGUAGE CPP, GADTs #-}
 
 module FamInst (
         FamInstEnvs, tcGetFamInstEnvs,
diff --git a/compiler/types/TypeRep.hs b/compiler/types/TypeRep.hs
index b732247..9a4bccf 100644
--- a/compiler/types/TypeRep.hs
+++ b/compiler/types/TypeRep.hs
@@ -16,7 +16,7 @@ Note [The Type-related module hierarchy]
 -}
 
 {-# LANGUAGE CPP, DeriveDataTypeable, DeriveFunctor, DeriveFoldable,
-             DeriveTraversable, DataKinds #-}
+             DeriveTraversable #-}
 {-# OPTIONS_HADDOCK hide #-}
 -- We expose the relevant stuff from this module via the Type module
 



More information about the ghc-commits mailing list