web3-0.9.1.0: Web3 API for Haskell.

CopyrightAlexander Krupenkin 2018
LicenseBSD3
Maintainermail@akru.me
Stabilityexperimental
Portabilitynoportable
Safe HaskellNone
LanguageHaskell2010

Data.Solidity.Prim.Int

Contents

Description

Ethereum Abi intN and uintN types.

Synopsis

The IntN type

data IntN (n :: Nat) Source #

Signed integer with fixed length in bits.

Instances
(KnownNat n, n <= 256) => Bounded (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

minBound :: IntN n #

maxBound :: IntN n #

Enum (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

succ :: IntN n -> IntN n #

pred :: IntN n -> IntN n #

toEnum :: Int -> IntN n #

fromEnum :: IntN n -> Int #

enumFrom :: IntN n -> [IntN n] #

enumFromThen :: IntN n -> IntN n -> [IntN n] #

enumFromTo :: IntN n -> IntN n -> [IntN n] #

enumFromThenTo :: IntN n -> IntN n -> IntN n -> [IntN n] #

Eq (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

(==) :: IntN n -> IntN n -> Bool #

(/=) :: IntN n -> IntN n -> Bool #

(KnownNat n, n <= 256) => Integral (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

quot :: IntN n -> IntN n -> IntN n #

rem :: IntN n -> IntN n -> IntN n #

div :: IntN n -> IntN n -> IntN n #

mod :: IntN n -> IntN n -> IntN n #

quotRem :: IntN n -> IntN n -> (IntN n, IntN n) #

divMod :: IntN n -> IntN n -> (IntN n, IntN n) #

toInteger :: IntN n -> Integer #

(KnownNat n, n <= 256) => Num (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

(+) :: IntN n -> IntN n -> IntN n #

(-) :: IntN n -> IntN n -> IntN n #

(*) :: IntN n -> IntN n -> IntN n #

negate :: IntN n -> IntN n #

abs :: IntN n -> IntN n #

signum :: IntN n -> IntN n #

fromInteger :: Integer -> IntN n #

Ord (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

compare :: IntN n -> IntN n -> Ordering #

(<) :: IntN n -> IntN n -> Bool #

(<=) :: IntN n -> IntN n -> Bool #

(>) :: IntN n -> IntN n -> Bool #

(>=) :: IntN n -> IntN n -> Bool #

max :: IntN n -> IntN n -> IntN n #

min :: IntN n -> IntN n -> IntN n #

(KnownNat n, n <= 256) => Real (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

toRational :: IntN n -> Rational #

(KnownNat n, n <= 256) => Show (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

showsPrec :: Int -> IntN n -> ShowS #

show :: IntN n -> String #

showList :: [IntN n] -> ShowS #

Generic (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Associated Types

type Rep (IntN n) :: Type -> Type #

Methods

from :: IntN n -> Rep (IntN n) x #

to :: Rep (IntN n) x -> IntN n #

Bits (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

(.&.) :: IntN n -> IntN n -> IntN n #

(.|.) :: IntN n -> IntN n -> IntN n #

xor :: IntN n -> IntN n -> IntN n #

complement :: IntN n -> IntN n #

shift :: IntN n -> Int -> IntN n #

rotate :: IntN n -> Int -> IntN n #

zeroBits :: IntN n #

bit :: Int -> IntN n #

setBit :: IntN n -> Int -> IntN n #

clearBit :: IntN n -> Int -> IntN n #

complementBit :: IntN n -> Int -> IntN n #

testBit :: IntN n -> Int -> Bool #

bitSizeMaybe :: IntN n -> Maybe Int #

bitSize :: IntN n -> Int #

isSigned :: IntN n -> Bool #

shiftL :: IntN n -> Int -> IntN n #

unsafeShiftL :: IntN n -> Int -> IntN n #

shiftR :: IntN n -> Int -> IntN n #

unsafeShiftR :: IntN n -> Int -> IntN n #

rotateL :: IntN n -> Int -> IntN n #

rotateR :: IntN n -> Int -> IntN n #

popCount :: IntN n -> Int #

n <= 256 => AbiGet (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

abiGet :: Get (IntN n) Source #

n <= 256 => AbiPut (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

abiPut :: Putter (IntN n) Source #

n <= 256 => AbiType (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

isDynamic :: Proxy (IntN n) -> Bool Source #

type Rep (IntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

type Rep (IntN n) = D1 (MetaData "IntN" "Data.Solidity.Prim.Int" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" True) (C1 (MetaCons "IntN" PrefixI True) (S1 (MetaSel (Just "unIntN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word256)))

The UIntN type

data UIntN (n :: Nat) Source #

Unsigned integer with fixed length in bits.

Instances
(KnownNat n, n <= 256) => Bounded (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

minBound :: UIntN n #

maxBound :: UIntN n #

Enum (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

succ :: UIntN n -> UIntN n #

pred :: UIntN n -> UIntN n #

toEnum :: Int -> UIntN n #

fromEnum :: UIntN n -> Int #

enumFrom :: UIntN n -> [UIntN n] #

enumFromThen :: UIntN n -> UIntN n -> [UIntN n] #

enumFromTo :: UIntN n -> UIntN n -> [UIntN n] #

enumFromThenTo :: UIntN n -> UIntN n -> UIntN n -> [UIntN n] #

Eq (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

(==) :: UIntN n -> UIntN n -> Bool #

(/=) :: UIntN n -> UIntN n -> Bool #

(KnownNat n, n <= 256) => Integral (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

quot :: UIntN n -> UIntN n -> UIntN n #

rem :: UIntN n -> UIntN n -> UIntN n #

div :: UIntN n -> UIntN n -> UIntN n #

mod :: UIntN n -> UIntN n -> UIntN n #

quotRem :: UIntN n -> UIntN n -> (UIntN n, UIntN n) #

divMod :: UIntN n -> UIntN n -> (UIntN n, UIntN n) #

toInteger :: UIntN n -> Integer #

(KnownNat n, n <= 256) => Num (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

(+) :: UIntN n -> UIntN n -> UIntN n #

(-) :: UIntN n -> UIntN n -> UIntN n #

(*) :: UIntN n -> UIntN n -> UIntN n #

negate :: UIntN n -> UIntN n #

abs :: UIntN n -> UIntN n #

signum :: UIntN n -> UIntN n #

fromInteger :: Integer -> UIntN n #

Ord (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

compare :: UIntN n -> UIntN n -> Ordering #

(<) :: UIntN n -> UIntN n -> Bool #

(<=) :: UIntN n -> UIntN n -> Bool #

(>) :: UIntN n -> UIntN n -> Bool #

(>=) :: UIntN n -> UIntN n -> Bool #

max :: UIntN n -> UIntN n -> UIntN n #

min :: UIntN n -> UIntN n -> UIntN n #

(KnownNat n, n <= 256) => Real (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

toRational :: UIntN n -> Rational #

(KnownNat n, n <= 256) => Show (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

showsPrec :: Int -> UIntN n -> ShowS #

show :: UIntN n -> String #

showList :: [UIntN n] -> ShowS #

Generic (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Associated Types

type Rep (UIntN n) :: Type -> Type #

Methods

from :: UIntN n -> Rep (UIntN n) x #

to :: Rep (UIntN n) x -> UIntN n #

Bits (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

(.&.) :: UIntN n -> UIntN n -> UIntN n #

(.|.) :: UIntN n -> UIntN n -> UIntN n #

xor :: UIntN n -> UIntN n -> UIntN n #

complement :: UIntN n -> UIntN n #

shift :: UIntN n -> Int -> UIntN n #

rotate :: UIntN n -> Int -> UIntN n #

zeroBits :: UIntN n #

bit :: Int -> UIntN n #

setBit :: UIntN n -> Int -> UIntN n #

clearBit :: UIntN n -> Int -> UIntN n #

complementBit :: UIntN n -> Int -> UIntN n #

testBit :: UIntN n -> Int -> Bool #

bitSizeMaybe :: UIntN n -> Maybe Int #

bitSize :: UIntN n -> Int #

isSigned :: UIntN n -> Bool #

shiftL :: UIntN n -> Int -> UIntN n #

unsafeShiftL :: UIntN n -> Int -> UIntN n #

shiftR :: UIntN n -> Int -> UIntN n #

unsafeShiftR :: UIntN n -> Int -> UIntN n #

rotateL :: UIntN n -> Int -> UIntN n #

rotateR :: UIntN n -> Int -> UIntN n #

popCount :: UIntN n -> Int #

n <= 256 => AbiGet (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

abiGet :: Get (UIntN n) Source #

n <= 256 => AbiPut (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

abiPut :: Putter (UIntN n) Source #

n <= 256 => AbiType (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

Methods

isDynamic :: Proxy (UIntN n) -> Bool Source #

type Rep (UIntN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Int

type Rep (UIntN n) = D1 (MetaData "UIntN" "Data.Solidity.Prim.Int" "web3-0.9.1.0-3q6w2KRBOG16VQPAACkK14" True) (C1 (MetaCons "UIntN" PrefixI True) (S1 (MetaSel (Just "unUIntN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word256)))

Word256 serializers

getWord256 :: Get Word256 Source #

Deserialize 256 bit unsigned integer.

putWord256 :: Putter Word256 Source #

Serialize 256 bit unsigned integer.

Orphan instances