{-# LANGUAGE GADTs #-}
module What4.Utils.OnlyIntRepr
( OnlyIntRepr(..)
, toBaseTypeRepr
) where
import Data.Hashable (Hashable(..))
import Data.Parameterized.Classes (HashableF(..))
import What4.BaseTypes
data OnlyIntRepr tp
= (tp ~ BaseIntegerType) => OnlyIntRepr
instance TestEquality OnlyIntRepr where
testEquality :: OnlyIntRepr a -> OnlyIntRepr b -> Maybe (a :~: b)
testEquality OnlyIntRepr a
OnlyIntRepr OnlyIntRepr b
OnlyIntRepr = (a :~: a) -> Maybe (a :~: a)
forall a. a -> Maybe a
Just a :~: a
forall k (a :: k). a :~: a
Refl
instance Hashable (OnlyIntRepr tp) where
hashWithSalt :: Int -> OnlyIntRepr tp -> Int
hashWithSalt Int
s OnlyIntRepr tp
OnlyIntRepr = Int
s
instance HashableF OnlyIntRepr where
hashWithSaltF :: Int -> OnlyIntRepr tp -> Int
hashWithSaltF = Int -> OnlyIntRepr tp -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt
toBaseTypeRepr :: OnlyIntRepr tp -> BaseTypeRepr tp
toBaseTypeRepr :: OnlyIntRepr tp -> BaseTypeRepr tp
toBaseTypeRepr OnlyIntRepr tp
OnlyIntRepr = BaseTypeRepr tp
BaseTypeRepr BaseIntegerType
BaseIntegerRepr