rewrite-inspector-0.1.0.11: Inspection of rewriting steps

Copyright(C) 2019 QBayLogic
LicenseBSD2 (see the file LICENSE)
MaintainerOrestis Melkonian <melkon.or@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Types

Contents

Description

Basic datatypes.

Synopsis

Basic types.

type Binder = String Source #

Program binders (i.e. top-level identifiers) are identified by their name.

data NoCustomEvent Source #

Our Brick TUI does not use any custom events.

data Name Source #

The type of resource names, used throughout the TUI.

Constructors

LeftViewport 
RightViewport

viewports

FormField String

form fields

SearchResult Int

search results with numbered occurrences

Other 
Instances
Eq Name Source # 
Instance details

Defined in Types

Methods

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

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

Ord Name Source # 
Instance details

Defined in Types

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 #

Show Name Source # 
Instance details

Defined in Types

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

MonadFail (EventM Name) Source #

Allow pattern matches in EventM monadic do blocks.

Instance details

Defined in BrickUI

Methods

fail :: String -> EventM Name a #

type Cursor = CursorLocation Name Source #

Type of cursors in our TUI.

data Command Source #

Commands that the user can issue through the input form.

Constructors

Step Int

move to given step in the current binder

Trans String

move to the next/previous transformation with the given name

Search String

move to the next/previous occurrence of the searched string

Instances
Eq Command Source # 
Instance details

Defined in Types

Methods

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

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

Ord Command Source # 
Instance details

Defined in Types

Show Command Source # 
Instance details

Defined in Types

data OptionsUI term Source #

Options kept and changed throught the TUI's input form.

Constructors

OptionsUI 

Fields

opts :: forall term term. Lens (OptionsUI term) (OptionsUI term) (Options term) (Options term) Source #

com :: forall term. Lens' (OptionsUI term) Command Source #

data VizState term Source #

Bottom-level state of the UI (navigate steps of a top-level binder).

Constructors

VizState 

Fields

steps :: forall term. Lens' (VizState term) (History term (Ctx term)) Source #

rightN :: forall term. Lens' (VizState term) Int Source #

prevState :: forall term. Lens' (VizState term) (Maybe (VizState term)) Source #

leftN :: forall term. Lens' (VizState term) Int Source #

curStep :: forall term. Lens' (VizState term) Int Source #

curOccur :: forall term. Lens' (VizState term) Int Source #

curExpr :: forall term. Lens' (VizState term) term Source #

data VizStates term Source #

Top-level state of the UI (navigate top-level binders).

Constructors

VizStates 

Fields

width :: forall term. Lens' (VizStates term) Int Source #

states :: forall term. Lens' (VizStates term) (Map Binder (VizState term)) Source #

showBot :: forall term. Lens' (VizStates term) Bool Source #

scroll :: forall term. Lens' (VizStates term) Bool Source #

height :: forall term. Lens' (VizStates term) Int Source #

form :: forall term. Lens' (VizStates term) (Form (OptionsUI term) NoCustomEvent Name) Source #

curBinder :: forall term. Lens' (VizStates term) Binder Source #

binders :: forall term. Lens' (VizStates term) [Binder] Source #

Getters and setters.

mkForm :: forall term. Diff term => OptionsUI term -> Form (OptionsUI term) NoCustomEvent Name Source #

Create the input form.

createVizStates :: forall term. Diff term => History term (Ctx term) -> VizStates term Source #

Group the rewrite history by the different top-level binders.

initialState :: Diff term => History term (Ctx term) -> VizState term Source #

State initialization for the bottom layer.

currentStepName :: VizState term -> String Source #

Get the name of the current transformation.

getStep :: VizStates term -> Binder -> (Int, Int, String) Source #

Get information about the current step.

getCurrentState :: VizStates term -> VizState term Source #

Get the current state of the bottom layer.

getSearchString :: Diff term => VizStates term -> String Source #

Get the current string we are searching for. NB: Returns the empty string of no search command has been issued.

formData :: forall term. Diff term => Lens' (VizStates term) (OptionsUI term) Source #

Lens from the global state to the input form's data.

updateState :: VizStates term -> VizState term -> VizStates term Source #

Update the local state of the current binder.

getCodeWidth :: VizStates term -> Int Source #

Get the available code width for one of the two code panes.

stepBinder :: VizStates term -> VizStates term Source #

Cycle through top-level binders in the global state.

stepBinder
Proceed forward.
unstepBinder
Proceed backward.

unstepBinder :: VizStates term -> VizStates term Source #

Cycle through top-level binders in the global state.

stepBinder
Proceed forward.
unstepBinder
Proceed backward.

step :: Diff term => VizState term -> VizState term Source #

Cycle through transformations of the current binder in the local state.

step
Proceed forward.
unstep
Proceed backward.
reset
Reset to the initial state.

unstep :: Diff term => VizState term -> VizState term Source #

Cycle through transformations of the current binder in the local state.

step
Proceed forward.
unstep
Proceed backward.
reset
Reset to the initial state.

reset :: Diff term => VizState term -> VizState term Source #

Cycle through transformations of the current binder in the local state.

step
Proceed forward.
unstep
Proceed backward.
reset
Reset to the initial state.

User-issued commands.

data Direction Source #

Some user commands have a notion of direction; either going forth or back.

Constructors

Forward 
Backward 

moveTo :: Diff term => Int -> VizState term -> VizState term Source #

Move to a specified step of the transformations of the current binder.

nextTrans :: Diff term => Direction -> String -> VizState term -> VizState term Source #

Move to the next/previous step with the given transformation name.

nextOccur :: Diff term => Direction -> VizState term -> VizState term Source #

Cycle through search occurrences.