Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GHCup.Brick.Widgets.Menu
Synopsis
- type Formatter n = Bool -> Widget n -> Widget n
- type Label = Text
- type HelpMessage = Text
- type ButtonName n = n
- idFormatter :: Formatter n
- type ErrorMessage = Text
- data ErrorStatus
- emptyLens :: Lens' s ()
- data FieldInput a b n = FieldInput {
- inputState :: b
- inputValidator :: b -> Either ErrorMessage a
- inputHelp :: HelpMessage
- inputRender :: Bool -> ErrorStatus -> HelpMessage -> Label -> b -> (Widget n -> Widget n) -> (Widget n, Maybe (Widget n))
- inputHandler :: BrickEvent n () -> EventM n b ()
- inputValidatorL :: forall a b n a. Lens (FieldInput a b n) (FieldInput a b n) (b -> Either ErrorMessage a) (b -> Either ErrorMessage a)
- inputStateL :: forall a b n. Lens' (FieldInput a b n) b
- inputHelpL :: forall a b n. Lens' (FieldInput a b n) HelpMessage
- data MenuField s n where
- isValidField :: MenuField s n -> Bool
- fieldStatusL :: forall s n. Lens' (MenuField s n) ErrorStatus
- fieldLabelL :: forall s n. Lens' (MenuField s n) Label
- data SelectState i n = SelectState {
- selectStateItems :: (NonEmpty (Int, (i, Bool)), Bool)
- selectStateEditState :: Maybe (Editor Text n)
- selectStateFocusRing :: FocusRing Int
- selectStateOverlayOpen :: Bool
- selectStateOverlayOpenL :: forall i n. Lens' (SelectState i n) Bool
- selectStateItemsL :: forall i n i. Lens (SelectState i n) (SelectState i n) (NonEmpty (Int, (i, Bool)), Bool) (NonEmpty (Int, (i, Bool)), Bool)
- selectStateFocusRingL :: forall i n. Lens' (SelectState i n) (FocusRing Int)
- selectStateEditStateL :: forall i n n. Lens (SelectState i n) (SelectState i n) (Maybe (Editor Text n)) (Maybe (Editor Text n))
- data EditState n = EditState {
- editState :: Editor Text n
- editStateOverlayOpen :: Bool
- editStateOverlayOpenL :: forall n. Lens' (EditState n) Bool
- editStateL :: forall n n. Lens (EditState n) (EditState n) (Editor Text n) (Editor Text n)
- data MenuKeyBindings = MenuKeyBindings {}
- mKbUpL :: Lens' MenuKeyBindings KeyCombination
- mKbQuitL :: Lens' MenuKeyBindings KeyCombination
- mKbDownL :: Lens' MenuKeyBindings KeyCombination
- fieldHelpMsgL :: Lens' (MenuField s n) HelpMessage
- drawField :: Formatter n -> Bool -> MenuField s n -> Widget n
- drawFieldOverlay :: MenuField s n -> Maybe (Widget n)
- type CheckBoxField = MenuField
- createCheckBoxInput :: FieldInput Bool Bool n
- createCheckBoxField :: n -> Lens' s Bool -> CheckBoxField s n
- type EditableField = MenuField
- createEditableInput :: (Ord n, Show n) => Text -> n -> (Text -> Either ErrorMessage a) -> FieldInput a (EditState n) n
- createEditableField' :: (Eq n, Ord n, Show n) => Text -> n -> (Text -> Either ErrorMessage a) -> Lens' s a -> EditableField s n
- createEditableField :: (Eq n, Ord n, Show n) => n -> (Text -> Either ErrorMessage a) -> Lens' s a -> EditableField s n
- type Button = MenuField
- createButtonInput :: FieldInput () () n
- createButtonField :: n -> Button s n
- type SelectField = MenuField
- 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
- createSelectField :: (Ord n, Show n) => n -> Lens' s (Maybe i) -> NonEmpty i -> (i -> Text) -> MenuKeyBindings -> SelectField s n
- createMultiSelectField :: (Ord n, Show n) => n -> Lens' s [i] -> NonEmpty i -> (i -> Text) -> MenuKeyBindings -> SelectField s n
- createSelectFieldWithEditable :: (Ord n, Show n) => n -> n -> Lens' s (Either a i) -> (Text -> Either ErrorMessage a) -> NonEmpty i -> (i -> Text) -> MenuKeyBindings -> SelectField s n
- highlighted :: Widget n -> Widget n
- renderAslabel :: Text -> Bool -> Widget n
- leftify :: Int -> Widget n -> Widget n
- rightify :: Int -> Widget n -> Widget n
- renderAsHelpMsg :: Text -> Widget n
- renderAsErrMsg :: Text -> Widget n
- overlayLayer :: Text -> Widget n -> Widget n
- data Menu s n = Menu {
- menuFields :: [MenuField s n]
- menuState :: s
- menuValidator :: s -> Maybe ErrorMessage
- menuButtons :: [Button s n]
- menuFocusRing :: FocusRing n
- menuKeyBindings :: MenuKeyBindings
- menuName :: n
- menuTitle :: Text
- menuValidatorL :: forall s n. Lens' (Menu s n) (s -> Maybe ErrorMessage)
- menuTitleL :: forall s n. Lens' (Menu s n) Text
- menuStateL :: forall s n. Lens' (Menu s n) s
- menuNameL :: forall s n. Lens' (Menu s n) n
- menuKeyBindingsL :: forall s n. Lens' (Menu s n) MenuKeyBindings
- menuFocusRingL :: forall s n. Lens' (Menu s n) (FocusRing n)
- menuFieldsL :: forall s n. Lens' (Menu s n) [MenuField s n]
- menuButtonsL :: forall s n. Lens' (Menu s n) [Button s n]
- isValidMenu :: Menu s n -> Bool
- createMenu :: n -> s -> Text -> (s -> Maybe ErrorMessage) -> MenuKeyBindings -> [Button s n] -> [MenuField s n] -> Menu s n
- handlerMenu :: forall n e s. Eq n => BrickEvent n e -> EventM n (Menu s n) ()
- drawMenu :: (Eq n, Ord n, Show n, Named (MenuField s n) n) => Menu s n -> [Widget n]
Documentation
type Formatter n = Bool -> Widget n -> Widget n Source #
Just some type synonym to make things explicit
type HelpMessage = Text Source #
A help message of an entry
type ButtonName n = n Source #
A button name
idFormatter :: Formatter n Source #
type ErrorMessage = Text Source #
An error message
data ErrorStatus Source #
Constructors
Valid | |
Invalid ErrorMessage |
Instances
Eq ErrorStatus Source # | |
Defined in GHCup.Brick.Widgets.Menu |
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
|
isValidField :: MenuField s n -> Bool Source #
fieldStatusL :: forall s n. Lens' (MenuField s n) ErrorStatus Source #
data SelectState i n Source #
Constructors
SelectState | |
Fields
|
selectStateOverlayOpenL :: forall i n. Lens' (SelectState i n) Bool Source #
selectStateItemsL :: forall i n i. Lens (SelectState i n) (SelectState i n) (NonEmpty (Int, (i, Bool)), Bool) (NonEmpty (Int, (i, Bool)), Bool) Source #
selectStateFocusRingL :: forall i n. Lens' (SelectState i n) (FocusRing Int) Source #
selectStateEditStateL :: forall i n n. Lens (SelectState i n) (SelectState i n) (Maybe (Editor Text n)) (Maybe (Editor Text n)) Source #
data MenuKeyBindings Source #
Constructors
MenuKeyBindings | |
Instances
Show MenuKeyBindings Source # | |
Defined in GHCup.Brick.Widgets.Menu Methods showsPrec :: Int -> MenuKeyBindings -> ShowS # show :: MenuKeyBindings -> String # showList :: [MenuKeyBindings] -> ShowS # |
mKbUpL :: Lens' MenuKeyBindings KeyCombination Source #
mKbQuitL :: Lens' MenuKeyBindings KeyCombination Source #
mKbDownL :: 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 *****************
type CheckBoxField = MenuField Source #
createCheckBoxField :: n -> Lens' s Bool -> CheckBoxField s n Source #
Editable widget *****************
type EditableField = MenuField Source #
createEditableInput :: (Ord n, Show n) => Text -> n -> (Text -> Either ErrorMessage a) -> FieldInput a (EditState n) n Source #
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 *****************
createButtonInput :: FieldInput () () n Source #
createButtonField :: n -> Button s n Source #
Select widget *****************
type SelectField = MenuField Source #
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
Menu widget *****************
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 #
menuStateL :: forall s n. Lens' (Menu s n) s Source #
menuKeyBindingsL :: forall s n. Lens' (Menu s n) MenuKeyBindings Source #
isValidMenu :: Menu s n -> Bool 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 #