reflex-vty-0.1.4.1: Reflex FRP host and widgets for VTY applications

Safe HaskellNone
LanguageHaskell2010

Reflex.Vty.Widget.Layout

Description

 
Synopsis

Documentation

data Layout t m a Source #

The Layout monad transformer keeps track of the configuration (e.g., Orientation) and Constraints of its child widgets, apportions vty real estate to each, and acts as a switchboard for focus requests. See tile and runLayout.

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

notReady :: Layout t m () #

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

Defined in Reflex.Vty.Widget.Layout

Associated Types

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

Methods

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

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

(Adjustable t m, MonadFix m, MonadHold t m) => Adjustable t (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

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

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

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

Defined in Reflex.Vty.Widget.Layout

MonadTrans (Layout t) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

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

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

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

now :: Layout t m (Event t ()) #

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

return :: a -> Layout t m a #

fail :: String -> Layout t m a #

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

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

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

Defined in Reflex.Vty.Widget.Layout

Methods

pure :: a -> Layout t m a #

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

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

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

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

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

Defined in Reflex.Vty.Widget.Layout

type Performable (Layout t m) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

type Performable (Layout t m)

runLayout Source #

Arguments

:: (MonadFix m, MonadHold t m, PostBuild t m, Monad m, MonadNodeId m) 
=> Dynamic t Orientation

The main-axis Orientation of this Layout

-> Int

The positional index of the initially focused tile

-> Event t Int

An event that shifts focus by a given number of tiles

-> Layout t m a

The Layout widget

-> VtyWidget t m a 

Run a Layout action

data TileConfig t Source #

Configuration options for and constraints on tile

Constructors

TileConfig 

Fields

Instances
Reflex t => Default (TileConfig t) Source # 
Instance details

Defined in Reflex.Vty.Widget.Layout

Methods

def :: TileConfig t #

tile Source #

Arguments

:: (Reflex t, Monad m, MonadNodeId m) 
=> TileConfig t

The tile's configuration

-> VtyWidget t m (Event t x, a)

A child widget. The Event that it returns is used to request that it be focused.

-> Layout t m a 

Tiles are the basic building blocks of Layout widgets. Each tile has a constraint on its size and ability to grow and on whether it can be focused. It also allows its child widget to request focus.

fixed :: (Reflex t, Monad m, MonadNodeId m) => Dynamic t Int -> VtyWidget t m a -> Layout t m a Source #

A tile of a fixed size that is focusable and gains focus on click

stretch :: (Reflex t, Monad m, MonadNodeId m) => VtyWidget t m a -> Layout t m a Source #

A tile that can stretch (i.e., has no fixed size) and has a minimum size of 0. This tile is focusable and gains focus on click.

col :: (MonadFix m, MonadHold t m, PostBuild t m, MonadNodeId m) => Layout t m a -> VtyWidget t m a Source #

A version of runLayout that arranges tiles in a column and uses tabNavigation to change tile focus.

row :: (MonadFix m, MonadHold t m, PostBuild t m, MonadNodeId m) => Layout t m a -> VtyWidget t m a Source #

A version of runLayout that arranges tiles in a row and uses tabNavigation to change tile focus.

tabNavigation :: (Reflex t, Monad m) => VtyWidget t m (Event t Int) Source #

Produces an Event that navigates forward one tile when the Tab key is pressed and backward one tile when Shift+Tab is pressed.

askOrientation :: Monad m => Layout t m (Dynamic t Orientation) Source #

Retrieve the current orientation of a Layout