data-sword-0.1.1: Shorter binary words

Safe HaskellNone
LanguageHaskell2010

Data.ShortWord

Description

This module provides signed and unsigned binary word data types of sizes 2, 4, 7, 24, and 48 bits.

Documentation

data Word2 Source #

Instances

Bounded Word2 Source # 
Enum Word2 Source # 
Eq Word2 Source # 

Methods

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

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

Integral Word2 Source # 
Data Word2 Source # 

Methods

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

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

toConstr :: Word2 -> Constr #

dataTypeOf :: Word2 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word2 Source # 
Ord Word2 Source # 

Methods

compare :: Word2 -> Word2 -> Ordering #

(<) :: Word2 -> Word2 -> Bool #

(<=) :: Word2 -> Word2 -> Bool #

(>) :: Word2 -> Word2 -> Bool #

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

max :: Word2 -> Word2 -> Word2 #

min :: Word2 -> Word2 -> Word2 #

Read Word2 Source # 
Real Word2 Source # 

Methods

toRational :: Word2 -> Rational #

Show Word2 Source # 

Methods

showsPrec :: Int -> Word2 -> ShowS #

show :: Word2 -> String #

showList :: [Word2] -> ShowS #

Ix Word2 Source # 
Bits Word2 Source # 
FiniteBits Word2 Source # 
BinaryWord Word2 Source # 
Hashable Word2 Source # 

Methods

hashWithSalt :: Int -> Word2 -> Int #

hash :: Word2 -> Int #

type SignedWord Word2 Source # 
type UnsignedWord Word2 Source # 

data Word4 Source #

Instances

Bounded Word4 Source # 
Enum Word4 Source # 
Eq Word4 Source # 

Methods

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

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

Integral Word4 Source # 
Data Word4 Source # 

Methods

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

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

toConstr :: Word4 -> Constr #

dataTypeOf :: Word4 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word4 Source # 
Ord Word4 Source # 

Methods

compare :: Word4 -> Word4 -> Ordering #

(<) :: Word4 -> Word4 -> Bool #

(<=) :: Word4 -> Word4 -> Bool #

(>) :: Word4 -> Word4 -> Bool #

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

max :: Word4 -> Word4 -> Word4 #

min :: Word4 -> Word4 -> Word4 #

Read Word4 Source # 
Real Word4 Source # 

Methods

toRational :: Word4 -> Rational #

Show Word4 Source # 

Methods

showsPrec :: Int -> Word4 -> ShowS #

show :: Word4 -> String #

showList :: [Word4] -> ShowS #

Ix Word4 Source # 
Bits Word4 Source # 
FiniteBits Word4 Source # 
BinaryWord Word4 Source # 
Hashable Word4 Source # 

Methods

hashWithSalt :: Int -> Word4 -> Int #

hash :: Word4 -> Int #

type SignedWord Word4 Source # 
type UnsignedWord Word4 Source # 

data Word7 Source #

Instances

Bounded Word7 Source # 
Enum Word7 Source # 
Eq Word7 Source # 

Methods

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

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

Integral Word7 Source # 
Data Word7 Source # 

Methods

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

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

toConstr :: Word7 -> Constr #

dataTypeOf :: Word7 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word7 Source # 
Ord Word7 Source # 

Methods

compare :: Word7 -> Word7 -> Ordering #

(<) :: Word7 -> Word7 -> Bool #

(<=) :: Word7 -> Word7 -> Bool #

(>) :: Word7 -> Word7 -> Bool #

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

max :: Word7 -> Word7 -> Word7 #

min :: Word7 -> Word7 -> Word7 #

Read Word7 Source # 
Real Word7 Source # 

Methods

toRational :: Word7 -> Rational #

Show Word7 Source # 

Methods

showsPrec :: Int -> Word7 -> ShowS #

show :: Word7 -> String #

showList :: [Word7] -> ShowS #

Ix Word7 Source # 
Bits Word7 Source # 
FiniteBits Word7 Source # 
BinaryWord Word7 Source # 
Hashable Word7 Source # 

Methods

hashWithSalt :: Int -> Word7 -> Int #

hash :: Word7 -> Int #

type SignedWord Word7 Source # 
type UnsignedWord Word7 Source # 

data Word24 Source #

Instances

Bounded Word24 Source # 
Enum Word24 Source # 
Eq Word24 Source # 

