Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Name
- type UiWidget = Widget Name
- data UiVmState = UiVmState {
- _uiVm :: VM
- _uiVmNextStep :: Stepper ()
- _uiVmStackList :: List Name (Int, Word)
- _uiVmBytecodeList :: List Name (Int, Op)
- _uiVmTraceList :: List Name Text
- _uiVmSolidityList :: List Name (Int, ByteString)
- _uiVmSolc :: Maybe SolcContract
- _uiVmDapp :: Maybe DappInfo
- _uiVmStepCount :: Int
- _uiVmFirstState :: UiVmState
- _uiVmMessage :: Maybe String
- _uiVmNotes :: [String]
- _uiVmShowMemory :: Bool
- data UiTestPickerState = UiTestPickerState {
- _testPickerList :: List Name (Text, Text)
- _testPickerDapp :: DappInfo
- data UiBrowserState = UiBrowserState {}
- data UiState
- uiVmTraceList :: Lens' UiVmState (List Name Text)
- uiVmStepCount :: Lens' UiVmState Int
- uiVmStackList :: Lens' UiVmState (List Name (Int, Word))
- uiVmSolidityList :: Lens' UiVmState (List Name (Int, ByteString))
- uiVmSolc :: Lens' UiVmState (Maybe SolcContract)
- uiVmShowMemory :: Lens' UiVmState Bool
- uiVmNotes :: Lens' UiVmState [String]
- uiVmNextStep :: Lens' UiVmState (Stepper ())
- uiVmMessage :: Lens' UiVmState (Maybe String)
- uiVmFirstState :: Lens' UiVmState UiVmState
- uiVmDapp :: Lens' UiVmState (Maybe DappInfo)
- uiVmBytecodeList :: Lens' UiVmState (List Name (Int, Op))
- uiVm :: Lens' UiVmState VM
- testPickerList :: Lens' UiTestPickerState (List Name (Text, Text))
- testPickerDapp :: Lens' UiTestPickerState DappInfo
- browserVm :: Lens' UiBrowserState UiVmState
- browserContractList :: Lens' UiBrowserState (List Name (Addr, Contract))
- _UiTestPickerScreen :: Prism' UiState UiTestPickerState
- _UiVmBrowserScreen :: Prism' UiState UiBrowserState
- _UiVmScreen :: Prism' UiState UiVmState
- type Pred a = a -> Bool
- data StepMode
- data StepOutcome a
- interpret :: (?fetcher :: Fetcher) => StepMode -> Stepper a -> State UiVmState (StepOutcome a)
- isUnitTestContract :: Text -> DappInfo -> Bool
- mkVty :: IO Vty
- runFromVM :: VM -> IO VM
- main :: UnitTestOptions -> FilePath -> FilePath -> IO ()
- data StepPolicy
- takeStep :: (?fetcher :: Fetcher) => UiVmState -> StepPolicy -> StepMode -> EventM n (Next UiState)
- app :: UnitTestOptions -> App UiState () Name
- initialUiVmStateForTest :: UnitTestOptions -> DappInfo -> (Text, Text) -> UiVmState
- myTheme :: [(AttrName, Attr)]
- drawUi :: UiState -> [UiWidget]
- drawTestPicker :: UiTestPickerState -> [UiWidget]
- drawVmBrowser :: UiBrowserState -> [UiWidget]
- drawVm :: UiVmState -> [UiWidget]
- drawHelpBar :: UiWidget
- stepOneOpcode :: UiVmState -> UiVmState
- isNextSourcePosition :: UiVmState -> Pred VM
- isNextSourcePositionWithoutEntering :: UiVmState -> Pred VM
- currentSrcMap :: DappInfo -> VM -> Maybe SrcMap
- currentSolc :: DappInfo -> VM -> Maybe SolcContract
- renderVm :: UiVmState -> UiVmState
- updateUiVmState :: UiVmState -> VM -> UiVmState
- drawStackPane :: UiVmState -> UiWidget
- showWordExplanation :: W256 -> Maybe DappInfo -> Text
- drawBytecodePane :: UiVmState -> UiWidget
- dim :: Widget n -> Widget n
- withHighlight :: Bool -> Widget n -> Widget n
- drawTracePane :: UiVmState -> UiWidget
- drawSolidityPane :: UiVmState -> UiWidget
- ifTallEnough :: Int -> Widget n -> Widget n -> Widget n
- showPc :: (Integral a, Show a) => a -> String
- opWidget :: (Integral a, Show a) => (a, Op) -> Widget n
- selectedAttr :: AttrName
- dimAttr :: AttrName
- wordAttr :: AttrName
- boldAttr :: AttrName
- activeAttr :: AttrName
Documentation
UiVmState | |
|
data UiTestPickerState Source #
data UiBrowserState Source #
uiVmSolidityList :: Lens' UiVmState (List Name (Int, ByteString)) Source #
testPickerList :: Lens' UiTestPickerState (List Name (Text, Text)) Source #
data StepOutcome a Source #
Each step command in the terminal should finish immediately with one of these outcomes.
interpret :: (?fetcher :: Fetcher) => StepMode -> Stepper a -> State UiVmState (StepOutcome a) Source #
This turns a Stepper
into a state action usable
from within the TTY loop, yielding a StepOutcome
depending on the StepMode
.
main :: UnitTestOptions -> FilePath -> FilePath -> IO () 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 #
StepNormally | Allow blocking and returning |
StepTimidly | Forbid blocking and returning |
takeStep :: (?fetcher :: Fetcher) => UiVmState -> StepPolicy -> StepMode -> EventM n (Next UiState) Source #
initialUiVmStateForTest :: UnitTestOptions -> DappInfo -> (Text, Text) -> UiVmState Source #
drawTestPicker :: UiTestPickerState -> [UiWidget] Source #
drawVmBrowser :: UiBrowserState -> [UiWidget] Source #
stepOneOpcode :: UiVmState -> UiVmState Source #
currentSolc :: DappInfo -> VM -> Maybe SolcContract Source #
drawStackPane :: UiVmState -> UiWidget Source #
drawBytecodePane :: UiVmState -> UiWidget Source #
drawTracePane :: UiVmState -> UiWidget Source #
drawSolidityPane :: UiVmState -> UiWidget Source #