hevm-0.51.1: Ethereum virtual machine evaluator
Safe HaskellSafe-Inferred
LanguageGHC2021

EVM.TTY

Synopsis

Documentation

data Name Source #

Instances

Instances details
Show Name Source # 
Instance details

Defined in EVM.TTY

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Eq Name Source # 
Instance details

Defined in EVM.TTY

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Ord Name Source # 
Instance details

Defined in EVM.TTY

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

data UiVmState Source #

Constructors

UiVmState 

Instances

Instances details
(k ~ A_Lens, a ~ Bool, b ~ Bool) => LabelOptic "showMemory" k UiVmState UiVmState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ Map Int (VM, Stepper ()), b ~ Map Int (VM, Stepper ())) => LabelOptic "snapshots" k UiVmState UiVmState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ Int, b ~ Int) => LabelOptic "step" k UiVmState UiVmState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ Stepper (), b ~ Stepper ()) => LabelOptic "stepper" k UiVmState UiVmState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ UnitTestOptions, b ~ UnitTestOptions) => LabelOptic "testOpts" k UiVmState UiVmState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ VM, b ~ VM) => LabelOptic "vm" k UiVmState UiVmState a b Source # 
Instance details

Defined in EVM.TTY

data UiTestPickerState Source #

Instances

Instances details
(k ~ A_Lens, a ~ DappInfo, b ~ DappInfo) => LabelOptic "dapp" k UiTestPickerState UiTestPickerState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ UnitTestOptions, b ~ UnitTestOptions) => LabelOptic "opts" k UiTestPickerState UiTestPickerState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ List Name (Text, Text), b ~ List Name (Text, Text)) => LabelOptic "tests" k UiTestPickerState UiTestPickerState a b Source # 
Instance details

Defined in EVM.TTY

data UiBrowserState Source #

Constructors

UiBrowserState 

Instances

Instances details
(k ~ A_Lens, a ~ List Name (Addr, Contract), b ~ List Name (Addr, Contract)) => LabelOptic "contracts" k UiBrowserState UiBrowserState a b Source # 
Instance details

Defined in EVM.TTY

(k ~ A_Lens, a ~ UiVmState, b ~ UiVmState) => LabelOptic "vm" k UiBrowserState UiBrowserState a b Source # 
Instance details

Defined in EVM.TTY

type Pred a = a -> Bool Source #

data StepMode Source #

Constructors

Step !Int

Run a specific number of steps

StepUntil (Pred VM)

Finish when a VM predicate holds

data Continuation a Source #

Each step command in the terminal should finish immediately with one of these outcomes.

Constructors

Stopped a

Program finished

Continue (Stepper a)

Took one step; more steps to go

interpret :: (?fetcher :: Fetcher, ?maxIter :: Maybe Integer) => StepMode -> Stepper a -> StateT UiVmState IO (Continuation a) Source #

This turns a Stepper into a state action usable from within the TTY loop, yielding a StepOutcome depending on the StepMode.

keepExecuting :: (?fetcher :: Fetcher, ?maxIter :: Maybe Integer) => StepMode -> Stepper a -> StateT UiVmState IO (Continuation a) Source #

takeStep :: (?fetcher :: Fetcher, ?maxIter :: Maybe Integer) => UiVmState -> StepMode -> EventM n UiState () Source #

backstepUntil :: (?fetcher :: Fetcher, ?maxIter :: Maybe Integer) => (UiVmState -> Pred VM) -> EventM n UiState () Source #

backstep :: (?fetcher :: Fetcher, ?maxIter :: Maybe Integer) => UiVmState -> IO UiVmState Source #

appEvent :: (?fetcher :: Fetcher, ?maxIter :: Maybe Integer) => BrickEvent Name e -> EventM Name UiState () Source #

opWidget :: (Integral a, Show a) => (a, Op) -> Widget n Source #