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
+{-# 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 #-}
-----------------------------------------------------------------------------
-- |
-{-# 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 #-}
-----------------------------------------------------------------------------
-- |
--
-----------------------------------------------------------------------------
-{-# LANGUAGE CPP
- , NoImplicitPrelude
- , OverlappingInstances
- , ScopedTypeVariables
- , FlexibleInstances
- , MagicHash
- , KindSignatures
- , PolyKinds
- , ConstraintKinds
- , DeriveDataTypeable
- , DataKinds
- , UndecidableInstances
- , StandaloneDeriving #-}
-
module Data.Typeable.Internal (
Proxy (..),
TypeRep(..),
NegativeLiterals
NoImplicitPrelude
NondecreasingIndentation
- OverlappingInstances
OverloadedStrings
ParallelArrays
PolyKinds