| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
EVM.Solidity
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 FunctionSelector Method
- eventMap :: Map W256 Event
- errorMap :: Map W256 SolError
- immutableReferences :: Map W256 [Reference]
- storageLayout :: Maybe (Map Text StorageItem)
- runtimeSrcmap :: Seq SrcMap
- creationSrcmap :: Seq SrcMap
- newtype Contracts = Contracts (Map Text SolcContract)
- data ProjectType
- data BuildOutput = BuildOutput {}
- data StorageItem = StorageItem {}
- data SourceCache = SourceCache {}
- data SrcMap = SM {}
- data CodeType
- data Method = Method {
- output :: [(Text, AbiType)]
- inputs :: [(Text, AbiType)]
- name :: Text
- methodSignature :: Text
- mutability :: Mutability
- data SlotType
- data Reference = Reference {}
- data Mutability
- = Pure
- | View
- | NonPayable
- | Payable
- readBuildOutput :: FilePath -> ProjectType -> IO (Either String BuildOutput)
- functionAbi :: Text -> IO Method
- makeSrcMaps :: Text -> Maybe (Seq SrcMap)
- readSolc :: ProjectType -> FilePath -> FilePath -> IO (Either String BuildOutput)
- readJSON :: ProjectType -> Text -> Text -> Maybe (Contracts, Asts, Sources)
- readStdJSON :: Text -> Maybe (Contracts, Asts, Sources)
- 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 :: FilePath -> Sources -> Asts -> IO SourceCache
Documentation
solcRuntime :: Text -> Text -> IO (Maybe ByteString) Source #
yulRuntime :: Text -> Text -> IO (Maybe ByteString) Source #
Constructors
| JumpInto | |
| JumpFrom | |
| JumpRegular |
Instances
| Generic JumpType Source # | |
| Show JumpType Source # | |
| Eq JumpType Source # | |
| Ord JumpType Source # | |
Defined in EVM.Solidity | |
| type Rep JumpType Source # | |
Defined in EVM.Solidity | |
data SolcContract Source #
Constructors
| SolcContract | |
Fields
| |
Instances
A mapping from contract identifiers (filepath:name) to a SolcContract object
Constructors
| Contracts (Map Text SolcContract) |
data ProjectType Source #
The various project types understood by hevm
Constructors
| DappTools | |
| CombinedJSON | |
| Foundry |
Instances
| Read ProjectType Source # | |
Defined in EVM.Solidity | |
| Show ProjectType Source # | |
Defined in EVM.Solidity | |
| Eq ProjectType Source # | |
Defined in EVM.Solidity Methods (==) :: ProjectType -> ProjectType -> Bool Source # (/=) :: ProjectType -> ProjectType -> Bool Source # | |
| ParseField ProjectType Source # | |
Defined in EVM.Solidity | |
data BuildOutput Source #
Constructors
| BuildOutput | |
Fields
| |
Instances
| Monoid BuildOutput Source # | |
Defined in EVM.Solidity Methods mempty :: BuildOutput Source # mappend :: BuildOutput -> BuildOutput -> BuildOutput Source # mconcat :: [BuildOutput] -> BuildOutput Source # | |
| Semigroup BuildOutput Source # | |
Defined in EVM.Solidity Methods (<>) :: BuildOutput -> BuildOutput -> BuildOutput Source # sconcat :: NonEmpty BuildOutput -> BuildOutput Source # stimes :: Integral b => b -> BuildOutput -> BuildOutput Source # | |
| Show BuildOutput Source # | |
Defined in EVM.Solidity | |
| Eq BuildOutput Source # | |
Defined in EVM.Solidity Methods (==) :: BuildOutput -> BuildOutput -> Bool Source # (/=) :: BuildOutput -> BuildOutput -> Bool Source # | |
data StorageItem Source #
Instances
| Show StorageItem Source # | |
Defined in EVM.Solidity | |
| Eq StorageItem Source # | |
Defined in EVM.Solidity Methods (==) :: StorageItem -> StorageItem -> Bool Source # (/=) :: StorageItem -> StorageItem -> Bool Source # | |
data SourceCache Source #
Constructors
| SourceCache | |
Instances
Constructors
| 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.51.2-inplace" 'False) (C1 ('MetaCons "SM" 'PrefixI 'True) ((S1 ('MetaSel ('Just "offset") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "length") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "file") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "jump") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 JumpType) :*: S1 ('MetaSel ('Just "modifierDepth") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))))) | |
Instances
| Show CodeType Source # | |
| Eq CodeType Source # | |
| Ord CodeType Source # | |
Defined in EVM.Solidity | |
Constructors
| Method | |
Fields
| |
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.51.2-inplace" 'False) (C1 ('MetaCons "Method" 'PrefixI 'True) ((S1 ('MetaSel ('Just "output") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, AbiType)]) :*: S1 ('MetaSel ('Just "inputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, AbiType)])) :*: (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "methodSignature") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "mutability") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mutability))))) | |
Constructors
| StorageMapping (NonEmpty AbiType) AbiType | |
| StorageValue AbiType |
data Mutability Source #
Constructors
| 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
readBuildOutput :: FilePath -> ProjectType -> IO (Either String BuildOutput) Source #
Reads all solc ouput json files found under the provided filepath and returns them merged into a BuildOutput
readSolc :: ProjectType -> FilePath -> FilePath -> IO (Either String BuildOutput) Source #
readStdJSON :: Text -> Maybe (Contracts, Asts, Sources) Source #
Parses the standard json output from solc
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 :: FilePath -> Sources -> Asts -> IO SourceCache Source #