reflex-vty-0.1.1.1: Reflex FRP host and widgets for vty applications

Safe HaskellNone
LanguageHaskell2010

Reflex.Vty.Widget

Description

 
Synopsis

Documentation

data VtyWidgetCtx t Source #

The context within which a VtyWidget runs

Constructors

VtyWidgetCtx 

Fields

newtype VtyWidget t m a Source #

A widget that can read its context and produce image output

Constructors

VtyWidget 
Instances
NotReady t m => NotReady t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

notReadyUntil :: Event t a -> VtyWidget t m () #

notReady :: VtyWidget t m () #

PerformEvent t m => PerformEvent t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Associated Types

type Performable (VtyWidget t m) :: Type -> Type #

Methods

performEvent :: Event t (Performable (VtyWidget t m) a) -> VtyWidget t m (Event t a) #

performEvent_ :: Event t (Performable (VtyWidget t m) ()) -> VtyWidget t m () #

TriggerEvent t m => TriggerEvent t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

newTriggerEvent :: VtyWidget t m (Event t a, a -> IO ()) #

newTriggerEventWithOnComplete :: VtyWidget t m (Event t a, a -> IO () -> IO ()) #

newEventWithLazyTriggerWithOnComplete :: ((a -> IO () -> IO ()) -> IO (IO ())) -> VtyWidget t m (Event t a) #

PostBuild t m => PostBuild t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

getPostBuild :: VtyWidget t m (Event t ()) #

(Adjustable t m, MonadHold t m, Reflex t) => Adjustable t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

runWithReplace :: VtyWidget t m a -> Event t (VtyWidget t m b) -> VtyWidget t m (a, Event t b) #

