| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Reflex.Vty.Widget
Description
Synopsis
- mainWidgetWithHandle :: Vty -> (forall t m. (MonadVtyApp t m, HasImageWriter t m, MonadNodeId m, HasDisplayRegion t m, HasFocusReader t m, HasInput t m, HasTheme t m) => m (Event t ())) -> IO ()
- data VtyWidgetOut t = VtyWidgetOut {- _vtyWidgetOut_shutdown :: Event t ()
 
- mainWidget :: (forall t m. (MonadVtyApp t m, HasImageWriter t m, MonadNodeId m, HasDisplayRegion t m, HasFocusReader t m, HasTheme t m, HasInput t m) => m (Event t ())) -> IO ()
- class HasInput t m | m -> t where
- newtype Input t m a = Input {}
- runInput :: Reflex t => Event t VtyEvent -> Input t m a -> m a
- type KeyCombo = (Key, [Modifier])
- key :: (Monad m, Reflex t, HasInput t m) => Key -> m (Event t KeyCombo)
- keys :: (Monad m, Reflex t, HasInput t m) => [Key] -> m (Event t KeyCombo)
- keyCombo :: (Reflex t, Monad m, HasInput t m) => KeyCombo -> m (Event t KeyCombo)
- keyCombos :: (Reflex t, Monad m, HasInput t m) => Set KeyCombo -> m (Event t KeyCombo)
- filterKeys :: (Reflex t, HasInput t m) => (KeyCombo -> Bool) -> m a -> m a
- mouseInRegion :: Region -> VtyEvent -> Maybe VtyEvent
- data MouseTrackingState
- inputInFocusedRegion :: forall t m. (MonadFix m, MonadHold t m, HasDisplayRegion t m, HasFocusReader t m, HasInput t m) => m (Event t VtyEvent)
- data Region = Region {- _region_left :: Int
- _region_top :: Int
- _region_width :: Int
- _region_height :: Int
 
- nilRegion :: Region
- regionSize :: Region -> (Int, Int)
- isWithin :: Region -> Int -> Int -> Bool
- regionBlankImage :: Attr -> Region -> Image
- class (Reflex t, Monad m) => HasDisplayRegion t m | m -> t where
- displayWidth :: HasDisplayRegion t m => m (Dynamic t Int)
- displayHeight :: HasDisplayRegion t m => m (Dynamic t Int)
- newtype DisplayRegion t m a = DisplayRegion {- unDisplayRegion :: ReaderT (Dynamic t Region) m a
 
- runDisplayRegion :: (Reflex t, Monad m) => Dynamic t Region -> DisplayRegion t m a -> m a
- class (Reflex t, Monad m) => HasFocusReader t m | m -> t where
- newtype FocusReader t m a = FocusReader {- unFocusReader :: ReaderT (Dynamic t Bool) m a
 
- runFocusReader :: (Reflex t, Monad m) => Dynamic t Bool -> FocusReader t m a -> m a
- class (Reflex t, Monad m) => HasImageWriter t m | m -> t where
- newtype ImageWriter t m a = ImageWriter {- unImageWriter :: BehaviorWriterT t [Image] m a
 
- runImageWriter :: (Reflex t, Monad m) => ImageWriter t m a -> m (a, Behavior t [Image])
- class (Reflex t, Monad m) => HasTheme t m | m -> t where
- newtype ThemeReader t m a = ThemeReader {- unThemeReader :: ReaderT (Behavior t Attr) m a
 
- runThemeReader :: (Reflex t, Monad m) => Behavior t Attr -> ThemeReader t m a -> m a
- withinImage :: Region -> Image -> Image
- imagesInRegion :: Reflex t => Behavior t Region -> Behavior t [Image] -> Behavior t [Image]
- pane :: (MonadFix m, MonadHold t m, HasInput t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Region -> Dynamic t Bool -> m a -> m a
- blank :: Monad m => m ()
Running a vty application
mainWidgetWithHandle :: Vty -> (forall t m. (MonadVtyApp t m, HasImageWriter t m, MonadNodeId m, HasDisplayRegion t m, HasFocusReader t m, HasInput t m, HasTheme t m) => m (Event t ())) -> IO () Source #
Sets up the top-level context for a vty widget and runs it with that context
data VtyWidgetOut t Source #
The output of a vty widget
Constructors
| VtyWidgetOut | |
| Fields 
 | |
mainWidget :: (forall t m. (MonadVtyApp t m, HasImageWriter t m, MonadNodeId m, HasDisplayRegion t m, HasFocusReader t m, HasTheme t m, HasInput t m) => m (Event t ())) -> IO () Source #
Like mainWidgetWithHandle, but uses a default vty configuration
Input Events
class HasInput t m | m -> t where Source #
A class for things that can receive vty events as input
Minimal complete definition
Nothing
Methods
input :: m (Event t VtyEvent) Source #
localInput :: (Event t VtyEvent -> Event t VtyEvent) -> m a -> m a Source #
User input events that the widget's parent chooses to share. These will generally be filtered for relevance.
A widget that can receive input events. See Event
Instances
runInput :: Reflex t => Event t VtyEvent -> Input t m a -> m a Source #
Runs an Input with a given context
Filtering input
key :: (Monad m, Reflex t, HasInput t m) => Key -> m (Event t KeyCombo) Source #
Emits an event that fires on a particular key press (without modifiers)
keys :: (Monad m, Reflex t, HasInput t m) => [Key] -> m (Event t KeyCombo) Source #
Emits an event that fires on particular key presses (without modifiers)
keyCombo :: (Reflex t, Monad m, HasInput t m) => KeyCombo -> m (Event t KeyCombo) Source #
Emit an event that fires whenever the provided key combination occurs
keyCombos :: (Reflex t, Monad m, HasInput t m) => Set KeyCombo -> m (Event t KeyCombo) Source #
Emit an event that fires whenever any of the provided key combinations occur
filterKeys :: (Reflex t, HasInput t m) => (KeyCombo -> Bool) -> m a -> m a Source #
Filter the keyboard input that a child widget may receive
mouseInRegion :: Region -> VtyEvent -> Maybe VtyEvent Source #
Filter mouse input events based on whether they target a particular region and translate them to the internal coordinate system of that region.
NB: Non-mouse events are passed through unfiltered and unchanged
data MouseTrackingState Source #
- Trackingstate means actively tracking the current stream of mouse events
- NotTrackingstate means not tracking the current stream of mouse events
- WaitingForInputmeans state will be set on next- EvMouseDownevent
Constructors
| Tracking Button | |
| NotTracking | |
| WaitingForInput | 
Instances
| Eq MouseTrackingState Source # | |
| Defined in Reflex.Vty.Widget Methods (==) :: MouseTrackingState -> MouseTrackingState -> Bool # (/=) :: MouseTrackingState -> MouseTrackingState -> Bool # | |
| Show MouseTrackingState Source # | |
| Defined in Reflex.Vty.Widget Methods showsPrec :: Int -> MouseTrackingState -> ShowS # show :: MouseTrackingState -> String # showList :: [MouseTrackingState] -> ShowS # | |
inputInFocusedRegion :: forall t m. (MonadFix m, MonadHold t m, HasDisplayRegion t m, HasFocusReader t m, HasInput t m) => m (Event t VtyEvent) Source #
Filter mouse input outside the current display region and all input if the region is not focused mouse drag sequences that start OFF the region are NOT reported mouse drag sequences that start ON the region and drag off ARE reported
Getting and setting the display region
A chunk of the display area
Constructors
| Region | |
| Fields 
 | |
regionBlankImage :: Attr -> Region -> Image Source #
Produces an Image that fills a region with space characters
class (Reflex t, Monad m) => HasDisplayRegion t m | m -> t where Source #
A class for things that know their own display size dimensions
Minimal complete definition
Nothing
Methods
askRegion :: m (Dynamic t Region) Source #
Retrieve the display region
default askRegion :: (f m' ~ m, MonadTrans f, HasDisplayRegion t m') => m (Dynamic t Region) Source #
localRegion :: (Dynamic t Region -> Dynamic t Region) -> m a -> m a Source #
Run an action in a local region, by applying a transformation to the region
default localRegion :: (f m' ~ m, Monad m', MFunctor f, HasDisplayRegion t m') => (Dynamic t Region -> Dynamic t Region) -> m a -> m a Source #
Instances
displayWidth :: HasDisplayRegion t m => m (Dynamic t Int) Source #
Retrieve the display width
displayHeight :: HasDisplayRegion t m => m (Dynamic t Int) Source #
Retrieve the display height
newtype DisplayRegion t m a Source #
A widget that has access to a particular region of the vty display
Constructors
| DisplayRegion | |
| Fields 
 | |
Instances
runDisplayRegion :: (Reflex t, Monad m) => Dynamic t Region -> DisplayRegion t m a -> m a Source #
Run a DisplayRegion action with a given Region
Getting focus state
class (Reflex t, Monad m) => HasFocusReader t m | m -> t where Source #
A class for things that can dynamically gain and lose focus
Minimal complete definition
Nothing
Methods
focus :: m (Dynamic t Bool) Source #
default focus :: (f m' ~ m, Monad m', MonadTrans f, HasFocusReader t m') => m (Dynamic t Bool) Source #
localFocus :: (Dynamic t Bool -> Dynamic t Bool) -> m a -> m a Source #
default localFocus :: (f m' ~ m, Monad m', MFunctor f, HasFocusReader t m') => (Dynamic t Bool -> Dynamic t Bool) -> m a -> m a Source #
Instances
newtype FocusReader t m a Source #
A widget that has access to information about whether it is focused
Constructors
| FocusReader | |
| Fields 
 | |
Instances
runFocusReader :: (Reflex t, Monad m) => Dynamic t Bool -> FocusReader t m a -> m a Source #
Run a FocusReader action with the given focus value
Image output
class (Reflex t, Monad m) => HasImageWriter t m | m -> t where Source #
A class for widgets that can produce images to draw to the display
Minimal complete definition
Nothing
Methods
tellImages :: Behavior t [Image] -> m () Source #
Send images upstream for rendering
default tellImages :: (f m' ~ m, Monad m', MonadTrans f, HasImageWriter t m') => Behavior t [Image] -> m () Source #
mapImages :: (Behavior t [Image] -> Behavior t [Image]) -> m a -> m a Source #
Apply a transformation to the images produced by the child actions
Instances
newtype ImageWriter t m a Source #
A widget that can produce images to draw onto the display
Constructors
| ImageWriter | |
| Fields 
 | |
Instances
runImageWriter :: (Reflex t, Monad m) => ImageWriter t m a -> m (a, Behavior t [Image]) Source #
Run a widget that can produce images
Theming
class (Reflex t, Monad m) => HasTheme t m | m -> t where Source #
A class for things that can be visually styled
Minimal complete definition
Nothing
Methods
theme :: m (Behavior t Attr) Source #
localTheme :: (Behavior t Attr -> Behavior t Attr) -> m a -> m a Source #
Instances
newtype ThemeReader t m a Source #
A widget that has access to theme information
Constructors
| ThemeReader | |
| Fields 
 | |
Instances
runThemeReader :: (Reflex t, Monad m) => Behavior t Attr -> ThemeReader t m a -> m a Source #
Run a ThemeReader action with the given focus value
Manipulating images
imagesInRegion :: Reflex t => Behavior t Region -> Behavior t [Image] -> Behavior t [Image] Source #
Crop a behavior of images to a behavior of regions. See withinImage.
Running sub-widgets
Arguments
| :: (MonadFix m, MonadHold t m, HasInput t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) | |
| => Dynamic t Region | |
| -> Dynamic t Bool | Whether the widget should be focused when the parent is. | 
| -> m a | |
| -> m a | 
Low-level widget combinator that runs a child widget 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 inside the region have their coordinates translated such * mouse drag sequences that start OFF the region are ignored * mouse drag sequences that start ON the region and drag off are NOT ignored that (0,0) is the top-left corner of the region