Skip to content

Commit

Permalink
Change to hashable-1.2.5.0 from hashable-extras
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Mar 29, 2017
1 parent ecdf139 commit 874051c
Show file tree
Hide file tree
Showing 5 changed files with 26 additions and 20 deletions.
3 changes: 1 addition & 2 deletions bound.cabal
Expand Up @@ -80,8 +80,7 @@ library
bytes >= 0.4 && < 1,
cereal >= 0.3.5.2 && < 0.6,
comonad >= 3 && < 6,
hashable >= 1.1 && < 1.3,
hashable-extras >= 0.1 && < 1,
hashable >= 1.2.5.0 && < 1.3,
profunctors >= 3.3 && < 6,
template-haskell >= 2.7 && < 3,
transformers >= 0.2 && < 0.6,
Expand Down
12 changes: 6 additions & 6 deletions src/Bound/Name.hs
Expand Up @@ -66,8 +66,8 @@ import Data.Data
import GHC.Generics
# endif
#endif
import Data.Hashable
import Data.Hashable.Extras
import Data.Hashable (Hashable(..))
import Data.Hashable.Lifted (Hashable1(..), Hashable2(..))
import Data.Profunctor
import qualified Data.Serialize as Serialize
import Data.Serialize (Serialize)
Expand Down Expand Up @@ -118,12 +118,12 @@ instance Eq b => Eq (Name n b) where
{-# INLINE (==) #-}

instance Hashable2 Name where
hashWithSalt2 m (Name _ a) = hashWithSalt m a
{-# INLINE hashWithSalt2 #-}
liftHashWithSalt2 _ h s (Name _ a) = h s a
{-# INLINE liftHashWithSalt2 #-}

instance Hashable1 (Name n) where
hashWithSalt1 m (Name _ a) = hashWithSalt m a
{-# INLINE hashWithSalt1 #-}
liftHashWithSalt h s (Name _ a) = h s a
{-# INLINE liftHashWithSalt #-}

instance Hashable a => Hashable (Name n a) where
hashWithSalt m (Name _ a) = hashWithSalt m a
Expand Down
10 changes: 6 additions & 4 deletions src/Bound/Scope.hs
Expand Up @@ -81,8 +81,8 @@ import Data.Bytes.Put
import Data.Bytes.Serial
import Data.Foldable
import Data.Functor.Classes
import Data.Hashable
import Data.Hashable.Extras
import Data.Hashable (Hashable (..))
import Data.Hashable.Lifted (Hashable1(..), hashWithSalt1)
import Data.Monoid
import qualified Data.Serialize as Serialize
import Data.Serialize (Serialize)
Expand Down Expand Up @@ -220,9 +220,11 @@ instance Bound (Scope b) where
Scope m >>>= f = Scope (liftM (fmap (>>= f)) m)
{-# INLINE (>>>=) #-}

-- {-# INLINE hashWithSalt1 #-}

instance (Hashable b, Monad f, Hashable1 f) => Hashable1 (Scope b f) where
hashWithSalt1 n m = hashWithSalt1 n (fromScope m)
{-# INLINE hashWithSalt1 #-}
liftHashWithSalt h s m = liftHashWithSalt (liftHashWithSalt h) s (fromScope m)
{-# INLINE liftHashWithSalt #-}

instance (Hashable b, Monad f, Hashable1 f, Hashable a) => Hashable (Scope b f a) where
hashWithSalt n m = hashWithSalt1 n (fromScope m)
Expand Down
8 changes: 4 additions & 4 deletions src/Bound/Scope/Simple.hs
Expand Up @@ -80,8 +80,8 @@ import Data.Bytes.Serial
import Data.Data
import Data.Foldable
import Data.Functor.Classes
import Data.Hashable
import Data.Hashable.Extras
import Data.Hashable (Hashable(..))
import Data.Hashable.Lifted (Hashable1(..), hashWithSalt1)
import Data.Monoid
import qualified Data.Serialize as Serialize
import Data.Serialize (Serialize)
Expand Down Expand Up @@ -220,8 +220,8 @@ instance Bound (Scope b) where
{-# INLINE (>>>=) #-}

instance (Hashable b, Hashable1 f) => Hashable1 (Scope b f) where
hashWithSalt1 n m = hashWithSalt1 n (unscope m)
{-# INLINE hashWithSalt1 #-}
liftHashWithSalt h n m = liftHashWithSalt (liftHashWithSalt h) n (unscope m)
{-# INLINE liftHashWithSalt #-}

instance (Hashable b, Hashable1 f, Hashable a) => Hashable (Scope b f a) where
hashWithSalt n m = hashWithSalt1 n (unscope m)
Expand Down
13 changes: 9 additions & 4 deletions src/Bound/Var.hs
Expand Up @@ -38,8 +38,8 @@ import Data.Foldable
import Data.Traversable
import Data.Monoid (Monoid(..))
#endif
import Data.Hashable
import Data.Hashable.Extras
import Data.Hashable (Hashable(..))
import Data.Hashable.Lifted (Hashable1(..), Hashable2(..))
import Data.Bifunctor
import Data.Bifoldable
import qualified Data.Binary as Binary
Expand Down Expand Up @@ -92,8 +92,13 @@ data Var b a
distinguisher :: Int
distinguisher = fromIntegral $ (maxBound :: Word) `quot` 3

instance Hashable2 Var
instance Hashable b => Hashable1 (Var b)
instance Hashable2 Var where
liftHashWithSalt2 h _ s (B b) = h s b
liftHashWithSalt2 _ h s (F a) = h s a `hashWithSalt` distinguisher
{-# INLINE liftHashWithSalt2 #-}
instance Hashable b => Hashable1 (Var b) where
liftHashWithSalt = liftHashWithSalt2 hashWithSalt
{-# INLINE liftHashWithSalt #-}
instance (Hashable b, Hashable a) => Hashable (Var b a) where
hashWithSalt s (B b) = hashWithSalt s b
hashWithSalt s (F a) = hashWithSalt s a `hashWithSalt` distinguisher
Expand Down

0 comments on commit 874051c

Please sign in to comment.