monomer-1.5.0.0: A GUI library for writing native Haskell applications.
Copyright(c) 2018 Francisco Vallarino
LicenseBSD-3-Clause (see the LICENSE file)
Maintainerfjvallarino@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Monomer.Core.WidgetTypes

Description

Basic types and definitions for Widgets.

Synopsis

Documentation

newtype Millisecond Source #

Time expressed in milliseconds. Useful for representing the time of events, length of intervals, start time of the application and ellapsed time since its start.

It can be converted from/to other numeric types using the standard functions.

Constructors

Millisecond 

Instances

Instances details
Bounded Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Enum Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Generic Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep Millisecond :: Type -> Type #

Num Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Read Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Integral Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Real Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Show Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Default Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

def :: Millisecond #

Eq Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Ord Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

TextShow Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasTs WidgetId Millisecond Source # 
Instance details

Defined in Monomer.Core.Lens

HasMs RenderSchedule Millisecond Source # 
Instance details

Defined in Monomer.Main.Lens

HasStart RenderSchedule Millisecond Source # 
Instance details

Defined in Monomer.Main.Lens

CmbDuration (FadeCfg e) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Animation.Fade

CmbDuration (SlideCfg e) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Animation.Slide

CmbCaretMs (TextAreaCfg s e) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Singles.TextArea

CmbCaretMs (TextFieldCfg s e) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Singles.TextField

HasAppStartTs (WidgetEnv s e) Millisecond Source # 
Instance details

Defined in Monomer.Core.Lens

HasTimestamp (WidgetEnv s e) Millisecond Source # 
Instance details

Defined in Monomer.Core.Lens

CmbCaretMs (DateFieldCfg s e a) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Singles.DateField

CmbCaretMs (NumericFieldCfg s e a) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Singles.NumericField

CmbCaretMs (TimeFieldCfg s e a) Millisecond Source # 
Instance details

Defined in Monomer.Widgets.Singles.TimeField

type Rep Millisecond Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

