Skip to content

Instantly share code, notes, and snippets.

@phadej
Last active November 15, 2021 21:02
Show Gist options
  • Save phadej/0e810832685cb4e70e3ca3a61e2f33d1 to your computer and use it in GitHub Desktop.
Save phadej/0e810832685cb4e70e3ca3a61e2f33d1 to your computer and use it in GitHub Desktop.
diff -ur orig/backprop-0.2.6.4/src/Numeric/Backprop/Internal.hs backprop-0.2.6.4/src/Numeric/Backprop/Internal.hs
--- orig/backprop-0.2.6.4/src/Numeric/Backprop/Internal.hs 2020-07-01 06:10:38.000000000 +0300
+++ backprop-0.2.6.4/src/Numeric/Backprop/Internal.hs 2021-10-27 22:32:19.437273463 +0300
@@ -796,7 +796,6 @@
-- @since 0.1.5.0
instance Eq a => Eq (BVar s a) where
(==) = (==) `on` _bvVal
- (/=) = (/=) `on` _bvVal
-- | Compares the values inside the 'BVar'.
--
diff -ur orig/basement-0.0.12/Basement/Compat/Base.hs basement-0.0.12/Basement/Compat/Base.hs
--- orig/basement-0.0.12/Basement/Compat/Base.hs 2019-09-07 06:32:46.000000000 +0300
+++ basement-0.0.12/Basement/Compat/Base.hs 2021-10-27 19:31:43.111163574 +0300
@@ -28,7 +28,7 @@
, Prelude.seq
, Prelude.Show (..)
, Prelude.Ord (..)
- , Prelude.Eq (..)
+ , Prelude.Eq (..), (Prelude./=)
, Prelude.Bounded (..)
, Prelude.Enum (..)
, Prelude.Functor (..)
diff -ur orig/basement-0.0.12/Basement/Imports.hs basement-0.0.12/Basement/Imports.hs
--- orig/basement-0.0.12/Basement/Imports.hs 2019-09-02 06:58:08.000000000 +0300
+++ basement-0.0.12/Basement/Imports.hs 2021-10-27 19:45:37.076591288 +0300
@@ -30,7 +30,7 @@
, Prelude.Show
, Basement.Show.show
, Prelude.Ord (..)
- , Prelude.Eq (..)
+ , Prelude.Eq (..), (Prelude./=)
, Prelude.Bounded (..)
, Prelude.Enum (..)
, Prelude.Functor (..)
diff -ur orig/basic-prelude-0.7.0/src/CorePrelude.hs basic-prelude-0.7.0/src/CorePrelude.hs
--- orig/basic-prelude-0.7.0/src/CorePrelude.hs 2017-12-05 06:23:18.000000000 +0200
+++ basic-prelude-0.7.0/src/CorePrelude.hs 2021-10-28 01:21:45.729315700 +0300
@@ -36,7 +36,7 @@
, Prelude.seq
-- ** Type classes
, Prelude.Ord (..)
- , Prelude.Eq (..)
+ , Prelude.Eq (..), (Prelude./=)
, Prelude.Bounded (..)
, Prelude.Enum (..)
, Prelude.Show
diff -ur orig/butcher-1.3.3.2/srcinc/prelude.inc butcher-1.3.3.2/srcinc/prelude.inc
--- orig/butcher-1.3.3.2/srcinc/prelude.inc 2001-09-09 04:46:40.000000000 +0300
+++ butcher-1.3.3.2/srcinc/prelude.inc 2021-10-28 02:21:10.091553870 +0300
@@ -132,7 +132,7 @@
, Double
, Bool (..)
, undefined
- , Eq (..)
+ , Eq (..), (/=)
, Ord (..)
, Enum (..)
, Bounded (..)
diff -ur orig/clash-lib-1.4.3/src/Clash/Core/DataCon.hs clash-lib-1.4.3/src/Clash/Core/DataCon.hs
--- orig/clash-lib-1.4.3/src/Clash/Core/DataCon.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-lib-1.4.3/src/Clash/Core/DataCon.hs 2021-10-28 02:36:41.092452507 +0300
@@ -60,7 +60,6 @@
instance Eq DataCon where
(==) = (==) `on` dcUniq
- (/=) = (/=) `on` dcUniq
instance Ord DataCon where
compare = compare `on` dcUniq
diff -ur orig/clash-lib-1.4.3/src/Clash/Core/Name.hs clash-lib-1.4.3/src/Clash/Core/Name.hs
--- orig/clash-lib-1.4.3/src/Clash/Core/Name.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-lib-1.4.3/src/Clash/Core/Name.hs 2021-10-28 02:34:23.169631959 +0300
@@ -46,7 +46,6 @@
instance Eq (Name a) where
(==) = (==) `on` nameUniq
- (/=) = (/=) `on` nameUniq
instance Ord (Name a) where
compare = compare `on` nameUniq
diff -ur orig/clash-lib-1.4.3/src/Clash/Core/TyCon.hs clash-lib-1.4.3/src/Clash/Core/TyCon.hs
--- orig/clash-lib-1.4.3/src/Clash/Core/TyCon.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-lib-1.4.3/src/Clash/Core/TyCon.hs 2021-10-28 02:35:44.472939500 +0300
@@ -78,7 +78,6 @@
instance Eq TyCon where
(==) = (==) `on` tyConUniq
- (/=) = (/=) `on` tyConUniq
instance Uniquable TyCon where
getUnique = tyConUniq
diff -ur orig/clash-lib-1.4.3/src/Clash/Core/Var.hs clash-lib-1.4.3/src/Clash/Core/Var.hs
--- orig/clash-lib-1.4.3/src/Clash/Core/Var.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-lib-1.4.3/src/Clash/Core/Var.hs 2021-10-28 02:36:07.212744335 +0300
@@ -91,7 +91,6 @@
instance Eq (Var a) where
(==) = (==) `on` varKey
- (/=) = (/=) `on` varKey
instance Ord (Var a) where
compare = compare `on` varKey
diff -ur orig/clash-lib-1.4.3/src/Clash/Netlist/Types.hs clash-lib-1.4.3/src/Clash/Netlist/Types.hs
--- orig/clash-lib-1.4.3/src/Clash/Netlist/Types.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-lib-1.4.3/src/Clash/Netlist/Types.hs 2021-10-28 02:37:35.719979414 +0300
@@ -267,7 +267,6 @@
instance Eq Identifier where
i1 == i2 = identifierKey# i1 == identifierKey# i2
- i1 /= i2 = identifierKey# i1 /= identifierKey# i2
instance Ord Identifier where
compare = compare `on` identifierKey#
diff -ur orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/BitVector.hs clash-prelude-1.4.3/src/Clash/Sized/Internal/BitVector.hs
--- orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/BitVector.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-prelude-1.4.3/src/Clash/Sized/Internal/BitVector.hs 2021-10-28 02:25:39.973782989 +0300
@@ -276,7 +276,6 @@
instance Eq Bit where
(==) = eq##
- (/=) = neq##
eq## :: Bit -> Bit -> Bool
eq## b1 b2 = eq# (pack# b1) (pack# b2)
@@ -490,7 +489,6 @@
instance KnownNat n => Eq (BitVector n) where
(==) = eq#
- (/=) = neq#
{-# NOINLINE eq# #-}
eq# :: KnownNat n => BitVector n -> BitVector n -> Bool
diff -ur orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/Index.hs clash-prelude-1.4.3/src/Clash/Sized/Internal/Index.hs
--- orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/Index.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-prelude-1.4.3/src/Clash/Sized/Internal/Index.hs 2021-10-28 02:28:35.608466331 +0300
@@ -193,7 +193,6 @@
instance Eq (Index n) where
(==) = eq#
- (/=) = neq#
{-# NOINLINE eq# #-}
eq# :: (Index n) -> (Index n) -> Bool
diff -ur orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/Signed.hs clash-prelude-1.4.3/src/Clash/Sized/Internal/Signed.hs
--- orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/Signed.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-prelude-1.4.3/src/Clash/Sized/Internal/Signed.hs 2021-10-28 02:28:14.512629593 +0300
@@ -232,7 +232,6 @@
instance Eq (Signed n) where
(==) = eq#
- (/=) = neq#
{-# NOINLINE eq# #-}
eq# :: Signed n -> Signed n -> Bool
diff -ur orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/Unsigned.hs clash-prelude-1.4.3/src/Clash/Sized/Internal/Unsigned.hs
--- orig/clash-prelude-1.4.3/src/Clash/Sized/Internal/Unsigned.hs 2001-09-09 04:46:40.000000000 +0300
+++ clash-prelude-1.4.3/src/Clash/Sized/Internal/Unsigned.hs 2021-10-28 02:26:53.601243467 +0300
@@ -241,7 +241,6 @@
instance Eq (Unsigned n) where
(==) = eq#
- (/=) = neq#
{-# NOINLINE eq# #-}
eq# :: Unsigned n -> Unsigned n -> Bool
diff -ur orig/clientsession-0.9.1.2/src/Web/ClientSession.hs clientsession-0.9.1.2/src/Web/ClientSession.hs
--- orig/clientsession-0.9.1.2/src/Web/ClientSession.hs 2016-07-07 18:34:41.000000000 +0300
+++ clientsession-0.9.1.2/src/Web/ClientSession.hs 2021-10-28 00:02:14.668276028 +0300
@@ -157,7 +157,6 @@
instance Eq IV where
(==) = (==) `on` unIV
- (/=) = (/=) `on` unIV
instance Ord IV where
compare = compare `on` unIV
diff -ur orig/compdata-0.12.1/src/Data/Comp/Multi/HFunctor.hs compdata-0.12.1/src/Data/Comp/Multi/HFunctor.hs
--- orig/compdata-0.12.1/src/Data/Comp/Multi/HFunctor.hs 2001-09-09 04:46:40.000000000 +0300
+++ compdata-0.12.1/src/Data/Comp/Multi/HFunctor.hs 2021-10-27 21:27:25.102369232 +0300
@@ -57,7 +57,6 @@
instance Eq a => Eq (K a i) where
K x == K y = x == y
- K x /= K y = x /= y
instance Ord a => Ord (K a i) where
K x < K y = x < y
diff -ur orig/compensated-0.8.3/src/Numeric/Compensated.hs compensated-0.8.3/src/Numeric/Compensated.hs
--- orig/compensated-0.8.3/src/Numeric/Compensated.hs 2001-09-09 04:46:40.000000000 +0300
+++ compensated-0.8.3/src/Numeric/Compensated.hs 2021-10-28 00:06:17.445737094 +0300
@@ -327,7 +327,6 @@
instance Compensable a => Eq (Compensated a) where
m == n = with m $ \a b -> with n $ \c d -> a == c && b == d
- m /= n = with m $ \a b -> with n $ \c d -> a /= c || b /= d
{-# INLINE (==) #-}
instance Compensable a => Ord (Compensated a) where
diff -ur orig/conduit-1.3.4.1/src/Data/Conduit/Combinators.hs conduit-1.3.4.1/src/Data/Conduit/Combinators.hs
--- orig/conduit-1.3.4.1/src/Data/Conduit/Combinators.hs 2021-03-02 08:49:28.000000000 +0200
+++ conduit-1.3.4.1/src/Data/Conduit/Combinators.hs 2021-10-28 00:07:31.216934029 +0300
@@ -229,7 +229,7 @@
import qualified Data.Vector.Generic as V
import qualified Data.Vector.Generic.Mutable as VM
import Data.Void (absurd)
-import Prelude (Bool (..), Eq (..), Int,
+import Prelude (Bool (..), Eq (..), (/=), Int,
Maybe (..), Either (..), Monad (..), Num (..),
Ord (..), fromIntegral, maybe, either,
($), Functor (..), Enum, seq, Show, Char,
Only in DBFunctor-0.1.2.1: cabal.project
Only in DBFunctor-0.1.2.1: dist-newstyle
Only in DBFunctor-0.1.2.1: .ghc.environment.x86_64-linux-8.6.5
diff -ur orig/DBFunctor-0.1.2.1/src/RTable/Core.hs DBFunctor-0.1.2.1/src/RTable/Core.hs
--- orig/DBFunctor-0.1.2.1/src/RTable/Core.hs 2021-05-23 18:03:12.000000000 +0300
+++ DBFunctor-0.1.2.1/src/RTable/Core.hs 2021-10-28 00:00:45.265149734 +0300
@@ -818,11 +818,6 @@
-- anything else is just False
_ == _ = False
- Null /= Null = False
- _ /= Null = False
- Null /= _ = False
- x /= y = not (x == y)
-
-- Need to explicitly specify due to "Null logic" (see Eq)
instance Ord RDataType where
compare Null _ = GT -- Null <= _ = False
@@ -4417,4 +4412,4 @@
data UniquenessViolationInUpsert =
UniquenessViolationInUpsert String -- ^ Error message
deriving(Eq, Show)
-instance Exception UniquenessViolationInUpsert
\ No newline at end of file
+instance Exception UniquenessViolationInUpsert
diff -ur orig/dimensional-1.4/src/Numeric/Units/Dimensional/Dimensions/TermLevel.hs dimensional-1.4/src/Numeric/Units/Dimensional/Dimensions/TermLevel.hs
--- orig/dimensional-1.4/src/Numeric/Units/Dimensional/Dimensions/TermLevel.hs 2021-05-02 13:37:37.000000000 +0300
+++ dimensional-1.4/src/Numeric/Units/Dimensional/Dimensions/TermLevel.hs 2021-10-28 01:04:19.475437990 +0300
@@ -40,7 +40,7 @@
import Data.Semigroup (Semigroup(..))
import Data.Monoid (Monoid(..))
import GHC.Generics
-import Prelude (id, all, fst, snd, fmap, otherwise, divMod, ($), (+), (-), (.), (&&), Int, Show, Eq(..), Ord(..), Maybe(..), Bool(..))
+import Prelude (id, all, fst, snd, fmap, otherwise, divMod, ($), (+), (-), (.), (&&), Int, Show, Eq(..), (/=), Ord(..), Maybe(..), Bool(..))
import qualified Prelude as P
-- $setup
diff -ur orig/eventstore-1.4.1/Database/EventStore/Internal/Prelude.hs eventstore-1.4.1/Database/EventStore/Internal/Prelude.hs
--- orig/eventstore-1.4.1/Database/EventStore/Internal/Prelude.hs 2001-09-09 04:46:40.000000000 +0300
+++ eventstore-1.4.1/Database/EventStore/Internal/Prelude.hs 2021-10-28 01:09:44.040276945 +0300
@@ -68,7 +68,7 @@
, FilePath
, Num(..)
, Show(..)
- , Eq(..)
+ , Eq(..), (/=)
, Ord(..)
, Enum(..)
, Bounded(..)
diff -ur orig/fb-2.1.1/src/Facebook/Object/Action.hs fb-2.1.1/src/Facebook/Object/Action.hs
--- orig/fb-2.1.1/src/Facebook/Object/Action.hs 2020-03-01 17:06:41.000000000 +0200
+++ fb-2.1.1/src/Facebook/Object/Action.hs 2021-10-28 01:11:47.655070141 +0300
@@ -72,7 +72,6 @@
-- | Since 0.7.1
instance Eq Action where
(==) = (==) `on` unAction
- (/=) = (/=) `on` unAction
-- | Since 0.7.1
instance Ord Action where
diff -ur orig/geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeatureCollection.hs geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeatureCollection.hs
--- orig/geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeatureCollection.hs 2020-04-03 07:21:00.000000000 +0300
+++ geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeatureCollection.hs 2021-10-28 01:12:40.026561662 +0300
@@ -34,7 +34,7 @@
import Data.Maybe (Maybe (..))
import qualified Data.Sequence as Sequence
import Data.Text (Text)
-import Prelude (Eq (..), Show, ($))
+import Prelude (Eq (..), (/=), Show, ($))
-- | See Section 2.3 /Feature Collection Objects/ of the GeoJSON spec
--
diff -ur orig/geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeature.hs geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeature.hs
--- orig/geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeature.hs 2020-04-03 07:21:00.000000000 +0300
+++ geojson-4.0.2/src/Data/Geospatial/Internal/GeoFeature.hs 2021-10-28 01:12:27.218683655 +0300
@@ -42,7 +42,7 @@
import Data.Maybe (Maybe)
import Data.Text (Text)
import GHC.Generics (Generic)
-import Prelude (Eq (..), Show, ($))
+import Prelude (Eq (..), (/=), Show, ($))
-- | See Section 2.2 /Feature Objects/ of the GeoJSON spec.
-- Parameterised on the property type
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/DataCon.hs ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/DataCon.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/DataCon.hs 2021-08-28 22:16:07.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/DataCon.hs 2021-10-27 20:03:13.372110496 +0300
@@ -783,7 +783,6 @@
instance Eq DataCon where
a == b = getUnique a == getUnique b
- a /= b = getUnique a /= getUnique b
instance Uniquable DataCon where
getUnique = dcUnique
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Name.hs ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Name.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Name.hs 2021-08-28 22:16:07.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Name.hs 2021-10-27 20:00:16.718178073 +0300
@@ -468,7 +468,6 @@
-- | The same comments as for `Name`'s `Ord` instance apply.
instance Eq Name where
a == b = case (a `compare` b) of { EQ -> True; _ -> False }
- a /= b = case (a `compare` b) of { EQ -> False; _ -> True }
-- | __Caution__: This instance is implemented via `nonDetCmpUnique`, which
-- means that the ordering is not stable across deserialization or rebuilds.
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/PatSyn.hs ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/PatSyn.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/PatSyn.hs 2021-08-28 22:16:07.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/PatSyn.hs 2021-10-27 20:02:55.000325347 +0300
@@ -322,7 +322,6 @@
instance Eq PatSyn where
(==) = (==) `on` getUnique
- (/=) = (/=) `on` getUnique
instance Uniquable PatSyn where
getUnique = psUnique
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Unique.hs ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Unique.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Unique.hs 2021-08-28 22:16:07.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/basicTypes/Unique.hs 2021-10-27 19:59:48.646507001 +0300
@@ -273,7 +273,6 @@
instance Eq Unique where
a == b = eqUnique a b
- a /= b = not (eqUnique a b)
instance Uniquable Unique where
getUnique u = u
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/types/Class.hs ghc-lib-parser-8.10.7.20210828/compiler/types/Class.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/types/Class.hs 2021-08-28 22:16:08.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/types/Class.hs 2021-10-27 20:01:45.485138659 +0300
@@ -329,7 +329,6 @@
instance Eq Class where
c1 == c2 = classKey c1 == classKey c2
- c1 /= c2 = classKey c1 /= classKey c2
instance Uniquable Class where
getUnique c = classKey c
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/types/CoAxiom.hs ghc-lib-parser-8.10.7.20210828/compiler/types/CoAxiom.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/types/CoAxiom.hs 2021-08-28 22:16:08.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/types/CoAxiom.hs 2021-10-27 20:01:28.897332817 +0300
@@ -438,7 +438,6 @@
instance Eq (CoAxiom br) where
a == b = getUnique a == getUnique b
- a /= b = getUnique a /= getUnique b
instance Uniquable (CoAxiom br) where
getUnique = co_ax_unique
diff -ur orig/ghc-lib-parser-8.10.7.20210828/compiler/types/TyCon.hs ghc-lib-parser-8.10.7.20210828/compiler/types/TyCon.hs
--- orig/ghc-lib-parser-8.10.7.20210828/compiler/types/TyCon.hs 2021-08-28 22:16:08.000000000 +0300
+++ ghc-lib-parser-8.10.7.20210828/compiler/types/TyCon.hs 2021-10-27 20:02:03.896923185 +0300
@@ -2611,7 +2611,6 @@
instance Eq TyCon where
a == b = getUnique a == getUnique b
- a /= b = getUnique a /= getUnique b
instance Uniquable TyCon where
getUnique tc = tyConUnique tc
diff -ur orig/haskell-gi-base-0.25.0/Data/GI/Base/ShortPrelude.hs haskell-gi-base-0.25.0/Data/GI/Base/ShortPrelude.hs
--- orig/haskell-gi-base-0.25.0/Data/GI/Base/ShortPrelude.hs 2001-09-09 04:46:40.000000000 +0300
+++ haskell-gi-base-0.25.0/Data/GI/Base/ShortPrelude.hs 2021-10-28 01:37:01.928401163 +0300
@@ -36,7 +36,7 @@
, Enum(fromEnum, toEnum)
, Show(..)
- , Eq(..)
+ , Eq(..), (/=)
, IO
, Monad(..)
, Maybe(..)
diff -ur orig/HaskellNet-0.6/src/Text/Packrat/Parse.hs HaskellNet-0.6/src/Text/Packrat/Parse.hs
--- orig/HaskellNet-0.6/src/Text/Packrat/Parse.hs 2001-09-09 04:46:40.000000000 +0300
+++ HaskellNet-0.6/src/Text/Packrat/Parse.hs 2021-10-27 22:03:50.249119872 +0300
@@ -251,7 +251,6 @@
-- Comparison operators for ParseError just compare relative positions.
instance Eq ParseError where
ParseError p1 _ == ParseError p2 _ = p1 == p2
- ParseError p1 _ /= ParseError p2 _ = p1 /= p2
instance Ord ParseError where
ParseError p1 _ < ParseError p2 _ = p1 < p2
diff -ur orig/hOpenPGP-2.9.5/Codec/Encryption/OpenPGP/Types/Internal/Base.hs hOpenPGP-2.9.5/Codec/Encryption/OpenPGP/Types/Internal/Base.hs
--- orig/hOpenPGP-2.9.5/Codec/Encryption/OpenPGP/Types/Internal/Base.hs 2020-10-31 21:51:18.000000000 +0200
+++ hOpenPGP-2.9.5/Codec/Encryption/OpenPGP/Types/Internal/Base.hs 2021-10-28 01:13:57.473823424 +0300
@@ -673,9 +673,6 @@
instance Hashable FeatureFlag
-instance Hashable a => Hashable (Set a) where
- hashWithSalt salt = hashWithSalt salt . Set.toList
-
instance Pretty FeatureFlag where
pretty ModificationDetection = pretty "modification-detection"
pretty (FeatureOther o) = pretty "unknown feature flag type" <+> pretty o
diff -ur orig/hybrid-vectors-0.2.2/src/Data/Vector/Hybrid/Internal.hs hybrid-vectors-0.2.2/src/Data/Vector/Hybrid/Internal.hs
--- orig/hybrid-vectors-0.2.2/src/Data/Vector/Hybrid/Internal.hs 2018-01-18 21:45:16.000000000 +0200
+++ hybrid-vectors-0.2.2/src/Data/Vector/Hybrid/Internal.hs 2021-10-28 01:15:28.188955388 +0300
@@ -170,10 +170,6 @@
xs == ys = Stream.eq (G.stream xs) (G.stream ys)
{-# INLINE (==) #-}
- xs /= ys = not (Stream.eq (G.stream xs) (G.stream ys))
- {-# INLINE (/=) #-}
-
-
-- See http://trac.haskell.org/vector/ticket/12
instance (G.Vector u a, G.Vector v b, Ord a, Ord b, c ~ (a, b)) => Ord (Vector u v c) where
{-# INLINE compare #-}
diff -ur orig/intro-0.9.0.0/src/Intro.hs intro-0.9.0.0/src/Intro.hs
--- orig/intro-0.9.0.0/src/Intro.hs 2020-08-28 13:48:46.000000000 +0300
+++ intro-0.9.0.0/src/Intro.hs 2021-10-28 01:24:11.339904147 +0300
@@ -380,7 +380,7 @@
-- * Equality and ordering
-- ** Eq
- , Data.Eq.Eq((==), (/=))
+ , Data.Eq.Eq((==)), (Data.Eq./=)
, Data.Functor.Classes.Eq1
, Data.Functor.Classes.Eq2
diff -ur orig/io-streams-1.5.2.1/src/System/IO/Streams/Internal/Search.hs io-streams-1.5.2.1/src/System/IO/Streams/Internal/Search.hs
--- orig/io-streams-1.5.2.1/src/System/IO/Streams/Internal/Search.hs 2001-09-09 04:46:40.000000000 +0300
+++ io-streams-1.5.2.1/src/System/IO/Streams/Internal/Search.hs 2021-10-28 01:16:06.324589556 +0300
@@ -16,7 +16,7 @@
import qualified Data.ByteString.Unsafe as S
import qualified Data.Vector.Unboxed as V
import qualified Data.Vector.Unboxed.Mutable as MV
-import Prelude (Bool (..), Either (..), Enum (..), Eq (..), IO, Int, Monad (..), Num (..), Ord (..), Show, either, id, maybe, not, otherwise, ($), ($!), (&&), (.), (||))
+import Prelude (Bool (..), Either (..), Enum (..), Eq (..), (/=), IO, Int, Monad (..), Num (..), Ord (..), Show, either, id, maybe, not, otherwise, ($), ($!), (&&), (.), (||))
------------------------------------------------------------------------------
import System.IO.Streams.Internal (InputStream)
import qualified System.IO.Streams.Internal as Streams
diff -ur orig/loc-0.1.3.10/src/Data/Loc/Internal/Prelude.hs loc-0.1.3.10/src/Data/Loc/Internal/Prelude.hs
--- orig/loc-0.1.3.10/src/Data/Loc/Internal/Prelude.hs 2019-02-27 03:08:20.000000000 +0200
+++ loc-0.1.3.10/src/Data/Loc/Internal/Prelude.hs 2021-10-27 19:57:29.516139186 +0300
@@ -11,7 +11,7 @@
import Data.Bifunctor as X (Bifunctor (..))
import Data.Bool as X (Bool (..), not, otherwise, (&&), (||))
import Data.Char (Char)
-import Data.Eq as X (Eq (..))
+import Data.Eq as X (Eq (..), (/=))
import Data.Foldable as X (Foldable (..), foldMap, traverse_)
import Data.Function as X (const, flip, id, on, ($), (&), (.))
import Data.Functor as X (Functor (..), void, ($>), (<$), (<$>))
diff -ur orig/mixed-types-num-0.5.9.1/src/Numeric/MixedTypes/PreludeHiding.hs mixed-types-num-0.5.9.1/src/Numeric/MixedTypes/PreludeHiding.hs
--- orig/mixed-types-num-0.5.9.1/src/Numeric/MixedTypes/PreludeHiding.hs 2019-01-04 23:45:35.000000000 +0200
+++ mixed-types-num-0.5.9.1/src/Numeric/MixedTypes/PreludeHiding.hs 2021-10-28 01:17:18.959891449 +0300
@@ -20,7 +20,7 @@
(
fromInteger, fromRational
, (!!), length, replicate, take, drop, splitAt
- , Eq(..), Ord(..), Num(..), Fractional(..), RealFrac(..), Floating(..), Integral(..)
+ , Eq(..), (/=), Ord(..), Num(..), Fractional(..), RealFrac(..), Floating(..), Integral(..)
, not, (&&), (||), and, or
, (^), (^^)
, minimum, maximum, sum, product
diff -ur orig/multistate-0.8.0.3/src/Control/Monad/Trans/MultiGST/Common.hs multistate-0.8.0.3/src/Control/Monad/Trans/MultiGST/Common.hs
--- orig/multistate-0.8.0.3/src/Control/Monad/Trans/MultiGST/Common.hs 2001-09-09 04:46:40.000000000 +0300
+++ multistate-0.8.0.3/src/Control/Monad/Trans/MultiGST/Common.hs 2021-10-28 01:18:36.795141661 +0300
@@ -137,23 +137,19 @@
instance Eq (HListM '[]) where
HNilM == HNilM = True
- HNilM /= HNilM = False
instance (Eq x, Eq (HListM xs))
=> Eq (HListM ('Gettable x ': xs))
where
x1 :+-: xr1 == x2 :+-: xr2 = x1==x2 && xr1==xr2
- x1 :+-: xr1 /= x2 :+-: xr2 = x1/=x2 || xr1/=xr2
instance (Eq x, Eq (HListM xs))
=> Eq (HListM ('Tellable x ': xs))
where
x1 :-+: xr1 == x2 :-+: xr2 = x1==x2 && xr1==xr2
- x1 :-+: xr1 /= x2 :-+: xr2 = x1/=x2 || xr1/=xr2
instance (Eq x, Eq (HListM xs))
=> Eq (HListM ('Settable x ': xs))
where
x1 :++: xr1 == x2 :++: xr2 = x1==x2 && xr1==xr2
- x1 :++: xr1 /= x2 :++: xr2 = x1/=x2 || xr1/=xr2
type family AppendM (l1 :: [CanReadWrite Type]) (l2 :: [CanReadWrite Type]) :: [CanReadWrite Type] where
AppendM '[] l2 = l2
diff -ur orig/multistate-0.8.0.3/src/Data/HList/HList.hs multistate-0.8.0.3/src/Data/HList/HList.hs
--- orig/multistate-0.8.0.3/src/Data/HList/HList.hs 2001-09-09 04:46:40.000000000 +0300
+++ multistate-0.8.0.3/src/Data/HList/HList.hs 2021-10-28 01:18:01.787479091 +0300
@@ -62,13 +62,11 @@
instance Eq (HList '[]) where
HNil == HNil = True
- HNil /= HNil = False
instance (Eq x, Eq (HList xs))
=> Eq (HList (x ': xs))
where
x1 :+: xr1 == x2 :+: xr2 = x1==x2 && xr1==xr2
- x1 :+: xr1 /= x2 :+: xr2 = x1/=x2 || xr1/=xr2
-- cannot use the closed variant because of ghc-7.8.4.
-- (was not investigated more closely; there simply
Only in numbers-3000.2.0.2: cabal.project
diff -ur orig/numbers-3000.2.0.2/Data/Number/Interval.hs numbers-3000.2.0.2/Data/Number/Interval.hs
--- orig/numbers-3000.2.0.2/Data/Number/Interval.hs 2018-05-14 20:55:03.000000000 +0300
+++ numbers-3000.2.0.2/Data/Number/Interval.hs 2021-10-27 20:23:06.392794465 +0300
@@ -12,7 +12,6 @@
instance (Ord a) => Eq (Interval a) where
I l h == I l' h' = l == h' && h == l'
- I l h /= I l' h' = h < l' || h' < l
instance (Ord a) => Ord (Interval a) where
I l h < I l' h' = h < l'
Only in numbers-3000.2.0.2: dist-newstyle
Only in numbers-3000.2.0.2: .ghc.environment.x86_64-linux-8.6.5
diff -ur orig/numeric-prelude-0.4.3.3/src/NumericPrelude/Base.hs numeric-prelude-0.4.3.3/src/NumericPrelude/Base.hs
--- orig/numeric-prelude-0.4.3.3/src/NumericPrelude/Base.hs 2021-03-14 23:40:46.000000000 +0200
+++ numeric-prelude-0.4.3.3/src/NumericPrelude/Base.hs 2021-10-28 02:24:31.862263375 +0300
@@ -16,7 +16,7 @@
P.Char,
P.Either(..),
P.Enum(..),
- P.Eq(..),
+ P.Eq(..), (P./=),
P.FilePath,
P.Functor(..),
P.IO,
diff -ur orig/postgresql-libpq-0.9.4.3/src/Database/PostgreSQL/LibPQ/Internal.hs postgresql-libpq-0.9.4.3/src/Database/PostgreSQL/LibPQ/Internal.hs
--- orig/postgresql-libpq-0.9.4.3/src/Database/PostgreSQL/LibPQ/Internal.hs 2001-09-09 04:46:40.000000000 +0300
+++ postgresql-libpq-0.9.4.3/src/Database/PostgreSQL/LibPQ/Internal.hs 2021-10-27 20:26:40.130550268 +0300
@@ -26,7 +26,6 @@
instance Eq Connection where
(Conn c _) == (Conn d _) = c == d
- (Conn c _) /= (Conn d _) = c /= d
withConn :: Connection
-> (Ptr PGconn -> IO b)
diff -ur orig/postgresql-simple-0.6.4/src/Database/PostgreSQL/Simple/Types.hs postgresql-simple-0.6.4/src/Database/PostgreSQL/Simple/Types.hs
--- orig/postgresql-simple-0.6.4/src/Database/PostgreSQL/Simple/Types.hs 2001-09-09 04:46:40.000000000 +0300
+++ postgresql-simple-0.6.4/src/Database/PostgreSQL/Simple/Types.hs 2021-10-28 00:12:45.553583131 +0300
@@ -52,7 +52,6 @@
instance Eq Null where
_ == _ = False
- _ /= _ = False
-- | A placeholder for the PostgreSQL @DEFAULT@ value.
data Default = Default
diff -ur orig/prelude-compat-0.0.0.2/src/Prelude2010.hs prelude-compat-0.0.0.2/src/Prelude2010.hs
--- orig/prelude-compat-0.0.0.2/src/Prelude2010.hs 2019-05-23 22:38:04.000000000 +0300
+++ prelude-compat-0.0.0.2/src/Prelude2010.hs 2021-10-27 20:27:06.814267807 +0300
@@ -14,7 +14,7 @@
Enum
(succ, pred, toEnum, fromEnum,
enumFrom, enumFromThen, enumFromTo, enumFromThenTo),
- Eq ((==), (/=)),
+ Eq ((==)), (/=),
FilePath,
Float,
Floating
diff -ur orig/primitive-addr-0.1.0.2/src/Data/Primitive/Addr.hs primitive-addr-0.1.0.2/src/Data/Primitive/Addr.hs
--- orig/primitive-addr-0.1.0.2/src/Data/Primitive/Addr.hs 2001-09-09 04:46:40.000000000 +0300
+++ primitive-addr-0.1.0.2/src/Data/Primitive/Addr.hs 2021-10-27 20:52:03.017750703 +0300
@@ -52,7 +52,6 @@
instance Eq Addr where
Addr a# == Addr b# = toBool# (eqAddr# a# b#)
- Addr a# /= Addr b# = toBool# (neAddr# a# b#)
instance Ord Addr where
Addr a# > Addr b# = toBool# (gtAddr# a# b#)
diff -ur orig/protolude-0.3.0/src/Protolude.hs protolude-0.3.0/src/Protolude.hs
--- orig/protolude-0.3.0/src/Protolude.hs 2020-03-21 15:19:57.000000000 +0200
+++ protolude-0.3.0/src/Protolude.hs 2021-10-27 21:29:56.292708591 +0300
@@ -209,7 +209,7 @@
-- Base typeclasses
import Data.Eq as Eq (
- Eq(..)
+ Eq(..), (/=),
)
import Data.Ord as Ord (
Ord(..)
diff -ur orig/relude-0.7.0.0/src/Relude/Base.hs relude-0.7.0.0/src/Relude/Base.hs
--- orig/relude-0.7.0.0/src/Relude/Base.hs 2001-09-09 04:46:40.000000000 +0300
+++ relude-0.7.0.0/src/Relude/Base.hs 2021-10-28 02:13:52.999642960 +0300
@@ -57,7 +57,7 @@
import System.IO (FilePath, Handle, IO, IOMode (..), stderr, stdin, stdout, withFile)
-- Base typeclasses
-import Data.Eq (Eq (..))
+import Data.Eq (Eq (..), (/=))
import Data.Ord (Down (..), Ord (..), Ordering (..), comparing)
-- Types for type-level computation
diff -ur orig/sbv-8.15/Data/SBV/Core/Data.hs sbv-8.15/Data/SBV/Core/Data.hs
--- orig/sbv-8.15/Data/SBV/Core/Data.hs 2001-09-09 04:46:40.000000000 +0300
+++ sbv-8.15/Data/SBV/Core/Data.hs 2021-10-28 01:29:02.061078240 +0300
@@ -380,7 +380,6 @@
-- 'Data.SBV.EqSymbolic' instead.
instance Eq (SBV a) where
SBV a == SBV b = a == b
- SBV a /= SBV b = a /= b
instance HasKind a => HasKind (SBV a) where
kindOf _ = kindOf (Proxy @a)
diff -ur orig/sbv-8.15/Data/SBV/Core/Symbolic.hs sbv-8.15/Data/SBV/Core/Symbolic.hs
--- orig/sbv-8.15/Data/SBV/Core/Symbolic.hs 2001-09-09 04:46:40.000000000 +0300
+++ sbv-8.15/Data/SBV/Core/Symbolic.hs 2021-10-28 00:16:30.427233613 +0300
@@ -1176,7 +1176,7 @@
-- <http://github.com/LeventErkok/sbv/issues/301>. We simply error out.
instance Eq SVal where
a == b = noEquals "==" ".==" (show a, show b)
- a /= b = noEquals "/=" "./=" (show a, show b)
+ -- a /= b = noEquals "/=" "./=" (show a, show b)
-- Bail out nicely.
noEquals :: String -> String -> (String, String) -> a
diff -ur orig/semirings-0.6/Data/Semiring.hs semirings-0.6/Data/Semiring.hs
--- orig/semirings-0.6/Data/Semiring.hs 2001-09-09 04:46:40.000000000 +0300
+++ semirings-0.6/Data/Semiring.hs 2021-10-28 00:08:59.683980567 +0300
@@ -61,7 +61,7 @@
import Data.Bool (Bool(..), (||), (&&), otherwise)
import Data.Coerce (Coercible, coerce)
import Data.Complex (Complex(..))
-import Data.Eq (Eq(..))
+import Data.Eq (Eq(..), (/=))
import Data.Fixed (Fixed, HasResolution)
import Data.Foldable (Foldable(foldMap))
import qualified Data.Foldable as Foldable
diff -ur orig/singletons-2.7/src/Data/Singletons.hs singletons-2.7/src/Data/Singletons.hs
--- orig/singletons-2.7/src/Data/Singletons.hs 2001-09-09 04:46:40.000000000 +0300
+++ singletons-2.7/src/Data/Singletons.hs 2021-10-28 00:09:42.755519650 +0300
@@ -130,7 +130,6 @@
instance SEq k => Eq (SomeSing k) where
SomeSing a == SomeSing b = fromSing (a %== b)
- SomeSing a /= SomeSing b = fromSing (a %/= b)
instance SOrd k => Ord (SomeSing k) where
SomeSing a `compare` SomeSing b = fromSing (a `sCompare` b)
diff -ur orig/snap-core-1.0.4.2/src/Snap/Internal/Parsing.hs snap-core-1.0.4.2/src/Snap/Internal/Parsing.hs
--- orig/snap-core-1.0.4.2/src/Snap/Internal/Parsing.hs 2001-09-09 04:46:40.000000000 +0300
+++ snap-core-1.0.4.2/src/Snap/Internal/Parsing.hs 2021-10-28 02:22:35.887032367 +0300
@@ -29,7 +29,7 @@
import Data.Word (Word8)
import GHC.Exts (Int (I#), uncheckedShiftRL#, word2Int#)
import GHC.Word (Word8 (..))
-import Prelude (Bool (..), Either (..), Enum (fromEnum, toEnum), Eq (..), Num (..), Ord (..), String, and, any, concatMap, elem, error, filter, flip, foldr, fst, id, map, not, otherwise, show, snd, ($), ($!), (&&), (++), (.), (||))
+import Prelude (Bool (..), Either (..), Enum (fromEnum, toEnum), Eq (..), (/=), Num (..), Ord (..), String, and, any, concatMap, elem, error, filter, flip, foldr, fst, id, map, not, otherwise, show, snd, ($), ($!), (&&), (++), (.), (||))
import Snap.Internal.Http.Types (Cookie (Cookie))
------------------------------------------------------------------------------
diff -ur orig/snap-core-1.0.4.2/src/Snap/Internal/Util/FileServe.hs snap-core-1.0.4.2/src/Snap/Internal/Util/FileServe.hs
--- orig/snap-core-1.0.4.2/src/Snap/Internal/Util/FileServe.hs 2001-09-09 04:46:40.000000000 +0300
+++ snap-core-1.0.4.2/src/Snap/Internal/Util/FileServe.hs 2021-10-28 02:23:02.486862030 +0300
@@ -44,7 +44,7 @@
import qualified Data.Text as T (Text, pack, unpack)
import qualified Data.Text.Encoding as T (decodeUtf8, encodeUtf8)
import Data.Word (Word64)
-import Prelude (Bool (..), Eq (..), FilePath, IO, Maybe (Just, Nothing), Num (..), Ord (..), Show (show), String, const, either, flip, fromIntegral, id, maybe, not, ($), ($!), (.), (||))
+import Prelude (Bool (..), Eq (..), (/=), FilePath, IO, Maybe (Just, Nothing), Num (..), Ord (..), Show (show), String, const, either, flip, fromIntegral, id, maybe, not, ($), ($!), (.), (||))
import qualified Prelude
import Snap.Core (MonadSnap (..), Request (rqPathInfo, rqQueryString, rqURI), deleteHeader, emptyResponse, finishWith, formatHttpTime, getHeader, getRequest, modifyResponse, parseHttpTime, pass, redirect, sendFile, sendFilePartial, setContentLength, setContentType, setHeader, setResponseBody, setResponseCode, urlDecode, writeBS)
import Snap.Internal.Debug (debug)
diff -ur orig/snap-core-1.0.4.2/src/Snap/Types/Headers.hs snap-core-1.0.4.2/src/Snap/Types/Headers.hs
--- orig/snap-core-1.0.4.2/src/Snap/Types/Headers.hs 2001-09-09 04:46:40.000000000 +0300
+++ snap-core-1.0.4.2/src/Snap/Types/Headers.hs 2021-10-28 02:22:17.375148607 +0300
@@ -56,7 +56,7 @@
import qualified Data.CaseInsensitive.Unsafe as CI
import qualified Data.List as List
import Data.Maybe (fromMaybe)
-import Prelude (Bool (..), Eq (..), Maybe (..), Show (..), fst, id, map, otherwise, uncurry, ($), ($!), (.))
+import Prelude (Bool (..), Eq (..), (/=), Maybe (..), Show (..), fst, id, map, otherwise, uncurry, ($), ($!), (.))
------------------------------------------------------------------------------
------------------------------------------------------------------------------
diff -ur orig/snap-core-1.0.4.2/src/Snap/Util/GZip.hs snap-core-1.0.4.2/src/Snap/Util/GZip.hs
--- orig/snap-core-1.0.4.2/src/Snap/Util/GZip.hs 2001-09-09 04:46:40.000000000 +0300
+++ snap-core-1.0.4.2/src/Snap/Util/GZip.hs 2021-10-28 02:23:26.694703759 +0300
@@ -29,7 +29,7 @@
import Data.Set (Set)
import qualified Data.Set as Set (fromList, member)
import Data.Typeable (Typeable)
-import Prelude (Either (..), Eq (..), IO, Show (show), id, not, ($), ($!), (&&), (++), (||))
+import Prelude (Either (..), Eq (..), (/=), IO, Show (show), id, not, ($), ($!), (&&), (++), (||))
import Snap.Core (MonadSnap, clearContentLength, finishWith, getHeader, getRequest, getResponse, modifyResponse, modifyResponseBody, setHeader)
import Snap.Internal.Debug (debug)
import Snap.Internal.Parsing (fullyParse)
diff -ur orig/sqlite-simple-0.4.18.0/Database/SQLite/Simple/Types.hs sqlite-simple-0.4.18.0/Database/SQLite/Simple/Types.hs
--- orig/sqlite-simple-0.4.18.0/Database/SQLite/Simple/Types.hs 2020-03-07 20:54:11.000000000 +0200
+++ sqlite-simple-0.4.18.0/Database/SQLite/Simple/Types.hs 2021-10-28 00:10:10.115227871 +0300
@@ -39,7 +39,6 @@
instance Eq Null where
_ == _ = False
- _ /= _ = False
-- | A query string. This type is intended to make it difficult to
-- construct a SQL query by concatenating string fragments, as that is
diff -ur orig/string-class-0.1.7.0/src/Data/String/Class.hs string-class-0.1.7.0/src/Data/String/Class.hs
--- orig/string-class-0.1.7.0/src/Data/String/Class.hs 2018-02-13 14:14:06.000000000 +0200
+++ string-class-0.1.7.0/src/Data/String/Class.hs 2021-10-27 21:00:17.344273829 +0300
@@ -964,8 +964,6 @@
instance Eq GenString where
_a == _b = case (_a, _b) of
((GenString _a), (GenString _b)) -> toGenDefaultString _a == toGenDefaultString _b
- _a /= _b = case (_a, _b) of
- ((GenString _a), (GenString _b)) -> toGenDefaultString _a /= toGenDefaultString _b
instance IsString GenString where
fromString = GenString
diff -ur orig/tfp-1.0.2/src/Data/SizedInt.hs tfp-1.0.2/src/Data/SizedInt.hs
--- orig/tfp-1.0.2/src/Data/SizedInt.hs 2021-03-14 22:54:21.000000000 +0200
+++ tfp-1.0.2/src/Data/SizedInt.hs 2021-10-28 00:12:20.513846751 +0300
@@ -32,7 +32,6 @@
instance Num.Natural nT => Eq (SizedInt nT) where
(SizedInt x) == (SizedInt y) = x == y
- (SizedInt x) /= (SizedInt y) = x /= y
instance Num.Natural nT => Show (SizedInt nT) where
showsPrec prec n =
diff -ur orig/tfp-1.0.2/src/Data/SizedWord.hs tfp-1.0.2/src/Data/SizedWord.hs
--- orig/tfp-1.0.2/src/Data/SizedWord.hs 2021-03-14 22:54:21.000000000 +0200
+++ tfp-1.0.2/src/Data/SizedWord.hs 2021-10-28 00:12:11.385942969 +0300
@@ -23,7 +23,6 @@
instance Num.Natural nT => Eq (SizedWord nT) where
(SizedWord x) == (SizedWord y) = x == y
- (SizedWord x) /= (SizedWord y) = x /= y
instance Num.Natural nT => Show (SizedWord nT) where
showsPrec prec n =
diff -ur orig/type-level-natural-number-2.0/TypeLevel/NaturalNumber.hs type-level-natural-number-2.0/TypeLevel/NaturalNumber.hs
--- orig/type-level-natural-number-2.0/TypeLevel/NaturalNumber.hs 2014-03-30 21:38:29.000000000 +0300
+++ type-level-natural-number-2.0/TypeLevel/NaturalNumber.hs 2021-10-27 20:37:08.483818384 +0300
@@ -90,10 +90,9 @@
instance Eq Zero where
(==) _ _ = True
- (/=) _ _ = False
+
instance NaturalNumber n => Eq (SuccessorTo n) where
(==) _ _ = True
- (/=) _ _ = False
instance Ord Zero where
compare _ _ = EQ
diff -ur orig/type-natural-1.1.0.0/src/Data/Type/Natural.hs type-natural-1.1.0.0/src/Data/Type/Natural.hs
--- orig/type-natural-1.1.0.0/src/Data/Type/Natural.hs 2021-01-17 18:06:18.000000000 +0200
+++ type-natural-1.1.0.0/src/Data/Type/Natural.hs 2021-10-28 00:11:33.246345695 +0300
@@ -150,7 +150,6 @@
instance Eq SomeSNat where
SomeSNat (SNat n) == SomeSNat (SNat m) = n == m
- SomeSNat (SNat n) /= SomeSNat (SNat m) = n /= m
toSomeSNat :: Natural -> SomeSNat
toSomeSNat n = case someNatVal n of
diff -ur orig/unboxing-vector-0.2.0.0/src/Data/Vector/Unboxing/Internal.hs unboxing-vector-0.2.0.0/src/Data/Vector/Unboxing/Internal.hs
--- orig/unboxing-vector-0.2.0.0/src/Data/Vector/Unboxing/Internal.hs 2020-09-27 08:42:40.000000000 +0300
+++ unboxing-vector-0.2.0.0/src/Data/Vector/Unboxing/Internal.hs 2021-10-28 00:11:08.814604314 +0300
@@ -260,9 +260,7 @@
instance (Eq a, Unboxable a) => Eq (Vector a) where
xs == ys = Bundle.eq (G.stream xs) (G.stream ys)
- xs /= ys = not (Bundle.eq (G.stream xs) (G.stream ys))
{-# INLINE (==) #-}
- {-# INLINE (/=) #-}
instance (Ord a, Unboxable a) => Ord (Vector a) where
compare xs ys = Bundle.cmp (G.stream xs) (G.stream ys)
diff -ur orig/uncertain-0.3.1.0/src/Numeric/Uncertain.hs uncertain-0.3.1.0/src/Numeric/Uncertain.hs
--- orig/uncertain-0.3.1.0/src/Numeric/Uncertain.hs 2016-05-22 12:16:52.000000000 +0300
+++ uncertain-0.3.1.0/src/Numeric/Uncertain.hs 2021-10-28 00:10:46.466841337 +0300
@@ -548,8 +548,6 @@
instance Eq a => Eq (Uncert a) where
(==) = (==) `on` uMean
{-# INLINE (==) #-}
- (/=) = (/=) `on` uMean
- {-# INLINE (/=) #-}
instance Ord a => Ord (Uncert a) where
compare = comparing uMean
diff -ur orig/unification-fd-0.11.1/src/Data/Functor/Fixedpoint.hs unification-fd-0.11.1/src/Data/Functor/Fixedpoint.hs
--- orig/unification-fd-0.11.1/src/Data/Functor/Fixedpoint.hs 2001-09-09 04:46:40.000000000 +0300
+++ unification-fd-0.11.1/src/Data/Functor/Fixedpoint.hs 2021-10-27 21:18:17.848381597 +0300
@@ -103,12 +103,10 @@
instance (Eq (f (Fix f))) => Eq (Fix f) where
Fix x == Fix y = x == y
- Fix x /= Fix y = x /= y
-- BUGFIX: Inlining causes a code explosion on GHC 8.0.1 and 8.0.2, but
-- will be fixed in 8.0.3. <https://ghc.haskell.org/trac/ghc/ticket/13081>
#if __GLASGOW_HASKELL__ == 800
{-# NOINLINE (==) #-}
- {-# NOINLINE (/=) #-}
#endif
instance (Ord (f (Fix f))) => Ord (Fix f) where
diff -ur orig/vector-0.12.3.0/Data/Vector/Primitive.hs vector-0.12.3.0/Data/Vector/Primitive.hs
--- orig/vector-0.12.3.0/Data/Vector/Primitive.hs 2021-04-04 17:15:20.000000000 +0300
+++ vector-0.12.3.0/Data/Vector/Primitive.hs 2021-10-27 22:28:45.331784762 +0300
@@ -258,9 +258,6 @@
{-# INLINE (==) #-}
xs == ys = Bundle.eq (G.stream xs) (G.stream ys)
- {-# INLINE (/=) #-}
- xs /= ys = not (Bundle.eq (G.stream xs) (G.stream ys))
-
-- See http://trac.haskell.org/vector/ticket/12
instance (Prim a, Ord a) => Ord (Vector a) where
{-# INLINE compare #-}
diff -ur orig/vector-0.12.3.0/Data/Vector/Storable.hs vector-0.12.3.0/Data/Vector/Storable.hs
--- orig/vector-0.12.3.0/Data/Vector/Storable.hs 2021-04-04 17:15:20.000000000 +0300
+++ vector-0.12.3.0/Data/Vector/Storable.hs 2021-10-27 22:29:08.443512440 +0300
@@ -273,9 +273,6 @@
{-# INLINE (==) #-}
xs == ys = Bundle.eq (G.stream xs) (G.stream ys)
- {-# INLINE (/=) #-}
- xs /= ys = not (Bundle.eq (G.stream xs) (G.stream ys))
-
-- See http://trac.haskell.org/vector/ticket/12
instance (Storable a, Ord a) => Ord (Vector a) where
{-# INLINE compare #-}
diff -ur orig/vector-0.12.3.0/Data/Vector/Unboxed.hs vector-0.12.3.0/Data/Vector/Unboxed.hs
--- orig/vector-0.12.3.0/Data/Vector/Unboxed.hs 2021-04-04 17:15:20.000000000 +0300
+++ vector-0.12.3.0/Data/Vector/Unboxed.hs 2021-10-27 22:29:39.283149578 +0300
@@ -217,9 +217,6 @@
{-# INLINE (==) #-}
xs == ys = Bundle.eq (G.stream xs) (G.stream ys)
- {-# INLINE (/=) #-}
- xs /= ys = not (Bundle.eq (G.stream xs) (G.stream ys))
-
-- See http://trac.haskell.org/vector/ticket/12
instance (Unbox a, Ord a) => Ord (Vector a) where
{-# INLINE compare #-}
diff -ur orig/vector-0.12.3.0/Data/Vector.hs vector-0.12.3.0/Data/Vector.hs
--- orig/vector-0.12.3.0/Data/Vector.hs 2021-04-04 17:15:20.000000000 +0300
+++ vector-0.12.3.0/Data/Vector.hs 2021-10-27 22:23:22.155637651 +0300
@@ -311,9 +311,6 @@
{-# INLINE (==) #-}
xs == ys = Bundle.eq (G.stream xs) (G.stream ys)
- {-# INLINE (/=) #-}
- xs /= ys = not (Bundle.eq (G.stream xs) (G.stream ys))
-
-- See http://trac.haskell.org/vector/ticket/12
instance Ord a => Ord (Vector a) where
{-# INLINE compare #-}
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment