[commit: ghc] master: Drop deprecated `OverlappingInstances` from base (cbb20ab)
git at git.haskell.org
git at git.haskell.org
Fri Oct 31 08:36:17 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/cbb20ab2c3222da75625bcf41f8ff67a7e9ba5f7/ghc
>---------------------------------------------------------------
commit cbb20ab2c3222da75625bcf41f8ff67a7e9ba5f7
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Fri Oct 31 08:52:47 2014 +0100
Drop deprecated `OverlappingInstances` from base
With #9242 the `OverlappingInstances` extension got deprecated, this
commit adapts the only two remaining places in `base` where it was still
used.
Starting with this commit, the `Typeable (s t)` instance (which seemingly
was the motivation for using `OverlappingInstances` in the first place
when `Typeable` was neither polykinded nor auto-derived-only, see also
commit ce3fd0e02826367e6134a3362d8d37aa114236f5 which introduced
overlapping instances) does no longer allow overlapping instances, and
there doesn't seem to be any good reason to keep allowing overlapping
instance now.
This also removes redundant `LANGUAGE`/`OPTIONS_GHC` pragmas from
`Data.Typeable` and refactors the language pragmas into more uniform
single-line pragmas.
Reviewed By: austin
Differential Revision: https://phabricator.haskell.org/D377
>---------------------------------------------------------------
cbb20ab2c3222da75625bcf41f8ff67a7e9ba5f7
libraries/base/Data/Typeable.hs | 21 +++++----------------
libraries/base/Data/Typeable/Internal.hs | 27 ++++++++++++---------------
libraries/base/base.cabal | 1 -
3 files changed, 17 insertions(+), 32 deletions(-)
diff --git a/libraries/base/Data/Typeable.hs b/libraries/base/Data/Typeable.hs
index f658a9e..ddb9582 100644
--- a/libraries/base/Data/Typeable.hs
+++ b/libraries/base/Data/Typeable.hs
@@ -1,20 +1,9 @@
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude
- , OverlappingInstances
- , ScopedTypeVariables
- , FlexibleInstances
- , TypeOperators
- , PolyKinds
- , GADTs
- , MagicHash
- #-}
-{-# OPTIONS_GHC -funbox-strict-fields #-}
-
--- The -XOverlappingInstances flag allows the user to over-ride
--- the instances for Typeable given here. In particular, we provide an instance
--- instance ... => Typeable (s a)
--- But a user might want to say
--- instance ... => Typeable (MyType a b)
+{-# LANGUAGE TypeOperators #-}
-----------------------------------------------------------------------------
-- |
diff --git a/libraries/base/Data/Typeable/Internal.hs b/libraries/base/Data/Typeable/Internal.hs
index 140b895..475f083 100644
--- a/libraries/base/Data/Typeable/Internal.hs
+++ b/libraries/base/Data/Typeable/Internal.hs
@@ -1,5 +1,16 @@
-{-# LANGUAGE Unsafe #-}
{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE CPP #-}
+{-# LANGUAGE ConstraintKinds #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE DeriveDataTypeable #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE MagicHash #-}
+{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE StandaloneDeriving #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# LANGUAGE Unsafe #-}
-----------------------------------------------------------------------------
-- |
@@ -13,20 +24,6 @@
--
-----------------------------------------------------------------------------
-{-# LANGUAGE CPP
- , NoImplicitPrelude
- , OverlappingInstances
- , ScopedTypeVariables
- , FlexibleInstances
- , MagicHash
- , KindSignatures
- , PolyKinds
- , ConstraintKinds
- , DeriveDataTypeable
- , DataKinds
- , UndecidableInstances
- , StandaloneDeriving #-}
-
module Data.Typeable.Internal (
Proxy (..),
TypeRep(..),
diff --git a/libraries/base/base.cabal b/libraries/base/base.cabal
index 957053d..6277d89 100644
--- a/libraries/base/base.cabal
+++ b/libraries/base/base.cabal
@@ -69,7 +69,6 @@ Library
NegativeLiterals
NoImplicitPrelude
NondecreasingIndentation
- OverlappingInstances
OverloadedStrings
ParallelArrays
PolyKinds
More information about the ghc-commits
mailing list