data-dword-0.3.1: Stick two binary words together to get a bigger one

Safe HaskellNone
LanguageHaskell2010

Data.DoubleWord

Description

This module provides strict (low and high halves are unpacked) signed and unsigned binary word data types of sizes 96, 128, 160, 192, 224, and 256 bits.

Synopsis

Documentation

class BinaryWord w => DoubleWord w where Source #

Defines a particular way to split a binary word in halves.

Minimal complete definition

loWord, hiWord, fromHiAndLo, extendLo, signExtendLo

Associated Types

type LoWord w Source #

The low half type

type HiWord w Source #

The high half type

Methods

loWord :: w -> LoWord w Source #

The low half of the word

hiWord :: w -> HiWord w Source #

The high half of the word

fromHiAndLo :: HiWord w -> LoWord w -> w Source #

Construct a word from the low and high halves

extendLo :: LoWord w -> w Source #

Extend the low half

signExtendLo :: SignedWord (LoWord w) -> w Source #

Sign-extend the low half

Instances

DoubleWord Int16 Source # 
DoubleWord Int32 Source # 
DoubleWord Int64 Source # 
DoubleWord Word16 Source # 
DoubleWord Word32 Source # 
DoubleWord Word64 Source # 
DoubleWord Int96 Source # 
DoubleWord Word96 Source # 
DoubleWord Int128 Source # 
DoubleWord Word128 Source # 
DoubleWord Int160 Source # 
DoubleWord Word160 Source # 
DoubleWord Int192 Source # 
DoubleWord Word192 Source # 
DoubleWord Int224 Source # 
DoubleWord Word224 Source # 
DoubleWord Int256 Source # 
DoubleWord Word256 Source # 

data Word96 Source #

Constructors

Word96 !Word32 !Word64 

Instances

Bounded Word96 Source # 
Enum Word96 Source # 
Eq Word96 Source # 

Methods

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

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

Integral Word96 Source # 
Data Word96 Source # 

Methods

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

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

toConstr :: Word96 -> Constr #

dataTypeOf :: Word96 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word96 Source # 
Ord Word96 Source # 
Read Word96 Source # 
Real Word96 Source # 
Show Word96 Source # 
Ix Word96 Source # 
Generic Word96 Source # 

Associated Types

type Rep Word96 :: * -> * #

Methods

from :: Word96 -> Rep Word96 x #

to :: Rep Word96 x -> Word96 #

Bits Word96 Source # 
FiniteBits Word96 Source # 
BinaryWord Word96 Source # 
Hashable Word96 Source # 

Methods

hashWithSalt :: Int -> Word96 -> Int #

hash :: Word96 -> Int #

