| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
EVM.ABI
Synopsis
- data AbiValue
- data AbiType
- data AbiKind
- data AbiVals
- abiKind :: AbiType -> AbiKind
- data Event = Event Text Anonymity [(Text, AbiType, Indexed)]
- data SolError = SolError Text [AbiType]
- data Anonymity
- data Indexed
- putAbi :: AbiValue -> Put
- getAbi :: AbiType -> Get AbiValue
- getAbiSeq :: Int -> [AbiType] -> Get (Vector AbiValue)
- genAbiValue :: AbiType -> Gen AbiValue
- abiValueType :: AbiValue -> AbiType
- abiTypeSolidity :: AbiType -> Text
- abiMethod :: Text -> AbiValue -> ByteString
- emptyAbi :: AbiValue
- encodeAbiValue :: AbiValue -> ByteString
- decodeAbiValue :: AbiType -> ByteString -> AbiValue
- decodeStaticArgs :: Buffer -> [SymWord]
- decodeBuffer :: [AbiType] -> Buffer -> AbiVals
- formatString :: ByteString -> String
- parseTypeName :: Vector AbiType -> Text -> Maybe AbiType
- makeAbiValue :: AbiType -> String -> AbiValue
- parseAbiValue :: AbiType -> ReadP AbiValue
- selector :: Text -> ByteString
Documentation
Constructors
Instances
Constructors
| AbiUIntType Int | |
| AbiIntType Int | |
| AbiAddressType | |
| AbiBoolType | |
| AbiBytesType Int | |
| AbiBytesDynamicType | |
| AbiStringType | |
| AbiArrayDynamicType AbiType | |
| AbiArrayType Int AbiType | |
| AbiTupleType (Vector AbiType) | 
Instances
Instances
| Eq Event Source # | |
| Ord Event Source # | |
| Show Event Source # | |
| Generic Event Source # | |
| type Rep Event Source # | |
| Defined in EVM.ABI type Rep Event = D1 ('MetaData "Event" "EVM.ABI" "hevm-0.49.0-inplace" 'False) (C1 ('MetaCons "Event" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Anonymity) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(Text, AbiType, Indexed)])))) | |
Instances
| Eq SolError Source # | |
| Ord SolError Source # | |
| Defined in EVM.ABI | |
| Show SolError Source # | |
| Generic SolError Source # | |
| type Rep SolError Source # | |
| Defined in EVM.ABI type Rep SolError = D1 ('MetaData "SolError" "EVM.ABI" "hevm-0.49.0-inplace" 'False) (C1 ('MetaCons "SolError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [AbiType]))) | |
Constructors
| Anonymous | |
| NotAnonymous | 
Instances
| Eq Anonymity Source # | |
| Ord Anonymity Source # | |
| Show Anonymity Source # | |
| Generic Anonymity Source # | |
| type Rep Anonymity Source # | |
Constructors
| Indexed | |
| NotIndexed | 
getAbiSeq :: Int -> [AbiType] -> Get (Vector AbiValue) Source #
Decode a sequence type (e.g. tuple / array). Will fail for non sequence types
abiValueType :: AbiValue -> AbiType Source #
abiTypeSolidity :: AbiType -> Text Source #
encodeAbiValue :: AbiValue -> ByteString Source #
decodeAbiValue :: AbiType -> ByteString -> AbiValue Source #
decodeStaticArgs :: Buffer -> [SymWord] Source #
formatString :: ByteString -> String Source #
selector :: Text -> ByteString Source #