brick-0.29.1: A declarative terminal user interface library

Safe HaskellNone
LanguageHaskell2010

Brick.Types

Contents

Description

Basic types used by this library.

Synopsis

The Widget type

data Widget n Source #

The type of widgets.

Constructors

Widget 

Fields

Location types and lenses

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 #

data CursorLocation n Source #

A cursor location. These are returned by the rendering process.

Constructors

CursorLocation 

Fields

Viewports

data Viewport Source #

Describes the state of a viewport as it appears as its most recent rendering.

Constructors

VP 

Fields

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.

Event-handling types

newtype EventM n a Source #

The monad in which event handlers run. Although it may be tempting to dig into the reader value yourself, just use lookupViewport.

Constructors

EventM 

Fields

Instances

Monad (EventM n) Source # 

Methods

(>>=) :: EventM n a -> (a -> EventM n b) -> EventM n b #

(>>) :: EventM n a -> EventM n b -> EventM n b #

return :: a -> EventM n a #

fail :: String -> EventM n a #

Functor (EventM n) Source # 

Methods

fmap :: (a -> b) -> EventM n a -> EventM n b #

(<$) :: a -> EventM n b -> EventM n a #

Applicative (EventM n) Source # 

Methods

pure :: a -> EventM n a #

(<*>) :: EventM n (a -> b) -> EventM n a -> EventM n b #

(*>) :: EventM n a -> EventM n b -> EventM n b #

(<*) :: EventM n a -> EventM n b -> EventM n a #

MonadIO (EventM n) Source # 

Methods

liftIO :: IO a -> EventM n a #

data Next a Source #

The type of actions to take upon completion of an event handler.

Instances

Functor Next Source # 

Methods

fmap :: (a -> b) -> Next a -> Next b #

(<$) :: a -> Next b -> Next a #

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 n value is the resource name of the clicked widget (see clickable).

MouseUp n (Maybe Button) Location

A mouse-up event on the specified region was received. The n value is the resource name of the clicked widget (see clickable).

Instances

(Eq n, Eq e) => Eq (BrickEvent n e) Source # 

Methods

(==) :: BrickEvent n e -> BrickEvent n e -> Bool #

(/=) :: BrickEvent n e -> BrickEvent n e -> Bool #

(Ord n, Ord e) => Ord (BrickEvent n e) Source # 

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 #

(Show n, Show e) => Show (BrickEvent n e) Source # 

Methods

showsPrec :: Int -> BrickEvent n e -> ShowS #

show :: BrickEvent n e -> String #

showList :: [BrickEvent n e] -> ShowS #

handleEventLensed Source #

Arguments

:: 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

data Context Source #

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.

Instances

attrL :: forall r. Getting r Context Attr Source #

The rendering context's current drawing attribute.

Rendering results

data Result n Source #

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

Show n => Show (Result n) Source # 

Methods

showsPrec :: Int -> Result n -> ShowS #

show :: Result n -> String #

showList :: [Result n] -> ShowS #

lookupAttrName :: AttrName -> RenderM n Attr Source #

Given an attribute name, obtain the attribute for the attribute name by consulting the context's attribute map.

data Extent n Source #

An extent of a named area: its size, location, and origin.

Instances

Show n => Show (Extent n) Source # 

Methods

showsPrec :: Int -> Extent n -> ShowS #

show :: Extent n -> String #

showList :: [Extent n] -> ShowS #

Rendering result lenses

imageL :: forall n. Lens' (Result n) Image Source #

extentsL :: forall n. Lens' (Result n) [Extent n] Source #

Visibility requests

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.

Miscellaneous

data Size Source #

Widget growth policies. These policies communicate to layout algorithms how a widget uses space when being rendered. These policies influence rendering order and space allocation in the box layout algorithm.

Constructors

Fixed

Fixed widgets take up the same amount of space no matter how much they are given (non-greedy).

Greedy

Greedy widgets take up all the space they are given.

Instances

Eq Size Source # 

Methods

(==) :: Size -> Size -> Bool #

(/=) :: Size -> Size -> Bool #

Ord Size Source # 

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

(>=) :: Size -> Size -> Bool #

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

data Padding Source #

The type of padding.

Constructors

Pad Int

Pad by the specified number of rows or columns.

Max

Pad up to the number of available rows or columns.

data Direction Source #

Scrolling direction.

Constructors

Up

Up/left

Down

Down/right

Orphan instances