| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
EVM.Emacs
Synopsis
- data UiVmState = UiVmState {}
- uiVmStepCount :: Lens' UiVmState Int
- uiVmSolc :: Lens' UiVmState (Maybe SolcContract)
- uiVmSentHashes :: Lens' UiVmState (Set W256)
- uiVmNextStep :: Lens' UiVmState (Stepper ())
- uiVmMessage :: Lens' UiVmState (Maybe Text)
- uiVmFirstState :: Lens' UiVmState UiVmState
- uiVmFetcher :: Lens' UiVmState Fetcher
- uiVmDapp :: Lens' UiVmState (Maybe DappInfo)
- uiVm :: Lens' UiVmState VM
- type Pred a = a -> Bool
- data StepMode
- data StepOutcome a
- interpret :: StepMode -> Stepper a -> State UiVmState (StepOutcome a)
- stepOneOpcode :: UiVmState -> UiVmState
- updateUiVmState :: UiVmState -> VM -> UiVmState
- updateSentHashes :: UiVmState -> UiVmState
- type Sexp = WellFormedSExpr HaskLikeAtom
- prompt :: Console (Maybe Sexp)
- class SDisplay a where
- display :: SDisplay a => a -> Text
- txt :: Show a => a -> Text
- data UiState
- type Console a = StateT UiState IO a
- output :: SDisplay a => a -> Console ()
- main :: IO ()
- loop :: Console ()
- handle :: Sexp -> Console ()
- handleCmd :: UiState -> (Text, [Sexp]) -> Console ()
- atFileLine :: DappInfo -> Text -> Int -> VM -> Bool
- codeByHash :: W256 -> VM -> Maybe ByteString
- allHashes :: VM -> Set W256
- prettifyCode :: ByteString -> String
- outputVm :: Console ()
- isNextSourcePosition :: UiVmState -> Pred VM
- parseStepMode :: UiVmState -> Text -> Maybe StepMode
- data StepPolicy
- takeStep :: UiVmState -> StepPolicy -> StepMode -> Console ()
- quoted :: Text -> Text
- sexpMemory :: Buffer -> SExpr Text
- defaultUnitTestOptions :: MonadIO m => m UnitTestOptions
- initialStateForTest :: UnitTestOptions -> (Text, Text) -> UiVmState
Documentation
Constructors
| UiVmState | |
| Fields 
 | |
data StepOutcome a Source #
stepOneOpcode :: UiVmState -> UiVmState Source #
type Sexp = WellFormedSExpr HaskLikeAtom Source #
class SDisplay a where Source #
Instances
| SDisplay String Source # | |
| SDisplay ByteString Source # | |
| SDisplay Addr Source # | |
| SDisplay Buffer Source # | |
| SDisplay W256 Source # | |
| SDisplay Word Source # | |
| SDisplay SymWord Source # | |
| SDisplay Contract Source # | |
| SDisplay Storage Source # | |
| SDisplay FrameState Source # | |
| SDisplay FrameContext Source # | |
| SDisplay Frame Source # | |
| SDisplay VM Source # | |
| SDisplay VMResult Source # | |
| SDisplay DappInfo Source # | |
| SDisplay a => SDisplay [a] Source # | |
| SDisplay a => SDisplay (Maybe a) Source # | |
| SDisplay (SExpr Text) Source # | |
| SDisplay (SWord 8) Source # | |
| SDisplay (SWord 256) Source # | |
| (SDisplay k, SDisplay v) => SDisplay (Map k v) Source # | |
codeByHash :: W256 -> VM -> Maybe ByteString Source #
prettifyCode :: ByteString -> String Source #
parseStepMode :: UiVmState -> Text -> Maybe StepMode Source #
Specifies whether to do I/O blocking or VM halting while stepping. When we step backwards, we don't want to allow those things.
data StepPolicy Source #
Constructors
| StepNormally | Allow blocking and returning | 
| StepTimidly | Forbid blocking and returning | 
defaultUnitTestOptions :: MonadIO m => m UnitTestOptions Source #
initialStateForTest :: UnitTestOptions -> (Text, Text) -> UiVmState Source #