Methods

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

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

Integral Word24 Source # 
Data Word24 Source # 

Methods

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

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

toConstr :: Word24 -> Constr #

dataTypeOf :: Word24 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word24 Source # 
Ord Word24 Source # 
Read Word24 Source # 
Real Word24 Source # 
Show Word24 Source # 
Ix Word24 Source # 
Bits Word24 Source # 
FiniteBits Word24 Source # 
BinaryWord Word24 Source # 
Hashable Word24 Source # 

Methods

hashWithSalt :: Int -> Word24 -> Int #

hash :: Word24 -> Int #

type SignedWord Word24 Source # 
type UnsignedWord Word24 Source # 

data Word48 Source #

Instances

Bounded Word48 Source # 
Enum Word48 Source # 
Eq Word48 Source # 

Methods

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

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

Integral Word48 Source # 
Data Word48 Source # 

Methods

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

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

toConstr :: Word48 -> Constr #

dataTypeOf :: Word48 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word48 Source # 
Ord Word48 Source # 
Read Word48 Source # 
Real Word48 Source # 
Show Word48 Source # 
Ix Word48 Source # 
Bits Word48 Source # 
FiniteBits Word48 Source # 
BinaryWord Word48 Source # 
Hashable Word48 Source # 

Methods

hashWithSalt :: Int -> Word48 -> Int #

hash :: Word48 -> Int #

type SignedWord Word48 Source # 
type UnsignedWord Word48 Source # 

data Int2 Source #

Instances

Bounded Int2 Source # 
Enum Int2 Source # 

Methods

succ :: Int2 -> Int2 #

pred :: Int2 -> Int2 #

toEnum :: Int -> Int2 #

fromEnum :: Int2 -> Int #

enumFrom :: Int2 -> [Int2] #

enumFromThen :: Int2 -> Int2 -> [Int2] #

enumFromTo :: Int2 -> Int2 -> [Int2] #

enumFromThenTo :: Int2 -> Int2 -> Int2 -> [Int2] #

Eq Int2 Source # 

Methods

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

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

Integral Int2 Source # 

Methods

quot :: Int2 -> Int2 -> Int2 #

rem :: Int2 -> Int2 -> Int2 #

div :: Int2 -> Int2 -> Int2 #

mod :: Int2 -> Int2 -> Int2 #

quotRem :: Int2 -> Int2 -> (Int2, Int2) #

divMod :: Int2 -> Int2 -> (Int2, Int2) #

toInteger :: Int2 -> Integer #

Data Int2 Source # 

Methods

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

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

toConstr :: Int2 -> Constr #

dataTypeOf :: Int2 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int2 Source # 

Methods

(+) :: Int2 -> Int2 -> Int2 #

(-) :: Int2 -> Int2 -> Int2 #

(*) :: Int2 -> Int2 -> Int2 #

negate :: Int2 -> Int2 #

abs :: Int2 -> Int2 #

signum :: Int2 -> Int2 #

fromInteger :: Integer -> Int2 #

Ord Int2 Source # 

Methods

compare :: Int2 -> Int2 -> Ordering #

(<) :: Int2 -> Int2 -> Bool #

(<=) :: Int2 -> Int2 -> Bool #

(>) :: Int2 -> Int2 -> Bool #

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

max :: Int2 -> Int2 -> Int2 #

min :: Int2 -> Int2 -> Int2 #

Read Int2 Source # 
Real Int2 Source # 

Methods

toRational :: Int2 -> Rational #

Show Int2 Source # 

Methods

showsPrec :: Int -> Int2 -> ShowS #

show :: Int2 -> String #

showList :: [Int2] -> ShowS #

Ix Int2 Source # 

Methods

range :: (Int2, Int2) -> [Int2] #

index :: (Int2, Int2) -> Int2 -> Int #

unsafeIndex :: (Int2, Int2) -> Int2 -> Int

inRange :: (Int2, Int2) -> Int2 -> Bool #

rangeSize :: (Int2, Int2) -> Int #

unsafeRangeSize :: (Int2, Int2) -> Int

Bits Int2 Source # 
FiniteBits Int2 Source # 
BinaryWord Int2 Source # 
Hashable Int2 Source # 

Methods

hashWithSalt :: Int -> Int2 -> Int #

