Copyright | (c) 2018 Francisco Vallarino |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | fjvallarino@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Basic types and definitions for Widgets.
Synopsis
- type Timestamp = Int
- type WidgetModel s = Typeable s
- type WidgetEvent e = Typeable e
- type WidgetKeyMap s e = Map WidgetKey (WidgetNode s e)
- data FocusDirection
- data WindowRequest
- newtype WidgetType = WidgetType Text
- data WidgetData s a
- = WidgetValue a
- | WidgetLens (ALens' s a)
- data WidgetId = WidgetId {}
- newtype WidgetKey = WidgetKey Text
- data WidgetState = forall i.WidgetModel i => WidgetState i
- data WidgetShared = forall i.Typeable i => WidgetShared i
- data WidgetRequest s e
- = IgnoreParentEvents
- | IgnoreChildrenEvents
- | ResizeWidgets WidgetId
- | ResizeWidgetsImmediate WidgetId
- | MoveFocus (Maybe WidgetId) FocusDirection
- | SetFocus WidgetId
- | GetClipboard WidgetId
- | SetClipboard ClipboardData
- | StartTextInput Rect
- | StopTextInput
- | SetOverlay WidgetId Path
- | ResetOverlay WidgetId
- | SetCursorIcon WidgetId CursorIcon
- | ResetCursorIcon WidgetId
- | StartDrag WidgetId Path WidgetDragMsg
- | StopDrag WidgetId
- | RenderOnce
- | RenderEvery WidgetId Int (Maybe Int)
- | RenderStop WidgetId
- | RemoveRendererImage Text
- | ExitApplication Bool
- | UpdateWindow WindowRequest
- | UpdateModel (s -> s)
- | SetWidgetPath WidgetId Path
- | ResetWidgetPath WidgetId
- | WidgetEvent e => RaiseEvent e
- | forall i.Typeable i => SendMessage WidgetId i
- | forall i.Typeable i => RunTask WidgetId Path (IO i)
- | forall i.Typeable i => RunProducer WidgetId Path ((i -> IO ()) -> IO ())
- data WidgetResult s e = WidgetResult {
- _wrNode :: WidgetNode s e
- _wrRequests :: Seq (WidgetRequest s e)
- data LayoutDirection
- data WidgetEnv s e = WidgetEnv {
- _weOs :: Text
- _weFontManager :: FontManager
- _weFindByPath :: Path -> Maybe WidgetNodeInfo
- _weMainButton :: Button
- _weContextButton :: Button
- _weTheme :: Theme
- _weWindowSize :: Size
- _weWidgetShared :: MVar (Map Text WidgetShared)
- _weWidgetKeyMap :: WidgetKeyMap s e
- _weHoveredPath :: Maybe Path
- _weFocusedPath :: Path
- _weOverlayPath :: Maybe Path
- _weDragStatus :: Maybe (Path, WidgetDragMsg)
- _weMainBtnPress :: Maybe (Path, Point)
- _weCursor :: Maybe (Path, CursorIcon)
- _weModel :: s
- _weInputStatus :: InputStatus
- _weTimestamp :: Timestamp
- _weThemeChanged :: Bool
- _weInTopLayer :: Point -> Bool
- _weLayoutDirection :: LayoutDirection
- _weViewport :: Rect
- _weOffset :: Point
- data WidgetNodeInfo = WidgetNodeInfo {
- _wniWidgetType :: !WidgetType
- _wniWidgetId :: !WidgetId
- _wniKey :: Maybe WidgetKey
- _wniPath :: !Path
- _wniSizeReqW :: !SizeReq
- _wniSizeReqH :: !SizeReq
- _wniEnabled :: !Bool
- _wniVisible :: !Bool
- _wniFocusable :: !Bool
- _wniViewport :: !Rect
- _wniStyle :: Style
- data WidgetNode s e = WidgetNode {
- _wnWidget :: Widget s e
- _wnInfo :: WidgetNodeInfo
- _wnChildren :: Seq (WidgetNode s e)
- data WidgetInstanceNode = WidgetInstanceNode {}
- data Widget s e = Widget {
- widgetInit :: WidgetEnv s e -> WidgetNode s e -> WidgetResult s e
- widgetMerge :: WidgetEnv s e -> WidgetNode s e -> WidgetNode s e -> WidgetResult s e
- widgetDispose :: WidgetEnv s e -> WidgetNode s e -> WidgetResult s e
- widgetGetState :: WidgetEnv s e -> WidgetNode s e -> Maybe WidgetState
- widgetGetInstanceTree :: WidgetEnv s e -> WidgetNode s e -> WidgetInstanceNode
- widgetFindNextFocus :: WidgetEnv s e -> WidgetNode s e -> FocusDirection -> Path -> Maybe WidgetNodeInfo
- widgetFindByPoint :: WidgetEnv s e -> WidgetNode s e -> Path -> Point -> Maybe WidgetNodeInfo
- widgetFindBranchByPath :: WidgetEnv s e -> WidgetNode s e -> Path -> Seq WidgetNodeInfo
- widgetHandleEvent :: WidgetEnv s e -> WidgetNode s e -> Path -> SystemEvent -> Maybe (WidgetResult s e)
- widgetHandleMessage :: forall i. Typeable i => WidgetEnv s e -> WidgetNode s e -> Path -> i -> Maybe (WidgetResult s e)
- widgetGetSizeReq :: WidgetEnv s e -> WidgetNode s e -> (SizeReq, SizeReq)
- widgetResize :: WidgetEnv s e -> WidgetNode s e -> Rect -> (Path -> Bool) -> WidgetResult s e
- widgetRender :: WidgetEnv s e -> WidgetNode s e -> Renderer -> IO ()
Documentation
type WidgetModel s = Typeable s Source #
Type constraints for a valid model
type WidgetEvent e = Typeable e Source #
Type constraints for a valid event
type WidgetKeyMap s e = Map WidgetKey (WidgetNode s e) Source #
Map of WidgetKeys to WidgetNodes. This association is valid only in the context of a Composite, with visibility of keys restricted to its scope. WidgetKeys inside nested Composites are not visible.
data FocusDirection Source #
Direction of focus movement.
FocusFwd | Focus moving forward (usually left to right, top to bottom). |
FocusBwd | Focus moving backward (usually right to left, top to bottom). |
Instances
Eq FocusDirection Source # | |
Defined in Monomer.Core.WidgetTypes (==) :: FocusDirection -> FocusDirection -> Bool # (/=) :: FocusDirection -> FocusDirection -> Bool # | |
Show FocusDirection Source # | |
Defined in Monomer.Core.WidgetTypes showsPrec :: Int -> FocusDirection -> ShowS # show :: FocusDirection -> String # showList :: [FocusDirection] -> ShowS # |
data WindowRequest Source #
WidgetRequest specific for window related operations.
WindowSetTitle Text | Sets the title of the window to the given text. |
WindowSetFullScreen | Switches to fullscreen mode. |
WindowMaximize | Maximizes the window. |
WindowMinimize | Minimizes the window. |
WindowRestore | Restores the window to its previous normal size. |
WindowBringToFront | Brings the window to the foreground. |
Instances
Eq WindowRequest Source # | |
Defined in Monomer.Core.WidgetTypes (==) :: WindowRequest -> WindowRequest -> Bool # (/=) :: WindowRequest -> WindowRequest -> Bool # | |
Show WindowRequest Source # | |
Defined in Monomer.Core.WidgetTypes showsPrec :: Int -> WindowRequest -> ShowS # show :: WindowRequest -> String # showList :: [WindowRequest] -> ShowS # |
newtype WidgetType Source #
Type of a widget. Used during the merge process.
Instances
data WidgetData s a Source #
Widgets can receive/report data using lenses or direct values. Reporting WidgetValue requires user events (in general, an onChange event).
WidgetValue a | A direct value. |
WidgetLens (ALens' s a) | A lens into the parent model. |
Widgets instances have an associated path from the root, which is unique at a specific point in time. This path may change, since widgets could be added before or after it (for example, a widget is added to the beginning of a list). WidgetIds are used by the runtime to create an association from a unique identifier to the current valid path of an instance; this unique identifier, the WidgetId, is the result of combining the timestamp when the instance was created and its path at that time.
Several WidgetRequests rely on this to find the destination of asynchronous requests (tasks, clipboard, etc).
Instances
During the merge process, widgets are matched based on WidgetType and WidgetKey. By default an instance's key is null, which means any matching type will be valid for merging. If you have items that can be reordered, using a key makes sure merge picks the correct instance for merging. Keys should be unique within the context of a Composite. Duplicate key behavior is undefined.
Instances
Eq WidgetKey Source # | |
Ord WidgetKey Source # | |
Defined in Monomer.Core.WidgetTypes | |
Show WidgetKey Source # | |
IsString WidgetKey Source # | |
Defined in Monomer.Core.WidgetTypes fromString :: String -> WidgetKey # | |
Generic WidgetKey Source # | |
HasKey WidgetNodeInfo (Maybe WidgetKey) Source # | |
Defined in Monomer.Core.Lens | |
HasWidgetKeyMap (WidgetEnv s e) (WidgetKeyMap s e) Source # | |
Defined in Monomer.Core.Lens widgetKeyMap :: Lens' (WidgetEnv s e) (WidgetKeyMap s e) Source # | |
type Rep WidgetKey Source # | |
Defined in Monomer.Core.WidgetTypes |
data WidgetState Source #
Wrapper of a Typeable instance representing the state of a widget. The widget is in charge of casting to the correct type.
forall i.WidgetModel i => WidgetState i |
Instances
Show WidgetState Source # | |
Defined in Monomer.Core.WidgetTypes showsPrec :: Int -> WidgetState -> ShowS # show :: WidgetState -> String # showList :: [WidgetState] -> ShowS # | |
HasState WidgetInstanceNode (Maybe WidgetState) Source # | |
Defined in Monomer.Core.Lens |
data WidgetShared Source #
Wrapper of a Typeable instance representing shared data between widgets. Used, for example, by image widget to avoid loading the same image multiple times. The widget is in charge of casting to the correct type.
forall i.Typeable i => WidgetShared i |
Instances
data WidgetRequest s e Source #
WidgetRequests are the way a widget can perform side effects, such as changing cursor icons, get/set the clipboard and perform asynchronous tasks. These requests are included as part of a WidgetResult in different points in the lifecycle of a widget.
IgnoreParentEvents | Ignore events generated by the parent. Could be used to consume the tab key and avoid having the focus move to the next widget. |
IgnoreChildrenEvents | Ignore children events. Scroll relies on this to handle click/wheel. |
ResizeWidgets WidgetId | The widget content changed and requires a different size. Processed at the end of the cycle, since several widgets may request it. |
ResizeWidgetsImmediate WidgetId | The widget content changed and requires a different size. Processed immediately. Avoid if possible, since it can affect performance. |
MoveFocus (Maybe WidgetId) FocusDirection | Moves the focus, optionally indicating a starting widgetId. |
SetFocus WidgetId | Sets the focus to the given widgetId. |
GetClipboard WidgetId | Requests the clipboard contents. It will be received as a SystemEvent. |
SetClipboard ClipboardData | Sets the clipboard to the given ClipboardData. |
StartTextInput Rect | Sets the viewport that should be remain visible when an on-screen keyboard is displayed. Required for mobile. |
StopTextInput | Resets the keyboard viewport, |
SetOverlay WidgetId Path | Sets a widget as the base target of future events. This is used by the dropdown component to handle list events; this list, acting as an overlay, is displayed on top of all other widgets. Tooltip uses it too. every other widget). |
ResetOverlay WidgetId | Removes the existing overlay. |
SetCursorIcon WidgetId CursorIcon | Sets the current active cursor icon. This acts as a stack, and resetting a widgetId means going back to the cursor set immediately before. |
ResetCursorIcon WidgetId | Removes a cursor icon from the stack. Duplicate requests are ignored. |
StartDrag WidgetId Path WidgetDragMsg | Sets the current item being dragged and the message it carries. This message can be used by targets to check if they accept it or not. |
StopDrag WidgetId | Cancels the current dragging process. |
RenderOnce | Requests rendering a single frame. Rendering is not done at a fixed rate, in order to reduce CPU usage. Widgets are responsible for requesting rendering at points of interest. Mouse (except mouse move) and keyboard events automatically generate render requests, but the result of a WidgetTask or WidgetProducer does not. |
RenderEvery WidgetId Int (Maybe Int) | Useful if a widget requires periodic rendering. An optional maximum number of frames can be provided. |
RenderStop WidgetId | Stops a previous periodic rendering request. |
RemoveRendererImage Text | Requests an image to be removed from the Renderer. In general, used by the dispose function. |
ExitApplication Bool | Requests to exit the application. Can also be used to cancel a previous request (or a window close). |
UpdateWindow WindowRequest | Performs a WindowRequest. |
UpdateModel (s -> s) | Request a model update. This usually involves lenses and "widgetDataSet". |
SetWidgetPath WidgetId Path | Updates the path of a given widget. Both Monomer.Widgets.Single and Monomer.Widgets.Container handle this automatically. |
ResetWidgetPath WidgetId | Clears an association between widgetId and path. |
WidgetEvent e => RaiseEvent e | Raises a user event, which usually will be processed in handleEvent by a Monomer.Widgets.Composite instance. |
forall i.Typeable i => SendMessage WidgetId i | Sends a message to the given widgetId. If the target does not expect the message's type, it will be ignored. |
forall i.Typeable i => RunTask WidgetId Path (IO i) | Runs an asynchronous tasks. It is mandatory to return a message that will be sent to the task owner (this is the only way to feed data back). |
forall i.Typeable i => RunProducer WidgetId Path ((i -> IO ()) -> IO ()) | Similar to RunTask, but can generate unlimited messages. This is useful for WebSockets and similar data sources. It receives a function that can be used to send messages back to the producer owner. |
Instances
Eq e => Eq (WidgetRequest s e) Source # | |
Defined in Monomer.Core.WidgetTypes (==) :: WidgetRequest s e -> WidgetRequest s e -> Bool # (/=) :: WidgetRequest s e -> WidgetRequest s e -> Bool # | |
Show (WidgetRequest s e) Source # | |
Defined in Monomer.Core.WidgetTypes showsPrec :: Int -> WidgetRequest s e -> ShowS # show :: WidgetRequest s e -> String # showList :: [WidgetRequest s e] -> ShowS # | |
HasRequests (WidgetResult s e) (Seq (WidgetRequest s e)) Source # | |
Defined in Monomer.Core.Lens requests :: Lens' (WidgetResult s e) (Seq (WidgetRequest s e)) Source # |
data WidgetResult s e Source #
Result of widget operations (init, merge, handleEvent, etc). The node is mandatory. The "resultNode", "resultEvts", "resultReqs" and "resultReqsEvts" helper functions can also be used.
In general a result starts in a child widget, but parent widgets can append requets or new versions of themselves.
WidgetResult | |
|
Instances
Show (WidgetResult s e) Source # | |
Defined in Monomer.Core.WidgetTypes showsPrec :: Int -> WidgetResult s e -> ShowS # show :: WidgetResult s e -> String # showList :: [WidgetResult s e] -> ShowS # | |
Semigroup (WidgetResult s e) Source # | |
Defined in Monomer.Core.WidgetTypes (<>) :: WidgetResult s e -> WidgetResult s e -> WidgetResult s e # sconcat :: NonEmpty (WidgetResult s e) -> WidgetResult s e # stimes :: Integral b => b -> WidgetResult s e -> WidgetResult s e # | |
HasRequests (WidgetResult s e) (Seq (WidgetRequest s e)) Source # | |
Defined in Monomer.Core.Lens requests :: Lens' (WidgetResult s e) (Seq (WidgetRequest s e)) Source # | |
HasNode (WidgetResult s e) (WidgetNode s e) Source # | |
Defined in Monomer.Core.Lens node :: Lens' (WidgetResult s e) (WidgetNode s e) Source # |
data LayoutDirection Source #
Used to indicate active layout direction. Some widgets, such as spacer, can use it to adapt themselves.
Instances
The widget environment. This includes system information, active viewport, and input status among other things.
WidgetEnv | |
|
Instances
data WidgetNodeInfo Source #
Complementary information to a Widget, forming a node in the widget tree.
WidgetNodeInfo | |
|
Instances
data WidgetNode s e Source #
An instance of the widget in the widget tree.
WidgetNode | |
|
Instances
data WidgetInstanceNode Source #
An instance of the widget in the widget tree, without specific type information. This allows querying for widgets that may be nested in Composites, which are not visible as a regular WidgetNode because of possible type mismatches (see WidgetKeyMap).
WidgetInstanceNode | |
|
Instances
Main widget type. This is the type all widgets implement. In general it's not needed to implement this type directly, and it's easier to use Monomer.Widgets.Container for widgets with children elements and Monomer.Widgets.Single for widgets without children.
Widget | |
|
Instances
HasWidget (WidgetNode s e) (Widget s e) Source # | |
Defined in Monomer.Core.Lens |