Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- solidity :: Text -> Text -> IO (Maybe ByteString)
- solcRuntime :: Text -> Text -> IO (Maybe ByteString)
- solidity' :: Text -> IO (Text, Text)
- yul' :: Text -> IO (Text, Text)
- yul :: Text -> Text -> IO (Maybe ByteString)
- yulRuntime :: Text -> Text -> IO (Maybe ByteString)
- data JumpType
- data SolcContract = SolcContract {
- _runtimeCodehash :: W256
- _creationCodehash :: W256
- _runtimeCode :: ByteString
- _creationCode :: ByteString
- _contractName :: Text
- _constructorInputs :: [(Text, AbiType)]
- _abiMap :: Map Word32 Method
- _eventMap :: Map W256 Event
- _errorMap :: Map W256 SolError
- _immutableReferences :: Map W256 [Reference]
- _storageLayout :: Maybe (Map Text StorageItem)
- _runtimeSrcmap :: Seq SrcMap
- _creationSrcmap :: Seq SrcMap
- data StorageItem = StorageItem {}
- data SourceCache = SourceCache {
- _sourceFiles :: [(Text, ByteString)]
- _sourceLines :: [Vector ByteString]
- _sourceAsts :: Map Text Value
- data SrcMap = SM {}
- data CodeType
- data Method = Method {
- _methodOutput :: [(Text, AbiType)]
- _methodInputs :: [(Text, AbiType)]
- _methodName :: Text
- _methodSignature :: Text
- _methodMutability :: Mutability
- data SlotType
- data Reference = Reference {
- _refStart :: Int
- _refLength :: Int
- data Mutability
- = Pure
- | View
- | NonPayable
- | Payable
- methodName :: Lens' Method Text
- methodSignature :: Lens' Method Text
- methodInputs :: Lens' Method [(Text, AbiType)]
- methodOutput :: Lens' Method [(Text, AbiType)]
- methodMutability :: Lens' Method Mutability
- abiMap :: Lens' SolcContract (Map Word32 Method)
- eventMap :: Lens' SolcContract (Map W256 Event)
- errorMap :: Lens' SolcContract (Map W256 SolError)
- storageLayout :: Lens' SolcContract (Maybe (Map Text StorageItem))
- contractName :: Lens' SolcContract Text
- constructorInputs :: Lens' SolcContract [(Text, AbiType)]
- creationCode :: Lens' SolcContract ByteString
- functionAbi :: Text -> IO Method
- makeSrcMaps :: Text -> Maybe (Seq SrcMap)
- readSolc :: FilePath -> IO (Maybe (Map Text SolcContract, SourceCache))
- readJSON :: Text -> Maybe (Map Text SolcContract, Map Text Value, [(Text, Maybe ByteString)])
- readStdJSON :: Text -> Maybe (Map Text SolcContract, Map Text Value, [(Text, Maybe ByteString)])
- readCombinedJSON :: Text -> Maybe (Map Text SolcContract, Map Text Value, [(Text, Maybe ByteString)])
- runtimeCode :: Lens' SolcContract ByteString
- runtimeCodehash :: Lens' SolcContract W256
- creationCodehash :: Lens' SolcContract W256
- runtimeSrcmap :: Lens' SolcContract (Seq SrcMap)
- creationSrcmap :: Lens' SolcContract (Seq SrcMap)
- sourceFiles :: Lens' SourceCache [(Text, ByteString)]
- sourceLines :: Lens' SourceCache [Vector ByteString]
- sourceAsts :: Lens' SourceCache (Map Text Value)
- immutableReferences :: Lens' SolcContract (Map W256 [Reference])
- stripBytecodeMetadata :: ByteString -> ByteString
- stripBytecodeMetadataSym :: [Expr Byte] -> [Expr Byte]
- signature :: AsValue s => s -> Text
- solc :: Language -> Text -> IO Text
- data Language
- stdjson :: Language -> Text -> Text
- parseMethodInput :: AsValue s => s -> (Text, AbiType)
- lineSubrange :: Vector ByteString -> (Int, Int) -> Int -> Maybe (Int, Int)
- astIdMap :: Foldable f => f Value -> Map Int Value
- astSrcMap :: Map Int Value -> SrcMap -> Maybe Value
- containsLinkerHole :: Text -> Bool
- makeSourceCache :: [(Text, Maybe ByteString)] -> Map Text Value -> IO SourceCache
Documentation
solcRuntime :: Text -> Text -> IO (Maybe ByteString) Source #
yulRuntime :: Text -> Text -> IO (Maybe ByteString) Source #
data SolcContract Source #
SolcContract | |
|
Instances
data StorageItem Source #
Instances
Show StorageItem Source # | |
Defined in EVM.Solidity showsPrec :: Int -> StorageItem -> ShowS # show :: StorageItem -> String # showList :: [StorageItem] -> ShowS # | |
Eq StorageItem Source # | |
Defined in EVM.Solidity (==) :: StorageItem -> StorageItem -> Bool # (/=) :: StorageItem -> StorageItem -> Bool # |
data SourceCache Source #
SourceCache | |
|
Instances
SM | |
|
Instances
Generic SrcMap Source # | |
Show SrcMap Source # | |
Eq SrcMap Source # | |
Ord SrcMap Source # | |
type Rep SrcMap Source # | |
Defined in EVM.Solidity type Rep SrcMap = D1 ('MetaData "SrcMap" "EVM.Solidity" "hevm-0.50.1-inplace" '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) :*: S1 ('MetaSel ('Just "srcMapModifierDepth") 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int))))) |
Method | |
|
Instances
Generic Method Source # | |
Show Method Source # | |
Eq Method Source # | |
Ord Method Source # | |
type Rep Method Source # | |
Defined in EVM.Solidity type Rep Method = D1 ('MetaData "Method" "EVM.Solidity" "hevm-0.50.1-inplace" 'False) (C1 ('MetaCons "Method" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_methodOutput") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [(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) :*: S1 ('MetaSel ('Just "_methodMutability") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Mutability))))) |
Reference | |
|
data Mutability Source #
Pure | specified to not read blockchain state |
View | specified to not modify the blockchain state |
NonPayable | function does not accept Ether - the default |
Payable | function accepts Ether |
Instances
storageLayout :: Lens' SolcContract (Maybe (Map Text StorageItem)) Source #
constructorInputs :: Lens' SolcContract [(Text, AbiType)] Source #
readSolc :: FilePath -> IO (Maybe (Map Text SolcContract, SourceCache)) Source #
readJSON :: Text -> Maybe (Map Text SolcContract, Map Text Value, [(Text, Maybe ByteString)]) Source #
readStdJSON :: Text -> Maybe (Map Text SolcContract, Map Text Value, [(Text, Maybe ByteString)]) Source #
readCombinedJSON :: Text -> Maybe (Map Text SolcContract, Map Text Value, [(Text, Maybe ByteString)]) Source #
sourceFiles :: Lens' SourceCache [(Text, ByteString)] Source #
sourceAsts :: Lens' SourceCache (Map Text Value) Source #
stripBytecodeMetadata :: ByteString -> ByteString Source #
When doing CREATE and passing constructor arguments, Solidity loads the argument data via the creation bytecode, since there is no "calldata" for CREATE.
This interferes with our ability to look up the current contract by codehash, so we must somehow strip away this extra suffix. Luckily we can detect the end of the actual bytecode by looking for the "metadata hash". (Not 100% correct, but works in practice.)
Actually, we strip away the entire BZZR suffix too, because as long as the codehash matches otherwise, we don't care if there is some difference there.
astIdMap :: Foldable f => f Value -> Map Int Value Source #
Every node in the AST has an ID, and other nodes reference those IDs. This function recurses through the tree looking for objects with the "id" key and makes a big map from ID to value.
containsLinkerHole :: Text -> Bool Source #
makeSourceCache :: [(Text, Maybe ByteString)] -> Map Text Value -> IO SourceCache Source #