hash :: Int2 -> Int #

type SignedWord Int2 Source # 
type UnsignedWord Int2 Source # 

data Int4 Source #

Instances

Bounded Int4 Source # 
Enum Int4 Source # 

Methods

succ :: Int4 -> Int4 #

pred :: Int4 -> Int4 #

toEnum :: Int -> Int4 #

fromEnum :: Int4 -> Int #

enumFrom :: Int4 -> [Int4] #

enumFromThen :: Int4 -> Int4 -> [Int4] #

enumFromTo :: Int4 -> Int4 -> [Int4] #

enumFromThenTo :: Int4 -> Int4 -> Int4 -> [Int4] #

Eq Int4 Source # 

Methods

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

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

Integral Int4 Source # 

Methods

quot :: Int4 -> Int4 -> Int4 #

rem :: Int4 -> Int4 -> Int4 #

div :: Int4 -> Int4 -> Int4 #

mod :: Int4 -> Int4 -> Int4 #

quotRem :: Int4 -> Int4 -> (Int4, Int4) #

divMod :: Int4 -> Int4 -> (Int4, Int4) #

toInteger :: Int4 -> Integer #

Data Int4 Source # 

Methods

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

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

toConstr :: Int4 -> Constr #

dataTypeOf :: Int4 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int4 Source # 

Methods

(+) :: Int4 -> Int4 -> Int4 #

(-) :: Int4 -> Int4 -> Int4 #

(*) :: Int4 -> Int4 -> Int4 #

negate :: Int4 -> Int4 #

abs :: Int4 -> Int4 #

signum :: Int4 -> Int4 #

fromInteger :: Integer -> Int4 #

Ord Int4 Source # 

Methods

compare :: Int4 -> Int4 -> Ordering #

(<) :: Int4 -> Int4 -> Bool #

(<=) :: Int4 -> Int4 -> Bool #

(>) :: Int4 -> Int4 -> Bool #

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

max :: Int4 -> Int4 -> Int4 #

min :: Int4 -> Int4 -> Int4 #

Read Int4 Source # 
Real Int4 Source # 

Methods

toRational :: Int4 -> Rational #

Show Int4 Source # 

Methods

showsPrec :: Int -> Int4 -> ShowS #

show :: Int4 -> String #

showList :: [Int4] -> ShowS #

Ix Int4 Source # 

Methods

range :: (Int4, Int4) -> [Int4] #

index :: (Int4, Int4) -> Int4 -> Int #

unsafeIndex :: (Int4, Int4) -> Int4 -> Int

inRange :: (Int4, Int4) -> Int4 -> Bool #

rangeSize :: (Int4, Int4) -> Int #

unsafeRangeSize :: (Int4, Int4) -> Int

Bits Int4 Source # 
FiniteBits Int4 Source # 
BinaryWord Int4 Source # 
Hashable Int4 Source # 

Methods

hashWithSalt :: Int -> Int4 -> Int #

hash :: Int4 -> Int #

type SignedWord Int4 Source # 
type UnsignedWord Int4 Source # 

data Int7 Source #

Instances

Bounded Int7 Source # 
Enum Int7 Source # 

Methods

succ :: Int7 -> Int7 #

pred :: Int7 -> Int7 #

toEnum :: Int -> Int7 #

fromEnum :: Int7 -> Int #

enumFrom :: Int7 -> [Int7] #

enumFromThen :: Int7 -> Int7 -> [Int7] #

enumFromTo :: Int7 -> Int7 -> [Int7] #

enumFromThenTo :: Int7 -> Int7 -> Int7 -> [Int7] #

Eq Int7 Source # 

Methods

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

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

Integral Int7 Source # 

Methods

quot :: Int7 -> Int7 -> Int7 #

rem :: Int7 -> Int7 -> Int7 #

div :: Int7 -> Int7 -> Int7 #

mod :: Int7 -> Int7 -> Int7 #

quotRem :: Int7 -> Int7 -> (Int7, Int7) #

divMod :: Int7 -> Int7 -> (Int7, Int7) #

toInteger :: Int7 -> Integer #

Data Int7 Source # 

Methods

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

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

toConstr :: Int7 -> Constr #

dataTypeOf :: Int7 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int7 Source # 

Methods

(+) :: Int7 -> Int7 -> Int7 #

