ghcup-0.1.50.1: ghc toolchain installer
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHCup.Brick.Widgets.Menu

Synopsis

Documentation

type Formatter n = Bool -> Widget n -> Widget n Source #

Just some type synonym to make things explicit

type Label = Text Source #

A label

type HelpMessage = Text Source #

A help message of an entry

type ButtonName n = n Source #

A button name

type ErrorMessage = Text Source #

An error message

data ErrorStatus Source #

Constructors

Valid 
Invalid ErrorMessage 

Instances

Instances details
Eq ErrorStatus Source # 
Instance details

Defined in GHCup.Brick.Widgets.Menu

emptyLens :: Lens' s () Source #

A lens which does nothing. Usefull to defined no-op fields

data FieldInput a b n Source #

A FieldInput is a pair label-content a - is the type of the field it manipulates b - is its internal state (modified in the gui) n - your application's resource name type

Constructors

FieldInput 

Fields

inputValidatorL :: forall a b n a. Lens (FieldInput a b n) (FieldInput a b n) (b -> Either ErrorMessage a) (b -> Either ErrorMessage a) Source #

inputStateL :: forall a b n. Lens' (FieldInput a b n) b Source #

inputHelpL :: forall a b n. Lens' (FieldInput a b n) HelpMessage Source #

data MenuField s n where Source #

The MenuField is an existential type which stores a Lens' to a part of the Menu state. In also contains a Field input which internal state is hidden

Constructors

MenuField 

Fields

Instances

Instances details
Named (MenuField s n) n Source # 
Instance details

Defined in GHCup.Brick.Widgets.Menu

Methods

getName :: MenuField s n -> n #

fieldLabelL :: forall s n. Lens' (MenuField s n) Label Source #

data SelectState i n Source #

Constructors

SelectState 

Fields

selectStateItemsL :: forall i n i. Lens (SelectState i n) (SelectState i n) (NonEmpty (Int, (i, Bool)), Bool) (NonEmpty (Int, (i, Bool)), Bool) Source #

data EditState n Source #

Constructors

EditState 

Fields

editStateL :: forall n n. Lens (EditState n) (EditState n) (Editor Text n) (Editor Text n) Source #

data MenuKeyBindings Source #

Constructors

MenuKeyBindings 

Fields

Instances

Instances details
Show MenuKeyBindings Source # 
Instance details

Defined in GHCup.Brick.Widgets.Menu

mKbUpL :: Lens' MenuKeyBindings KeyCombination Source #

fieldHelpMsgL :: Lens' (MenuField s n) HelpMessage Source #

A fancy lens to the help message

drawField :: Formatter n -> Bool -> MenuField s n -> Widget n Source #

How to draw a field given a formater

CheckBox widget *****************

Editable widget *****************

createEditableField' :: (Eq n, Ord n, Show n) => Text -> n -> (Text -> Either ErrorMessage a) -> Lens' s a -> EditableField s n Source #

createEditableField :: (Eq n, Ord n, Show n) => n -> (Text -> Either ErrorMessage a) -> Lens' s a -> EditableField s n Source #

Button widget *****************

Select widget *****************

createSelectInput :: (Ord n, Show n) => NonEmpty i -> (i -> Text) -> (Int -> (NonEmpty (Int, (i, Bool)), Bool) -> (NonEmpty (Int, (i, Bool)), Bool)) -> (([i], Maybe Text) -> Either ErrorMessage k) -> n -> Maybe n -> MenuKeyBindings -> FieldInput k (SelectState i n) n Source #

createSelectField :: (Ord n, Show n) => n -> Lens' s (Maybe i) -> NonEmpty i -> (i -> Text) -> MenuKeyBindings -> SelectField s n Source #

Select Field with only single selection possible, aka radio button

createMultiSelectField :: (Ord n, Show n) => n -> Lens' s [i] -> NonEmpty i -> (i -> Text) -> MenuKeyBindings -> SelectField s n Source #

Select Field with multiple selections possible

createSelectFieldWithEditable :: (Ord n, Show n) => n -> n -> Lens' s (Either a i) -> (Text -> Either ErrorMessage a) -> NonEmpty i -> (i -> Text) -> MenuKeyBindings -> SelectField s n Source #

Select Field with only single selection possible, along with an editable field

Utilities *****************

highlighted :: Widget n -> Widget n Source #

highlights a widget (using List.listSelectedFocusedAttr)

renderAslabel :: Text -> Bool -> Widget n Source #

Given a text, crates a highlighted label on focus. An amplifier can be passed

leftify :: Int -> Widget n -> Widget n Source #

Creates a left align column. Example: |- col2 is align dispite the length of col1 row1_col1 row1_col2 row2_col1_large row2_col2

rightify :: Int -> Widget n -> Widget n Source #

Creates a right align column. Example: |- col2 is align dispite the length of col1 row1_col1 row1_col2 row2_col1_large row2_col2

renderAsHelpMsg :: Text -> Widget n Source #

render some Text using helpMsgAttr

renderAsErrMsg :: Text -> Widget n Source #

render some Text using errMsgAttr

overlayLayer :: Text -> Widget n -> Widget n Source #

Used to create a layer on top of menu

Menu widget *****************

data Menu s n Source #

A menu is a list of Fields and a state. Informally we can think about s in terms of the record type returned by a form.

Constructors

Menu 

Fields

menuValidatorL :: forall s n. Lens' (Menu s n) (s -> Maybe ErrorMessage) Source #

menuTitleL :: forall s n. Lens' (Menu s n) Text Source #

menuStateL :: forall s n. Lens' (Menu s n) s Source #

menuNameL :: forall s n. Lens' (Menu s n) n Source #

menuFocusRingL :: forall s n. Lens' (Menu s n) (FocusRing n) Source #

menuFieldsL :: forall s n. Lens' (Menu s n) [MenuField s n] Source #

menuButtonsL :: forall s n. Lens' (Menu s n) [Button s n] Source #

createMenu :: n -> s -> Text -> (s -> Maybe ErrorMessage) -> MenuKeyBindings -> [Button s n] -> [MenuField s n] -> Menu s n Source #

handlerMenu :: forall n e s. Eq n => BrickEvent n e -> EventM n (Menu s n) () Source #

drawMenu :: (Eq n, Ord n, Show n, Named (MenuField s n) n) => Menu s n -> [Widget n] Source #