type Rep Millisecond = D1 ('MetaData "Millisecond" "Monomer.Core.WidgetTypes" "monomer-1.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'True) (C1 ('MetaCons "Millisecond" 'PrefixI 'True) (S1 ('MetaSel ('Just "unMilliseconds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

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.

Constructors

FocusFwd

Focus moving forward (usually left to right, top to bottom).

FocusBwd

Focus moving backward (usually right to left, top to bottom).

data WindowRequest Source #

WidgetRequest specific for window related operations.

Constructors

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

Instances details
Show WindowRequest Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Eq WindowRequest Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

newtype WidgetType Source #

Type of a widget. Used during the merge process.

Constructors

WidgetType Text 

Instances

Instances details
IsString WidgetType Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Generic WidgetType Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep WidgetType :: Type -> Type #

Show WidgetType Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Eq WidgetType Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasWidgetType WidgetNodeInfo WidgetType Source # 
Instance details

Defined in Monomer.Core.Lens

type Rep WidgetType Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

type Rep WidgetType = D1 ('MetaData "WidgetType" "Monomer.Core.WidgetTypes" "monomer-1.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'True) (C1 ('MetaCons "WidgetType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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).

Constructors

WidgetValue a

A direct value.

WidgetLens (ALens' s a)

A lens into the parent model.

data WidgetId Source #

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).

Constructors

WidgetId 

Fields

Instances

Instances details
Generic WidgetId Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep WidgetId :: Type -> Type #

Methods

from :: WidgetId -> Rep WidgetId x #

to :: Rep WidgetId x -> WidgetId #

Show WidgetId Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Default WidgetId Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

def :: WidgetId #

Eq WidgetId Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Ord WidgetId Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasPath WidgetId Path Source # 
Instance details

Defined in Monomer.Core.Lens

HasTs WidgetId Millisecond Source # 
Instance details

Defined in Monomer.Core.Lens

HasWidgetId WidgetNodeInfo WidgetId Source # 
Instance details

Defined in Monomer.Core.Lens

HasWidgetId DragAction WidgetId Source # 
Instance details

Defined in Monomer.Main.Lens

HasWidgetId RenderSchedule WidgetId Source # 
Instance details

Defined in Monomer.Main.Lens

HasFocusedWidgetId (MonomerCtx s e) WidgetId Source # 
Instance details

Defined in Monomer.Main.Lens

HasCursorStack (MonomerCtx s e) [(WidgetId, CursorIcon)] Source # 
Instance details

Defined in Monomer.Main.Lens

HasHoveredWidgetId (MonomerCtx s e) (Maybe WidgetId) Source # 
Instance details

Defined in Monomer.Main.Lens

HasOverlayWidgetId (MonomerCtx s e) (Maybe WidgetId) Source # 
Instance details

Defined in Monomer.Main.Lens

HasResizeRequests (MonomerCtx s e) (Seq WidgetId) Source # 
Instance details

Defined in Monomer.Main.Lens

HasRenderSchedule (MonomerCtx s e) (Map WidgetId RenderSchedule) Source # 
Instance details

Defined in Monomer.Main.Lens

HasWidgetPaths (MonomerCtx s e) (Map WidgetId Path) Source # 
Instance details

Defined in Monomer.Main.Lens

type Rep WidgetId Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

type Rep WidgetId = D1 ('MetaData "WidgetId" "Monomer.Core.WidgetTypes" "monomer-1.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'False) (C1 ('MetaCons "WidgetId" 'PrefixI 'True) (S1 ('MetaSel ('Just "_widTs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Millisecond) :*: S1 ('MetaSel ('Just "_widPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Path)))

newtype WidgetKey Source #

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.

Constructors

WidgetKey Text 

Instances

Instances details
IsString WidgetKey Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Generic WidgetKey Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep WidgetKey :: Type -> Type #

Show WidgetKey Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Eq WidgetKey Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Ord WidgetKey Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasKey WidgetNodeInfo (Maybe WidgetKey) Source # 
Instance details

Defined in Monomer.Core.Lens

HasWidgetKeyMap (WidgetEnv s e) (WidgetKeyMap s e) Source # 
Instance details

Defined in Monomer.Core.Lens

type Rep WidgetKey Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

type Rep WidgetKey = D1 ('MetaData "WidgetKey" "Monomer.Core.WidgetTypes" "monomer-1.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'True) (C1 ('MetaCons "WidgetKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

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.

Constructors

forall i.WidgetModel i => WidgetState i 

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.

Constructors

forall i.Typeable i => WidgetShared i 

Instances

Instances details
Show WidgetShared Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasWidgetShared (WidgetEnv s e) (MVar (Map Text WidgetShared)) Source # 
Instance details

Defined in Monomer.Core.Lens

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.

Constructors

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 RunTask or RunProducer does not.

RenderEvery WidgetId Millisecond (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.

forall i.Typeable i => RunInRenderThread WidgetId Path (IO i)

Runs an asynchronous tasks in the render thread. It is mandatory to return a message that will be sent to the task owner (this is the only way to feed data back). This should only be used when implementing low level rendering widgets that need to create API specific resources.

Instances

Instances details
Show (WidgetRequest s e) Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Eq e => Eq (WidgetRequest s e) Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

(==) :: WidgetRequest s e -> WidgetRequest s e -> Bool #

(/=) :: WidgetRequest s e -> WidgetRequest s e -> Bool #

HasRequests (WidgetResult s e) (Seq (WidgetRequest s e)) Source # 
Instance details

Defined in Monomer.Core.Lens

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 requests or new versions of themselves.

Constructors

WidgetResult 

Fields

Instances

Instances details
Semigroup (WidgetResult s e) Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

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

Show (WidgetResult s e) Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasRequests (WidgetResult s e) (Seq (WidgetRequest s e)) Source # 
Instance details

Defined in Monomer.Core.Lens

HasNode (WidgetResult s e) (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

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

Instances details
Generic LayoutDirection Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep LayoutDirection :: Type -> Type #

Show LayoutDirection Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Eq LayoutDirection Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasLayoutDirection (WidgetEnv s e) LayoutDirection Source # 
Instance details

Defined in Monomer.Core.Lens

type Rep LayoutDirection Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

type Rep LayoutDirection = D1 ('MetaData "LayoutDirection" "Monomer.Core.WidgetTypes" "monomer-1.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'False) (C1 ('MetaCons "LayoutNone" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "LayoutHorizontal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LayoutVertical" 'PrefixI 'False) (U1 :: Type -> Type)))

data WidgetEnv s e Source #

The widget environment. This includes system information, active viewport, and input status among other things.

Constructors

WidgetEnv 

Fields

Instances

Instances details
Show (WidgetEnv s e) Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

showsPrec :: Int -> WidgetEnv s e -> ShowS #

show :: WidgetEnv s e -> String #

showList :: [WidgetEnv s e] -> ShowS #

HasAppStartTs (WidgetEnv s e) Millisecond Source # 
Instance details

Defined in Monomer.Core.Lens

HasContextButton (WidgetEnv s e) Button Source # 
Instance details

Defined in Monomer.Core.Lens

HasDpr (WidgetEnv s e) Double Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

dpr :: Lens' (WidgetEnv s e) Double Source #

HasFocusedPath (WidgetEnv s e) Path Source # 
Instance details

Defined in Monomer.Core.Lens

HasFontManager (WidgetEnv s e) FontManager Source # 
Instance details

Defined in Monomer.Core.Lens

HasInputStatus (WidgetEnv s e) InputStatus Source # 
Instance details

Defined in Monomer.Core.Lens

HasLayoutDirection (WidgetEnv s e) LayoutDirection Source # 
Instance details

Defined in Monomer.Core.Lens

HasMainButton (WidgetEnv s e) Button Source # 
Instance details

Defined in Monomer.Core.Lens

HasModel (WidgetEnv s e) s Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

model :: Lens' (WidgetEnv s e) s Source #

HasOffset (WidgetEnv s e) Point Source # 
Instance details

Defined in Monomer.Core.Lens

HasOs (WidgetEnv s e) Text Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

os :: Lens' (WidgetEnv s e) Text Source #

HasTheme (WidgetEnv s e) Theme Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

theme :: Lens' (WidgetEnv s e) Theme Source #

HasThemeChanged (WidgetEnv s e) Bool Source # 
Instance details

Defined in Monomer.Core.Lens

HasTimestamp (WidgetEnv s e) Millisecond Source # 
Instance details

Defined in Monomer.Core.Lens

HasViewport (WidgetEnv s e) Rect Source # 
Instance details

Defined in Monomer.Core.Lens

HasWindowSize (WidgetEnv s e) Size Source # 
Instance details

Defined in Monomer.Core.Lens

HasCursor (WidgetEnv s e) (Maybe (Path, CursorIcon)) Source # 
Instance details

Defined in Monomer.Core.Lens

HasDragStatus (WidgetEnv s e) (Maybe (Path, WidgetDragMsg)) Source # 
Instance details

Defined in Monomer.Core.Lens

HasHoveredPath (WidgetEnv s e) (Maybe Path) Source # 
Instance details

Defined in Monomer.Core.Lens

HasMainBtnPress (WidgetEnv s e) (Maybe (Path, Point)) Source # 
Instance details

Defined in Monomer.Core.Lens

HasOverlayPath (WidgetEnv s e) (Maybe Path) Source # 
Instance details

Defined in Monomer.Core.Lens

HasWidgetShared (WidgetEnv s e) (MVar (Map Text WidgetShared)) Source # 
Instance details

Defined in Monomer.Core.Lens

HasFindBranchByPath (WidgetEnv s e) (Path -> Seq WidgetNodeInfo) Source # 
Instance details

Defined in Monomer.Core.Lens

HasInTopLayer (WidgetEnv s e) (Point -> Bool) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

inTopLayer :: Lens' (WidgetEnv s e) (Point -> Bool) Source #

HasWidgetKeyMap (WidgetEnv s e) (WidgetKeyMap s e) Source # 
Instance details

Defined in Monomer.Core.Lens

HasIsActive (CurrentStyleCfg s e) (IsActive s e) Source # 
Instance details

Defined in Monomer.Widgets.Util.Lens

HasIsFocused (CurrentStyleCfg s e) (IsFocused s e) Source # 
Instance details

Defined in Monomer.Widgets.Util.Lens

HasIsHovered (CurrentStyleCfg s e) (IsHovered s e) Source # 
Instance details

Defined in Monomer.Widgets.Util.Lens

CmbMergeRequired (BoxCfg s e) (WidgetEnv s e) s Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

mergeRequired :: (WidgetEnv s e -> s -> s -> Bool) -> BoxCfg s e Source #

CmbMergeRequired (DropdownCfg s e a) (WidgetEnv s e) (Seq a) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

mergeRequired :: (WidgetEnv s e -> Seq a -> Seq a -> Bool) -> DropdownCfg s e a Source #

CmbMergeRequired (SelectListCfg s e a) (WidgetEnv s e) (Seq a) Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

mergeRequired :: (WidgetEnv s e -> Seq a -> Seq a -> Bool) -> SelectListCfg s e a Source #

CmbMergeRequired (CompositeCfg s e sp ep) (WidgetEnv s e) s Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

mergeRequired :: (WidgetEnv s e -> s -> s -> Bool) -> CompositeCfg s e sp ep Source #

data WidgetNodeInfo Source #

Complementary information to a Widget, forming a node in the widget tree.

Constructors

WidgetNodeInfo 

Fields

Instances

Instances details
Generic WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep WidgetNodeInfo :: Type -> Type #

Show WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Default WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

def :: WidgetNodeInfo #

Eq WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasEnabled WidgetNodeInfo Bool Source # 
Instance details

Defined in Monomer.Core.Lens

HasFocusable WidgetNodeInfo Bool Source # 
Instance details

Defined in Monomer.Core.Lens

HasInfo WidgetInstanceNode WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.Lens

HasPath WidgetNodeInfo Path Source # 
Instance details

Defined in Monomer.Core.Lens

HasSizeReqH WidgetNodeInfo SizeReq Source # 
Instance details

Defined in Monomer.Core.Lens

HasSizeReqW WidgetNodeInfo SizeReq Source # 
Instance details

Defined in Monomer.Core.Lens

HasStyle WidgetNodeInfo Style Source # 
Instance details

Defined in Monomer.Core.Lens

HasViewport WidgetNodeInfo Rect Source # 
Instance details

Defined in Monomer.Core.Lens

HasVisible WidgetNodeInfo Bool Source # 
Instance details

Defined in Monomer.Core.Lens

HasWidgetId WidgetNodeInfo WidgetId Source # 
Instance details

Defined in Monomer.Core.Lens

HasWidgetType WidgetNodeInfo WidgetType Source # 
Instance details

Defined in Monomer.Core.Lens

HasKey WidgetNodeInfo (Maybe WidgetKey) Source # 
Instance details

Defined in Monomer.Core.Lens

HasInfo (WidgetNode s e) WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.Lens

HasFindBranchByPath (WidgetEnv s e) (Path -> Seq WidgetNodeInfo) Source # 
Instance details

Defined in Monomer.Core.Lens

type Rep WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

data WidgetNode s e Source #

An instance of the widget in the widget tree.

Constructors

WidgetNode 

Fields

Instances

Instances details
Show (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Methods

showsPrec :: Int -> WidgetNode s e -> ShowS #

show :: WidgetNode s e -> String #

showList :: [WidgetNode s e] -> ShowS #

CmbStyleActive (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleBasic (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleDisabled (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleFocus (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleFocusHover (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleHover (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

HasInfo (WidgetNode s e) WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.Lens

HasChildren (WidgetNode s e) (Seq (WidgetNode s e)) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

children :: Lens' (WidgetNode s e) (Seq (WidgetNode s e)) Source #

HasNode (WidgetResult s e) (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

node :: Lens' (WidgetResult s e) (WidgetNode s e) Source #

HasWidget (WidgetNode s e) (Widget s e) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

widget :: Lens' (WidgetNode s e) (Widget s e) Source #

HasWidgetKeyMap (WidgetEnv s e) (WidgetKeyMap s e) Source # 
Instance details

Defined in Monomer.Core.Lens

HasIsActive (CurrentStyleCfg s e) (IsActive s e) Source # 
Instance details

Defined in Monomer.Widgets.Util.Lens

HasIsFocused (CurrentStyleCfg s e) (IsFocused s e) Source # 
Instance details

Defined in Monomer.Widgets.Util.Lens

HasIsHovered (CurrentStyleCfg s e) (IsHovered s e) Source # 
Instance details

Defined in Monomer.Widgets.Util.Lens

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).

Constructors

WidgetInstanceNode 

Fields

Instances

Instances details
Generic WidgetInstanceNode Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

Associated Types

type Rep WidgetInstanceNode :: Type -> Type #

Show WidgetInstanceNode Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

HasInfo WidgetInstanceNode WidgetNodeInfo Source # 
Instance details

Defined in Monomer.Core.Lens

HasChildren WidgetInstanceNode (Seq WidgetInstanceNode) Source # 
Instance details

Defined in Monomer.Core.Lens

HasState WidgetInstanceNode (Maybe WidgetState) Source # 
Instance details

Defined in Monomer.Core.Lens

type Rep WidgetInstanceNode Source # 
Instance details

Defined in Monomer.Core.WidgetTypes

type Rep WidgetInstanceNode = D1 ('MetaData "WidgetInstanceNode" "Monomer.Core.WidgetTypes" "monomer-1.5.0.0-Qyhewrg5o52dfUHeNdP9B" 'False) (C1 ('MetaCons "WidgetInstanceNode" 'PrefixI 'True) (S1 ('MetaSel ('Just "_winInfo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 WidgetNodeInfo) :*: (S1 ('MetaSel ('Just "_winState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe WidgetState)) :*: S1 ('MetaSel ('Just "_winChildren") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Seq WidgetInstanceNode)))))

data Widget s e Source #

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.

Constructors

Widget 

Fields

  • widgetInit :: WidgetEnv s e -> WidgetNode s e -> WidgetResult s e

    Initializes the given node. This could include rebuilding the widget in case internal state needs to use model/environment information, generate user events or make requests to the runtime.

    Arguments:

    • The widget environment.
    • The widget node.

    Returns:

    • The result of the init operation.
  • widgetMerge :: WidgetEnv s e -> WidgetNode s e -> WidgetNode s e -> WidgetResult s e

    Merges the current node with the node it matched with during the merge process. Receives the newly created node (whose *init* function is not called), the previous node and the state extracted from that node. This process is widget dependent, and may use or ignore the previous state depending on newly available information.

    In general, you want to at least keep the previous state unless the widget is stateless or only consumes model/environment information.

    Arguments:

    • The widget environment.
    • The widget node.
    • The previous widget node.

    Returns:

    • The result of the merge operation.
  • widgetDispose :: WidgetEnv s e -> WidgetNode s e -> WidgetResult s e

    Disposes the current node. Only used by widgets which allocate resources during init or merge, and will usually involve requests to the runtime.

    Arguments:

    • The widget environment.
    • The widget node.

    Returns:

    • The result of the dispose operation.
  • widgetGetState :: WidgetEnv s e -> WidgetNode s e -> Maybe WidgetState

    Returns the current internal state, which can later be used when during the merge process.

    Arguments:

    • The widget environment.
    • The widget node.

    Returns:

    • The internal state, if any.
  • widgetGetInstanceTree :: WidgetEnv s e -> WidgetNode s e -> WidgetInstanceNode

    Returns information about the instance and its children.

    Arguments:

    • The widget environment.
    • The widget node.

    Returns:

    • The untyped node information.
  • widgetFindNextFocus :: WidgetEnv s e -> WidgetNode s e -> FocusDirection -> Path -> Maybe WidgetNodeInfo

    Returns the next focusable node. What next/previous is, depends on how the widget works. Moving left to right, top to bottom is usually considered forward.

    Arguments:

    • The widget environment.
    • The widget node.
    • The direction in which focus is moving.
    • The path to start the search from.

    Returns:

    • The next focusable node info.
  • widgetFindByPoint :: WidgetEnv s e -> WidgetNode s e -> Path -> Point -> Maybe WidgetNodeInfo

    Returns the currently hovered widget, if any.

    Arguments:

    • The widget environment.
    • The widget node.
    • The path to start the search from.
    • The point to test for.

    Returns:

    • The hovered child index, if any.
  • widgetFindBranchByPath :: WidgetEnv s e -> WidgetNode s e -> Path -> Seq WidgetNodeInfo

    Returns the widget matching the given path, plus all its parents.

    Arguments:

    • The widget environment.
    • The widget node.
    • The path to search for.

    Returns:

    • The sequence of widgets up to path, ordered from root to target.
  • widgetHandleEvent :: WidgetEnv s e -> WidgetNode s e -> Path -> SystemEvent -> Maybe (WidgetResult s e)

    Receives a System event and, optionally, returns a result. This can include an updated version of the widget (in case it has internal state), user events or requests to the runtime.

    Arguments:

    • The widget environment.
    • The widget node.
    • The target path of the event.
    • The SystemEvent to handle.

    Returns:

    • The result of handling the event, if any.
  • widgetHandleMessage :: forall i. Typeable i => WidgetEnv s e -> WidgetNode s e -> Path -> i -> Maybe (WidgetResult s e)

    Receives a message and, optionally, returns a result. This can include an updated version of the widget (in case it has internal state), user events or requests to the runtime. There is no validation regarding the message type, and the widget should take care of casting to the correct type using cast.

    Arguments:

    • The widget environment.
    • The widget node.
    • The target path of the message.
    • The message to handle.

    Returns:

    • The result of handling the message, if any.
  • widgetGetSizeReq :: WidgetEnv s e -> WidgetNode s e -> (SizeReq, SizeReq)

    Returns the preferred size for the widget.

    Arguments:

    • The widget environment.
    • The widget node.

    Returns:

    • The horizontal and vertical requirements.
  • widgetResize :: WidgetEnv s e -> WidgetNode s e -> Rect -> (Path -> Bool) -> WidgetResult s e

    Resizes the widget to the provided size.

    Arguments:

    • The widget environment.
    • The widget node.
    • The new viewport.
    • Helper to checks if a given path, or its children, requested resize.

    Returns:

    • The result of resizing the widget.
  • widgetRender :: WidgetEnv s e -> WidgetNode s e -> Renderer -> IO ()

    Renders the widget's content using the given Renderer.

    Arguments:

    • The widget environment.
    • The widget node.
    • The renderer, providing low level drawing functions.

    Returns:

    • The IO action with rendering instructions.

Instances

Instances details
HasWidget (WidgetNode s e) (Widget s e) Source # 
Instance details

Defined in Monomer.Core.Lens

Methods

widget :: Lens' (WidgetNode s e) (Widget s e) Source #