module Codec.Borsh.Internal.Util.BitwiseCast (BitwiseCast(..)) where
import Data.Int
import Data.WideWord.Int128
import Data.WideWord.Word128
import Data.Word
import GHC.Float
class BitwiseCast a b where
castBits :: a -> b
instance BitwiseCast Float Word32 where castBits :: Float -> Word32
castBits = Float -> Word32
castFloatToWord32
instance BitwiseCast Double Word64 where castBits :: Double -> Word64
castBits = Double -> Word64
castDoubleToWord64
instance BitwiseCast Word32 Float where castBits :: Word32 -> Float
castBits = Word32 -> Float
castWord32ToFloat
instance BitwiseCast Word64 Double where castBits :: Word64 -> Double
castBits = Word64 -> Double
castWord64ToDouble
instance BitwiseCast Word8 Int8 where castBits :: Word8 -> Int8
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Word16 Int16 where castBits :: Word16 -> Int16
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Word32 Int32 where castBits :: Word32 -> Int32
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Word64 Int64 where castBits :: Word64 -> Int64
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Word128 Int128 where castBits :: Word128 -> Int128
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Int8 Word8 where castBits :: Int8 -> Word8
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Int16 Word16 where castBits :: Int16 -> Word16
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Int32 Word32 where castBits :: Int32 -> Word32
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Int64 Word64 where castBits :: Int64 -> Word64
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral
instance BitwiseCast Int128 Word128 where castBits :: Int128 -> Word128
castBits = forall a b. (Integral a, Num b) => a -> b
fromIntegral