(-) :: Int7 -> Int7 -> Int7 #

(*) :: Int7 -> Int7 -> Int7 #

negate :: Int7 -> Int7 #

abs :: Int7 -> Int7 #

signum :: Int7 -> Int7 #

fromInteger :: Integer -> Int7 #

Ord Int7 Source # 

Methods

compare :: Int7 -> Int7 -> Ordering #

(<) :: Int7 -> Int7 -> Bool #

(<=) :: Int7 -> Int7 -> Bool #

(>) :: Int7 -> Int7 -> Bool #

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

max :: Int7 -> Int7 -> Int7 #

min :: Int7 -> Int7 -> Int7 #

Read Int7 Source # 
Real Int7 Source # 

Methods

toRational :: Int7 -> Rational #

Show Int7 Source # 

Methods

showsPrec :: Int -> Int7 -> ShowS #

show :: Int7 -> String #

showList :: [Int7] -> ShowS #

Ix Int7 Source # 

Methods

range :: (Int7, Int7) -> [Int7] #

index :: (Int7, Int7) -> Int7 -> Int #

unsafeIndex :: (Int7, Int7) -> Int7 -> Int

inRange :: (Int7, Int7) -> Int7 -> Bool #

rangeSize :: (Int7, Int7) -> Int #

unsafeRangeSize :: (Int7, Int7) -> Int

Bits Int7 Source # 
FiniteBits Int7 Source # 
BinaryWord Int7 Source # 
Hashable Int7 Source # 

Methods

hashWithSalt :: Int -> Int7 -> Int #

hash :: Int7 -> Int #

type SignedWord Int7 Source # 
type UnsignedWord Int7 Source # 

data Int24 Source #

Instances

Bounded Int24 Source # 
Enum Int24 Source # 
Eq Int24 Source # 

Methods

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

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

Integral Int24 Source # 
Data Int24 Source # 

Methods

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

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

toConstr :: Int24 -> Constr #

dataTypeOf :: Int24 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int24 Source # 
Ord Int24 Source # 

Methods

compare :: Int24 -> Int24 -> Ordering #

(<) :: Int24 -> Int24 -> Bool #

(<=) :: Int24 -> Int24 -> Bool #

(>) :: Int24 -> Int24 -> Bool #

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

max :: Int24 -> Int24 -> Int24 #

min :: Int24 -> Int24 -> Int24 #

Read Int24 Source # 
Real Int24 Source # 

Methods

toRational :: Int24 -> Rational #

Show Int24 Source # 

Methods

showsPrec :: Int -> Int24 -> ShowS #

show :: Int24 -> String #

showList :: [Int24] -> ShowS #

Ix Int24 Source # 
Bits Int24 Source # 
FiniteBits Int24 Source # 
BinaryWord Int24 Source # 
Hashable Int24 Source # 

Methods

hashWithSalt :: Int -> Int24 -> Int #

hash :: Int24 -> Int #

type SignedWord Int24 Source # 
type UnsignedWord Int24 Source # 

data Int48 Source #

Instances

Bounded Int48 Source # 
Enum Int48 Source # 
Eq Int48 Source # 

Methods

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

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

Integral Int48 Source # 
Data Int48 Source # 

Methods

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

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

toConstr :: Int48 -> Constr #

dataTypeOf :: Int48 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int48 Source # 
Ord Int48 Source # 

Methods

compare :: Int48 -> Int48 -> Ordering #

(<) :: Int48 -> Int48 -> Bool #

(<=) :: Int48 -> Int48 -> Bool #

(>) :: Int48 -> Int48 -> Bool #

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

max :: Int48 -> Int48 -> Int48 #

min :: Int48 -> Int48 -> Int48 #

Read Int48 Source # 
Real Int48 Source # 

Methods

toRational :: Int48 -> Rational #

Show Int48 Source # 

Methods

showsPrec :: Int -> Int48 -> ShowS #

show :: Int48 -> String #

showList :: [Int48] -> ShowS #

Ix Int48 Source # 
Bits Int48 Source # 
FiniteBits Int48 Source # 
BinaryWord Int48 Source # 
Hashable Int48 Source # 

Methods

hashWithSalt :: Int -> Int48 -> Int #

hash :: Int48 -> Int #

type SignedWord Int48 Source # 
type UnsignedWord Int48 Source #