Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic types used by this library.
Synopsis
- data Widget n = Widget {}
- data Location = Location {}
- 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)
- cursorLocationL :: forall n. Lens' (CursorLocation n) Location
- cursorLocationNameL :: forall n n. Lens (CursorLocation n) (CursorLocation n) (Maybe n) (Maybe n)
- data Viewport = VP {}
- data ViewportType
- = Vertical
- | Horizontal
- | Both
- vpSize :: Lens' Viewport DisplayRegion
- vpTop :: Lens' Viewport Int
- vpLeft :: Lens' Viewport Int
- newtype EventM n a = EventM {}
- data Next a
- data BrickEvent n e
- handleEventLensed :: a -> Lens' a b -> (e -> b -> EventM n b) -> e -> EventM n a
- type RenderM n a = ReaderT Context (State (RenderState n)) a
- getContext :: RenderM n Context
- data Context
- attrL :: forall r. Getting r Context Attr
- availWidthL :: Lens' Context Int
- availHeightL :: Lens' Context Int
- windowWidthL :: Lens' Context Int
- windowHeightL :: Lens' Context Int
- ctxAttrMapL :: Lens' Context AttrMap
- ctxAttrNameL :: Lens' Context AttrName
- ctxBorderStyleL :: Lens' Context BorderStyle
- ctxDynBordersL :: Lens' Context Bool
- 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. Lens' (Result n) Image
- cursorsL :: forall n. Lens' (Result n) [CursorLocation n]
- visibilityRequestsL :: forall n. Lens' (Result n) [VisibilityRequest]
- extentsL :: forall n. Lens' (Result n) [Extent n]
- data VisibilityRequest = VR {}
- vrPositionL :: Lens' VisibilityRequest Location
- vrSizeL :: Lens' VisibilityRequest DisplayRegion
- suffixLenses :: Name -> DecsQ
- bordersL :: forall n. Lens' (Result n) (BorderMap DynBorder)
- data DynBorder = DynBorder {}
- 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. Lens' (Edges a) a
- eBottomL :: forall a. Lens' (Edges a) a
- eRightL :: forall a. Lens' (Edges a) a
- eLeftL :: forall a. Lens' (Edges a) a
- data Size
- data Padding
- data Direction
- data RenderState n
The Widget type
The type of widgets.
Location types and lenses
A terminal screen location.
Instances
Eq Location Source # | |
Ord Location Source # | |
Defined in Brick.Types.Common | |
Read Location Source # | |
Show Location Source # | |
Generic Location Source # | |
Semigroup Location Source # | |
Monoid Location Source # | |
NFData Location Source # | |
Defined in Brick.Types.Common | |
TerminalLocation Location Source # | |
Defined in Brick.Types.Internal | |
Field1 Location Location Int Int Source # | |
Field2 Location Location Int Int Source # | |
type Rep Location Source # | |
Defined in Brick.Types.Common |
class TerminalLocation a where Source #
The class of types that behave like terminal locations.
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 | |
TerminalLocation (CursorLocation n) Source # | |
Defined in Brick.Types 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.
CursorLocation | |
|
Instances
cursorLocationL :: forall n. Lens' (CursorLocation n) Location Source #
cursorLocationNameL :: forall n n. Lens (CursorLocation n) (CursorLocation n) (Maybe n) (Maybe n) Source #
Viewports
Describes the state of a viewport as it appears as its most recent rendering.
Instances
Read Viewport Source # | |
Show Viewport Source # | |
Generic 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-0.60.2-HWZUtq8CAIx83hEucgtRjx" '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)))) |
data ViewportType Source #
The type of viewports that indicates the direction(s) in which a viewport is scrollable.
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
Eq ViewportType Source # | |
Defined in Brick.Types.Internal (==) :: ViewportType -> ViewportType -> Bool # (/=) :: ViewportType -> ViewportType -> Bool # | |
Show ViewportType Source # | |
Defined in Brick.Types.Internal showsPrec :: Int -> ViewportType -> ShowS # show :: ViewportType -> String # showList :: [ViewportType] -> ShowS # |
Event-handling types
The monad in which event handlers run. Although it may be tempting
to dig into the reader value yourself, just use
lookupViewport
.
Instances
Monad (EventM n) Source # | |
Functor (EventM n) Source # | |
MonadFail (EventM n) Source # | |
Defined in Brick.Types | |
Applicative (EventM n) Source # | |
MonadIO (EventM n) Source # | |
Defined in Brick.Types | |
MonadThrow (EventM n) Source # | |
Defined in Brick.Types | |
MonadCatch (EventM n) Source # | |
MonadMask (EventM n) Source # | |
The type of actions to take upon completion of an event handler.
data BrickEvent n e Source #
The type of events.
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
(Eq e, Eq n) => Eq (BrickEvent n e) Source # | |
Defined in Brick.Types.Internal (==) :: 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 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 # | |
(Show e, Show n) => Show (BrickEvent n e) Source # | |
Defined in Brick.Types.Internal showsPrec :: Int -> BrickEvent n e -> ShowS # show :: BrickEvent n e -> String # showList :: [BrickEvent n e] -> ShowS # |
:: a | The state value. |
-> Lens' a b | The lens to use to extract and store the target of the event. |
-> (e -> b -> EventM n b) | The event handler. |
-> e | The event to handle. |
-> EventM n a |
A convenience function for handling events intended for values
that are targets of lenses in your application state. This function
obtains the target value of the specified lens, invokes handleEvent
on it, and stores the resulting transformed value back in the state
using the lens.
Rendering infrastructure
type RenderM n a = ReaderT Context (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 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.
attrL :: forall r. Getting r Context Attr Source #
The rendering context's current drawing attribute.
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.
Result | |
|
Instances
Read n => Read (Result n) Source # | |
Show n => Show (Result n) Source # | |
Generic (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-0.60.2-HWZUtq8CAIx83hEucgtRjx" 'False) (C1 ('MetaCons "Result" 'PrefixI 'True) ((S1 ('MetaSel ('Just "image") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Image) :*: S1 ('MetaSel ('Just "cursors") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [CursorLocation n])) :*: (S1 ('MetaSel ('Just "visibilityRequests") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VisibilityRequest]) :*: (S1 ('MetaSel ('Just "extents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Extent n]) :*: S1 ('MetaSel ('Just "borders") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (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.
Extent | |
|
Instances
Read n => Read (Extent n) Source # | |
Show n => Show (Extent n) Source # | |
Generic (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-0.60.2-HWZUtq8CAIx83hEucgtRjx" 'False) (C1 ('MetaCons "Extent" 'PrefixI 'True) (S1 ('MetaSel ('Just "extentName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 n) :*: (S1 ('MetaSel ('Just "extentUpperLeft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Location) :*: S1 ('MetaSel ('Just "extentSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int, Int))))) |
Rendering result lenses
visibilityRequestsL :: forall n. Lens' (Result n) [VisibilityRequest] Source #
Visibility requests
data VisibilityRequest Source #
Instances
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.
Dynamic borders
Information about how to redraw a dynamic border character when it abuts another dynamic border character.
DynBorder | |
|
Instances
Eq DynBorder Source # | |
Read DynBorder Source # | |
Show DynBorder Source # | |
Generic DynBorder Source # | |
NFData DynBorder Source # | |
Defined in Brick.Types.Internal | |
type Rep DynBorder Source # | |
Defined in Brick.Types.Internal type Rep DynBorder = D1 ('MetaData "DynBorder" "Brick.Types.Internal" "brick-0.60.2-HWZUtq8CAIx83hEucgtRjx" '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))))) |
data BorderSegment Source #
A border character has four segments, one extending in each direction (horizontally and vertically) from the center of the character.
Instances
Instances
Monad Edges Source # | |
Functor Edges Source # | |
Applicative Edges Source # | |
Eq a => Eq (Edges a) Source # | |
Ord a => Ord (Edges a) Source # | |
Read a => Read (Edges a) Source # | |
Show a => Show (Edges a) Source # | |
Generic (Edges a) Source # | |
NFData a => NFData (Edges a) Source # | |
Defined in Brick.Types.Common | |
type Rep (Edges a) Source # | |
Defined in Brick.Types.Common type Rep (Edges a) = D1 ('MetaData "Edges" "Brick.Types.Common" "brick-0.60.2-HWZUtq8CAIx83hEucgtRjx" '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
.
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. |
The type of padding.
Scrolling direction.
Renderer internals (for benchmarking)
data RenderState n Source #
Instances
(Ord n, Read n) => Read (RenderState n) Source # | |
Defined in Brick.Types.Internal 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 showsPrec :: Int -> RenderState n -> ShowS # show :: RenderState n -> String # showList :: [RenderState n] -> ShowS # | |
Generic (RenderState n) Source # | |
Defined in Brick.Types.Internal type Rep (RenderState n) :: Type -> Type # from :: RenderState n -> Rep (RenderState n) x # to :: Rep (RenderState n) x -> RenderState n # | |
NFData n => NFData (RenderState n) Source # | |
Defined in Brick.Types.Internal rnf :: RenderState n -> () # | |
type Rep (RenderState n) Source # | |
Defined in Brick.Types.Internal |
Orphan instances
TerminalLocation (CursorLocation n) Source # | |
locationColumnL :: Lens' (CursorLocation n) Int Source # locationColumn :: CursorLocation n -> Int Source # locationRowL :: Lens' (CursorLocation n) Int Source # locationRow :: CursorLocation n -> Int Source # |