{-# LANGUAGE TypeFamilies #-} module HaskellWorks.Data.Unsign ( Unsign(..) ) where import Data.Int import Data.Word class Unsign a where type UnsignOf a unsign :: a -> UnsignOf a instance Unsign Int where type UnsignOf Int = Word unsign :: Int -> UnsignOf Int unsign = Int -> UnsignOf Int forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Int8 where type UnsignOf Int8 = Word8 unsign :: Int8 -> UnsignOf Int8 unsign = Int8 -> UnsignOf Int8 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Int16 where type UnsignOf Int16 = Word16 unsign :: Int16 -> UnsignOf Int16 unsign = Int16 -> UnsignOf Int16 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Int32 where type UnsignOf Int32 = Word32 unsign :: Int32 -> UnsignOf Int32 unsign = Int32 -> UnsignOf Int32 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Int64 where type UnsignOf Int64 = Word64 unsign :: Int64 -> UnsignOf Int64 unsign = Int64 -> UnsignOf Int64 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Word where type UnsignOf Word = Word unsign :: Word -> UnsignOf Word unsign = Word -> UnsignOf Word forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Word8 where type UnsignOf Word8 = Word8 unsign :: Word8 -> UnsignOf Word8 unsign = Word8 -> UnsignOf Word8 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Word16 where type UnsignOf Word16 = Word16 unsign :: Word16 -> UnsignOf Word16 unsign = Word16 -> UnsignOf Word16 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Word32 where type UnsignOf Word32 = Word32 unsign :: Word32 -> UnsignOf Word32 unsign = Word32 -> UnsignOf Word32 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-} instance Unsign Word64 where type UnsignOf Word64 = Word64 unsign :: Word64 -> UnsignOf Word64 unsign = Word64 -> UnsignOf Word64 forall a b. (Integral a, Num b) => a -> b fromIntegral {-# INLINE unsign #-}