brick-panes-1.0.0.3: Panes library for Brick providing composition and isolation for TUI apps.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Brick.Panes

Description

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.

This is done by representing each Pane via a class that describes the common types and methods for that Pane, as well as the internal state of the Pane. The full Pane class is shown here in brief (more extensive documentation is available below):

 class Pane n appEv pane | pane -> n where
   data PaneState pane appEv

   type InitConstraints pane initctxt :: Constraint
   initPaneState :: (InitConstraints pane i) => i -> PaneState pane appEv

   type DrawConstraints pane drwctxt n :: Constraint
   drawPane :: (DrawConstraints pane drawcontext n, Eq n)
            => PaneState pane appEv -> drawcontext -> Maybe (Widget n)

   type EventConstraints pane evctxt :: Constraint
   type EventType pane n appEv
   focusable :: (EventConstraints pane eventcontext, Eq n)
             => eventcontext -> PaneState pane appEv -> Seq.Seq n
   focusable _ _ = mempty
   handlePaneEvent :: (EventConstraints pane eventcontext, Eq n)
                   => eventcontext
                   -> EventType pane n appEv
                   -> PaneState pane appEv
                   -> EventM n es (PaneState pane appEv)
   handlePaneEvent _ _ = return

   type UpdateType pane
   updatePane :: UpdateType pane
              -> PaneState pane appEv
              -> PaneState pane appEv

Each Pane can be added to an overall Panel, where the Panel provides appropriate focus management and consolidates event and draw dispatching to the (appropriate) panes. The Panel can support modal panes which grab focus (and are not visible when not active and focused), panes which participate in a normal focus ring, and panes which are never focused. The Panel is represented by a recursive data structure that is initialized by calling the basePanel function with the global application state and passing that result to the addToPanel function for each Pane that should be added to the Panel.

Synopsis

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 pane
  • appEv = The application's event type
  • n = 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.

Minimal complete definition

initPaneState, drawPane

data family PaneState pane appEv Source #

State information associated with this pane

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. This is usually used when the Pane must establish class constraints on the drawcontext that it is passed, since this class definition is fully polymorphic. The default is () which indicate there are no constraints on the Pane's draw function (meaning the Pane can be fully drawn using only the internal PaneState).

drawPane :: (Pane n appEv pane, DrawConstraints pane drawcontext n, Eq n) => PaneState pane appEv -> drawcontext -> Maybe (Widget n) Source #

Function called to draw the Pane as a Brick Widget, or Nothing if this Pane should not be drawn at the current time.

Event Handling

type family EventConstraints pane evctxt :: Constraint Source #

The constraints that should exist on the eventcontext argment passed to focusable and handlePaneEvent. This is usually used when the Pane must establish class constraints on the eventcontext, since this class definition is fully polymorphic. The default is () which indicate there are no constraints on the Pane's focusable and handlePaneEvent functions (meaning the Pane can be fully drawn using only the internal PaneState).

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 EventType pane n. This is used internally in the brick-panes implementation and client code does not need to explicitly specify instances of this class.

Minimal complete definition

dispEv

Instances

Instances details
DispatchEvent n appev pane Event Source # 
Instance details

Defined in Brick.Panes

Methods

dispEv :: (Pane n appev pane, EventConstraints pane base, Eq n) => (EventType pane n appev :~: Event) -> base -> BrickEvent n appev -> PaneState pane appev -> EventM n es (PaneState pane appev)

DispatchEvent n appev pane (BrickEvent n appev) Source # 
Instance details

Defined in Brick.Panes

Methods

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 #

The focusable method is called to determine which Widget targets should be part of the Brick FocusRing.

The default is mempty, which indicates that no part of this Pane is ever focusable.

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.

The default is to return the pane state unmodified, indicating that this Pane never responds to any events.

Updating the Pane's state

type family UpdateType pane Source #

Type of data provided to updatePane.

The default is (), indicating that this Pane does not receive any external data during an update (which usually indicates that the Pane does not update once created).

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.

The default is to return the pane state unmodified, indicating that this Pane cannot have its internal state changed after creation.

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.

Instances

Instances details
HasFocus appState n => HasFocus (Panel n appEv appState panes) n Source #

If the base state provides Focus information, then the Panel can provide focus information.

Instance details

Defined in Brick.Panes

Methods

getFocus :: Lens' (Panel n appEv appState panes) (Focused n) Source #

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).

newtype Focused n Source #

This is a newtype to wrap the identification of the current focused element (if any).

Constructors

Focused (Maybe n) 

focused :: Focused n -> Maybe n Source #

The current focused element or Nothing.

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.

Instances

Instances details
HasFocus appState n => HasFocus (Panel n appEv appState panes) n Source #

If the base state provides Focus information, then the Panel can provide focus information.

Instance details

Defined in Brick.Panes

Methods

getFocus :: Lens' (Panel n appEv appState panes) (Focused n) Source #

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 #

Each Pane that is part of the Panel should be added to the Panel via this function, which also specifies when the Pane should receive Events.

data PaneFocus n Source #

Specifies when a Pane should receive events.

Constructors

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 focusable return from the Pane.

WhenFocusedModal

Indicates that the pane should receive events when the current focus is equal to a focusable return from the Pane, and that this should block all non-modal focus candidates (it is expected that there is only one modal, but this is not required).

WhenFocusedModalHandlingAllEvents

Indicates that the pane should receive events when the current focus is equal to a focusable return from the Pane, and that this should block all non-modal focus candidates, just as with WhenFocusedModal. However, this also sends *all* events to the modal Pane instead of the normal Panel handling of events (e.g. TAB/Shift-TAB).

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).

data PanelMode Source #

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.

Constructors

Normal 
Modal PaneNumber 

Instances

Instances details
Eq PanelMode Source # 
Instance details

Defined in Brick.Panes

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.

Methods

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

Instances details
(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 # 
Instance details

Defined in Brick.Panes

Methods

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 # 
Instance details

Defined in Brick.Panes

Methods

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 # 
Instance details

Defined in Brick.Panes

Methods

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.