| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Michelson.Runtime
Contents
Description
Interpreter and typechecker of a contract in Morley language.
Synopsis
- originateContract :: FilePath -> OriginationOperation -> ("verbose" :! Bool) -> IO Address
- runContract :: Maybe Timestamp -> Word64 -> Mutez -> FilePath -> Value -> Contract -> TxData -> ("verbose" :! Bool) -> ("dryRun" :! Bool) -> IO ()
- transfer :: Maybe Timestamp -> Word64 -> FilePath -> Address -> TxData -> ("verbose" :! Bool) -> ("dryRun" :? Bool) -> IO ()
- parseContract :: Maybe FilePath -> Text -> Either ParserException (Contract' ParsedOp)
- parseExpandContract :: Maybe FilePath -> Text -> Either ParserException Contract
- readAndParseContract :: Maybe FilePath -> IO (Contract' ParsedOp)
- prepareContract :: Maybe FilePath -> IO Contract
- typeCheckWithDb :: FilePath -> Contract -> IO (Either TCError SomeContract)
- data ContractState = ContractState {
- csBalance :: !Mutez
- csStorage :: !Value
- csContract :: !Contract
- csTypedContract :: !(Maybe SomeContract)
- csTypedStorage :: !(Maybe SomeValue)
- data AddressState
- data TxData = TxData {
- tdSenderAddress :: !Address
- tdParameter :: !Value
- tdAmount :: !Mutez
- data InterpreterOp
- data InterpreterRes = InterpreterRes {
- _irGState :: !GState
- _irOperations :: [InterpreterOp]
- _irUpdates :: ![GStateUpdate]
- _irInterpretResults :: [(Address, InterpretResult)]
- _irSourceAddress :: !(Maybe Address)
- _irRemainingSteps :: !RemainingSteps
- data InterpreterError' a
- = IEUnknownContract !a
- | IEInterpreterFailed !a !InterpretError
- | IEAlreadyOriginated !a !ContractState
- | IEUnknownSender !a
- | IEUnknownManager !a
- | IENotEnoughFunds !a !Mutez
- | IEZeroTransaction !a
- | IEFailedToApplyUpdates !GStateUpdateError
- | IEIllTypedContract !TCError
- | IEIllTypedStorage !TCError
- | IEIllTypedParameter !TCError
- type InterpreterError = InterpreterError' Address
- interpreterPure :: Timestamp -> RemainingSteps -> GState -> [InterpreterOp] -> Either InterpreterError InterpreterRes
- irInterpretResults :: Lens' InterpreterRes [(Address, InterpretResult)]
- irUpdates :: Lens' InterpreterRes [GStateUpdate]
High level interface for end user
originateContract :: FilePath -> OriginationOperation -> ("verbose" :! Bool) -> IO Address Source #
Originate a contract. Returns the address of the originated contract.
runContract :: Maybe Timestamp -> Word64 -> Mutez -> FilePath -> Value -> Contract -> TxData -> ("verbose" :! Bool) -> ("dryRun" :! Bool) -> IO () Source #
Run a contract. The contract is originated first (if it's not already) and then we pretend that we send a transaction to it.
transfer :: Maybe Timestamp -> Word64 -> FilePath -> Address -> TxData -> ("verbose" :! Bool) -> ("dryRun" :? Bool) -> IO () Source #
Send a transaction to given address with given parameters.
Other helpers
parseContract :: Maybe FilePath -> Text -> Either ParserException (Contract' ParsedOp) Source #
Parse a contract from Text.
parseExpandContract :: Maybe FilePath -> Text -> Either ParserException Contract Source #
Parse a contract from Text and expand macros.
prepareContract :: Maybe FilePath -> IO Contract Source #
Read a contract using readAndParseContract, expand and
flatten. The contract is not type checked.
typeCheckWithDb :: FilePath -> Contract -> IO (Either TCError SomeContract) Source #
Re-exports
data ContractState Source #
State of a contract with code.
Constructors
| ContractState | |
Fields
| |
Instances
| Show ContractState Source # | |
Defined in Michelson.Runtime.GState Methods showsPrec :: Int -> ContractState -> ShowS # show :: ContractState -> String # showList :: [ContractState] -> ShowS # | |
| ToJSON ContractState Source # | |
Defined in Michelson.Runtime.GState Methods toJSON :: ContractState -> Value # toEncoding :: ContractState -> Encoding # toJSONList :: [ContractState] -> Value # toEncodingList :: [ContractState] -> Encoding # | |
| FromJSON ContractState Source # | |
Defined in Michelson.Runtime.GState Methods parseJSON :: Value -> Parser ContractState # parseJSONList :: Value -> Parser [ContractState] # | |
| Buildable ContractState Source # | |
Defined in Michelson.Runtime.GState Methods build :: ContractState -> Builder # | |
data AddressState Source #
State of an arbitrary address.
Constructors
| ASSimple !Mutez | For contracts without code we store only its balance. |
| ASContract !ContractState | For contracts with code we store more state represented by
|
Instances
Data associated with a particular transaction.
Constructors
| TxData | |
Fields
| |
For testing
data InterpreterOp Source #
Operations executed by interpreter.
In our model one Michelson's operation (operation type in Michelson)
corresponds to 0 or 1 interpreter operation.
Note: Address is not part of TxData, because TxData is
supposed to be provided by the user, while Address can be
computed by our code.
Constructors
| OriginateOp !OriginationOperation | Originate a contract. |
| TransferOp Address TxData | Send a transaction to given address which is assumed to be the address of an originated contract. |
Instances
| Show InterpreterOp Source # | |
Defined in Michelson.Runtime Methods showsPrec :: Int -> InterpreterOp -> ShowS # show :: InterpreterOp -> String # showList :: [InterpreterOp] -> ShowS # | |
data InterpreterRes Source #
Result of a single execution of interpreter.
Constructors
| InterpreterRes | |
Fields
| |
Instances
| Show InterpreterRes Source # | |
Defined in Michelson.Runtime Methods showsPrec :: Int -> InterpreterRes -> ShowS # show :: InterpreterRes -> String # showList :: [InterpreterRes] -> ShowS # | |
| Semigroup InterpreterRes Source # | |
Defined in Michelson.Runtime Methods (<>) :: InterpreterRes -> InterpreterRes -> InterpreterRes # sconcat :: NonEmpty InterpreterRes -> InterpreterRes # stimes :: Integral b => b -> InterpreterRes -> InterpreterRes # | |
data InterpreterError' a Source #
Errors that can happen during contract interpreting.
Type parameter a determines how contracts will be represented
in these errors, e.g. Address
Constructors
| IEUnknownContract !a | The interpreted contract hasn't been originated. |
| IEInterpreterFailed !a !InterpretError | Interpretation of Michelson contract failed. |
| IEAlreadyOriginated !a !ContractState | A contract is already originated. |
| IEUnknownSender !a | Sender address is unknown. |
| IEUnknownManager !a | Manager address is unknown. |
| IENotEnoughFunds !a !Mutez | Sender doesn't have enough funds. |
| IEZeroTransaction !a | Sending 0tz towards an address. |
| IEFailedToApplyUpdates !GStateUpdateError | Failed to apply updates to GState. |
| IEIllTypedContract !TCError | A contract is ill-typed. |
| IEIllTypedStorage !TCError | Contract storage is ill-typed |
| IEIllTypedParameter !TCError | Contract parameter is ill-typed |
Instances
| Show a => Show (InterpreterError' a) Source # | |
Defined in Michelson.Runtime Methods showsPrec :: Int -> InterpreterError' a -> ShowS # show :: InterpreterError' a -> String # showList :: [InterpreterError' a] -> ShowS # | |
| (Typeable a, Show a, Buildable a) => Exception (InterpreterError' a) Source # | |
Defined in Michelson.Runtime Methods toException :: InterpreterError' a -> SomeException # fromException :: SomeException -> Maybe (InterpreterError' a) # displayException :: InterpreterError' a -> String # | |
| Buildable a => Buildable (InterpreterError' a) Source # | |
Defined in Michelson.Runtime Methods build :: InterpreterError' a -> Builder # | |
interpreterPure :: Timestamp -> RemainingSteps -> GState -> [InterpreterOp] -> Either InterpreterError InterpreterRes Source #
Implementation of interpreter outside IO. It reads operations,
interprets them one by one and updates state accordingly.
Each operation from the passed list is fully interpreted before
the next one is considered.