monomer-1.0.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 HaskellNone
LanguageHaskell2010

Monomer.Core.Combinators

Description

Combinator typeclasses used for style and widget configutation. The reason for using typeclasses is for the ability to reuse names such as onClick.

Boolean combinators in general have two versions:

  • combinatorName: uses the default value, normally True, and is derived from the combinator with _ suffix.
  • combinatorName_: receives a boolean parameter. This is the function that needs to be overriden in widgets.
Synopsis

Documentation

class CmbMergeRequired t s | t -> s where Source #

Given two values, usually model, checks if merge is required for a given widget. The first parameter corresponds to the old value, and the second to the new.

Methods

mergeRequired :: (s -> s -> Bool) -> t Source #

Instances

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

Defined in Monomer.Widgets.Containers.Box

Methods

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

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

Defined in Monomer.Widgets.Containers.SelectList

Methods

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

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

Defined in Monomer.Widgets.Composite

Methods

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

class CmbValidInput t s | t -> s where Source #

Listener for the validation status of a field using a lens.

Methods

validInput :: ALens' s Bool -> t Source #

class CmbValidInputV t e | t -> e where Source #

Listener for the validation status of a field using an event handler.

Methods

validInputV :: (Bool -> e) -> t Source #

class CmbSelectOnFocus t where Source #

Defines whether a widget selects all its content when receiving focus.

Minimal complete definition

selectOnFocus_

class CmbResizeOnChange t where Source #

Defines whether a widget changes its size when the model changes.

Minimal complete definition

resizeOnChange_

class CmbAutoStart t where Source #

Defines whether animation should start automatically.

Minimal complete definition

autoStart_

Methods

autoStart :: t Source #

autoStart_ :: Bool -> t Source #

class CmbDuration t a | t -> a where Source #

Defines the animation length.

Methods

duration :: a -> t Source #

class CmbTitleCaption t where Source #

Title caption of a widget, usually a dialog.

Methods

titleCaption :: Text -> t Source #

class CmbAcceptCaption t where Source #

Accept caption of a widget, usually a button.

Methods

acceptCaption :: Text -> t Source #

class CmbCancelCaption t where Source #

Cancel caption of a widget, usually a button.

Methods

cancelCaption :: Text -> t Source #

class CmbCloseCaption t where Source #

Close caption of a widget, usually a button.

Methods

closeCaption :: Text -> t Source #

class CmbMinValue t a | t -> a where Source #

Minimum value of a widget, usually numeric.

Methods

minValue :: a -> t Source #

class CmbMaxValue t a | t -> a where Source #

Maximum value of a widget, usually numeric.

Methods

maxValue :: a -> t Source #

class CmbDragRate t a | t -> a where Source #

Drag rate of a widget, usually numeric.

Methods

dragRate :: a -> t Source #

class CmbWheelRate t a | t -> a where Source #

Wheel rate of a widget, usually numeric or scrollable.

Methods

wheelRate :: a -> t Source #

class CmbIgnoreEmptyArea t where Source #

Whether to ignore pointer events where no widget exists.

Minimal complete definition

ignoreEmptyArea_

Instances