traverseIntMapWithKeyWithAdjust :: (Key -> v -> VtyWidget t m v') -> IntMap v -> Event t (PatchIntMap v) -> VtyWidget t m (IntMap v', Event t (PatchIntMap v')) #

traverseDMapWithKeyWithAdjust :: GCompare k => (forall a. k a -> v a -> VtyWidget t m (v' a)) -> DMap k v -> Event t (PatchDMap k v) -> VtyWidget t m (DMap k v', Event t (PatchDMap k v')) #

traverseDMapWithKeyWithAdjustWithMove :: GCompare k => (forall a. k a -> v a -> VtyWidget t m (v' a)) -> DMap k v -> Event t (PatchDMapWithMove k v) -> VtyWidget t m (DMap k v', Event t (PatchDMapWithMove k v')) #

MonadReflexCreateTrigger t m => MonadReflexCreateTrigger t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

newEventWithTrigger :: (EventTrigger t a -> IO (IO ())) -> VtyWidget t m (Event t a) #

newFanEventWithTrigger :: GCompare k => (forall a. k a -> EventTrigger t a -> IO (IO ())) -> VtyWidget t m (EventSelector t k) #

(Reflex t, Monad m) => ImageWriter t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

tellImages :: Behavior t [Image] -> VtyWidget t m () Source #

(Reflex t, Monad m) => HasFocus t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

focus :: VtyWidget t m (Dynamic t Bool) Source #

(Reflex t, Monad m) => HasVtyInput t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

input :: VtyWidget t m (Event t VtyEvent) Source #

(Reflex t, Monad m) => HasDisplaySize t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

MonadTrans (VtyWidget t) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

lift :: Monad m => m a -> VtyWidget t m a #

MonadSample t m => MonadSample (t :: Type) (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

sample :: Behavior t a -> VtyWidget t m a #

MonadHold t m => MonadHold (t :: Type) (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

hold :: a -> Event t a -> VtyWidget t m (Behavior t a) #

holdDyn :: a -> Event t a -> VtyWidget t m (Dynamic t a) #

holdIncremental :: Patch p => PatchTarget p -> Event t p -> VtyWidget t m (Incremental t p) #

buildDynamic :: PushM t a -> Event t a -> VtyWidget t m (Dynamic t a) #

headE :: Event t a -> VtyWidget t m (Event t a) #

Monad m => Monad (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

(>>=) :: VtyWidget t m a -> (a -> VtyWidget t m b) -> VtyWidget t m b #

(>>) :: VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m b #

return :: a -> VtyWidget t m a #

fail :: String -> VtyWidget t m a #

Functor m => Functor (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

fmap :: (a -> b) -> VtyWidget t m a -> VtyWidget t m b #

(<$) :: a -> VtyWidget t m b -> VtyWidget t m a #

MonadFix m => MonadFix (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

mfix :: (a -> VtyWidget t m a) -> VtyWidget t m a #

Monad m => Applicative (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

pure :: a -> VtyWidget t m a #

(<*>) :: VtyWidget t m (a -> b) -> VtyWidget t m a -> VtyWidget t m b #

liftA2 :: (a -> b -> c) -> VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m c #

(*>) :: VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m b #

(<*) :: VtyWidget t m a -> VtyWidget t m b -> VtyWidget t m a #

MonadIO m => MonadIO (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

liftIO :: IO a -> VtyWidget t m a #

MonadNodeId m => MonadNodeId (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

type Performable (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

data VtyWidgetOut t Source #

The output of a VtyWidget

Constructors

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

Methods

tellImages :: Behavior t [Image] -> m () Source #

Send images upstream for rendering

Instances
(Reflex t, Monad m) => ImageWriter t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

tellImages :: Behavior t [Image] -> VtyWidget t m () Source #

(Monad m, Reflex t) => ImageWriter t (BehaviorWriterT t [Image] m) Source # 
Instance details

Defined in Reflex.Vty.Widget

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

Minimal complete definition

Nothing

Methods

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
HasDisplaySize t m => HasDisplaySize t (NodeIdT m) Source # 
Instance details

Defined in Reflex.Vty.Widget

HasDisplaySize t m => HasDisplaySize t (ReaderT x m) Source # 
Instance details

Defined in Reflex.Vty.Widget

(Reflex t, Monad m) => HasDisplaySize t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

(Reflex t, Monad m) => HasDisplaySize t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

HasDisplaySize t m => HasDisplaySize t (EventWriterT t x m) Source # 
Instance details

Defined in Reflex.Vty.Widget

HasDisplaySize t m => HasDisplaySize t (DynamicWriterT t x m) Source # 
Instance details

Defined in Reflex.Vty.Widget

HasDisplaySize t m => HasDisplaySize t (BehaviorWriterT t x m) Source # 
Instance details

Defined in Reflex.Vty.Widget

class HasFocus t m | m -> t where Source #

A class for things that can dynamically gain and lose focus

Methods

focus :: m (Dynamic t Bool) Source #

Instances
(Reflex t, Monad m) => HasFocus t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

focus :: VtyWidget t m (Dynamic t Bool) Source #

class HasVtyInput t m | m -> t where Source #

A class for things that can receive vty events as input

Methods

input :: m (Event t VtyEvent) Source #

Instances
(Reflex t, Monad m) => HasVtyInput t (VtyWidget t m) Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

input :: VtyWidget t m (Event t VtyEvent) Source #

data DynRegion t Source #

A dynamic chunk of the display area

currentRegion :: Reflex t => DynRegion t -> Behavior t Region Source #

A behavior of the current display area represented by a DynRegion

data Region Source #

A chunk of the display area

Instances
Eq Region Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

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

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

Ord Region Source # 
Instance details

Defined in Reflex.Vty.Widget

Read Region Source # 
Instance details

Defined in Reflex.Vty.Widget

Show Region Source # 
Instance details

Defined in Reflex.Vty.Widget

regionSize :: Region -> (Int, Int) Source #

The width and height of a Region

regionBlankImage :: Region -> Image Source #

Produces an Image that fills a region with space characters

data Drag Source #

Information about a drag operation

Constructors

Drag 

Fields

Instances
Eq Drag Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

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

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

Ord Drag Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

compare :: Drag -> Drag -> Ordering #

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

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

(>) :: Drag -> Drag -> Bool #

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

max :: Drag -> Drag -> Drag #

min :: Drag -> Drag -> Drag #

Show Drag Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

showsPrec :: Int -> Drag -> ShowS #

show :: Drag -> String #

showList :: [Drag] -> ShowS #

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 Drags

data MouseDown Source #

Information about a mouse down event

data MouseUp Source #

Information about a mouse up event

Instances
Eq MouseUp Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

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

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

Ord MouseUp Source # 
Instance details

Defined in Reflex.Vty.Widget

Show MouseUp Source # 
Instance details

Defined in Reflex.Vty.Widget

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

pane Source #

Arguments

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

splitV Source #

Arguments

:: (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 # 
Instance details

Defined in Reflex.Vty.Widget

Methods

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

data BoxStyle Source #

Defines a set of symbols to use to draw the outlines of boxes C.f. https://en.wikipedia.org/wiki/Box-drawing_character

Instances
Default BoxStyle Source # 
Instance details

Defined in Reflex.Vty.Widget

Methods

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

type KeyCombo = (Key, [Modifier]) Source #

Type synonym for a key and modifier combination

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)

keyCombos :: (Reflex t, Monad m) => Set KeyCombo -> VtyWidget t m (Event t KeyCombo) Source #

Emit an event that fires whenever any of the provided key combinations occur

blank :: Monad m => VtyWidget t m () Source #

A widget that draws nothing