binrep-0.3.0: Encode precise binary representations directly in types
Safe HaskellSafe-Inferred
LanguageHaskell2010

Binrep.Type.Int

Synopsis

Documentation

newtype I (sign :: ISign) (size :: ISize) (e :: Endianness) Source #

Wrapper type grouping machine integers (sign, size) along with an explicit endianness.

The internal representation is selected via a type family to correspond to the relevant Haskell data type, so common overflow behaviour should match. We derive lots of handy instances, so you may perform regular arithmetic on pairs of these types. For example:

>>> 255 + 1 :: I 'U 'I1 e
0
>>> 255 + 1 :: I 'U 'I2 e
256

Constructors

I 

Fields

Instances

Instances details
FromJSON (IRep sign size) => FromJSON (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

parseJSON :: Value -> Parser (I sign size e) #

parseJSONList :: Value -> Parser [I sign size e] #

ToJSON (IRep sign size) => ToJSON (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

toJSON :: I sign size e -> Value #

toEncoding :: I sign size e -> Encoding #

toJSONList :: [I sign size e] -> Value #

toEncodingList :: [I sign size e] -> Encoding #

(Data (IRep sign size), Typeable sign, Typeable size, Typeable e) => Data (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> I sign size e -> c (I sign size e) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (I sign size e) #

toConstr :: I sign size e -> Constr #

dataTypeOf :: I sign size e -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (I sign size e)) #

dataCast2 :: Typeable t => (forall d e0. (Data d, Data e0) => c (t d e0)) -> Maybe (c (I sign size e)) #

gmapT :: (forall b. Data b => b -> b) -> I sign size e -> I sign size e #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> I sign size e -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> I sign size e -> r #

gmapQ :: (forall d. Data d => d -> u) -> I sign size e -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> I sign size e -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> I sign size e -> m (I sign size e) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> I sign size e -> m (I sign size e) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> I sign size e -> m (I sign size e) #

Bounded (IRep sign size) => Bounded (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

minBound :: I sign size e #

maxBound :: I sign size e #

Enum (IRep sign size) => Enum (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

succ :: I sign size e -> I sign size e #

pred :: I sign size e -> I sign size e #

toEnum :: Int -> I sign size e #

fromEnum :: I sign size e -> Int #

enumFrom :: I sign size e -> [I sign size e] #

enumFromThen :: I sign size e -> I sign size e -> [I sign size e] #

enumFromTo :: I sign size e -> I sign size e -> [I sign size e] #

enumFromThenTo :: I sign size e -> I sign size e -> I sign size e -> [I sign size e] #

Generic (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Associated Types

type Rep (I sign size e) :: Type -> Type #

Methods

from :: I sign size e -> Rep (I sign size e) x #

to :: Rep (I sign size e) x -> I sign size e #

Num (IRep sign size) => Num (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

(+) :: I sign size e -> I sign size e -> I sign size e #

(-) :: I sign size e -> I sign size e -> I sign size e #

(*) :: I sign size e -> I sign size e -> I sign size e #

negate :: I sign size e -> I sign size e #

abs :: I sign size e -> I sign size e #

signum :: I sign size e -> I sign size e #

fromInteger :: Integer -> I sign size e #

Integral (IRep sign size) => Integral (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

quot :: I sign size e -> I sign size e -> I sign size e #

rem :: I sign size e -> I sign size e -> I sign size e #

div :: I sign size e -> I sign size e -> I sign size e #

mod :: I sign size e -> I sign size e -> I sign size e #

quotRem :: I sign size e -> I sign size e -> (I sign size e, I sign size e) #

divMod :: I sign size e -> I sign size e -> (I sign size e, I sign size e) #

toInteger :: I sign size e -> Integer #

Real (IRep sign size) => Real (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

toRational :: I sign size e -> Rational #

Show (IRep sign size) => Show (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

showsPrec :: Int -> I sign size e -> ShowS #

show :: I sign size e -> String #

showList :: [I sign size e] -> ShowS #

KnownNat (CBLen (I sign size end)) => BLen (I sign size end) Source # 
Instance details

Defined in Binrep.Type.Int

Associated Types

type CBLen (I sign size end) :: Natural Source #

Methods

blen :: I sign size end -> BLenT Source #

Get (I 'S 'I1 e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I1 e) Source #

Get (I 'S 'I2 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I2 'BE) Source #

Get (I 'S 'I2 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I2 'LE) Source #

Get (I 'S 'I4 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I4 'BE) Source #

Get (I 'S 'I4 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I4 'LE) Source #

Get (I 'S 'I8 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I8 'BE) Source #

Get (I 'S 'I8 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'S 'I8 'LE) Source #

Get (I 'U 'I1 e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I1 e) Source #

Get (I 'U 'I2 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I2 'BE) Source #

Get (I 'U 'I2 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I2 'LE) Source #

Get (I 'U 'I4 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I4 'BE) Source #

Get (I 'U 'I4 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I4 'LE) Source #

Get (I 'U 'I8 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I8 'BE) Source #

Get (I 'U 'I8 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

get :: Getter (I 'U 'I8 'LE) Source #

Put (I 'S 'I1 e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I1 e -> Builder Source #

Put (I 'S 'I2 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I2 'BE -> Builder Source #

Put (I 'S 'I2 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I2 'LE -> Builder Source #

Put (I 'S 'I4 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I4 'BE -> Builder Source #

Put (I 'S 'I4 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I4 'LE -> Builder Source #

Put (I 'S 'I8 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I8 'BE -> Builder Source #

Put (I 'S 'I8 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'S 'I8 'LE -> Builder Source #

Put (I 'U 'I1 e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I1 e -> Builder Source #

Put (I 'U 'I2 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I2 'BE -> Builder Source #

Put (I 'U 'I2 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I2 'LE -> Builder Source #

Put (I 'U 'I4 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I4 'BE -> Builder Source #

Put (I 'U 'I4 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I4 'LE -> Builder Source #

Put (I 'U 'I8 'BE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I8 'BE -> Builder Source #

Put (I 'U 'I8 'LE) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

put :: I 'U 'I8 'LE -> Builder Source #

Eq (IRep sign size) => Eq (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

(==) :: I sign size e -> I sign size e -> Bool #

(/=) :: I sign size e -> I sign size e -> Bool #

Ord (IRep sign size) => Ord (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

compare :: I sign size e -> I sign size e -> Ordering #

(<) :: I sign size e -> I sign size e -> Bool #

(<=) :: I sign size e -> I sign size e -> Bool #

(>) :: I sign size e -> I sign size e -> Bool #

(>=) :: I sign size e -> I sign size e -> Bool #

max :: I sign size e -> I sign size e -> I sign size e #

min :: I sign size e -> I sign size e -> I sign size e #

(irep ~ IRep 'S size, Integral irep, Bounded irep, Show irep, Typeable size, Typeable end) => Strengthen (I 'S size end) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

strengthen :: Weak (I 'S size end) -> Validation (NonEmpty StrengthenFail) (I 'S size end) #

(irep ~ IRep 'U size, Integral irep, Bounded irep, Show irep, Typeable size, Typeable end) => Strengthen (I 'U size end) Source # 
Instance details

Defined in Binrep.Type.Int

Methods

strengthen :: Weak (I 'U size end) -> Validation (NonEmpty StrengthenFail) (I 'U size end) #

(irep ~ IRep 'S size, Integral irep) => Weaken (I 'S size end) Source #

Signed machine integers can be idealized as integers.

Instance details

Defined in Binrep.Type.Int

Associated Types

type Weak (I 'S size end) #

Methods

weaken :: I 'S size end -> Weak (I 'S size end) #

(irep ~ IRep 'U size, Integral irep) => Weaken (I 'U size end) Source #

Unsigned machine integers can be idealized as naturals.

Instance details

Defined in Binrep.Type.Int

Associated Types

type Weak (I 'U size end) #

Methods

weaken :: I 'U size end -> Weak (I 'U size end) #

type Rep (I sign size e) Source # 
Instance details

Defined in Binrep.Type.Int

type Rep (I sign size e) = D1 ('MetaData "I" "Binrep.Type.Int" "binrep-0.3.0-inplace" 'True) (C1 ('MetaCons "I" 'PrefixI 'True) (S1 ('MetaSel ('Just "getI") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (IRep sign size))))
type CBLen (I sign size end) Source # 
Instance details

Defined in Binrep.Type.Int

type CBLen (I sign size end) = CBLen (IRep sign size)
type Weak (I 'S size end) Source # 
Instance details

Defined in Binrep.Type.Int

type Weak (I 'S size end) = Integer
type Weak (I 'U size end) Source # 
Instance details

Defined in Binrep.Type.Int

type Weak (I 'U size end) = Natural

data ISign Source #

Machine integer sign.

Constructors

S

signed

U

unsigned

Instances

Instances details
Data ISign Source # 
Instance details

Defined in Binrep.Type.Int

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ISign -> c ISign #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ISign #

toConstr :: ISign -> Constr #

dataTypeOf :: ISign -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ISign) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ISign) #

gmapT :: (forall b. Data b => b -> b) -> ISign -> ISign #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ISign -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ISign -> r #

gmapQ :: (forall d. Data d => d -> u) -> ISign -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ISign -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ISign -> m ISign #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ISign -> m ISign #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ISign -> m ISign #

Generic ISign Source # 
Instance details

Defined in Binrep.Type.Int

Associated Types

type Rep ISign :: Type -> Type #

Methods

from :: ISign -> Rep ISign x #

to :: Rep ISign x -> ISign #

Show ISign Source # 
Instance details

Defined in Binrep.Type.Int

Methods

showsPrec :: Int -> ISign -> ShowS #

show :: ISign -> String #

showList :: [ISign] -> ShowS #

Eq ISign Source # 
Instance details

Defined in Binrep.Type.Int

Methods

(==) :: ISign -> ISign -> Bool #

(/=) :: ISign -> ISign -> Bool #

type Rep ISign Source # 
Instance details

Defined in Binrep.Type.Int

type Rep ISign = D1 ('MetaData "ISign" "Binrep.Type.Int" "binrep-0.3.0-inplace" 'False) (C1 ('MetaCons "S" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "U" 'PrefixI 'False) (U1 :: Type -> Type))

data ISize Source #

Machine integer size in number of bytes.

Constructors

I1 
I2 
I4 
I8 

Instances

Instances details
Data ISize Source # 
Instance details

Defined in Binrep.Type.Int

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ISize -> c ISize #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ISize #

toConstr :: ISize -> Constr #

dataTypeOf :: ISize -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ISize) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ISize) #

gmapT :: (forall b. Data b => b -> b) -> ISize -> ISize #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ISize -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ISize -> r #

gmapQ :: (forall d. Data d => d -> u) -> ISize -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ISize -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ISize -> m ISize #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ISize -> m ISize #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ISize -> m ISize #

Generic ISize Source # 
Instance details

Defined in Binrep.Type.Int

Associated Types

type Rep ISize :: Type -> Type #

Methods

from :: ISize -> Rep ISize x #

to :: Rep ISize x -> ISize #

Show ISize Source # 
Instance details

Defined in Binrep.Type.Int

Methods

showsPrec :: Int -> ISize -> ShowS #

show :: ISize -> String #

showList :: [ISize] -> ShowS #

Eq ISize Source # 
Instance details

Defined in Binrep.Type.Int

Methods

(==) :: ISize -> ISize -> Bool #

(/=) :: ISize -> ISize -> Bool #

type Rep ISize Source # 
Instance details

Defined in Binrep.Type.Int

type Rep ISize = D1 ('MetaData "ISize" "Binrep.Type.Int" "binrep-0.3.0-inplace" 'False) ((C1 ('MetaCons "I1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "I2" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "I4" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "I8" 'PrefixI 'False) (U1 :: Type -> Type)))

type family IRep (sign :: ISign) (size :: ISize) where ... Source #

Grouping for matching a signedness and size to a Haskell integer data type.

Equations

IRep 'U 'I1 = Word8 
IRep 'S 'I1 = Int8 
IRep 'U 'I2 = Word16 
IRep 'S 'I2 = Int16 
IRep 'U 'I4 = Word32 
IRep 'S 'I4 = Int32 
IRep 'U 'I8 = Word64 
IRep 'S 'I8 = Int64 

type family IMax (sign :: ISign) (size :: ISize) :: Natural where ... Source #

Shortcut.

Equations

IMax sign size = MaxBound (IRep sign size) 

type family MaxBound w :: Natural where ... Source #

Restricted reflected version of maxBound.

Equations

MaxBound Word8 = 255 
MaxBound Int8 = 127 
MaxBound Word16 = 65535 
MaxBound Int16 = 32767 
MaxBound Word32 = 4294967295 
MaxBound Int32 = 2147483647 
MaxBound Word64 = 18446744073709551615 
MaxBound Int64 = 9223372036854775807