Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This package provides an overlay library for Brick that allows individual TUI screen areas to be independently developed and then easily composed into the overall application.
Synopsis
- class Pane n appEv pane | pane -> n
- data family PaneState pane appEv
- type family InitConstraints pane initctxt :: Constraint
- initPaneState :: (Pane n appEv pane, InitConstraints pane i) => i -> PaneState pane appEv
- type family DrawConstraints pane drwctxt n :: Constraint
- drawPane :: (Pane n appEv pane, DrawConstraints pane drawcontext n, Eq n) => PaneState pane appEv -> drawcontext -> Maybe (Widget n)
- type family EventConstraints pane evctxt :: Constraint
- type family EventType pane n appEv
- class DispatchEvent n appev pane evtype
- focusable :: (Pane n appEv pane, EventConstraints pane eventcontext, Eq n) => eventcontext -> PaneState pane appEv -> Seq n
- handlePaneEvent :: (Pane n appEv pane, EventConstraints pane eventcontext, Eq n) => eventcontext -> EventType pane n appEv -> PaneState pane appEv -> EventM n es (PaneState pane appEv)
- type family UpdateType pane
- updatePane :: Pane n appEv pane => UpdateType pane -> PaneState pane appEv -> PaneState pane appEv
- focus1If :: n -> Bool -> Seq n
- class HasFocus b n | b -> n
- getFocus :: HasFocus b n => Lens' b (Focused n)
- newtype Focused n = Focused (Maybe n)
- focused :: Focused n -> Maybe n
- data Panel n appev state (panes :: [Type])
- basePanel :: state -> Panel n appev state '[]
- addToPanel :: Pane n appev pane => InitConstraints pane (Panel n appev state panes) => DrawConstraints pane (Panel n appev state panes) n => EventConstraints pane (Panel n appev state panes) => DispatchEvent n appev pane (EventType pane n appev) => PaneFocus n -> Panel n appev state panes -> Panel n appev state (pane ': panes)
- data PaneFocus n
- onPane :: forall pane n appev state panes. PanelOps pane n appev panes state => Lens' (Panel n appev state panes) (PaneState pane appev)
- onBaseState :: Lens' (Panel n appev state panes) state
- panelDraw :: forall pane n appev s panes. (DrawConstraints pane (Panel n appev s panes) n, PanelOps pane n appev panes s, Pane n appev pane, Eq n) => Panel n appev s panes -> Maybe (Widget n)
- handleFocusAndPanelEvents :: Eq n => Ord n => Lens' (Panel n appev s panes) (FocusRing n) -> Panel n appev s panes -> BrickEvent n appev -> EventM n es (PanelTransition, Panel n appev s panes)
- focusRingUpdate :: (Eq n, Ord n) => Lens' (Panel n appev s panes) (FocusRing n) -> Panel n appev s panes -> Panel n appev s panes
- isPanelModal :: Eq n => Ord n => Lens' (Panel n appev s panes) (FocusRing n) -> Panel n appev s panes -> Bool
- enteredModal :: forall pane n appev state panes. PanelOps pane n appev panes state => PanelTransition -> Panel n appev state panes -> Bool
- exitedModal :: forall pane n appev state panes. PanelOps pane n appev panes state => PanelTransition -> Panel n appev state panes -> Bool
- data PanelMode
- type PanelTransition = Maybe (PanelMode, PanelMode)
- class PanelOps pane n appev panes s | pane -> n where
- handlePanelEvent :: (EventConstraints pane s, Eq n) => s -> pane -> Panel n appev s panes -> BrickEvent n appev -> EventM n es (Panel n appev s panes)
- panelState :: Panel n appev s panes -> PaneState pane appev
- panelStateUpdate :: Panel n appev s panes -> PaneState pane appev -> Panel n appev s panes
- paneNumber :: Panel n appev s panes -> PaneNumber
- data PaneNumber
Pane Specification
Definition and Initialization
class Pane n appEv pane | pane -> n Source #
Class to manage each pane in the Brick TUI.
Type parameters:
pane
= Pane Type, uniquely identifying this paneappEv
= The application's event typen
= Widget type parameter
The PaneState
specifies the state that should be stored globally
and which provides the primary information for handling this pane
(for both draw and event handling operations).
The initPaneState
method is responsible for returning an initial PaneState
value (at startup).
The drawPane
method is called to render the pane into a Widget
(or Nothing
if this Pane should not currently be drawn). It is passed the PaneState
and
also a drawing parameter. The DrawConstraints
can be used to specify
additional instance requirements for the drawing parameter. The global
application state is often passed as this drawing parameter, but the
drawPane
method should only perform DrawConstraints
operations, along with
general Brick drawing operations.
The focusable
method should return the names of the widgets that can be the
target of the FocusRing
in the current state. This should always return an
empty list if the drawPane
returns Nothing
.
The handlePaneEvent
method is called to handle an event that has occurred
within this Pane. It should return the updated PaneState
in the context of
an EventM
monadic operation.
The updatePane
method is called with the UpdateType
to perform any
updating of the PaneState
from the update type data.
type family InitConstraints pane initctxt :: Constraint Source #
Constraints on argument passed to initPaneState
. If there are no
constraints, this may be specified as ()
, or simply omitted because ()
is the default.
initPaneState :: (Pane n appEv pane, InitConstraints pane i) => i -> PaneState pane appEv Source #
Function called to initialize the internal PaneState
Drawing
type family DrawConstraints pane drwctxt n :: Constraint Source #
Constraints on the drawcontext
parameter passed to drawPane
.
drawPane :: (Pane n appEv pane, DrawConstraints pane drawcontext n, Eq n) => PaneState pane appEv -> drawcontext -> Maybe (Widget n) Source #
Event Handling
type family EventConstraints pane evctxt :: Constraint Source #
The constraints that should exist on the eventcontext
argment passed to
focusable
and handlePaneEvent
.
type family EventType pane n appEv Source #
The type of the event argument delivered to handlePaneEvent
. This
should either be Event
or BrickEvent
, depending on what level of
granularity the handlePaneEvent
operates at.
class DispatchEvent n appev pane evtype Source #
The DispatchEvent
class is used to determine which type of event to
dispatch to a Pane
by selecting on the
. This is used
internally in the brick-panes implementation and client code does not need to
explicitly specify instances of this class.EventType
pane n
dispEv
Instances
DispatchEvent n appev pane Event Source # | |
Defined in Brick.Panes | |
DispatchEvent n appev pane (BrickEvent n appev) Source # | |
Defined in Brick.Panes dispEv :: (Pane n appev pane, EventConstraints pane base, Eq n) => (EventType pane n appev :~: BrickEvent n appev) -> base -> BrickEvent n appev -> PaneState pane appev -> EventM n es (PaneState pane appev) |
focusable :: (Pane n appEv pane, EventConstraints pane eventcontext, Eq n) => eventcontext -> PaneState pane appEv -> Seq n Source #
handlePaneEvent :: (Pane n appEv pane, EventConstraints pane eventcontext, Eq n) => eventcontext -> EventType pane n appEv -> PaneState pane appEv -> EventM n es (PaneState pane appEv) Source #
Called to handle an EventType
event for the Pane
. This is typically
only called when (one of the focusable
targets of) the Pane
is the focus
of the FocusRing
. It should modify the internal PaneState
as
appropriate and make any appropriate changes to properly render the Pane
on the next drawPane
call.
Note that this function also receives an eventcontext which it may stipulate constraints on. Those constraints should be *read-only* constraints. This is especially important when the pane is used as part of a panel: the Panel itself is passed as the eventcontext, but the panel may not be modified because the panel event dispatching will discard any changes on completion.
Updating the Pane's state
type family UpdateType pane Source #
Type of data provided to updatePane
updatePane :: Pane n appEv pane => UpdateType pane -> PaneState pane appEv -> PaneState pane appEv Source #
Function called to update the internal PaneState
, using the passed
updateType
argument.
Focus management helpers and constraints
focus1If :: n -> Bool -> Seq n Source #
This is a helper function for a Pane with a single Widget name and a conditional focus. For example, if a widget is always focusable, then it can specify:
instance Pane N E ThisPane () where ... focusable _ = const $ focus1If MyWidgetName True
class HasFocus b n | b -> n Source #
This class allows retrieval of the current focused Widget (if any). This
class is frequently specified as one of the constraints for the
DrawConstraints
or EventConstraints
of a Pane
.
getFocus :: HasFocus b n => Lens' b (Focused n) Source #
Provides a lens from the primary type to the Focused
type, which
specifies the current focused element (if any).
This is a newtype to wrap the identification of the current focused element (if any).
Panel Specification
Definition and Initialization
data Panel n appev state (panes :: [Type]) Source #
A Panel is a recursive data sequence of individual Pane
elements
with a core state. The core state represents the base state of the
Brick application, independent of the various Pane data. Each Pane
has an instance that defines its PaneState
, which is associated
here with a potential Widget name (allowing selected actions; see
handleFocusAndPanelEvents
).
The Panel
type closes over the state
type argument, which is used for all
three of the Pane
constraints (DrawConstraints
, EventConstraints
, and
indirectly the InitConstraints
), which means that the same state
type must
be passed to all three associated Pane methods; a Pane
used outside of the
Panel
container is not constrained in this manner and each method could have
a different argument. For the Panel, the state
is typically the Panel
"beneath" the current Pane, which is the aggregate of the base state and all
Panes added before the current pane.
basePanel :: state -> Panel n appev state '[] Source #
This is the base constructor for Panel that is given the core application state.
addToPanel :: Pane n appev pane => InitConstraints pane (Panel n appev state panes) => DrawConstraints pane (Panel n appev state panes) n => EventConstraints pane (Panel n appev state panes) => DispatchEvent n appev pane (EventType pane n appev) => PaneFocus n -> Panel n appev state panes -> Panel n appev state (pane ': panes) Source #
Specifies when a Pane should receive events.
Always | Indicates that this Pane always receives all events, although it is never part of a focus ring. This should be used for Widgets that have a global event handling. |
Never | Indicates that this Pane's handlePaneEvent is never called |
WhenFocused | Indicates that the pane should receive events when the current focus is
equal to a |
WhenFocusedModal | Indicates that the pane should receive events when the current focus is
equal to a |
WhenFocusedModalHandlingAllEvents | Indicates that the pane should receive events when the current focus is
equal to a |
Pane and base state access
onPane :: forall pane n appev state panes. PanelOps pane n appev panes state => Lens' (Panel n appev state panes) (PaneState pane appev) Source #
This is a lens providing access to the PaneState for a specific Pane in the
Panel. The Pane is typically specified via a type application
(e.g. @MyPane
).
onBaseState :: Lens' (Panel n appev state panes) state Source #
This is a lens providing access to the base application state at the core of the Panel.
Drawing
panelDraw :: forall pane n appev s panes. (DrawConstraints pane (Panel n appev s panes) n, PanelOps pane n appev panes s, Pane n appev pane, Eq n) => Panel n appev s panes -> Maybe (Widget n) Source #
Called to draw a specific pane in the panel. Typically invoked from the applications' global drawing function.
Focus and Event management
handleFocusAndPanelEvents :: Eq n => Ord n => Lens' (Panel n appev s panes) (FocusRing n) -> Panel n appev s panes -> BrickEvent n appev -> EventM n es (PanelTransition, Panel n appev s panes) Source #
Called to handle events for the entire Panel
, including focus-changing
events. The current focused Pane
is determined and that Pane's handler is
called (based on the Widget
names returned as focusable
for that Pane).
If a Pane has no associated Widget name (the PaneFocus
value is specified as
Nothing
when adding the Pane to the Panel) then its handler is never called.
This function returns the updated Panel state, as well as an indication of whether a modal transition occured while handling the event.
This function manages updating the focus when Tab
or Shift-Tab
is
selected, except when the currently focused pane was created with the
WhenFocusedModalHandlingAllEvents
, in which case all events are passed
through to the Pane.
focusRingUpdate :: (Eq n, Ord n) => Lens' (Panel n appev s panes) (FocusRing n) -> Panel n appev s panes -> Panel n appev s panes Source #
When the Panel is managing focus events (e.g. when using
handleFocusAndPanelEvents
), this function can be called if there
has been a situation where the members of the focus ring might need
to be updated. This is automatically called at the end of the
handleFocusAndPanelEvents
, but it should be explicitly called
once when the Panel is initialized, and it can additionally be
called whenever needed in a situation where the
handleFocusAndPanelEvents
invocation is insufficient (e.g. a
separate global action enables a modal pane).
isPanelModal :: Eq n => Ord n => Lens' (Panel n appev s panes) (FocusRing n) -> Panel n appev s panes -> Bool Source #
This function can be called at any time to determine if the Panel is currently displaying a Modal Pane. This needs the Panel object and a lens that can be used to extract the FocusRing from the Panel.
enteredModal :: forall pane n appev state panes. PanelOps pane n appev panes state => PanelTransition -> Panel n appev state panes -> Bool Source #
Indicates if the specified Pane (via Type Application) is the one that was modally entered as a result of processing an event (as indicated by PanelTransition).
exitedModal :: forall pane n appev state panes. PanelOps pane n appev panes state => PanelTransition -> Panel n appev state panes -> Bool Source #
Indicates if the specified Pane (via Type Application) is the one that was modally exited (dismissed) as a result of processing an event (as indicated by PanelTransition).
Indicates the current mode of the Panel. If Modal, the currently active
modal Panel is identified by the PaneNumber, which matches the return value of
the paneNumber
of PanelOps; in general, the use of isPaneModal
is
recommended over attempting to determine _which_ actual modal pane is active.
type PanelTransition = Maybe (PanelMode, PanelMode) Source #
This is returned from the handleFocusAndPanelEvents
function to indicate
whether a modal transition occured during the panel's (and associated Pane's)
handling of this event. This can be used by the outer-level application code
to determine if a modal Pane was entered or exited due to the Event.
Access and operations
class PanelOps pane n appev panes s | pane -> n where Source #
This class defines the various operations that can be performed on a Panel. Most of these operations specify a particular Pane as the target of the operation; the operation is performed on that pane and the Panel is is updated with the result.
The user of this library will not need to develop new instances of this class:
the instances defined internally are sufficient. Users may need to specify
PanelOps
constraints on various functions.
handlePanelEvent :: (EventConstraints pane s, Eq n) => s -> pane -> Panel n appev s panes -> BrickEvent n appev -> EventM n es (Panel n appev s panes) Source #
This is called to pass the VTY Event to the specified Pane's handler with a Panel.
panelState :: Panel n appev s panes -> PaneState pane appev Source #
This is used to obtain the state of a specific Pane within the Panel. The
pane is usually specified by a type application (e.g. @MyPane
).
panelStateUpdate :: Panel n appev s panes -> PaneState pane appev -> Panel n appev s panes Source #
This is used to update the state of a specific Pane within the Panel. The
pane is usually specified by a type application (e.g. @MyPane
).
paneNumber :: Panel n appev s panes -> PaneNumber Source #
This returns an ordinal index of the pane within the panel.
Instances
(TypeError (((('Text "No " :<>: 'ShowType pane) :<>: 'Text " in Panel") :$$: 'Text "Add this pane to your Panel (or move it lower)") :$$: 'Text "(Possibly driven by DrawConstraints)") :: Constraint, Pane n appev pane) => PanelOps pane n appev ('[] :: [Type]) s Source # | |
Defined in Brick.Panes handlePanelEvent :: (EventConstraints pane s, Eq n) => s -> pane -> Panel n appev s '[] -> BrickEvent n appev -> EventM n es (Panel n appev s '[]) Source # panelState :: Panel n appev s '[] -> PaneState pane appev Source # panelStateUpdate :: Panel n appev s '[] -> PaneState pane appev -> Panel n appev s '[] Source # paneNumber :: Panel n appev s '[] -> PaneNumber Source # | |
PanelOps pane n appev panes s => PanelOps pane n appev (o ': panes) s Source # | |
Defined in Brick.Panes handlePanelEvent :: (EventConstraints pane s, Eq n) => s -> pane -> Panel n appev s (o ': panes) -> BrickEvent n appev -> EventM n es (Panel n appev s (o ': panes)) Source # panelState :: Panel n appev s (o ': panes) -> PaneState pane appev Source # panelStateUpdate :: Panel n appev s (o ': panes) -> PaneState pane appev -> Panel n appev s (o ': panes) Source # paneNumber :: Panel n appev s (o ': panes) -> PaneNumber Source # | |
Pane n appev pane => PanelOps pane n appev (pane ': panes) s Source # | |
Defined in Brick.Panes handlePanelEvent :: (EventConstraints pane s, Eq n) => s -> pane -> Panel n appev s (pane ': panes) -> BrickEvent n appev -> EventM n es (Panel n appev s (pane ': panes)) Source # panelState :: Panel n appev s (pane ': panes) -> PaneState pane appev Source # panelStateUpdate :: Panel n appev s (pane ': panes) -> PaneState pane appev -> Panel n appev s (pane ': panes) Source # paneNumber :: Panel n appev s (pane ': panes) -> PaneNumber Source # |
data PaneNumber Source #
Internal bookkeeping to identify a particular Pane within a Panel by number.
Instances
Enum PaneNumber Source # | |
Defined in Brick.Panes succ :: PaneNumber -> PaneNumber # pred :: PaneNumber -> PaneNumber # toEnum :: Int -> PaneNumber # fromEnum :: PaneNumber -> Int # enumFrom :: PaneNumber -> [PaneNumber] # enumFromThen :: PaneNumber -> PaneNumber -> [PaneNumber] # enumFromTo :: PaneNumber -> PaneNumber -> [PaneNumber] # enumFromThenTo :: PaneNumber -> PaneNumber -> PaneNumber -> [PaneNumber] # | |
Eq PaneNumber Source # | |
Defined in Brick.Panes (==) :: PaneNumber -> PaneNumber -> Bool # (/=) :: PaneNumber -> PaneNumber -> Bool # |