1- {-# LANGUAGE BangPatterns #-}
2- {-# LANGUAGE CApiFFI #-}
3- {-# LANGUAGE CPP #-}
4- {-# LANGUAGE DefaultSignatures #-}
5- {-# LANGUAGE FlexibleContexts #-}
6- {-# LANGUAGE MagicHash #-}
7- {-# LANGUAGE MultiParamTypeClasses #-}
8- {-# LANGUAGE PackageImports #-}
9- {-# LANGUAGE PolyKinds #-}
10- {-# LANGUAGE ScopedTypeVariables #-}
11- {-# LANGUAGE Trustworthy #-}
12- {-# LANGUAGE TypeFamilies #-}
13- {-# LANGUAGE UnliftedFFITypes #-}
1+ {-# LANGUAGE BangPatterns #-}
2+ {-# LANGUAGE CApiFFI #-}
3+ {-# LANGUAGE CPP #-}
4+ {-# LANGUAGE DefaultSignatures #-}
5+ {-# LANGUAGE DerivingStrategies #-}
6+ {-# LANGUAGE FlexibleContexts #-}
7+ {-# LANGUAGE GeneralizedNewtypeDeriving #-}
8+ {-# LANGUAGE MagicHash #-}
9+ {-# LANGUAGE MultiParamTypeClasses #-}
10+ {-# LANGUAGE PackageImports #-}
11+ {-# LANGUAGE PolyKinds #-}
12+ {-# LANGUAGE ScopedTypeVariables #-}
13+ {-# LANGUAGE StandaloneDeriving #-}
14+ {-# LANGUAGE StandaloneDeriving #-}
15+ {-# LANGUAGE Trustworthy #-}
16+ {-# LANGUAGE TypeFamilies #-}
17+ {-# LANGUAGE UnliftedFFITypes #-}
1418
1519{-# OPTIONS_GHC -fno-warn-deprecations #-}
1620
@@ -652,33 +656,19 @@ instance Hashable BSI.ShortByteString where
652656
653657#if HAS_OS_STRING_filepath || HAS_OS_STRING_os_string
654658-- | @since 1.4.2.0
655- instance Hashable PosixString where
656- hash (PosixString s) = hash s
657- hashWithSalt salt (PosixString s) = hashWithSalt salt s
659+ deriving newtype instance Hashable PosixString
658660
659661-- | @since 1.4.2.0
660- instance Hashable WindowsString where
661- hash (WindowsString s) = hash s
662- hashWithSalt salt (WindowsString s) = hashWithSalt salt s
662+ deriving newtype instance Hashable WindowsString
663663
664664-- | @since 1.4.2.0
665- instance Hashable OsString where
666- hash (OsString s) = hash s
667- hashWithSalt salt (OsString s) = hashWithSalt salt s
665+ deriving newtype instance Hashable OsString
668666#endif
669667
670668#if HAS_OS_STRING_filepath && HAS_OS_STRING_os_string
671- instance Hashable FP. PosixString where
672- hash (FP. PosixString s) = hash s
673- hashWithSalt salt (FP. PosixString s) = hashWithSalt salt s
674- 675- instance Hashable FP. WindowsString where
676- hash (FP. WindowsString s) = hash s
677- hashWithSalt salt (FP. WindowsString s) = hashWithSalt salt s
678- 679- instance Hashable FP. OsString where
680- hash (FP. OsString s) = hash s
681- hashWithSalt salt (FP. OsString s) = hashWithSalt salt s
669+ deriving newtype instance Hashable FP. PosixString
670+ deriving newtype instance Hashable FP. WindowsString
671+ deriving newtype instance Hashable FP. OsString
682672#endif
683673
684674#if MIN_VERSION_text(2,0,0)
@@ -811,17 +801,14 @@ instance Hashable Version where
811801 hashWithSalt salt (Version branch tags) =
812802 salt `hashWithSalt` branch `hashWithSalt` tags
813803
814- instance Hashable (Fixed a ) where
815- hashWithSalt salt (MkFixed i) = hashWithSalt salt i
804+ deriving newtype instance Hashable (Fixed a )
816805
817- instance Hashable a => Hashable (Identity a ) where
818- hashWithSalt = hashWithSalt1
806+ deriving newtype instance Hashable a => Hashable (Identity a )
819807instance Hashable1 Identity where
820808 liftHashWithSalt h salt (Identity x) = h salt x
821809
822810-- Using hashWithSalt1 would cause needless constraint
823- instance Hashable a => Hashable (Const a b ) where
824- hashWithSalt salt (Const x) = hashWithSalt salt x
811+ deriving newtype instance Hashable a => Hashable (Const a b )
825812
826813instance Hashable a => Hashable1 (Const a ) where
827814 liftHashWithSalt = defaultLiftHashWithSalt
@@ -843,34 +830,21 @@ instance Hashable a => Hashable (NE.NonEmpty a) where
843830instance Hashable1 NE. NonEmpty where
844831 liftHashWithSalt h salt (a NE. :| as) = liftHashWithSalt h (h salt a) as
845832
846- instance Hashable a => Hashable (Semi. Min a ) where
847- hashWithSalt p (Semi. Min a) = hashWithSalt p a
848- 849- instance Hashable a => Hashable (Semi. Max a ) where
850- hashWithSalt p (Semi. Max a) = hashWithSalt p a
833+ deriving newtype instance Hashable a => Hashable (Semi. Min a )
834+ deriving newtype instance Hashable a => Hashable (Semi. Max a )
851835
852836-- | __Note__: Prior to @hashable-1.3.0.0@ the hash computation included the second argument of 'Arg' which wasn't consistent with its 'Eq' instance.
853837--
854838-- @since 1.3.0.0
855839instance Hashable a => Hashable (Semi. Arg a b ) where
856840 hashWithSalt p (Semi. Arg a _) = hashWithSalt p a
857841
858- instance Hashable a => Hashable (Semi. First a ) where
859- hashWithSalt p (Semi. First a) = hashWithSalt p a
860- 861- 862- instance Hashable a => Hashable (Semi. Last a ) where
863- hashWithSalt p (Semi. Last a) = hashWithSalt p a
864- 865- 866- instance Hashable a => Hashable (Semi. WrappedMonoid a ) where
867- hashWithSalt p (Semi. WrapMonoid a) = hashWithSalt p a
868- 842+ deriving newtype instance Hashable a => Hashable (Semi. First a )
843+ deriving newtype instance Hashable a => Hashable (Semi. Last a )
844+ deriving newtype instance Hashable a => Hashable (Semi. WrappedMonoid a )
869845
870846#if !MIN_VERSION_base(4,16,0)
871- instance Hashable a => Hashable (Semi. Option a ) where
872- hashWithSalt p (Semi. Option a) = hashWithSalt p a
873- 847+ deriving newtype instance Hashable a => Hashable (Semi. Option a )
874848#endif
875849
876850-- TODO: this instance is removed as there isn't Eq1 Min/Max, ...
0 commit comments