Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype FocusId = FocusId NodeId
- newtype FocusSet = FocusSet {}
- singletonFS :: FocusId -> FocusSet
- data Refocus
- shiftFS :: FocusSet -> Maybe FocusId -> Int -> Maybe FocusId
- class (Monad m, Reflex t) => HasFocus t m | m -> t where
- newtype Focus t m a = Focus {
- unFocus :: DynamicWriterT t FocusSet (ReaderT (Dynamic t (Maybe FocusId)) (EventWriterT t (First Refocus) m)) a
- runFocus :: (MonadFix m, MonadHold t m, Reflex t) => Focus t m a -> m (a, Dynamic t FocusSet)
- anyChildFocused :: (HasFocus t m, MonadFix m) => (Dynamic t Bool -> m a) -> m a
- tabNavigation :: (Reflex t, HasInput t m, HasFocus t m) => m ()
- data Constraint
- fixed :: Reflex t => Dynamic t Int -> Dynamic t Constraint
- stretch :: Reflex t => Dynamic t Int -> Dynamic t Constraint
- flex :: Reflex t => Dynamic t Constraint
- data Orientation
- row :: (Reflex t, MonadFix m, HasLayout t m) => m a -> m a
- col :: (Reflex t, MonadFix m, HasLayout t m) => m a -> m a
- data LayoutTree a = LayoutTree a (LayoutForest a)
- newtype LayoutForest a = LayoutForest {
- unLayoutForest :: OMap NodeId (LayoutTree a)
- lookupLF :: NodeId -> LayoutForest a -> Maybe (LayoutTree a)
- singletonLF :: NodeId -> LayoutTree a -> LayoutForest a
- fromListLF :: [(NodeId, LayoutTree a)] -> LayoutForest a
- rootLT :: LayoutTree a -> a
- childrenLT :: LayoutTree a -> LayoutForest a
- solve :: Orientation -> Region -> LayoutForest (Constraint, Orientation) -> LayoutTree (Region, Orientation)
- chunk :: Orientation -> Region -> (Int, Int) -> Region
- class Monad m => HasLayout t m | m -> t where
- axis :: Dynamic t Orientation -> Dynamic t Constraint -> m a -> m a
- region :: Dynamic t Constraint -> m (Dynamic t Region)
- askOrientation :: m (Dynamic t Orientation)
- newtype Layout t m a = Layout {
- unLayout :: DynamicWriterT t (LayoutForest (Constraint, Orientation)) (ReaderT (Dynamic t (LayoutTree (Region, Orientation))) m) a
- hoistRunLayout :: (HasDisplayRegion t m, MonadFix m, Monad n) => (m a -> n b) -> Layout t m a -> Layout t n b
- runLayout :: (MonadFix m, Reflex t) => Dynamic t Orientation -> Dynamic t Region -> Layout t m a -> m a
- initLayout :: (HasDisplayRegion t m, MonadFix m) => Layout t m a -> m a
- initManager :: (HasDisplayRegion t m, Reflex t, MonadHold t m, MonadFix m) => Layout t (Focus t m) a -> m (a, Dynamic t FocusSet)
- initManager_ :: (HasDisplayRegion t m, Reflex t, MonadHold t m, MonadFix m) => Layout t (Focus t m) a -> m a
- tile' :: (MonadFix m, Reflex t, HasInput t m, HasFocus t m, HasLayout t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m (FocusId, a)
- tile :: (MonadFix m, Reflex t, HasInput t m, HasFocus t m, HasLayout t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m a
- grout :: (Reflex t, HasLayout t m, HasInput t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m a
Focus
The focus monad tracks which element is currently focused and processes
requests to change focus. Focusable elements are assigned a FocusId
and
can manually request focus or receive focus due to some other action (e.g.,
a tab press in a sibling element, a click event).
Focusable elements will usually be created via tile
, but can also be
constructed via makeFocus
in HasFocus
. The latter option allows for
more find-grained control of focus behavior.
Storing focus state
Identifies an element that is focusable. Can be created using makeFocus
.
An ordered set of focus identifiers. The order here determines the order in which focus cycles between focusable elements.
Changing focus state
Operations that change the currently focused element.
Refocus_Shift Int | Shift the focus by a certain number of positions (see |
Refocus_Id FocusId | Focus a particular element |
Refocus_Clear | Remove focus from all elements |
shiftFS :: FocusSet -> Maybe FocusId -> Int -> Maybe FocusId Source #
Given a FocusSet
, a currently focused element, and a number of positions
to move by, determine the newly focused element.
The focus management monad
class (Monad m, Reflex t) => HasFocus t m | m -> t where Source #
A class for things that can produce focusable elements.
makeFocus :: m FocusId Source #
Create a focusable element.
requestFocus :: Event t Refocus -> m () Source #
Emit an Event
of requests to change the focus.
isFocused :: FocusId -> m (Dynamic t Bool) Source #
subFoci :: m a -> m (a, Dynamic t FocusSet) Source #
Run an action, additionally returning the focusable elements it produced.
focusedId :: m (Dynamic t (Maybe FocusId)) Source #
Get a Dynamic
of the currently focused element identifier.
A monad transformer that keeps track of the set of focusable elements and which, if any, are currently focused, and allows focus requests.
Focus | |
|
Instances
runFocus :: (MonadFix m, MonadHold t m, Reflex t) => Focus t m a -> m (a, Dynamic t FocusSet) Source #
Runs a Focus
action, maintaining the selection state internally.
anyChildFocused :: (HasFocus t m, MonadFix m) => (Dynamic t Bool -> m a) -> m a Source #
Runs an action in the focus monad, providing it with information about whether any of the foci created within it are focused.
Focus controls
Layout
The layout monad keeps track of a tree of elements, each having its own layout constraints and orientation. Given the available rendering space, it computes a layout solution and provides child elements with their particular layout solution (the width and height of their rendering space).
Complex layouts are built up though some combination of:
Layout restrictions
Constraints
data Constraint Source #
Datatype representing constraints on a widget's size along the main axis (see Orientation
)
Instances
Eq Constraint Source # | |
Defined in Reflex.Vty.Widget.Layout (==) :: Constraint -> Constraint -> Bool # (/=) :: Constraint -> Constraint -> Bool # | |
Ord Constraint Source # | |
Defined in Reflex.Vty.Widget.Layout compare :: Constraint -> Constraint -> Ordering # (<) :: Constraint -> Constraint -> Bool # (<=) :: Constraint -> Constraint -> Bool # (>) :: Constraint -> Constraint -> Bool # (>=) :: Constraint -> Constraint -> Bool # max :: Constraint -> Constraint -> Constraint # min :: Constraint -> Constraint -> Constraint # | |
Read Constraint Source # | |
Defined in Reflex.Vty.Widget.Layout readsPrec :: Int -> ReadS Constraint # readList :: ReadS [Constraint] # readPrec :: ReadPrec Constraint # readListPrec :: ReadPrec [Constraint] # | |
Show Constraint Source # | |
Defined in Reflex.Vty.Widget.Layout showsPrec :: Int -> Constraint -> ShowS # show :: Constraint -> String # showList :: [Constraint] -> ShowS # |
fixed :: Reflex t => Dynamic t Int -> Dynamic t Constraint Source #
Shorthand for constructing a fixed constraint
stretch :: Reflex t => Dynamic t Int -> Dynamic t Constraint Source #
Shorthand for constructing a minimum size constraint
flex :: Reflex t => Dynamic t Constraint Source #
Shorthand for constructing a constraint of no minimum size
Orientation
data Orientation Source #
The main-axis orientation of a Layout
widget
Instances
Eq Orientation Source # | |
Defined in Reflex.Vty.Widget.Layout (==) :: Orientation -> Orientation -> Bool # (/=) :: Orientation -> Orientation -> Bool # | |
Ord Orientation Source # | |
Defined in Reflex.Vty.Widget.Layout compare :: Orientation -> Orientation -> Ordering # (<) :: Orientation -> Orientation -> Bool # (<=) :: Orientation -> Orientation -> Bool # (>) :: Orientation -> Orientation -> Bool # (>=) :: Orientation -> Orientation -> Bool # max :: Orientation -> Orientation -> Orientation # min :: Orientation -> Orientation -> Orientation # | |
Read Orientation Source # | |
Defined in Reflex.Vty.Widget.Layout readsPrec :: Int -> ReadS Orientation # readList :: ReadS [Orientation] # readPrec :: ReadPrec Orientation # readListPrec :: ReadPrec [Orientation] # | |
Show Orientation Source # | |
Defined in Reflex.Vty.Widget.Layout showsPrec :: Int -> Orientation -> ShowS # show :: Orientation -> String # showList :: [Orientation] -> ShowS # |
Layout management data
data LayoutTree a Source #
A collection of information related to the layout of the screen. The root
node is a "parent" widget, and the contents of the LayoutForest
are its
children.
LayoutTree a (LayoutForest a) |
Instances
Show a => Show (LayoutTree a) Source # | |
Defined in Reflex.Vty.Widget.Layout showsPrec :: Int -> LayoutTree a -> ShowS # show :: LayoutTree a -> String # showList :: [LayoutTree a] -> ShowS # |
newtype LayoutForest a Source #
An ordered, indexed collection of LayoutTree
s representing information
about the children of some widget.
Instances
Show a => Show (LayoutForest a) Source # | |
Defined in Reflex.Vty.Widget.Layout showsPrec :: Int -> LayoutForest a -> ShowS # show :: LayoutForest a -> String # showList :: [LayoutForest a] -> ShowS # | |
Semigroup (LayoutForest a) Source # | |
Defined in Reflex.Vty.Widget.Layout (<>) :: LayoutForest a -> LayoutForest a -> LayoutForest a # sconcat :: NonEmpty (LayoutForest a) -> LayoutForest a # stimes :: Integral b => b -> LayoutForest a -> LayoutForest a # | |
Monoid (LayoutForest a) Source # | |
Defined in Reflex.Vty.Widget.Layout mempty :: LayoutForest a # mappend :: LayoutForest a -> LayoutForest a -> LayoutForest a # mconcat :: [LayoutForest a] -> LayoutForest a # |
lookupLF :: NodeId -> LayoutForest a -> Maybe (LayoutTree a) Source #
Perform a lookup by NodeId
in a LayoutForest
singletonLF :: NodeId -> LayoutTree a -> LayoutForest a Source #
Create a LayoutForest
with one element
fromListLF :: [(NodeId, LayoutTree a)] -> LayoutForest a Source #
Produce a LayoutForest
from a list. The order of the list is preserved.
rootLT :: LayoutTree a -> a Source #
Extract the information at the root of a LayoutTree
childrenLT :: LayoutTree a -> LayoutForest a Source #
Extract the child nodes of a LayoutTree
solve :: Orientation -> Region -> LayoutForest (Constraint, Orientation) -> LayoutTree (Region, Orientation) Source #
Produce a layout solution given a starting orientation, the overall screen size, and a set of constraints.
chunk :: Orientation -> Region -> (Int, Int) -> Region Source #
Produce a Region
given a starting orientation and region, and the offset
and main-axis size of the chunk.
The layout monad
class Monad m => HasLayout t m | m -> t where Source #
A class of operations for creating screen layouts.
axis :: Dynamic t Orientation -> Dynamic t Constraint -> m a -> m a Source #
Starts a parent element in the current layout with the given size constraint, which lays out its children according to the provided orientation.
region :: Dynamic t Constraint -> m (Dynamic t Region) Source #
Creates a child element in the current layout with the given size
constraint, returning the Region
that the child element is allocated.
askOrientation :: m (Dynamic t Orientation) Source #
Returns the orientation of the containing axis
.
Instances
(Monad m, MonadNodeId m, Reflex t, MonadFix m) => HasLayout (t :: Type) (Layout t m) Source # | |
Defined in Reflex.Vty.Widget.Layout axis :: Dynamic t Orientation -> Dynamic t Constraint -> Layout t m a -> Layout t m a Source # region :: Dynamic t Constraint -> Layout t m (Dynamic t Region) Source # askOrientation :: Layout t m (Dynamic t Orientation) Source # |
A monad transformer that collects layout constraints and provides a layout solution that satisfies those constraints.
Layout | |
|
Instances
hoistRunLayout :: (HasDisplayRegion t m, MonadFix m, Monad n) => (m a -> n b) -> Layout t m a -> Layout t n b Source #
Apply a transformation to the context of a child Layout
action and run
that action
runLayout :: (MonadFix m, Reflex t) => Dynamic t Orientation -> Dynamic t Region -> Layout t m a -> m a Source #
Runs a Layout
action, using the given orientation and region to
calculate layout solutions.
initLayout :: (HasDisplayRegion t m, MonadFix m) => Layout t m a -> m a Source #
Initialize and run the layout monad, using all of the available screen space.
The tile "window manager"
Generally HasLayout and HasFocus are used together to build a user interface. These functions check the available screen size and initialize the layout monad with that information, and also initialize the focus monad.
initManager :: (HasDisplayRegion t m, Reflex t, MonadHold t m, MonadFix m) => Layout t (Focus t m) a -> m (a, Dynamic t FocusSet) Source #
initManager_ :: (HasDisplayRegion t m, Reflex t, MonadHold t m, MonadFix m) => Layout t (Focus t m) a -> m a Source #
Layout tiles
Focusable
tile' :: (MonadFix m, Reflex t, HasInput t m, HasFocus t m, HasLayout t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m (FocusId, a) Source #
A widget that is focusable and occupies a layout region based on the
provided constraint. Returns the FocusId
allowing for manual focus
management.
tile :: (MonadFix m, Reflex t, HasInput t m, HasFocus t m, HasLayout t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m a Source #
A widget that is focusable and occupies a layout region based on the provided constraint.
Unfocusable
grout :: (Reflex t, HasLayout t m, HasInput t m, HasImageWriter t m, HasDisplayRegion t m, HasFocusReader t m) => Dynamic t Constraint -> m a -> m a Source #
A widget that is not focusable and occupies a layout region based on the provided constraint.