DoubleWord Word96 Source # 
type Rep Word96 Source # 
type Rep Word96 = D1 (MetaData "Word96" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Word96" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word32)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64))))
type SignedWord Word96 Source # 
type UnsignedWord Word96 Source # 
type LoWord Word96 Source # 
type HiWord Word96 Source # 

data Word128 Source #

Constructors

Word128 !Word64 !Word64 

Instances

Bounded Word128 Source # 
Enum Word128 Source # 
Eq Word128 Source # 

Methods

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

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

Integral Word128 Source # 
Data Word128 Source # 

Methods

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

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

toConstr :: Word128 -> Constr #

dataTypeOf :: Word128 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word128 Source # 
Ord Word128 Source # 
Read Word128 Source # 
Real Word128 Source # 
Show Word128 Source # 
Ix Word128 Source # 
Generic Word128 Source # 

Associated Types

type Rep Word128 :: * -> * #

Methods

from :: Word128 -> Rep Word128 x #

to :: Rep Word128 x -> Word128 #

Bits Word128 Source # 
FiniteBits Word128 Source # 
BinaryWord Word128 Source # 
Hashable Word128 Source # 

Methods

hashWithSalt :: Int -> Word128 -> Int #

hash :: Word128 -> Int #

DoubleWord Word128 Source # 
type Rep Word128 Source # 
type Rep Word128 = D1 (MetaData "Word128" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Word128" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64))))
type SignedWord Word128 Source # 
type UnsignedWord Word128 Source # 
type LoWord Word128 Source # 
type HiWord Word128 Source # 

data Word160 Source #

Constructors

Word160 !Word32 !Word128 

Instances

Bounded Word160 Source # 
Enum Word160 Source # 
Eq Word160 Source # 

Methods

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

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

Integral Word160 Source # 
Data Word160 Source # 

Methods

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

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

toConstr :: Word160 -> Constr #

dataTypeOf :: Word160 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word160 Source # 
Ord Word160 Source # 
Read Word160 Source # 
Real Word160 Source # 
Show Word160 Source # 
Ix Word160 Source # 
Generic Word160 Source # 

Associated Types

type Rep Word160 :: * -> * #

Methods

from :: Word160 -> Rep Word160 x #

to :: Rep Word160 x -> Word160 #

Bits Word160 Source # 
FiniteBits Word160 Source # 
BinaryWord Word160 Source # 
Hashable Word160 Source # 

Methods

hashWithSalt :: Int -> Word160 -> Int #

hash :: Word160 -> Int #

DoubleWord Word160 Source # 
type Rep Word160 Source # 
type Rep Word160 = D1 (MetaData "Word160" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Word160" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word32)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Word160 Source # 
type UnsignedWord Word160 Source # 
type LoWord Word160 Source # 
type HiWord Word160 Source # 

data Word192 Source #

Constructors

Word192 !Word64 !Word128 

Instances

Bounded Word192 Source # 
Enum Word192 Source # 
Eq Word192 Source # 

Methods

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

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

Integral Word192 Source # 
Data Word192 Source # 

Methods

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

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

toConstr :: Word192 -> Constr #

dataTypeOf :: Word192 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word192 Source # 
Ord Word192 Source # 
Read Word192 Source # 
Real Word192 Source # 
Show Word192 Source # 
Ix Word192 Source # 
Generic Word192 Source # 

Associated Types

type Rep Word192 :: * -> * #

Methods

from :: Word192 -> Rep Word192 x #

to :: Rep Word192 x -> Word192 #

Bits Word192 Source # 
FiniteBits Word192 Source # 
BinaryWord Word192 Source # 
Hashable Word192 Source # 

Methods

hashWithSalt :: Int -> Word192 -> Int #

hash :: Word192 -> Int #

DoubleWord Word192 Source # 
type Rep Word192 Source # 
type Rep Word192 = D1 (MetaData "Word192" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Word192" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Word192 Source # 
type UnsignedWord Word192 Source # 
type LoWord Word192 Source # 
type HiWord Word192 Source # 

data Word224 Source #

Constructors

Word224 !Word96 !Word128 

Instances

Bounded Word224 Source # 
Enum Word224 Source # 
Eq Word224 Source # 

Methods

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

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

Integral Word224 Source # 
Data Word224 Source # 

Methods

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

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

toConstr :: Word224 -> Constr #

dataTypeOf :: Word224 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word224 Source # 
Ord Word224 Source # 
Read Word224 Source # 
Real Word224 Source # 
Show Word224 Source # 
Ix Word224 Source # 
Generic Word224 Source # 

Associated Types

type Rep Word224 :: * -> * #

Methods

from :: Word224 -> Rep Word224 x #

to :: Rep Word224 x -> Word224 #

Bits Word224 Source # 
FiniteBits Word224 Source # 
BinaryWord Word224 Source # 
Hashable Word224 Source # 

Methods

hashWithSalt :: Int -> Word224 -> Int #

hash :: Word224 -> Int #

DoubleWord Word224 Source # 
type Rep Word224 Source # 
type Rep Word224 = D1 (MetaData "Word224" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Word224" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word96)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Word224 Source # 
type UnsignedWord Word224 Source # 
type LoWord Word224 Source # 
type HiWord Word224 Source # 

data Word256 Source #

Constructors

Word256 !Word128 !Word128 

Instances

Bounded Word256 Source # 
Enum Word256 Source # 
Eq Word256 Source # 

Methods

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

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

Integral Word256 Source # 
Data Word256 Source # 

Methods

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

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

toConstr :: Word256 -> Constr #

dataTypeOf :: Word256 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Word256 Source # 
Ord Word256 Source # 
Read Word256 Source # 
Real Word256 Source # 
Show Word256 Source # 
Ix Word256 Source # 
Generic Word256 Source # 

Associated Types

type Rep Word256 :: * -> * #

Methods

from :: Word256 -> Rep Word256 x #

to :: Rep Word256 x -> Word256 #

Bits Word256 Source # 
FiniteBits Word256 Source # 
BinaryWord Word256 Source # 
Hashable Word256 Source # 

Methods

hashWithSalt :: Int -> Word256 -> Int #

hash :: Word256 -> Int #

DoubleWord Word256 Source # 
type Rep Word256 Source # 
type Rep Word256 = D1 (MetaData "Word256" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Word256" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Word256 Source # 
type UnsignedWord Word256 Source # 
type LoWord Word256 Source # 
type HiWord Word256 Source # 

data Int96 Source #

Constructors

Int96 !Int32 !Word64 

Instances

Bounded Int96 Source # 
Enum Int96 Source # 
Eq Int96 Source # 

Methods

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

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

Integral Int96 Source # 
Data Int96 Source # 

Methods

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

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

toConstr :: Int96 -> Constr #

dataTypeOf :: Int96 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int96 Source # 
Ord Int96 Source # 

Methods

compare :: Int96 -> Int96 -> Ordering #

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

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

(>) :: Int96 -> Int96 -> Bool #

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

max :: Int96 -> Int96 -> Int96 #

min :: Int96 -> Int96 -> Int96 #

Read Int96 Source # 
Real Int96 Source # 

Methods

toRational :: Int96 -> Rational #

Show Int96 Source # 

Methods

showsPrec :: Int -> Int96 -> ShowS #

show :: Int96 -> String #

showList :: [Int96] -> ShowS #

Ix Int96 Source # 
Generic Int96 Source # 

Associated Types

type Rep Int96 :: * -> * #

Methods

from :: Int96 -> Rep Int96 x #

to :: Rep Int96 x -> Int96 #

Bits Int96 Source # 
FiniteBits Int96 Source # 
BinaryWord Int96 Source # 
Hashable Int96 Source # 

Methods

hashWithSalt :: Int -> Int96 -> Int #

hash :: Int96 -> Int #

DoubleWord Int96 Source # 
type Rep Int96 Source # 
type Rep Int96 = D1 (MetaData "Int96" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Int96" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int32)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64))))
type SignedWord Int96 Source # 
type UnsignedWord Int96 Source # 
type LoWord Int96 Source # 
type HiWord Int96 Source # 

data Int128 Source #

Constructors

Int128 !Int64 !Word64 

Instances

Bounded Int128 Source # 
Enum Int128 Source # 
Eq Int128 Source # 

Methods

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

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

Integral Int128 Source # 
Data Int128 Source # 

Methods

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

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

toConstr :: Int128 -> Constr #

dataTypeOf :: Int128 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int128 Source # 
Ord Int128 Source # 
Read Int128 Source # 
Real Int128 Source # 
Show Int128 Source # 
Ix Int128 Source # 
Generic Int128 Source # 

Associated Types

type Rep Int128 :: * -> * #

Methods

from :: Int128 -> Rep Int128 x #

to :: Rep Int128 x -> Int128 #

Bits Int128 Source # 
FiniteBits Int128 Source # 
BinaryWord Int128 Source # 
Hashable Int128 Source # 

Methods

hashWithSalt :: Int -> Int128 -> Int #

hash :: Int128 -> Int #

DoubleWord Int128 Source # 
type Rep Int128 Source # 
type Rep Int128 = D1 (MetaData "Int128" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Int128" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word64))))
type SignedWord Int128 Source # 
type UnsignedWord Int128 Source # 
type LoWord Int128 Source # 
type HiWord Int128 Source # 

data Int160 Source #

Constructors

Int160 !Int32 !Word128 

Instances

Bounded Int160 Source # 
Enum Int160 Source # 
Eq Int160 Source # 

Methods

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

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

Integral Int160 Source # 
Data Int160 Source # 

Methods

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

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

toConstr :: Int160 -> Constr #

dataTypeOf :: Int160 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int160 Source # 
Ord Int160 Source # 
Read Int160 Source # 
Real Int160 Source # 
Show Int160 Source # 
Ix Int160 Source # 
Generic Int160 Source # 

Associated Types

type Rep Int160 :: * -> * #

Methods

from :: Int160 -> Rep Int160 x #

to :: Rep Int160 x -> Int160 #

Bits Int160 Source # 
FiniteBits Int160 Source # 
BinaryWord Int160 Source # 
Hashable Int160 Source # 

Methods

hashWithSalt :: Int -> Int160 -> Int #

hash :: Int160 -> Int #

DoubleWord Int160 Source # 
type Rep Int160 Source # 
type Rep Int160 = D1 (MetaData "Int160" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Int160" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int32)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Int160 Source # 
type UnsignedWord Int160 Source # 
type LoWord Int160 Source # 
type HiWord Int160 Source # 

data Int192 Source #

Constructors

Int192 !Int64 !Word128 

Instances

Bounded Int192 Source # 
Enum Int192 Source # 
Eq Int192 Source # 

Methods

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

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

Integral Int192 Source # 
Data Int192 Source # 

Methods

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

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

toConstr :: Int192 -> Constr #

dataTypeOf :: Int192 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int192 Source # 
Ord Int192 Source # 
Read Int192 Source # 
Real Int192 Source # 
Show Int192 Source # 
Ix Int192 Source # 
Generic Int192 Source # 

Associated Types

type Rep Int192 :: * -> * #

Methods

from :: Int192 -> Rep Int192 x #

to :: Rep Int192 x -> Int192 #

Bits Int192 Source # 
FiniteBits Int192 Source # 
BinaryWord Int192 Source # 
Hashable Int192 Source # 

Methods

hashWithSalt :: Int -> Int192 -> Int #

hash :: Int192 -> Int #

DoubleWord Int192 Source # 
type Rep Int192 Source # 
type Rep Int192 = D1 (MetaData "Int192" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Int192" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int64)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Int192 Source # 
type UnsignedWord Int192 Source # 
type LoWord Int192 Source # 
type HiWord Int192 Source # 

data Int224 Source #

Constructors

Int224 !Int96 !Word128 

Instances

Bounded Int224 Source # 
Enum Int224 Source # 
Eq Int224 Source # 

Methods

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

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

Integral Int224 Source # 
Data Int224 Source # 

Methods

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

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

toConstr :: Int224 -> Constr #

dataTypeOf :: Int224 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int224 Source # 
Ord Int224 Source # 
Read Int224 Source # 
Real Int224 Source # 
Show Int224 Source # 
Ix Int224 Source # 
Generic Int224 Source # 

Associated Types

type Rep Int224 :: * -> * #

Methods

from :: Int224 -> Rep Int224 x #

to :: Rep Int224 x -> Int224 #

Bits Int224 Source # 
FiniteBits Int224 Source # 
BinaryWord Int224 Source # 
Hashable Int224 Source # 

Methods

hashWithSalt :: Int -> Int224 -> Int #

hash :: Int224 -> Int #

DoubleWord Int224 Source # 
type Rep Int224 Source # 
type Rep Int224 = D1 (MetaData "Int224" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Int224" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int96)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Int224 Source # 
type UnsignedWord Int224 Source # 
type LoWord Int224 Source # 
type HiWord Int224 Source # 

data Int256 Source #

Constructors

Int256 !Int128 !Word128 

Instances

Bounded Int256 Source # 
Enum Int256 Source # 
Eq Int256 Source # 

Methods

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

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

Integral Int256 Source # 
Data Int256 Source # 

Methods

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

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

toConstr :: Int256 -> Constr #

dataTypeOf :: Int256 -> DataType #

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

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

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

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

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

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

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

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

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

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

Num Int256 Source # 
Ord Int256 Source # 
Read Int256 Source # 
Real Int256 Source # 
Show Int256 Source # 
Ix Int256 Source # 
Generic Int256 Source # 

Associated Types

type Rep Int256 :: * -> * #

Methods

from :: Int256 -> Rep Int256 x #

to :: Rep Int256 x -> Int256 #

Bits Int256 Source # 
FiniteBits Int256 Source # 
BinaryWord Int256 Source # 
Hashable Int256 Source # 

Methods

hashWithSalt :: Int -> Int256 -> Int #

hash :: Int256 -> Int #

DoubleWord Int256 Source # 
type Rep Int256 Source # 
type Rep Int256 = D1 (MetaData "Int256" "Data.DoubleWord" "data-dword-0.3.1-BAkRQELOb1j9mKPAdATg68" False) (C1 (MetaCons "Int256" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Int128)) (S1 (MetaSel (Nothing Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Word128))))
type SignedWord Int256 Source # 
type UnsignedWord Int256 Source # 
type LoWord Int256 Source # 
type HiWord Int256 Source #