Instances details
CmbIgnoreEmptyArea (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbDecimals t where Source #

How many decimals a numeric widget accepts.

Methods

decimals :: Int -> t Source #

class CmbMaxLength t where Source #

Max length a widget accepts.

Methods

maxLength :: Int -> t Source #

class CmbMaxLines t where Source #

Max lines a widget accepts.

Methods

maxLines :: Int -> t Source #

Instances

Instances details
CmbMaxLines (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

Methods

maxLines :: Int -> LabelCfg s e Source #

class CmbAcceptTab t where Source #

Whether a widget accepts tab key.

Minimal complete definition

acceptTab_

Methods

acceptTab :: t Source #

acceptTab_ :: Bool -> t Source #

class CmbMultiline t where Source #

Whether a text based widget is multiline.

Minimal complete definition

multiline_

Methods

multiline :: t Source #

multiline_ :: Bool -> t Source #

Instances

Instances details
CmbMultiline (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

class CmbEllipsis t where Source #

Whether to use ellipsis or not.

Minimal complete definition

ellipsis_

Methods

ellipsis :: t Source #

ellipsis_ :: Bool -> t Source #

Instances

Instances details
CmbEllipsis (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

class CmbTrimSpaces t where Source #

Whether to trim spaces or not.

Minimal complete definition

trimSpaces_

Instances

Instances details
CmbTrimSpaces (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

class CmbSelectOnBlur t where Source #

Whether to automatically select a value on blur (for example, dropdown).

Minimal complete definition

selectOnBlur_

Instances

Instances details
CmbSelectOnBlur (SelectListCfg s e a) Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

class CmbPlaceholder t a | t -> a where Source #

Placeholder to use when main value is empty.

Methods

placeholder :: a -> t Source #

class CmbCaretWidth t a | t -> a where Source #

Width of the caret in a text widget.

Methods

caretWidth :: a -> t Source #

class CmbCaretMs t a | t -> a where Source #

Blink period of the caret in a text widget.

Methods

caretMs :: a -> t Source #

class CmbTextFont t where Source #

Text font.

Methods

textFont :: Font -> t Source #

Instances

Instances details
CmbTextFont TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextFont StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextSize t where Source #

Text size.

Methods

textSize :: Double -> t Source #

Instances

Instances details
CmbTextSize TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextSize StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextSpaceH t where Source #

Horizontal text spacing.

Methods

textSpaceH :: Double -> t Source #

Instances

Instances details
CmbTextSpaceH TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextSpaceH StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextSpaceV t where Source #

Vertical text spacing.

Methods

textSpaceV :: Double -> t Source #

Instances

Instances details
CmbTextSpaceV TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextSpaceV StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextColor t where Source #

Text color.

Methods

textColor :: Color -> t Source #

Instances

Instances details
CmbTextColor TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextColor StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextLeft t where Source #

Align text to the left.

Minimal complete definition

textLeft_

Methods

textLeft :: t Source #

textLeft_ :: Bool -> t Source #

Instances

Instances details
CmbTextLeft TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextLeft StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextCenter t where Source #

Align text to the center.

Minimal complete definition

textCenter_

class CmbTextRight t where Source #

Align text to the right.

Minimal complete definition

textRight_

Methods

textRight :: t Source #

textRight_ :: Bool -> t Source #

Instances

Instances details
CmbTextRight TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextRight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextTop t where Source #

Align text to the top.

Minimal complete definition

textTop_

Methods

textTop :: t Source #

textTop_ :: Bool -> t Source #

Instances

Instances details
CmbTextTop TextStyle Source # 
Instance details

Defined in Monomer.Core.Style

CmbTextTop StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTextMiddle t where Source #

Align text to the vertical middle based on the line height.

Minimal complete definition

textMiddle_

class CmbTextAscender t where Source #

Align text to the vertical middle based on the ascender.

Minimal complete definition

textAscender_

class CmbTextLowerX t where Source #

Align text to the vertical middle based on the x height.

Minimal complete definition

textLowerX_

class CmbTextBottom t where Source #

Align text to the bottom.

Minimal complete definition

textBottom_

class CmbTextBaseline t where Source #

Align text to the baseline.

Minimal complete definition

textBaseline_

class CmbTextUnderline t where Source #

Display a line under the text.

Minimal complete definition

textUnderline_

class CmbTextOverline t where Source #

Display a line above the text.

Minimal complete definition

textOverline_

class CmbTextThroughline t where Source #

Display a line over the text.

Minimal complete definition

textThroughline_

class CmbFitNone t where Source #

Does not apply any kind of resizing to fit to container.

Methods

fitNone :: t Source #

class CmbFitFill t where Source #

Fits to use all the container's space.

Methods

fitFill :: t Source #

class CmbFitWidth t where Source #

Fits to use all the container's width.

Methods

fitWidth :: t Source #

class CmbFitHeight t where Source #

Fits to use all the container's height.

Methods

fitHeight :: t Source #

class CmbImageNearest t where Source #

Applies nearest filtering when stretching an image.

Methods

imageNearest :: t Source #

class CmbImageRepeatX t where Source #

Applies horizontal repetition when stretching an image.

Methods

imageRepeatX :: t Source #

class CmbImageRepeatY t where Source #

Applies vertical repetition when stretching an image.

Methods

imageRepeatY :: t Source #

class CmbBarColor t where Source #

The color of a bar, for example in a scroll.

Methods

barColor :: Color -> t Source #

class CmbBarHoverColor t where Source #

The hover color of a bar, for example in a scroll.

Methods

barHoverColor :: Color -> t Source #

class CmbBarWidth t where Source #

The width of a bar, for example in a scroll.

Methods

barWidth :: Double -> t Source #

class CmbThumbColor t where Source #

The color of a thumb, for example in a scroll.

Methods

thumbColor :: Color -> t Source #

class CmbThumbHoverColor t where Source #

The hover color of a thumb, for example in a scroll.

Methods

thumbHoverColor :: Color -> t Source #

class CmbThumbFactor t where Source #

The thumb factor. For example, in slider this makes the thumb proportional to the width of the slider.

Methods

thumbFactor :: Double -> t Source #

class CmbThumbRadius t where Source #

The radius of a thumb's rect, for example in a scroll.

Methods

thumbRadius :: Double -> t Source #

class CmbThumbVisible t where Source #

Whether the thumb is visible, for example in a scroll.

Minimal complete definition

thumbVisible_

class CmbThumbWidth t where Source #

The width color of a thumb, for example in a scroll.

Methods

thumbWidth :: Double -> t Source #

class CmbShowAlpha t where Source #

Whether to show an alpha channel, for instance in color selector.

Minimal complete definition

showAlpha_

Methods

showAlpha :: t Source #

showAlpha_ :: Bool -> t Source #

class CmbIgnoreChildrenEvts t where Source #

Whether to ignore children events.

Minimal complete definition

ignoreChildrenEvts_

class CmbOnInit t e | t -> e where Source #

On init event.

Methods

onInit :: e -> t Source #

Instances

Instances details
CmbOnInit (CompositeCfg s e sp ep) e Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onInit :: e -> CompositeCfg s e sp ep Source #

class CmbOnDispose t e | t -> e where Source #

On dispose event.

Methods

onDispose :: e -> t Source #

Instances

Instances details
CmbOnDispose (CompositeCfg s e sp ep) e Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onDispose :: e -> CompositeCfg s e sp ep Source #

class CmbOnResize t e a | t -> e a where Source #

On resize event.

Methods

onResize :: (a -> e) -> t Source #

Instances

Instances details
CmbOnResize (CompositeCfg s e sp ep) e Rect Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onResize :: (Rect -> e) -> CompositeCfg s e sp ep Source #

class CmbOnFocus t e a | t -> e a where Source #

On focus event.

Methods

onFocus :: (a -> e) -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnFocus (CheckboxCfg s e) e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

onFocus :: (Path -> e) -> CheckboxCfg s e Source #

WidgetEvent e => CmbOnFocus (BoxCfg s e) e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onFocus :: (Path -> e) -> BoxCfg s e Source #

WidgetEvent e => CmbOnFocus (RadioCfg s e a) e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

onFocus :: (Path -> e) -> RadioCfg s e a Source #

WidgetEvent e => CmbOnFocus (SelectListCfg s e a) e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onFocus :: (Path -> e) -> SelectListCfg s e a Source #

WidgetEvent e => CmbOnFocus (DropdownCfg s e a) e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onFocus :: (Path -> e) -> DropdownCfg s e a Source #

class CmbOnFocusReq t s e a | t -> s e a where Source #

On focus WidgetRequest.

Methods

onFocusReq :: (a -> WidgetRequest s e) -> t Source #

Instances

Instances details
CmbOnFocusReq (CheckboxCfg s e) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

onFocusReq :: (Path -> WidgetRequest s e) -> CheckboxCfg s e Source #

CmbOnFocusReq (BoxCfg s e) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onFocusReq :: (Path -> WidgetRequest s e) -> BoxCfg s e Source #

CmbOnFocusReq (RadioCfg s e a) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

onFocusReq :: (Path -> WidgetRequest s e) -> RadioCfg s e a Source #

CmbOnFocusReq (SelectListCfg s e a) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onFocusReq :: (Path -> WidgetRequest s e) -> SelectListCfg s e a Source #

CmbOnFocusReq (DropdownCfg s e a) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onFocusReq :: (Path -> WidgetRequest s e) -> DropdownCfg s e a Source #

class CmbOnBlur t e a | t -> e a where Source #

On blur event.

Methods

onBlur :: (a -> e) -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnBlur (CheckboxCfg s e) e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

onBlur :: (Path -> e) -> CheckboxCfg s e Source #

WidgetEvent e => CmbOnBlur (BoxCfg s e) e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onBlur :: (Path -> e) -> BoxCfg s e Source #

WidgetEvent e => CmbOnBlur (RadioCfg s e a) e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

onBlur :: (Path -> e) -> RadioCfg s e a Source #

WidgetEvent e => CmbOnBlur (SelectListCfg s e a) e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onBlur :: (Path -> e) -> SelectListCfg s e a Source #

WidgetEvent e => CmbOnBlur (DropdownCfg s e a) e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onBlur :: (Path -> e) -> DropdownCfg s e a Source #

class CmbOnBlurReq t s e a | t -> s e a where Source #

On blur WidgetRequest.

Methods

onBlurReq :: (a -> WidgetRequest s e) -> t Source #

Instances

Instances details
CmbOnBlurReq (CheckboxCfg s e) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

onBlurReq :: (Path -> WidgetRequest s e) -> CheckboxCfg s e Source #

CmbOnBlurReq (BoxCfg s e) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onBlurReq :: (Path -> WidgetRequest s e) -> BoxCfg s e Source #

CmbOnBlurReq (RadioCfg s e a) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

onBlurReq :: (Path -> WidgetRequest s e) -> RadioCfg s e a Source #

CmbOnBlurReq (SelectListCfg s e a) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onBlurReq :: (Path -> WidgetRequest s e) -> SelectListCfg s e a Source #

CmbOnBlurReq (DropdownCfg s e a) s e Path Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onBlurReq :: (Path -> WidgetRequest s e) -> DropdownCfg s e a Source #

class CmbOnEnter t e | t -> e where Source #

On enter event.

Methods

onEnter :: e -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnEnter (BoxCfg s e) e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onEnter :: e -> BoxCfg s e Source #

class CmbOnEnterReq t s e | t -> s e where Source #

On enter WidgetRequest.

Methods

onEnterReq :: WidgetRequest s e -> t Source #

Instances

Instances details
CmbOnEnterReq (BoxCfg s e) s e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onEnterReq :: WidgetRequest s e -> BoxCfg s e Source #

class CmbOnLeave t e | t -> e where Source #

On leave event.

Methods

onLeave :: e -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnLeave (BoxCfg s e) e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onLeave :: e -> BoxCfg s e Source #

class CmbOnLeaveReq t s e | t -> s e where Source #

On leave WidgetRequest.

Methods

onLeaveReq :: WidgetRequest s e -> t Source #

Instances

Instances details
CmbOnLeaveReq (BoxCfg s e) s e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onLeaveReq :: WidgetRequest s e -> BoxCfg s e Source #

class CmbOnClick t e | t -> e where Source #

On click event.

Methods

onClick :: e -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnClick (BoxCfg s e) e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onClick :: e -> BoxCfg s e Source #

class CmbOnClickReq t s e | t -> s e where Source #

On click WidgetRequest.

Methods

onClickReq :: WidgetRequest s e -> t Source #

Instances

Instances details
CmbOnClickReq (BoxCfg s e) s e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onClickReq :: WidgetRequest s e -> BoxCfg s e Source #

class CmbOnClickEmpty t e | t -> e where Source #

On click empty event, where supported (box, for example).

Methods

onClickEmpty :: e -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnClickEmpty (BoxCfg s e) e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onClickEmpty :: e -> BoxCfg s e Source #

class CmbOnClickEmptyReq t s e | t -> s e where Source #

On click empty WidgetRequest, where supported (box, for example).

Instances

Instances details
CmbOnClickEmptyReq (BoxCfg s e) s e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbOnBtnPressed t e | t -> e where Source #

On button pressed event.

Methods

onBtnPressed :: (Button -> Int -> e) -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnBtnPressed (BoxCfg s e) e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onBtnPressed :: (Button -> Int -> e) -> BoxCfg s e Source #

class CmbOnBtnPressedReq t s e | t -> s e where Source #

On button pressed WidgetRequest.

Methods

onBtnPressedReq :: (Button -> Int -> WidgetRequest s e) -> t Source #

Instances

Instances details
CmbOnBtnPressedReq (BoxCfg s e) s e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onBtnPressedReq :: (Button -> Int -> WidgetRequest s e) -> BoxCfg s e Source #

class CmbOnBtnReleased t e | t -> e where Source #

On button released event.

Methods

onBtnReleased :: (Button -> Int -> e) -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnBtnReleased (BoxCfg s e) e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onBtnReleased :: (Button -> Int -> e) -> BoxCfg s e Source #

class CmbOnBtnReleasedReq t s e | t -> s e where Source #

On button released WidgetRequest.

Methods

onBtnReleasedReq :: (Button -> Int -> WidgetRequest s e) -> t Source #

Instances

Instances details
CmbOnBtnReleasedReq (BoxCfg s e) s e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

Methods

onBtnReleasedReq :: (Button -> Int -> WidgetRequest s e) -> BoxCfg s e Source #

class CmbOnEnabledChange t e | t -> e where Source #

On enabled change event.

Methods

onEnabledChange :: e -> t Source #

Instances

Instances details
CmbOnEnabledChange (CompositeCfg s e sp ep) e Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onEnabledChange :: e -> CompositeCfg s e sp ep Source #

class CmbOnVisibleChange t e | t -> e where Source #

On visible change event.

Methods

onVisibleChange :: e -> t Source #

Instances

Instances details
CmbOnVisibleChange (CompositeCfg s e sp ep) e Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onVisibleChange :: e -> CompositeCfg s e sp ep Source #

class CmbOnChange t a e | t -> e where Source #

On change event.

Methods

onChange :: (a -> e) -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnChange (CheckboxCfg s e) Bool e Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

onChange :: (Bool -> e) -> CheckboxCfg s e Source #

WidgetEvent e => CmbOnChange (RadioCfg s e a) a e Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

onChange :: (a -> e) -> RadioCfg s e a Source #

WidgetEvent e => CmbOnChange (SelectListCfg s e a) a e Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onChange :: (a -> e) -> SelectListCfg s e a Source #

WidgetEvent e => CmbOnChange (DropdownCfg s e a) a e Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onChange :: (a -> e) -> DropdownCfg s e a Source #

WidgetEvent ep => CmbOnChange (CompositeCfg s e sp ep) s ep Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onChange :: (s -> ep) -> CompositeCfg s e sp ep Source #

class CmbOnChangeIdx t e a | t -> e a where Source #

On change event, including index.

Methods

onChangeIdx :: (Int -> a -> e) -> t Source #

Instances

Instances details
WidgetEvent e => CmbOnChangeIdx (SelectListCfg s e a) e a Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onChangeIdx :: (Int -> a -> e) -> SelectListCfg s e a Source #

WidgetEvent e => CmbOnChangeIdx (DropdownCfg s e a) e a Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onChangeIdx :: (Int -> a -> e) -> DropdownCfg s e a Source #

class CmbOnChangeReq t s e a | t -> s e a where Source #

On change WidgetRequest.

Methods

onChangeReq :: (a -> WidgetRequest s e) -> t Source #

Instances

Instances details
CmbOnChangeReq (CheckboxCfg s e) s e Bool Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

onChangeReq :: (Bool -> WidgetRequest s e) -> CheckboxCfg s e Source #

CmbOnChangeReq (RadioCfg s e a) s e a Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

onChangeReq :: (a -> WidgetRequest s e) -> RadioCfg s e a Source #

CmbOnChangeReq (SelectListCfg s e a) s e a Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onChangeReq :: (a -> WidgetRequest s e) -> SelectListCfg s e a Source #

CmbOnChangeReq (DropdownCfg s e a) s e a Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onChangeReq :: (a -> WidgetRequest s e) -> DropdownCfg s e a Source #

CmbOnChangeReq (CompositeCfg s e sp ep) sp ep s Source # 
Instance details

Defined in Monomer.Widgets.Composite

Methods

onChangeReq :: (s -> WidgetRequest sp ep) -> CompositeCfg s e sp ep Source #

class CmbOnChangeIdxReq t s e a | t -> s e a where Source #

On change WidgetRequest, including index.

Methods

onChangeIdxReq :: (Int -> a -> WidgetRequest s e) -> t Source #

Instances

Instances details
CmbOnChangeIdxReq (SelectListCfg s e a) s e a Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

Methods

onChangeIdxReq :: (Int -> a -> WidgetRequest s e) -> SelectListCfg s e a Source #

CmbOnChangeIdxReq (DropdownCfg s e a) s e a Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

onChangeIdxReq :: (Int -> a -> WidgetRequest s e) -> DropdownCfg s e a Source #

class CmbOnLoadError t e a | t -> e a where Source #

On load error event.

Methods

onLoadError :: (a -> e) -> t Source #

class CmbOnFinished t e | t -> e where Source #

On finished event.

Methods

onFinished :: e -> t Source #

class CmbWidth t where Source #

Width combinator.

Methods

width :: Double -> t Source #

Instances

Instances details
CmbWidth StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbWidth SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

Methods

width :: Double -> SizeReq Source #

CmbWidth (CheckboxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Checkbox

Methods

width :: Double -> CheckboxCfg s e Source #

CmbWidth (RadioCfg s e a) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Radio

Methods

width :: Double -> RadioCfg s e a Source #

class CmbHeight t where Source #

Height combinator.

Methods

height :: Double -> t Source #

Instances

Instances details
CmbHeight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbHeight SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbFlexWidth t where Source #

Flex width combinator.

Methods

flexWidth :: Double -> t Source #

Instances

Instances details
CmbFlexWidth StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbFlexWidth SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbFlexHeight t where Source #

Flex height combinator.

Methods

flexHeight :: Double -> t Source #

Instances

Instances details
CmbFlexHeight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbFlexHeight SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbMinWidth t where Source #

Min width combinator.

Methods

minWidth :: Double -> t Source #

Instances

Instances details
CmbMinWidth StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbMinWidth SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbMinHeight t where Source #

Min height combinator.

Methods

minHeight :: Double -> t Source #

Instances

Instances details
CmbMinHeight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbMinHeight SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbMaxWidth t where Source #

Max width combinator.

Methods

maxWidth :: Double -> t Source #

Instances

Instances details
CmbMaxWidth StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbMaxWidth SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbMaxHeight t where Source #

Max height combinator.

Methods

maxHeight :: Double -> t Source #

Instances

Instances details
CmbMaxHeight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbMaxHeight SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

CmbMaxHeight (DropdownCfg s e a) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

Methods

maxHeight :: Double -> DropdownCfg s e a Source #

class CmbExpandWidth t where Source #

Expand width combinator.

Methods

expandWidth :: Double -> t Source #

Instances

Instances details
CmbExpandWidth StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbExpandWidth SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbExpandHeight t where Source #

Expand height combinator.

Methods

expandHeight :: Double -> t Source #

Instances

Instances details
CmbExpandHeight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbExpandHeight SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRangeWidth t where Source #

Range width combinator.

Methods

rangeWidth :: Double -> Double -> t Source #

Instances

Instances details
CmbRangeWidth StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbRangeWidth SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRangeHeight t where Source #

Range height combinator.

Methods

rangeHeight :: Double -> Double -> t Source #

Instances

Instances details
CmbRangeHeight StyleState Source # 
Instance details

Defined in Monomer.Core.Style

CmbRangeHeight SizeReq Source # 
Instance details

Defined in Monomer.Core.Style

class CmbSizeReqW t where Source #

Custom SizeReq width combinator.

Methods

sizeReqW :: SizeReq -> t Source #

Instances

Instances details
CmbSizeReqW StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbSizeReqH t where Source #

Custom SizeReq height combinator.

Methods

sizeReqH :: SizeReq -> t Source #

Instances

Instances details
CmbSizeReqH StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbSizeReqUpdater t where Source #

SizeReq updater. Useful to make modifications to widget SizeReqs without completely overriding them.

Instances

Instances details
CmbSizeReqUpdater (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbResizeFactor t where Source #

Resize factor combinator.

Methods

resizeFactor :: Double -> t Source #

Instances

Instances details
CmbResizeFactor (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

class CmbResizeFactorDim t where Source #

Resize factor combinator for individual w and h components.

Instances

Instances details
CmbResizeFactorDim (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

class CmbStyleBasic t where Source #

Basic style combinator, used mainly infix for widgets as a list.

Methods

styleBasic :: t -> [StyleState] -> t infixl 5 Source #

Instances

Instances details
CmbStyleBasic Style Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleBasic (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

class CmbStyleHover t where Source #

Hover style combinator, used mainly infix for widgets as a list.

Methods

styleHover :: t -> [StyleState] -> t infixl 5 Source #

Instances

Instances details
CmbStyleHover Style Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleHover (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

class CmbStyleFocus t where Source #

Focus style combinator, used mainly infix for widgets as a list.

Methods

styleFocus :: t -> [StyleState] -> t infixl 5 Source #

Instances

Instances details
CmbStyleFocus Style Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleFocus (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

class CmbStyleFocusHover t where Source #

Focus Hover style combinator, used mainly infix for widgets as a list.

Methods

styleFocusHover :: t -> [StyleState] -> t infixl 5 Source #

Instances

Instances details
CmbStyleFocusHover Style Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleFocusHover (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

class CmbStyleActive t where Source #

Active style combinator, used mainly infix for widgets as a list.

Methods

styleActive :: t -> [StyleState] -> t infixl 5 Source #

Instances

Instances details
CmbStyleActive Style Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleActive (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

class CmbStyleDisabled t where Source #

Disabled style combinator, used mainly infix for widgets as a list.

Methods

styleDisabled :: t -> [StyleState] -> t infixl 5 Source #

Instances

Instances details
CmbStyleDisabled Style Source # 
Instance details

Defined in Monomer.Core.StyleUtil

CmbStyleDisabled (WidgetNode s e) Source # 
Instance details

Defined in Monomer.Core.StyleUtil

class CmbIgnoreTheme t where Source #

Ignore theme settings and start with blank style.

Minimal complete definition

ignoreTheme_

Instances

Instances details
CmbIgnoreTheme (LabelCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Singles.Label

class CmbBgColor t where Source #

Background color.

Methods

bgColor :: Color -> t Source #

Instances

Instances details
CmbBgColor StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbFgColor t where Source #

Foreground color.

Methods

fgColor :: Color -> t Source #

Instances

Instances details
CmbFgColor StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbSndColor t where Source #

Secondary color.

Methods

sndColor :: Color -> t Source #

Instances

Instances details
CmbSndColor StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbHlColor t where Source #

Highlight color.

Methods

hlColor :: Color -> t Source #

Instances

Instances details
CmbHlColor StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbTransparency t where Source #

Transparency level.

Methods

transparency :: Double -> t Source #

class CmbItemBasicStyle t s | t -> s where Source #

Basic style for each item of a list.

Methods

itemBasicStyle :: s -> t Source #

Instances

Instances details
CmbItemBasicStyle (SelectListCfg s e a) Style Source # 
Instance details

Defined in Monomer.Widgets.Containers.SelectList

CmbItemBasicStyle (DropdownCfg s e a) Style Source # 
Instance details

Defined in Monomer.Widgets.Containers.Dropdown

class CmbItemHoverStyle t s | t -> s where Source #

Hover style for an item of a list.

Methods

itemHoverStyle :: s -> t Source #

class CmbItemSelectedStyle t s | t -> s where Source #

Selected style for an item of a list.

Methods

itemSelectedStyle :: s -> t Source #

class CmbAlignLeft t where Source #

Align object to the left (not text).

Minimal complete definition

alignLeft_

Methods

alignLeft :: t Source #

alignLeft_ :: Bool -> t Source #

Instances

Instances details
CmbAlignLeft (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbAlignCenter t where Source #

Align object to the center (not text).

Minimal complete definition

alignCenter_

Instances

Instances details
CmbAlignCenter (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbAlignRight t where Source #

Align object to the right (not text).

Minimal complete definition

alignRight_

Instances

Instances details
CmbAlignRight (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbAlignTop t where Source #

Align object to the top (not text).

Minimal complete definition

alignTop_

Methods

alignTop :: t Source #

alignTop_ :: Bool -> t Source #

Instances

Instances details
CmbAlignTop (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbAlignMiddle t where Source #

Align object to the middle (not text).

Minimal complete definition

alignMiddle_

Instances

Instances details
CmbAlignMiddle (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbAlignBottom t where Source #

Align object to the bottom (not text).

Minimal complete definition

alignBottom_

Instances

Instances details
CmbAlignBottom (BoxCfg s e) Source # 
Instance details

Defined in Monomer.Widgets.Containers.Box

class CmbPadding t where Source #

Set padding to the same size on all sides.

Methods

padding :: Double -> t Source #

Instances

Instances details
CmbPadding Padding Source # 
Instance details

Defined in Monomer.Core.Style

CmbPadding StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbPaddingL t where Source #

Set padding for the left side.

Methods

paddingL :: Double -> t Source #

Instances

Instances details
CmbPaddingL Padding Source # 
Instance details

Defined in Monomer.Core.Style

CmbPaddingL StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbPaddingR t where Source #

Set padding for the right side.

Methods

paddingR :: Double -> t Source #

Instances

Instances details
CmbPaddingR Padding Source # 
Instance details

Defined in Monomer.Core.Style

CmbPaddingR StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbPaddingT t where Source #

Set padding for the top side.

Methods

paddingT :: Double -> t Source #

Instances

Instances details
CmbPaddingT Padding Source # 
Instance details

Defined in Monomer.Core.Style

CmbPaddingT StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbPaddingB t where Source #

Set padding for the bottom side.

Methods

paddingB :: Double -> t Source #

Instances

Instances details
CmbPaddingB Padding Source # 
Instance details

Defined in Monomer.Core.Style

CmbPaddingB StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbBorder t where Source #

Set border to the same style on all sides.

Methods

border :: Double -> Color -> t Source #

Instances

Instances details
CmbBorder Border Source # 
Instance details

Defined in Monomer.Core.Style

Methods

border :: Double -> Color -> Border Source #

CmbBorder StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbBorderL t where Source #

Set border for the left side.

Methods

borderL :: Double -> Color -> t Source #

Instances

Instances details
CmbBorderL Border Source # 
Instance details

Defined in Monomer.Core.Style

Methods

borderL :: Double -> Color -> Border Source #

CmbBorderL StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbBorderR t where Source #

Set border for the right side.

Methods

borderR :: Double -> Color -> t Source #

Instances

Instances details
CmbBorderR Border Source # 
Instance details

Defined in Monomer.Core.Style

Methods

borderR :: Double -> Color -> Border Source #

CmbBorderR StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbBorderT t where Source #

Set border for the top side.

Methods

borderT :: Double -> Color -> t Source #

Instances

Instances details
CmbBorderT Border Source # 
Instance details

Defined in Monomer.Core.Style

Methods

borderT :: Double -> Color -> Border Source #

CmbBorderT StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbBorderB t where Source #

Set border for the bottom side.

Methods

borderB :: Double -> Color -> t Source #

Instances

Instances details
CmbBorderB Border Source # 
Instance details

Defined in Monomer.Core.Style

Methods

borderB :: Double -> Color -> Border Source #

CmbBorderB StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRadius t where Source #

Set radius to the same size on all corners.

Methods

radius :: Double -> t Source #

Instances

Instances details
CmbRadius Radius Source # 
Instance details

Defined in Monomer.Core.Style

Methods

radius :: Double -> Radius Source #

CmbRadius StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRadiusTL t where Source #

Set radius for the top left corner.

Methods

radiusTL :: Double -> t Source #

Instances

Instances details
CmbRadiusTL Radius Source # 
Instance details

Defined in Monomer.Core.Style

CmbRadiusTL StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRadiusTR t where Source #

Set radius for the top right corner.

Methods

radiusTR :: Double -> t Source #

Instances

Instances details
CmbRadiusTR Radius Source # 
Instance details

Defined in Monomer.Core.Style

CmbRadiusTR StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRadiusBL t where Source #

Set radius for the bottom left corner.

Methods

radiusBL :: Double -> t Source #

Instances

Instances details
CmbRadiusBL Radius Source # 
Instance details

Defined in Monomer.Core.Style

CmbRadiusBL StyleState Source # 
Instance details

Defined in Monomer.Core.Style

class CmbRadiusBR t where Source #

Set radius for the bottom right corner.

Methods

radiusBR :: Double -> t Source #

Instances

Instances details
CmbRadiusBR Radius Source # 
Instance details

Defined in Monomer.Core.Style

CmbRadiusBR StyleState Source # 
Instance details

Defined in Monomer.Core.Style