Safe Haskell | None |
---|---|
Language | Haskell2010 |
Brick.Types
Description
Basic types used by this library.
Synopsis
- data Widget n = Widget {}
- data Location = Location {
- loc :: (Int, Int)
- locL :: Lens' Location (Int, Int)
- class TerminalLocation a where
- locationColumnL :: Lens' a Int
- locationColumn :: a -> Int
- locationRowL :: Lens' a Int
- locationRow :: a -> Int
- data CursorLocation n = CursorLocation {
- cursorLocation :: !Location
- cursorLocationName :: !(Maybe n)
- cursorLocationVisible :: !Bool
- cursorLocationL :: forall n f. Functor f => (Location -> f Location) -> CursorLocation n -> f (CursorLocation n)
- cursorLocationNameL :: forall n1 n2 f. Functor f => (Maybe n1 -> f (Maybe n2)) -> CursorLocation n1 -> f (CursorLocation n2)
- data Viewport = VP {
- _vpLeft :: Int
- _vpTop :: Int
- _vpSize :: DisplayRegion
- _vpContentSize :: DisplayRegion
- data ViewportType
- = Vertical
- | Horizontal
- | Both
- vpSize :: Lens' Viewport DisplayRegion
- vpTop :: Lens' Viewport Int
- vpLeft :: Lens' Viewport Int
- vpContentSize :: Lens' Viewport DisplayRegion
- data VScrollBarOrientation
- data HScrollBarOrientation
- data VScrollbarRenderer n = VScrollbarRenderer {}
- data HScrollbarRenderer n = HScrollbarRenderer {}
- data ClickableScrollbarElement
- data EventM n s a
- data BrickEvent n e
- nestEventM :: a -> EventM n a b -> EventM n s (a, b)
- nestEventM' :: a -> EventM n a b -> EventM n s a
- type RenderM n a = ReaderT (Context n) (State (RenderState n)) a
- getContext :: RenderM n (Context n)
- data Context n
- attrL :: Getting r (Context n) Attr
- availWidthL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n)
- availHeightL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n)
- windowWidthL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n)
- windowHeightL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n)
- ctxVScrollBarOrientationL :: forall n f. Functor f => (Maybe VScrollBarOrientation -> f (Maybe VScrollBarOrientation)) -> Context n -> f (Context n)
- ctxVScrollBarRendererL :: forall n f. Functor f => (Maybe (VScrollbarRenderer n) -> f (Maybe (VScrollbarRenderer n))) -> Context n -> f (Context n)
- ctxHScrollBarOrientationL :: forall n f. Functor f => (Maybe HScrollBarOrientation -> f (Maybe HScrollBarOrientation)) -> Context n -> f (Context n)
- ctxHScrollBarRendererL :: forall n f. Functor f => (Maybe (HScrollbarRenderer n) -> f (Maybe (HScrollbarRenderer n))) -> Context n -> f (Context n)
- ctxAttrMapL :: forall n f. Functor f => (AttrMap -> f AttrMap) -> Context n -> f (Context n)
- ctxAttrNameL :: forall n f. Functor f => (AttrName -> f AttrName) -> Context n -> f (Context n)
- ctxBorderStyleL :: forall n f. Functor f => (BorderStyle -> f BorderStyle) -> Context n -> f (Context n)
- ctxDynBordersL :: forall n f. Functor f => (Bool -> f Bool) -> Context n -> f (Context n)
- data Result n = Result {
- image :: !Image
- cursors :: ![CursorLocation n]
- visibilityRequests :: ![VisibilityRequest]
- extents :: ![Extent n]
- borders :: !(BorderMap DynBorder)
- emptyResult :: Result n
- lookupAttrName :: AttrName -> RenderM n Attr
- data Extent n = Extent {
- extentName :: !n
- extentUpperLeft :: !Location
- extentSize :: !(Int, Int)
- imageL :: forall n f. Functor f => (Image -> f Image) -> Result n -> f (Result n)
- cursorsL :: forall n f. Functor f => ([CursorLocation n] -> f [CursorLocation n]) -> Result n -> f (Result n)
- visibilityRequestsL :: forall n f. Functor f => ([VisibilityRequest] -> f [VisibilityRequest]) -> Result n -> f (Result n)
- extentsL :: forall n f. Functor f => ([Extent n] -> f [Extent n]) -> Result n -> f (Result n)
- data VisibilityRequest = VR {
- vrPosition :: Location
- vrSize :: DisplayRegion
- vrPositionL :: Lens' VisibilityRequest Location
- vrSizeL :: Lens' VisibilityRequest DisplayRegion
- suffixLenses :: Name -> DecsQ
- suffixLensesWith :: String -> LensRules -> Name -> DecsQ
- bordersL :: forall n f. Functor f => (BorderMap DynBorder -> f (BorderMap DynBorder)) -> Result n -> f (Result n)
- data DynBorder = DynBorder {
- dbStyle :: BorderStyle
- dbAttr :: Attr
- dbSegments :: Edges BorderSegment
- dbStyleL :: Lens' DynBorder BorderStyle
- dbAttrL :: Lens' DynBorder Attr
- dbSegmentsL :: Lens' DynBorder (Edges BorderSegment)
- data BorderSegment = BorderSegment {}
- bsAcceptL :: Lens' BorderSegment Bool
- bsOfferL :: Lens' BorderSegment Bool
- bsDrawL :: Lens' BorderSegment Bool
- data Edges a = Edges {}
- eTopL :: forall a f. Functor f => (a -> f a) -> Edges a -> f (Edges a)
- eBottomL :: forall a f. Functor f => (a -> f a) -> Edges a -> f (Edges a)
- eRightL :: forall a f. Functor f => (a -> f a) -> Edges a -> f (Edges a)
- eLeftL :: forall a f. Functor f => (a -> f a) -> Edges a -> f (Edges a)
- data Size
- data Direction
- data RenderState n
- get :: MonadState s m => m s
- gets :: MonadState s m => (s -> a) -> m a
- put :: MonadState s m => s -> m ()
- modify :: MonadState s m => (s -> s) -> m ()
- zoom :: Zoom m n s t => LensLike' (Zoomed m c) t s -> m c -> n c
The Widget type
The type of widgets.
Location types and lenses
A terminal screen location.
Instances
Monoid Location Source # | |||||
Semigroup Location Source # | |||||
Generic Location Source # | |||||
Defined in Brick.Types.Common Associated Types
| |||||
Read Location Source # | |||||
Defined in Brick.Types.Common | |||||
Show Location Source # | |||||
TerminalLocation Location Source # | |||||
Defined in Brick.Types.Internal Methods locationColumnL :: Lens' Location Int Source # locationColumn :: Location -> Int Source # locationRowL :: Lens' Location Int Source # locationRow :: Location -> Int Source # | |||||
NFData Location Source # | |||||
Defined in Brick.Types.Common | |||||
Eq Location Source # | |||||
Ord Location Source # | |||||
Defined in Brick.Types.Common | |||||
Field1 Location Location Int Int Source # | |||||
Defined in Brick.Types.Common | |||||
Field2 Location Location Int Int Source # | |||||
Defined in Brick.Types.Common | |||||
type Rep Location Source # | |||||
Defined in Brick.Types.Common type Rep Location = D1 ('MetaData "Location" "Brick.Types.Common" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "Location" 'PrefixI 'True) (S1 ('MetaSel ('Just "loc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int)))) |
class TerminalLocation a where Source #
The class of types that behave like terminal locations.
Methods
locationColumnL :: Lens' a Int Source #
Get the column out of the value
locationColumn :: a -> Int Source #
locationRowL :: Lens' a Int Source #
Get the row out of the value
locationRow :: a -> Int Source #
Instances
TerminalLocation Location Source # | |
Defined in Brick.Types.Internal Methods locationColumnL :: Lens' Location Int Source # locationColumn :: Location -> Int Source # locationRowL :: Lens' Location Int Source # locationRow :: Location -> Int Source # | |
TerminalLocation (CursorLocation n) Source # | |
Defined in Brick.Types Methods locationColumnL :: Lens' (CursorLocation n) Int Source # locationColumn :: CursorLocation n -> Int Source # locationRowL :: Lens' (CursorLocation n) Int Source # locationRow :: CursorLocation n -> Int Source # |
data CursorLocation n Source #
A cursor location. These are returned by the rendering process.
Constructors
CursorLocation | |
Fields
|
Instances
Generic (CursorLocation n) Source # | |||||
Defined in Brick.Types.Internal Associated Types
Methods from :: CursorLocation n -> Rep (CursorLocation n) x to :: Rep (CursorLocation n) x -> CursorLocation n | |||||
Read n => Read (CursorLocation n) Source # | |||||
Defined in Brick.Types.Internal Methods readsPrec :: Int -> ReadS (CursorLocation n) readList :: ReadS [CursorLocation n] readPrec :: ReadPrec (CursorLocation n) readListPrec :: ReadPrec [CursorLocation n] | |||||
Show n => Show (CursorLocation n) Source # | |||||
Defined in Brick.Types.Internal Methods showsPrec :: Int -> CursorLocation n -> ShowS show :: CursorLocation n -> String showList :: [CursorLocation n] -> ShowS | |||||
TerminalLocation (CursorLocation n) Source # | |||||
Defined in Brick.Types Methods locationColumnL :: Lens' (CursorLocation n) Int Source # locationColumn :: CursorLocation n -> Int Source # locationRowL :: Lens' (CursorLocation n) Int Source # locationRow :: CursorLocation n -> Int Source # | |||||
NFData n => NFData (CursorLocation n) Source # | |||||
Defined in Brick.Types.Internal Methods rnf :: CursorLocation n -> () | |||||
type Rep (CursorLocation n) Source # | |||||
Defined in Brick.Types.Internal type Rep (CursorLocation n) = D1 ('MetaData "CursorLocation" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "CursorLocation" 'PrefixI 'True) (S1 ('MetaSel ('Just "cursorLocation") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Location) :*: (S1 ('MetaSel ('Just "cursorLocationName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe n)) :*: S1 ('MetaSel ('Just "cursorLocationVisible") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))) |
cursorLocationL :: forall n f. Functor f => (Location -> f Location) -> CursorLocation n -> f (CursorLocation n) Source #
cursorLocationNameL :: forall n1 n2 f. Functor f => (Maybe n1 -> f (Maybe n2)) -> CursorLocation n1 -> f (CursorLocation n2) Source #
Viewports
Describes the state of a viewport as it appears as its most recent rendering.
Constructors
VP | |
Fields
|
Instances
Generic Viewport Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
Read Viewport Source # | |||||
Defined in Brick.Types.Internal | |||||
Show Viewport Source # | |||||
NFData Viewport Source # | |||||
Defined in Brick.Types.Internal | |||||
type Rep Viewport Source # | |||||
Defined in Brick.Types.Internal type Rep Viewport = D1 ('MetaData "Viewport" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "VP" 'PrefixI 'True) ((S1 ('MetaSel ('Just "_vpLeft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "_vpTop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "_vpSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisplayRegion) :*: S1 ('MetaSel ('Just "_vpContentSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisplayRegion)))) |
data ViewportType Source #
The type of viewports that indicates the direction(s) in which a viewport is scrollable.
Constructors
Vertical | Viewports of this type are scrollable only vertically. |
Horizontal | Viewports of this type are scrollable only horizontally. |
Both | Viewports of this type are scrollable vertically and horizontally. |
Instances
Show ViewportType Source # | |
Defined in Brick.Types.Internal Methods showsPrec :: Int -> ViewportType -> ShowS show :: ViewportType -> String showList :: [ViewportType] -> ShowS | |
Eq ViewportType Source # | |
Defined in Brick.Types.Internal |
vpContentSize :: Lens' Viewport DisplayRegion Source #
data VScrollBarOrientation Source #
Orientations for vertical scroll bars.
Instances
Show VScrollBarOrientation Source # | |
Defined in Brick.Types.Internal Methods showsPrec :: Int -> VScrollBarOrientation -> ShowS show :: VScrollBarOrientation -> String showList :: [VScrollBarOrientation] -> ShowS | |
Eq VScrollBarOrientation Source # | |
Defined in Brick.Types.Internal Methods (==) :: VScrollBarOrientation -> VScrollBarOrientation -> Bool (/=) :: VScrollBarOrientation -> VScrollBarOrientation -> Bool |
data HScrollBarOrientation Source #
Orientations for horizontal scroll bars.
Instances
Show HScrollBarOrientation Source # | |
Defined in Brick.Types.Internal Methods showsPrec :: Int -> HScrollBarOrientation -> ShowS show :: HScrollBarOrientation -> String showList :: [HScrollBarOrientation] -> ShowS | |
Eq HScrollBarOrientation Source # | |
Defined in Brick.Types.Internal Methods (==) :: HScrollBarOrientation -> HScrollBarOrientation -> Bool (/=) :: HScrollBarOrientation -> HScrollBarOrientation -> Bool |
data VScrollbarRenderer n Source #
A vertical scroll bar renderer.
Constructors
VScrollbarRenderer | |
Fields
|
data HScrollbarRenderer n Source #
A horizontal scroll bar renderer.
Constructors
HScrollbarRenderer | |
Fields
|
data ClickableScrollbarElement Source #
Clickable elements of a scroll bar.
Constructors
SBHandleBefore | The handle at the beginning (left/top) of the scroll bar. |
SBHandleAfter | The handle at the end (right/bottom) of the scroll bar. |
SBBar | The scroll bar itself. |
SBTroughBefore | The trough before the scroll bar. |
SBTroughAfter | The trough after the scroll bar. |
Instances
Event-handling types and functions
The monad in which event handlers run.
Instances
MonadState s (EventM n s) Source # | |
MonadIO (EventM n s) Source # | |
Defined in Brick.Types.EventM | |
Applicative (EventM n s) Source # | |
Functor (EventM n s) Source # | |
Monad (EventM n s) Source # | |
MonadCatch (EventM n s) Source # | |
Defined in Brick.Types.EventM | |
MonadMask (EventM n s) Source # | |
Defined in Brick.Types.EventM Methods mask :: HasCallStack => ((forall a. EventM n s a -> EventM n s a) -> EventM n s b) -> EventM n s b uninterruptibleMask :: HasCallStack => ((forall a. EventM n s a -> EventM n s a) -> EventM n s b) -> EventM n s b generalBracket :: HasCallStack => EventM n s a -> (a -> ExitCase b -> EventM n s c) -> (a -> EventM n s b) -> EventM n s (b, c) | |
MonadThrow (EventM n s) Source # | |
Defined in Brick.Types.EventM | |
Zoom (EventM n s) (EventM n t) s t Source # | |
type Zoomed (EventM n s) Source # | |
Defined in Brick.Types.EventM type Zoomed (EventM n s) |
data BrickEvent n e Source #
The type of events.
Constructors
VtyEvent Event | The event was a Vty event. |
AppEvent e | The event was an application event. |
MouseDown n Button [Modifier] Location | A mouse-down event on the specified region was
received. The |
MouseUp n (Maybe Button) Location | A mouse-up event on the specified region was
received. The |
Instances
(Show e, Show n) => Show (BrickEvent n e) Source # | |
Defined in Brick.Types.Internal Methods showsPrec :: Int -> BrickEvent n e -> ShowS show :: BrickEvent n e -> String showList :: [BrickEvent n e] -> ShowS | |
(Eq e, Eq n) => Eq (BrickEvent n e) Source # | |
Defined in Brick.Types.Internal Methods (==) :: BrickEvent n e -> BrickEvent n e -> Bool (/=) :: BrickEvent n e -> BrickEvent n e -> Bool | |
(Ord e, Ord n) => Ord (BrickEvent n e) Source # | |
Defined in Brick.Types.Internal Methods compare :: BrickEvent n e -> BrickEvent n e -> Ordering (<) :: BrickEvent n e -> BrickEvent n e -> Bool (<=) :: BrickEvent n e -> BrickEvent n e -> Bool (>) :: BrickEvent n e -> BrickEvent n e -> Bool (>=) :: BrickEvent n e -> BrickEvent n e -> Bool max :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e min :: BrickEvent n e -> BrickEvent n e -> BrickEvent n e |
Arguments
:: a | The initial state to use in the nested action. |
-> EventM n a b | The action to run. |
-> EventM n s (a, b) |
Given a state value and an EventM
that mutates that state, run
the specified action and return both the resulting modified state and
the result of the action itself.
Arguments
:: a | The initial state to use in the nested action. |
-> EventM n a b | The action to run. |
-> EventM n s a |
Given a state value and an EventM
that mutates that state, run
the specified action and return resulting modified state.
Rendering infrastructure
type RenderM n a = ReaderT (Context n) (State (RenderState n)) a Source #
The type of the rendering monad. This monad is used by the library's rendering routines to manage rendering state and communicate rendering parameters to widgets' rendering functions.
getContext :: RenderM n (Context n) Source #
Get the current rendering context.
The rendering context
The rendering context. This tells widgets how to render: how much space they have in which to render, which attribute they should use to render, which bordering style should be used, and the attribute map available for rendering.
availWidthL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n) Source #
availHeightL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n) Source #
windowWidthL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n) Source #
windowHeightL :: forall n f. Functor f => (Int -> f Int) -> Context n -> f (Context n) Source #
ctxVScrollBarOrientationL :: forall n f. Functor f => (Maybe VScrollBarOrientation -> f (Maybe VScrollBarOrientation)) -> Context n -> f (Context n) Source #
ctxVScrollBarRendererL :: forall n f. Functor f => (Maybe (VScrollbarRenderer n) -> f (Maybe (VScrollbarRenderer n))) -> Context n -> f (Context n) Source #
ctxHScrollBarOrientationL :: forall n f. Functor f => (Maybe HScrollBarOrientation -> f (Maybe HScrollBarOrientation)) -> Context n -> f (Context n) Source #
ctxHScrollBarRendererL :: forall n f. Functor f => (Maybe (HScrollbarRenderer n) -> f (Maybe (HScrollbarRenderer n))) -> Context n -> f (Context n) Source #
ctxAttrMapL :: forall n f. Functor f => (AttrMap -> f AttrMap) -> Context n -> f (Context n) Source #
ctxAttrNameL :: forall n f. Functor f => (AttrName -> f AttrName) -> Context n -> f (Context n) Source #
ctxBorderStyleL :: forall n f. Functor f => (BorderStyle -> f BorderStyle) -> Context n -> f (Context n) Source #
ctxDynBordersL :: forall n f. Functor f => (Bool -> f Bool) -> Context n -> f (Context n) Source #
Rendering results
The type of result returned by a widget's rendering function. The result provides the image, cursor positions, and visibility requests that resulted from the rendering process.
Constructors
Result | |
Fields
|
Instances
Generic (Result n) Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
Read n => Read (Result n) Source # | |||||
Defined in Brick.Types.Internal | |||||
Show n => Show (Result n) Source # | |||||
NFData n => NFData (Result n) Source # | |||||
Defined in Brick.Types.Internal | |||||
type Rep (Result n) Source # | |||||
Defined in Brick.Types.Internal type Rep (Result n) = D1 ('MetaData "Result" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "Result" 'PrefixI 'True) ((S1 ('MetaSel ('Just "image") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Image) :*: S1 ('MetaSel ('Just "cursors") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [CursorLocation n])) :*: (S1 ('MetaSel ('Just "visibilityRequests") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [VisibilityRequest]) :*: (S1 ('MetaSel ('Just "extents") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [Extent n]) :*: S1 ('MetaSel ('Just "borders") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (BorderMap DynBorder)))))) |
emptyResult :: Result n Source #
lookupAttrName :: AttrName -> RenderM n Attr Source #
Given an attribute name, obtain the attribute for the attribute name by consulting the context's attribute map.
An extent of a named area: its size, location, and origin.
Constructors
Extent | |
Fields
|
Instances
Generic (Extent n) Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
Read n => Read (Extent n) Source # | |||||
Defined in Brick.Types.Internal | |||||
Show n => Show (Extent n) Source # | |||||
NFData n => NFData (Extent n) Source # | |||||
Defined in Brick.Types.Internal | |||||
type Rep (Extent n) Source # | |||||
Defined in Brick.Types.Internal type Rep (Extent n) = D1 ('MetaData "Extent" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "Extent" 'PrefixI 'True) (S1 ('MetaSel ('Just "extentName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 n) :*: (S1 ('MetaSel ('Just "extentUpperLeft") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Location) :*: S1 ('MetaSel ('Just "extentSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Int, Int))))) |
Rendering result lenses
cursorsL :: forall n f. Functor f => ([CursorLocation n] -> f [CursorLocation n]) -> Result n -> f (Result n) Source #
visibilityRequestsL :: forall n f. Functor f => ([VisibilityRequest] -> f [VisibilityRequest]) -> Result n -> f (Result n) Source #
extentsL :: forall n f. Functor f => ([Extent n] -> f [Extent n]) -> Result n -> f (Result n) Source #
Visibility requests
data VisibilityRequest Source #
Constructors
VR | |
Fields
|
Instances
Generic VisibilityRequest Source # | |||||
Defined in Brick.Types.Internal Associated Types
Methods from :: VisibilityRequest -> Rep VisibilityRequest x to :: Rep VisibilityRequest x -> VisibilityRequest | |||||
Read VisibilityRequest Source # | |||||
Defined in Brick.Types.Internal Methods readsPrec :: Int -> ReadS VisibilityRequest readList :: ReadS [VisibilityRequest] readPrec :: ReadPrec VisibilityRequest readListPrec :: ReadPrec [VisibilityRequest] | |||||
Show VisibilityRequest Source # | |||||
Defined in Brick.Types.Internal Methods showsPrec :: Int -> VisibilityRequest -> ShowS show :: VisibilityRequest -> String showList :: [VisibilityRequest] -> ShowS | |||||
NFData VisibilityRequest Source # | |||||
Defined in Brick.Types.Internal Methods rnf :: VisibilityRequest -> () | |||||
Eq VisibilityRequest Source # | |||||
Defined in Brick.Types.Internal Methods (==) :: VisibilityRequest -> VisibilityRequest -> Bool (/=) :: VisibilityRequest -> VisibilityRequest -> Bool | |||||
type Rep VisibilityRequest Source # | |||||
Defined in Brick.Types.Internal type Rep VisibilityRequest = D1 ('MetaData "VisibilityRequest" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "VR" 'PrefixI 'True) (S1 ('MetaSel ('Just "vrPosition") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location) :*: S1 ('MetaSel ('Just "vrSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DisplayRegion))) |
vrPositionL :: Lens' VisibilityRequest Location Source #
vrSizeL :: Lens' VisibilityRequest DisplayRegion Source #
Making lenses
suffixLenses :: Name -> DecsQ Source #
A template haskell function to build lenses for a record type. This
function differs from the makeLenses
function in that
it does not require the record fields to be prefixed with underscores
and it adds an L suffix to lens names to make it clear that they
are lenses.
suffixLensesWith :: String -> LensRules -> Name -> DecsQ Source #
A more general version of suffixLenses
that allows customization
of the lens-building rules and allows customization of the suffix.
Dynamic borders
bordersL :: forall n f. Functor f => (BorderMap DynBorder -> f (BorderMap DynBorder)) -> Result n -> f (Result n) Source #
Information about how to redraw a dynamic border character when it abuts another dynamic border character.
Constructors
DynBorder | |
Fields
|
Instances
Generic DynBorder Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
Read DynBorder Source # | |||||
Defined in Brick.Types.Internal | |||||
Show DynBorder Source # | |||||
NFData DynBorder Source # | |||||
Defined in Brick.Types.Internal | |||||
Eq DynBorder Source # | |||||
type Rep DynBorder Source # | |||||
Defined in Brick.Types.Internal type Rep DynBorder = D1 ('MetaData "DynBorder" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "DynBorder" 'PrefixI 'True) (S1 ('MetaSel ('Just "dbStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BorderStyle) :*: (S1 ('MetaSel ('Just "dbAttr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Attr) :*: S1 ('MetaSel ('Just "dbSegments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Edges BorderSegment))))) |
dbStyleL :: Lens' DynBorder BorderStyle Source #
dbSegmentsL :: Lens' DynBorder (Edges BorderSegment) Source #
data BorderSegment Source #
A border character has four segments, one extending in each direction (horizontally and vertically) from the center of the character.
Constructors
BorderSegment | |
Instances
Generic BorderSegment Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
Read BorderSegment Source # | |||||
Defined in Brick.Types.Internal Methods readsPrec :: Int -> ReadS BorderSegment readList :: ReadS [BorderSegment] readPrec :: ReadPrec BorderSegment readListPrec :: ReadPrec [BorderSegment] | |||||
Show BorderSegment Source # | |||||
Defined in Brick.Types.Internal Methods showsPrec :: Int -> BorderSegment -> ShowS show :: BorderSegment -> String showList :: [BorderSegment] -> ShowS | |||||
NFData BorderSegment Source # | |||||
Defined in Brick.Types.Internal Methods rnf :: BorderSegment -> () | |||||
Eq BorderSegment Source # | |||||
Defined in Brick.Types.Internal | |||||
Ord BorderSegment Source # | |||||
Defined in Brick.Types.Internal Methods compare :: BorderSegment -> BorderSegment -> Ordering (<) :: BorderSegment -> BorderSegment -> Bool (<=) :: BorderSegment -> BorderSegment -> Bool (>) :: BorderSegment -> BorderSegment -> Bool (>=) :: BorderSegment -> BorderSegment -> Bool max :: BorderSegment -> BorderSegment -> BorderSegment min :: BorderSegment -> BorderSegment -> BorderSegment | |||||
type Rep BorderSegment Source # | |||||
Defined in Brick.Types.Internal type Rep BorderSegment = D1 ('MetaData "BorderSegment" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "BorderSegment" 'PrefixI 'True) (S1 ('MetaSel ('Just "bsAccept") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "bsOffer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "bsDraw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) |
bsAcceptL :: Lens' BorderSegment Bool Source #
bsOfferL :: Lens' BorderSegment Bool Source #
bsDrawL :: Lens' BorderSegment Bool Source #
Instances
Applicative Edges Source # | |||||
Functor Edges Source # | |||||
Monad Edges Source # | |||||
Generic (Edges a) Source # | |||||
Defined in Brick.Types.Common Associated Types
| |||||
Read a => Read (Edges a) Source # | |||||
Defined in Brick.Types.Common | |||||
Show a => Show (Edges a) Source # | |||||
NFData a => NFData (Edges a) Source # | |||||
Defined in Brick.Types.Common | |||||
Eq a => Eq (Edges a) Source # | |||||
Ord a => Ord (Edges a) Source # | |||||
type Rep (Edges a) Source # | |||||
Defined in Brick.Types.Common type Rep (Edges a) = D1 ('MetaData "Edges" "Brick.Types.Common" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "Edges" 'PrefixI 'True) ((S1 ('MetaSel ('Just "eTop") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "eBottom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :*: (S1 ('MetaSel ('Just "eLeft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "eRight") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))) |
Miscellaneous
Widget size policies. These policies communicate how a widget uses
space when being rendered. These policies influence rendering order
and space allocation in the box layout algorithm for hBox
and
vBox
.
Constructors
Fixed | Widgets advertising this size policy should take up the same amount of space no matter how much they are given, i.e. their size depends on their contents alone rather than on the size of the rendering area. |
Greedy | Widgets advertising this size policy must take up all the space they are given. |
Scrolling direction.
Instances
Generic Direction Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
Read Direction Source # | |||||
Defined in Brick.Types.Internal | |||||
Show Direction Source # | |||||
NFData Direction Source # | |||||
Defined in Brick.Types.Internal | |||||
Eq Direction Source # | |||||
type Rep Direction Source # | |||||
Defined in Brick.Types.Internal type Rep Direction = D1 ('MetaData "Direction" "Brick.Types.Internal" "brick-2.4-HuR3vx2rzRf3YKIkMGcubg" 'False) (C1 ('MetaCons "Up" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Down" 'PrefixI 'False) (U1 :: Type -> Type)) |
Renderer internals (for benchmarking)
data RenderState n Source #
Instances
Generic (RenderState n) Source # | |||||
Defined in Brick.Types.Internal Associated Types
| |||||
(Ord n, Read n) => Read (RenderState n) Source # | |||||
Defined in Brick.Types.Internal Methods readsPrec :: Int -> ReadS (RenderState n) readList :: ReadS [RenderState n] readPrec :: ReadPrec (RenderState n) readListPrec :: ReadPrec [RenderState n] | |||||
Show n => Show (RenderState n) Source # | |||||
Defined in Brick.Types.Internal Methods showsPrec :: Int -> RenderState n -> ShowS show :: RenderState n -> String showList :: [RenderState n] -> ShowS | |||||
NFData n => NFData (RenderState n) Source # | |||||
Defined in Brick.Types.Internal Methods rnf :: RenderState n -> () | |||||
type Rep (RenderState n) Source # | |||||
Defined in Brick.Types.Internal type Rep (RenderState n) |
Re-exports for convenience
Orphan instances
TerminalLocation (CursorLocation n) Source # | |
Methods locationColumnL :: Lens' (CursorLocation n) Int Source # locationColumn :: CursorLocation n -> Int Source # locationRowL :: Lens' (CursorLocation n) Int Source # locationRow :: CursorLocation n -> Int Source # |