hevm-0.42.0: Ethereum virtual machine evaluator

Safe HaskellNone
LanguageHaskell2010

EVM.ABI

Documentation

data AbiValue Source #

Instances
Eq AbiValue Source # 
Instance details

Defined in EVM.ABI

Ord AbiValue Source # 
Instance details

Defined in EVM.ABI

Read AbiValue Source # 
Instance details

Defined in EVM.ABI

Show AbiValue Source #

Pretty-print some AbiValue.

Instance details

Defined in EVM.ABI

Generic AbiValue Source # 
Instance details

Defined in EVM.ABI

Associated Types

type Rep AbiValue :: Type -> Type #

Methods

from :: AbiValue -> Rep AbiValue x #

to :: Rep AbiValue x -> AbiValue #

Arbitrary AbiValue Source # 
Instance details

Defined in EVM.ABI

type Rep AbiValue Source # 
Instance details

Defined in EVM.ABI

type Rep AbiValue = D1 (MetaData "AbiValue" "EVM.ABI" "hevm-0.42.0-inplace" False) (((C1 (MetaCons "AbiUInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Word256)) :+: C1 (MetaCons "AbiInt" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int256))) :+: (C1 (MetaCons "AbiAddress" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Addr)) :+: (C1 (MetaCons "AbiBool" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Bool)) :+: C1 (MetaCons "AbiBytes" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString))))) :+: ((C1 (MetaCons "AbiBytesDynamic" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString)) :+: C1 (MetaCons "AbiString" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 ByteString))) :+: (C1 (MetaCons "AbiArrayDynamic" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 AbiType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector AbiValue))) :+: (C1 (MetaCons "AbiArray" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 AbiType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector AbiValue)))) :+: C1 (MetaCons "AbiTuple" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Vector AbiValue)))))))

data AbiType Source #

Instances
Eq AbiType Source # 
Instance details

Defined in EVM.ABI

Methods

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

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

Ord AbiType Source # 
Instance details

Defined in EVM.ABI

Read AbiType Source # 
Instance details

Defined in EVM.ABI

Show AbiType Source # 
Instance details

Defined in EVM.ABI

Generic AbiType Source # 
Instance details

Defined in EVM.ABI

Associated Types

type Rep AbiType :: Type -> Type #

Methods

from :: AbiType -> Rep AbiType x #

to :: Rep AbiType x -> AbiType #

Arbitrary AbiType Source # 
Instance details

Defined in EVM.ABI

type Rep AbiType Source # 
Instance details

Defined in EVM.ABI

data AbiKind Source #

Constructors

Dynamic 
Static 
Instances
Eq AbiKind Source # 
Instance details

Defined in EVM.ABI

Methods

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

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

Ord AbiKind Source # 
Instance details

Defined in EVM.ABI

Read AbiKind Source # 
Instance details

Defined in EVM.ABI

Show AbiKind Source # 
Instance details

Defined in EVM.ABI

Generic AbiKind Source # 
Instance details

Defined in EVM.ABI

Associated Types

type Rep AbiKind :: Type -> Type #

Methods

from :: AbiKind -> Rep AbiKind x #

to :: Rep AbiKind x -> AbiKind #

type Rep AbiKind Source # 
Instance details

Defined in EVM.ABI

type Rep AbiKind = D1 (MetaData "AbiKind" "EVM.ABI" "hevm-0.42.0-inplace" False) (C1 (MetaCons "Dynamic" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Static" PrefixI False) (U1 :: Type -> Type))

data Event Source #

Constructors

Event Text Anonymity [(AbiType, Indexed)] 
Instances
Eq Event Source # 
Instance details

Defined in EVM.ABI

Methods

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

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

Ord Event Source # 
Instance details

Defined in EVM.ABI

Methods

compare :: Event -> Event -> Ordering #

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

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

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Show Event Source # 
Instance details

Defined in EVM.ABI

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in EVM.ABI

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

type Rep Event Source # 
Instance details

Defined in EVM.ABI

data Anonymity Source #

Constructors

Anonymous 
NotAnonymous 
Instances
Eq Anonymity Source # 
Instance details

Defined in EVM.ABI

Ord Anonymity Source # 
Instance details

Defined in EVM.ABI

Show Anonymity Source # 
Instance details

Defined in EVM.ABI

Generic Anonymity Source # 
Instance details

Defined in EVM.ABI

Associated Types

type Rep Anonymity :: Type -> Type #

type Rep Anonymity Source # 
Instance details

Defined in EVM.ABI

type Rep Anonymity = D1 (MetaData "Anonymity" "EVM.ABI" "hevm-0.42.0-inplace" False) (C1 (MetaCons "Anonymous" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotAnonymous" PrefixI False) (U1 :: Type -> Type))

data Indexed Source #

Constructors

Indexed 
NotIndexed 
Instances
Eq Indexed Source # 
Instance details

Defined in EVM.ABI

Methods

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

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

Ord Indexed Source # 
Instance details

Defined in EVM.ABI

Show Indexed Source # 
Instance details

Defined in EVM.ABI

Generic Indexed Source # 
Instance details

Defined in EVM.ABI

Associated Types

type Rep Indexed :: Type -> Type #

Methods

from :: Indexed -> Rep Indexed x #

to :: Rep Indexed x -> Indexed #

type Rep Indexed Source # 
Instance details

Defined in EVM.ABI

type Rep Indexed = D1 (MetaData "Indexed" "EVM.ABI" "hevm-0.42.0-inplace" False) (C1 (MetaCons "Indexed" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "NotIndexed" PrefixI False) (U1 :: Type -> Type))