Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- solidity :: Text -> Text -> IO (Maybe ByteString)
- data JumpType
- data SolcContract = SolcContract {}
- data SourceCache = SourceCache {
- _snippetCache :: Map (Int, Int) ByteString
- _sourceFiles :: Map Int (Text, ByteString)
- _sourceLines :: Map Int (Vector ByteString)
- _sourceAsts :: Map Text Value
- data SrcMap = SM {
- srcMapOffset :: Int
- srcMapLength :: Int
- srcMapFile :: Int
- srcMapJump :: JumpType
- data CodeType
- data Method = Method {
- _methodOutput :: Maybe (Text, AbiType)
- _methodInputs :: [(Text, AbiType)]
- _methodName :: Text
- _methodSignature :: Text
- methodName :: Lens' Method Text
- methodSignature :: Lens' Method Text
- methodInputs :: Lens' Method [(Text, AbiType)]
- methodOutput :: Lens' Method (Maybe (Text, AbiType))
- abiMap :: Lens' SolcContract (Map Word32 Method)
- eventMap :: Lens' SolcContract (Map W256 Event)
- contractName :: Lens' SolcContract Text
- constructorInputs :: Lens' SolcContract [(Text, AbiType)]
- creationCode :: Lens' SolcContract ByteString
- makeSrcMaps :: Text -> Maybe (Seq SrcMap)
- readSolc :: FilePath -> IO (Maybe (Map Text SolcContract, SourceCache))
- runtimeCode :: Lens' SolcContract ByteString
- snippetCache :: Lens' SourceCache (Map (Int, Int) ByteString)
- runtimeCodehash :: Lens' SolcContract W256
- creationCodehash :: Lens' SolcContract W256
- runtimeSrcmap :: Lens' SolcContract (Seq SrcMap)
- creationSrcmap :: Lens' SolcContract (Seq SrcMap)
- contractAst :: Lens' SolcContract Value
- sourceFiles :: Lens' SourceCache (Map Int (Text, ByteString))
- sourceLines :: Lens' SourceCache (Map Int (Vector ByteString))
- sourceAsts :: Lens' SourceCache (Map Text Value)
- stripBytecodeMetadata :: ByteString -> ByteString
- lineSubrange :: Vector ByteString -> (Int, Int) -> Int -> Maybe (Int, Int)
- astIdMap :: Foldable f => f Value -> Map Int Value
- astSrcMap :: Map Int Value -> SrcMap -> Maybe Value
Documentation
data SolcContract Source #
SolcContract | |
|
Instances
data SourceCache Source #
SourceCache | |
|
Instances
SM | |
|
Instances
Eq SrcMap Source # | |
Ord SrcMap Source # | |
Show SrcMap Source # | |
Generic SrcMap Source # | |
type Rep SrcMap Source # | |
Defined in EVM.Solidity type Rep SrcMap = D1 (MetaData "SrcMap" "EVM.Solidity" "hevm-0.21-9xzTS2VdCVH70nnTNQL2Eg" False) (C1 (MetaCons "SM" PrefixI True) ((S1 (MetaSel (Just "srcMapOffset") SourceUnpack NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "srcMapLength") SourceUnpack NoSourceStrictness DecidedStrict) (Rec0 Int)) :*: (S1 (MetaSel (Just "srcMapFile") SourceUnpack NoSourceStrictness DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "srcMapJump") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 JumpType)))) |
Method | |
|
Instances
Eq Method Source # | |
Ord Method Source # | |
Show Method Source # | |
Generic Method Source # | |
type Rep Method Source # | |
Defined in EVM.Solidity type Rep Method = D1 (MetaData "Method" "EVM.Solidity" "hevm-0.21-9xzTS2VdCVH70nnTNQL2Eg" False) (C1 (MetaCons "Method" PrefixI True) ((S1 (MetaSel (Just "_methodOutput") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 (Maybe (Text, AbiType))) :*: S1 (MetaSel (Just "_methodInputs") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 [(Text, AbiType)])) :*: (S1 (MetaSel (Just "_methodName") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_methodSignature") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Text)))) |
constructorInputs :: Lens' SolcContract [(Text, AbiType)] Source #
readSolc :: FilePath -> IO (Maybe (Map Text SolcContract, SourceCache)) Source #
snippetCache :: Lens' SourceCache (Map (Int, Int) ByteString) Source #
sourceFiles :: Lens' SourceCache (Map Int (Text, ByteString)) Source #
sourceLines :: Lens' SourceCache (Map Int (Vector ByteString)) Source #
sourceAsts :: Lens' SourceCache (Map Text Value) Source #