{-# LANGUAGE UnicodeSyntax, RankNTypes, QuantifiedConstraints, UndecidableInstances, CPP #-}
module Data.Equality.Utils where
#if MIN_VERSION_base(4,20,0)
#else
import Data.Foldable
#endif
import Data.Bits
newtype Fix f = Fix { forall (f :: * -> *). Fix f -> f (Fix f)
unFix :: f (Fix f) }
instance (∀ a. Eq a => Eq (f a)) => Eq (Fix f) where
== :: Fix f -> Fix f -> Bool
(==) (Fix f (Fix f)
a) (Fix f (Fix f)
b) = f (Fix f)
a f (Fix f) -> f (Fix f) -> Bool
forall a. Eq a => a -> a -> Bool
== f (Fix f)
b
{-# INLINE (==) #-}
instance (∀ a. Show a => Show (f a)) => Show (Fix f) where
showsPrec :: Int -> Fix f -> ShowS
showsPrec Int
d (Fix f (Fix f)
f) = Int -> f (Fix f) -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec Int
d f (Fix f)
f
{-# INLINE showsPrec #-}
cata :: Functor f => (f a -> a) -> (Fix f -> a)
cata :: forall (f :: * -> *) a. Functor f => (f a -> a) -> Fix f -> a
cata f a -> a
f = f a -> a
f (f a -> a) -> (Fix f -> f a) -> Fix f -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Fix f -> a) -> f (Fix f) -> f a
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((f a -> a) -> Fix f -> a
forall (f :: * -> *) a. Functor f => (f a -> a) -> Fix f -> a
cata f a -> a
f) (f (Fix f) -> f a) -> (Fix f -> f (Fix f)) -> Fix f -> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fix f -> f (Fix f)
forall (f :: * -> *). Fix f -> f (Fix f)
unFix
{-# INLINE cata #-}
hashString :: String -> Int
hashString :: String -> Int
hashString = (Int -> Char -> Int) -> Int -> String -> Int
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (\Int
h Char
c -> Int
33Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
h Int -> Int -> Int
forall a. Bits a => a -> a -> a
`xor` Char -> Int
forall a. Enum a => a -> Int
fromEnum Char
c) Int
5381
{-# INLINE hashString #-}