web3-0.8.2.0: Ethereum API for Haskell

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

Data.Solidity.Prim

Description

Solidity primitive data types.

Synopsis

Documentation

data Address Source #

Ethereum account address

Instances
Eq Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Methods

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

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

Ord Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Show Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

IsString Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Methods

fromString :: String -> Address #

Generic Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Associated Types

type Rep Address :: * -> * #

Methods

from :: Address -> Rep Address x #

to :: Rep Address x -> Address #

ToJSON Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

FromJSON Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Default Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Methods

def :: Address #

Generic Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

Associated Types

type Code Address :: [[*]] #

AbiGet Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

AbiPut Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

AbiType Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

type Rep Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

type Rep Address = D1 (MetaData "Address" "Data.Solidity.Prim.Address" "web3-0.8.2.0-1eFGqTvt0D0HQmcf3z8jPt" True) (C1 (MetaCons "Address" PrefixI True) (S1 (MetaSel (Just "unAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (UIntN 160))))
type Code Address Source # 
Instance details

Defined in Data.Solidity.Prim.Address

data Bytes #

Simplest Byte Array

Instances
Eq Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

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

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

Ord Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

compare :: Bytes -> Bytes -> Ordering #

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

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

(>) :: Bytes -> Bytes -> Bool #

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

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Show Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

IsString Bytes # 
Instance details

Defined in Data.Solidity.Prim.Bytes

Methods

fromString :: String -> Bytes #

Semigroup Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

(<>) :: Bytes -> Bytes -> Bytes #

sconcat :: NonEmpty Bytes -> Bytes #

stimes :: Integral b => b -> Bytes -> Bytes #

Monoid Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

mempty :: Bytes #

mappend :: Bytes -> Bytes -> Bytes #

mconcat :: [Bytes] -> Bytes #

ToJSON Bytes # 
Instance details

Defined in Data.Solidity.Prim.Bytes

FromJSON Bytes # 
Instance details

Defined in Data.Solidity.Prim.Bytes

NormalForm Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

toNormalForm :: Bytes -> () #

NFData Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

rnf :: Bytes -> () #

ByteArray Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Bytes) #

ByteArrayAccess Bytes 
Instance details

Defined in Data.ByteArray.Bytes

Methods

length :: Bytes -> Int #

withByteArray :: Bytes -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: Bytes -> Ptr p -> IO () #

AbiGet Bytes Source # 
Instance details

Defined in Data.Solidity.Prim.Bytes

Methods

abiGet :: Get Bytes Source #

AbiPut Bytes Source # 
Instance details

Defined in Data.Solidity.Prim.Bytes

AbiType Bytes Source # 
Instance details

Defined in Data.Solidity.Prim.Bytes

(KnownNat n, n <= 32) => IsString (BytesN n) # 
Instance details

Defined in Data.Solidity.Prim.Bytes

Methods

fromString :: String -> BytesN n #

(KnownNat n, n <= 32) => ToJSON (BytesN n) # 
Instance details

Defined in Data.Solidity.Prim.Bytes

(KnownNat n, n <= 32) => FromJSON (BytesN n) # 
Instance details

Defined in Data.Solidity.Prim.Bytes

(KnownNat n, n <= 32) => AbiGet (BytesN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Bytes

Methods

abiGet :: Get (BytesN n) Source #

(KnownNat n, n <= 32) => AbiPut (BytesN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Bytes

Methods

abiPut :: Putter (BytesN n) Source #

n <= 32 => AbiType (BytesN n) Source # 
Instance details

Defined in Data.Solidity.Prim.Bytes

Methods

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

type BytesN n = SizedByteArray n Bytes Source #

Sized byte array with fixed length in bytes

data IntN (n :: Nat) Source #

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) :: * -> * #

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.8.2.0-1eFGqTvt0D0HQmcf3z8jPt" True) (C1 (MetaCons "IntN" PrefixI True) (S1 (MetaSel (Just "unIntN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word256)))

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) :: * -> * #

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.8.2.0-1eFGqTvt0D0HQmcf3z8jPt" True) (C1 (MetaCons "UIntN" PrefixI True) (S1 (MetaSel (Just "unUIntN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word256)))

data ListN (n :: Nat) a #

A Typed-level sized List equivalent to [a]

Instances
(NatWithinBound Int n, KnownNat n) => IsList (ListN n a) # 
Instance details

Defined in Data.Solidity.Prim.List

Associated Types

type Item (ListN n a) :: * #

Methods

fromList :: [Item (ListN n a)] -> ListN n a #

fromListN :: Int -> [Item (ListN n a)] -> ListN n a #

toList :: ListN n a -> [Item (ListN n a)] #

Eq a => Eq (ListN n a) 
Instance details

Defined in Basement.Sized.List

Methods

(==) :: ListN n a -> ListN n a -> Bool #

(/=) :: ListN n a -> ListN n a -> Bool #

Ord a => Ord (ListN n a) 
Instance details

Defined in Basement.Sized.List

Methods

compare :: ListN n a -> ListN n a -> Ordering #

(<) :: ListN n a -> ListN n a -> Bool #

(<=) :: ListN n a -> ListN n a -> Bool #

(>) :: ListN n a -> ListN n a -> Bool #

(>=) :: ListN n a -> ListN n a -> Bool #

max :: ListN n a -> ListN n a -> ListN n a #

min :: ListN n a -> ListN n a -> ListN n a #

Show a => Show (ListN n a) 
Instance details

Defined in Basement.Sized.List

Methods

showsPrec :: Int -> ListN n a -> ShowS #

show :: ListN n a -> String #

showList :: [ListN n a] -> ShowS #

Generic (ListN n a) 
Instance details

Defined in Basement.Sized.List

Associated Types

type Rep (ListN n a) :: * -> * #

Methods

from :: ListN n a -> Rep (ListN n a) x #

to :: Rep (ListN n a) x -> ListN n a #

NormalForm a => NormalForm (ListN n a) 
Instance details

Defined in Basement.Sized.List

Methods

toNormalForm :: ListN n a -> () #

(NatWithinBound Int n, KnownNat n, AbiGet a) => AbiGet (ListN n a) Source # 
Instance details

Defined in Data.Solidity.Prim.List

Methods

abiGet :: Get (ListN n a) Source #

AbiPut a => AbiPut (ListN n a) Source # 
Instance details

Defined in Data.Solidity.Prim.List

Methods

abiPut :: Putter (ListN n a) Source #

AbiType (ListN n a) Source # 
Instance details

Defined in Data.Solidity.Prim.List

Methods

isDynamic :: Proxy (ListN n a) -> Bool Source #

type Rep (ListN n a) 
Instance details

Defined in Basement.Sized.List

type Rep (ListN n a) = D1 (MetaData "ListN" "Basement.Sized.List" "basement-0.0.8-8QjArDsw3GWCcbHE5iqtz3" True) (C1 (MetaCons "ListN" PrefixI True) (S1 (MetaSel (Just "unListN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [a])))
type Item (ListN n a) # 
Instance details

Defined in Data.Solidity.Prim.List

type Item (ListN n a) = a