Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data VtyWidgetCtx t = VtyWidgetCtx {}
- newtype VtyWidget t m a = VtyWidget {
- unVtyWidget :: BehaviorWriterT t [Image] (ReaderT (VtyWidgetCtx t) m) a
- data VtyWidgetOut t = VtyWidgetOut {
- _vtyWidgetOut_shutdown :: Event t ()
- class (Reflex t, Monad m) => ImageWriter t m | m -> t where
- tellImages :: Behavior t [Image] -> m ()
- runVtyWidget :: (Reflex t, MonadNodeId m) => VtyWidgetCtx t -> VtyWidget t m a -> m (a, Behavior t [Image])
- mainWidget :: (forall t m. (MonadVtyApp t m, MonadNodeId m) => VtyWidget t m (Event t ())) -> IO ()
- mainWidgetWithHandle :: Vty -> (forall t m. (MonadVtyApp t m, MonadNodeId m) => VtyWidget t m (Event t ())) -> IO ()
- class (Reflex t, Monad m) => HasDisplaySize t m | m -> t where
- displayWidth :: m (Dynamic t Int)
- displayHeight :: m (Dynamic t Int)
- class HasFocus t m | m -> t where
- class HasVtyInput t m | m -> t where
- data DynRegion t = DynRegion {
- _dynRegion_left :: Dynamic t Int
- _dynRegion_top :: Dynamic t Int
- _dynRegion_width :: Dynamic t Int
- _dynRegion_height :: Dynamic t Int
- currentRegion :: Reflex t => DynRegion t -> Behavior t Region
- data Region = Region {
- _region_left :: Int
- _region_top :: Int
- _region_width :: Int
- _region_height :: Int
- regionSize :: Region -> (Int, Int)
- regionBlankImage :: Region -> Image
- data Drag = Drag {
- _drag_from :: (Int, Int)
- _drag_to :: (Int, Int)
- _drag_button :: Button
- _drag_modifiers :: [Modifier]
- _drag_end :: Bool
- drag :: (Reflex t, MonadFix m, MonadHold t m) => Button -> VtyWidget t m (Event t Drag)
- data MouseDown = MouseDown {}
- data MouseUp = MouseUp {
- _mouseUp_button :: Maybe Button
- _mouseUp_coordinates :: (Int, Int)
- mouseDown :: (Reflex t, Monad m) => Button -> VtyWidget t m (Event t MouseDown)
- mouseUp :: (Reflex t, Monad m) => VtyWidget t m (Event t MouseUp)
- pane :: (Reflex t, Monad m, MonadNodeId m) => DynRegion t -> Dynamic t Bool -> VtyWidget t m a -> VtyWidget t m a
- splitV :: (Reflex t, Monad m, MonadNodeId m) => Dynamic t (Int -> Int) -> Dynamic t (Bool, Bool) -> VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m (a, b)
- splitVDrag :: (Reflex t, MonadFix m, MonadHold t m, MonadNodeId m) => VtyWidget t m () -> VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m (a, b)
- box :: (Monad m, Reflex t, MonadNodeId m) => Behavior t BoxStyle -> VtyWidget t m a -> VtyWidget t m a
- boxStatic :: (Reflex t, Monad m, MonadNodeId m) => BoxStyle -> VtyWidget t m a -> VtyWidget t m a
- data RichTextConfig t = RichTextConfig {}
- richText :: (Reflex t, Monad m) => RichTextConfig t -> Behavior t Text -> VtyWidget t m ()
- text :: (Reflex t, Monad m) => Behavior t Text -> VtyWidget t m ()
- display :: (Reflex t, Monad m, Show a) => Behavior t a -> VtyWidget t m ()
- data BoxStyle = BoxStyle {
- _boxStyle_nw :: Char
- _boxStyle_n :: Char
- _boxStyle_ne :: Char
- _boxStyle_e :: Char
- _boxStyle_se :: Char
- _boxStyle_s :: Char
- _boxStyle_sw :: Char
- _boxStyle_w :: Char
- hyphenBoxStyle :: BoxStyle
- singleBoxStyle :: BoxStyle
- roundedBoxStyle :: BoxStyle
- thickBoxStyle :: BoxStyle
- doubleBoxStyle :: BoxStyle
- fill :: (Reflex t, Monad m) => Char -> VtyWidget t m ()
- hRule :: (Reflex t, Monad m) => BoxStyle -> VtyWidget t m ()
- type KeyCombo = (Key, [Modifier])
- key :: (Monad m, Reflex t) => Key -> VtyWidget t m (Event t KeyCombo)
- keys :: (Monad m, Reflex t) => [Key] -> VtyWidget t m (Event t KeyCombo)
- keyCombos :: (Reflex t, Monad m) => Set KeyCombo -> VtyWidget t m (Event t KeyCombo)
- blank :: Monad m => VtyWidget t m ()
Documentation
data VtyWidgetCtx t Source #
The context within which a VtyWidget
runs
VtyWidgetCtx | |
|
newtype VtyWidget t m a Source #
A widget that can read its context and produce image output
VtyWidget | |
|
Instances
data VtyWidgetOut t Source #
The output of a VtyWidget
VtyWidgetOut | |
|
class (Reflex t, Monad m) => ImageWriter t m | m -> t where Source #
A class for widgets that can produce images to draw to the display
tellImages :: Behavior t [Image] -> m () Source #
Send images upstream for rendering
Instances
(Reflex t, Monad m) => ImageWriter t (VtyWidget t m) Source # | |
Defined in Reflex.Vty.Widget | |
(Monad m, Reflex t) => ImageWriter t (BehaviorWriterT t [Image] m) Source # | |
Defined in Reflex.Vty.Widget tellImages :: Behavior t [Image] -> BehaviorWriterT t [Image] m () Source # |
runVtyWidget :: (Reflex t, MonadNodeId m) => VtyWidgetCtx t -> VtyWidget t m a -> m (a, Behavior t [Image]) Source #
Runs a VtyWidget
with a given context
mainWidget :: (forall t m. (MonadVtyApp t m, MonadNodeId m) => VtyWidget t m (Event t ())) -> IO () Source #
Like mainWidgetWithHandle
, but uses a default vty configuration
mainWidgetWithHandle :: Vty -> (forall t m. (MonadVtyApp t m, MonadNodeId m) => VtyWidget t m (Event t ())) -> IO () Source #
Sets up the top-level context for a VtyWidget
and runs it with that context
class (Reflex t, Monad m) => HasDisplaySize t m | m -> t where Source #
A class for things that know their own display size dimensions
Nothing
displayWidth :: m (Dynamic t Int) Source #
Retrieve the display width (columns)
displayWidth :: (f m' ~ m, MonadTrans f, HasDisplaySize t m') => m (Dynamic t Int) Source #
Retrieve the display width (columns)
displayHeight :: m (Dynamic t Int) Source #
Retrieve the display height (rows)
displayHeight :: (f m' ~ m, MonadTrans f, HasDisplaySize t m') => m (Dynamic t Int) Source #
Retrieve the display height (rows)
Instances
class HasFocus t m | m -> t where Source #
A class for things that can dynamically gain and lose focus
class HasVtyInput t m | m -> t where Source #
A class for things that can receive vty events as input
A dynamic chunk of the display area
DynRegion | |
|
currentRegion :: Reflex t => DynRegion t -> Behavior t Region Source #
A behavior of the current display area represented by a DynRegion
A chunk of the display area
Region | |
|
regionBlankImage :: Region -> Image Source #
Produces an Image
that fills a region with space characters
Information about a drag operation
Drag | |
|
drag :: (Reflex t, MonadFix m, MonadHold t m) => Button -> VtyWidget t m (Event t Drag) Source #
Converts raw vty mouse drag events into an event stream of Drag
s
Information about a mouse down event
MouseDown | |
|
Information about a mouse up event
MouseUp | |
|
mouseDown :: (Reflex t, Monad m) => Button -> VtyWidget t m (Event t MouseDown) Source #
Mouse down events for a particular mouse button
mouseUp :: (Reflex t, Monad m) => VtyWidget t m (Event t MouseUp) Source #
Mouse up events for a particular mouse button
:: (Reflex t, Monad m, MonadNodeId m) | |
=> DynRegion t | |
-> Dynamic t Bool | Whether the widget should be focused when the parent is. |
-> VtyWidget t m a | |
-> VtyWidget t m a |
Low-level widget combinator that runs a child VtyWidget
within
a given region and context. This widget filters and modifies the input
that the child widget receives such that:
* unfocused widgets receive no key events
* mouse inputs outside the region are ignored
* mouse inputs inside the region have their coordinates translated such
that (0,0) is the top-left corner of the region
:: (Reflex t, Monad m, MonadNodeId m) | |
=> Dynamic t (Int -> Int) | Function used to determine size of first pane based on available size |
-> Dynamic t (Bool, Bool) | How to focus the two sub-panes, given that we are focused. |
-> VtyWidget t m a | Widget for first pane |
-> VtyWidget t m b | Widget for second pane |
-> VtyWidget t m (a, b) |
A plain split of the available space into vertically stacked panes. No visual separator is built in here.
splitVDrag :: (Reflex t, MonadFix m, MonadHold t m, MonadNodeId m) => VtyWidget t m () -> VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m (a, b) Source #
A split of the available space into two parts with a draggable separator. Starts with half the space allocated to each, and the first pane has focus. Clicking in a pane switches focus.
box :: (Monad m, Reflex t, MonadNodeId m) => Behavior t BoxStyle -> VtyWidget t m a -> VtyWidget t m a Source #
Draws a box in the provided style and a child widget inside of that box
boxStatic :: (Reflex t, Monad m, MonadNodeId m) => BoxStyle -> VtyWidget t m a -> VtyWidget t m a Source #
A box whose style is static
data RichTextConfig t Source #
Configuration options for displaying "rich" text
Instances
Reflex t => Default (RichTextConfig t) Source # | |
Defined in Reflex.Vty.Widget def :: RichTextConfig t # |
richText :: (Reflex t, Monad m) => RichTextConfig t -> Behavior t Text -> VtyWidget t m () Source #
A widget that displays text with custom time-varying attributes
text :: (Reflex t, Monad m) => Behavior t Text -> VtyWidget t m () Source #
Renders text, wrapped to the container width
display :: (Reflex t, Monad m, Show a) => Behavior t a -> VtyWidget t m () Source #
Renders any behavior whose value can be converted to
String
as text
Defines a set of symbols to use to draw the outlines of boxes C.f. https://en.wikipedia.org/wiki/Box-drawing_character
BoxStyle | |
|
hyphenBoxStyle :: BoxStyle Source #
A box style that uses hyphens and pipe characters. Doesn't handle corners very well.
singleBoxStyle :: BoxStyle Source #
A single line box style
roundedBoxStyle :: BoxStyle Source #
A single line box style with rounded corners
thickBoxStyle :: BoxStyle Source #
A thick single line box style
doubleBoxStyle :: BoxStyle Source #
A double line box style
fill :: (Reflex t, Monad m) => Char -> VtyWidget t m () Source #
Fill the background with a particular character.
hRule :: (Reflex t, Monad m) => BoxStyle -> VtyWidget t m () Source #
Fill the background with the bottom
key :: (Monad m, Reflex t) => Key -> VtyWidget t m (Event t KeyCombo) Source #
Emits an event that fires on a particular key press (without modifiers)
keys :: (Monad m, Reflex t) => [Key] -> VtyWidget t m (Event t KeyCombo) Source #
Emits an event that fires on particular key presses (without modifiers)