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 |
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
- class CmbMergeRequired t s | t -> s where
- mergeRequired :: (s -> s -> Bool) -> t
- class CmbValidInput t s | t -> s where
- validInput :: ALens' s Bool -> t
- class CmbValidInputV t e | t -> e where
- validInputV :: (Bool -> e) -> t
- class CmbSelectOnFocus t where
- selectOnFocus :: t
- selectOnFocus_ :: Bool -> t
- class CmbResizeOnChange t where
- resizeOnChange :: t
- resizeOnChange_ :: Bool -> t
- class CmbAutoStart t where
- autoStart :: t
- autoStart_ :: Bool -> t
- class CmbDuration t a | t -> a where
- duration :: a -> t
- class CmbTitleCaption t where
- titleCaption :: Text -> t
- class CmbAcceptCaption t where
- acceptCaption :: Text -> t
- class CmbCancelCaption t where
- cancelCaption :: Text -> t
- class CmbCloseCaption t where
- closeCaption :: Text -> t
- class CmbMinValue t a | t -> a where
- minValue :: a -> t
- class CmbMaxValue t a | t -> a where
- maxValue :: a -> t
- class CmbDragRate t a | t -> a where
- dragRate :: a -> t
- class CmbWheelRate t a | t -> a where
- wheelRate :: a -> t
- class CmbIgnoreEmptyArea t where
- ignoreEmptyArea :: t
- ignoreEmptyArea_ :: Bool -> t
- class CmbDecimals t where
- class CmbMaxLength t where
- class CmbMaxLines t where
- class CmbAcceptTab t where
- acceptTab :: t
- acceptTab_ :: Bool -> t
- class CmbMultiline t where
- multiline :: t
- multiline_ :: Bool -> t
- class CmbEllipsis t where
- class CmbTrimSpaces t where
- trimSpaces :: t
- trimSpaces_ :: Bool -> t
- class CmbSelectOnBlur t where
- selectOnBlur :: t
- selectOnBlur_ :: Bool -> t
- class CmbPlaceholder t a | t -> a where
- placeholder :: a -> t
- class CmbCaretWidth t a | t -> a where
- caretWidth :: a -> t
- class CmbCaretMs t a | t -> a where
- caretMs :: a -> t
- class CmbTextFont t where
- class CmbTextSize t where
- class CmbTextSpaceH t where
- textSpaceH :: Double -> t
- class CmbTextSpaceV t where
- textSpaceV :: Double -> t
- class CmbTextColor t where
- class CmbTextLeft t where
- class CmbTextCenter t where
- textCenter :: t
- textCenter_ :: Bool -> t
- class CmbTextRight t where
- textRight :: t
- textRight_ :: Bool -> t
- class CmbTextTop t where
- class CmbTextMiddle t where
- textMiddle :: t
- textMiddle_ :: Bool -> t
- class CmbTextAscender t where
- textAscender :: t
- textAscender_ :: Bool -> t
- class CmbTextLowerX t where
- textLowerX :: t
- textLowerX_ :: Bool -> t
- class CmbTextBottom t where
- textBottom :: t
- textBottom_ :: Bool -> t
- class CmbTextBaseline t where
- textBaseline :: t
- textBaseline_ :: Bool -> t
- class CmbTextUnderline t where
- textUnderline :: t
- textUnderline_ :: Bool -> t
- class CmbTextOverline t where
- textOverline :: t
- textOverline_ :: Bool -> t
- class CmbTextThroughline t where
- textThroughline :: t
- textThroughline_ :: Bool -> t
- class CmbFitNone t where
- fitNone :: t
- class CmbFitFill t where
- fitFill :: t
- class CmbFitWidth t where
- fitWidth :: t
- class CmbFitHeight t where
- fitHeight :: t
- class CmbImageNearest t where
- imageNearest :: t
- class CmbImageRepeatX t where
- imageRepeatX :: t
- class CmbImageRepeatY t where
- imageRepeatY :: t
- class CmbBarColor t where
- class CmbBarHoverColor t where
- barHoverColor :: Color -> t
- class CmbBarWidth t where
- class CmbThumbColor t where
- thumbColor :: Color -> t
- class CmbThumbHoverColor t where
- thumbHoverColor :: Color -> t
- class CmbThumbFactor t where
- thumbFactor :: Double -> t
- class CmbThumbRadius t where
- thumbRadius :: Double -> t
- class CmbThumbVisible t where
- thumbVisible :: t
- thumbVisible_ :: Bool -> t
- class CmbThumbWidth t where
- thumbWidth :: Double -> t
- class CmbShowAlpha t where
- showAlpha :: t
- showAlpha_ :: Bool -> t
- class CmbIgnoreChildrenEvts t where
- ignoreChildrenEvts :: t
- ignoreChildrenEvts_ :: Bool -> t
- class CmbOnInit t e | t -> e where
- onInit :: e -> t
- class CmbOnDispose t e | t -> e where
- onDispose :: e -> t
- class CmbOnResize t e a | t -> e a where
- onResize :: (a -> e) -> t
- class CmbOnFocus t e a | t -> e a where
- onFocus :: (a -> e) -> t
- class CmbOnFocusReq t s e a | t -> s e a where
- onFocusReq :: (a -> WidgetRequest s e) -> t
- class CmbOnBlur t e a | t -> e a where
- onBlur :: (a -> e) -> t
- class CmbOnBlurReq t s e a | t -> s e a where
- onBlurReq :: (a -> WidgetRequest s e) -> t
- class CmbOnEnter t e | t -> e where
- onEnter :: e -> t
- class CmbOnEnterReq t s e | t -> s e where
- onEnterReq :: WidgetRequest s e -> t
- class CmbOnLeave t e | t -> e where
- onLeave :: e -> t
- class CmbOnLeaveReq t s e | t -> s e where
- onLeaveReq :: WidgetRequest s e -> t
- class CmbOnClick t e | t -> e where
- onClick :: e -> t
- class CmbOnClickReq t s e | t -> s e where
- onClickReq :: WidgetRequest s e -> t
- class CmbOnClickEmpty t e | t -> e where
- onClickEmpty :: e -> t
- class CmbOnClickEmptyReq t s e | t -> s e where
- onClickEmptyReq :: WidgetRequest s e -> t
- class CmbOnBtnPressed t e | t -> e where
- onBtnPressed :: (Button -> Int -> e) -> t
- class CmbOnBtnPressedReq t s e | t -> s e where
- onBtnPressedReq :: (Button -> Int -> WidgetRequest s e) -> t
- class CmbOnBtnReleased t e | t -> e where
- onBtnReleased :: (Button -> Int -> e) -> t
- class CmbOnBtnReleasedReq t s e | t -> s e where
- onBtnReleasedReq :: (Button -> Int -> WidgetRequest s e) -> t
- class CmbOnEnabledChange t e | t -> e where
- onEnabledChange :: e -> t
- class CmbOnVisibleChange t e | t -> e where
- onVisibleChange :: e -> t
- class CmbOnChange t a e | t -> e where
- onChange :: (a -> e) -> t
- class CmbOnChangeIdx t e a | t -> e a where
- onChangeIdx :: (Int -> a -> e) -> t
- class CmbOnChangeReq t s e a | t -> s e a where
- onChangeReq :: (a -> WidgetRequest s e) -> t
- class CmbOnChangeIdxReq t s e a | t -> s e a where
- onChangeIdxReq :: (Int -> a -> WidgetRequest s e) -> t
- class CmbOnLoadError t e a | t -> e a where
- onLoadError :: (a -> e) -> t
- class CmbOnFinished t e | t -> e where
- onFinished :: e -> t
- class CmbWidth t where
- class CmbHeight t where
- class CmbFlexWidth t where
- class CmbFlexHeight t where
- flexHeight :: Double -> t
- class CmbMinWidth t where
- class CmbMinHeight t where
- class CmbMaxWidth t where
- class CmbMaxHeight t where
- class CmbExpandWidth t where
- expandWidth :: Double -> t
- class CmbExpandHeight t where
- expandHeight :: Double -> t
- class CmbRangeWidth t where
- rangeWidth :: Double -> Double -> t
- class CmbRangeHeight t where
- rangeHeight :: Double -> Double -> t
- class CmbSizeReqW t where
- class CmbSizeReqH t where
- class CmbSizeReqUpdater t where
- sizeReqUpdater :: ((SizeReq, SizeReq) -> (SizeReq, SizeReq)) -> t
- class CmbResizeFactor t where
- resizeFactor :: Double -> t
- class CmbResizeFactorDim t where
- resizeFactorW :: Double -> t
- resizeFactorH :: Double -> t
- class CmbStyleBasic t where
- styleBasic :: t -> [StyleState] -> t
- class CmbStyleHover t where
- styleHover :: t -> [StyleState] -> t
- class CmbStyleFocus t where
- styleFocus :: t -> [StyleState] -> t
- class CmbStyleFocusHover t where
- styleFocusHover :: t -> [StyleState] -> t
- class CmbStyleActive t where
- styleActive :: t -> [StyleState] -> t
- class CmbStyleDisabled t where
- styleDisabled :: t -> [StyleState] -> t
- class CmbIgnoreTheme t where
- ignoreTheme :: t
- ignoreTheme_ :: Bool -> t
- class CmbBgColor t where
- class CmbFgColor t where
- class CmbSndColor t where
- class CmbHlColor t where
- class CmbTransparency t where
- transparency :: Double -> t
- class CmbCursorIcon t where
- cursorArrow :: t
- cursorHand :: t
- cursorIBeam :: t
- cursorInvalid :: t
- cursorSizeH :: t
- cursorSizeV :: t
- cursorDiagTL :: t
- cursorDiagTR :: t
- cursorIcon :: CursorIcon -> t
- class CmbItemBasicStyle t s | t -> s where
- itemBasicStyle :: s -> t
- class CmbItemHoverStyle t s | t -> s where
- itemHoverStyle :: s -> t
- class CmbItemSelectedStyle t s | t -> s where
- itemSelectedStyle :: s -> t
- class CmbAlignLeft t where
- alignLeft :: t
- alignLeft_ :: Bool -> t
- class CmbAlignCenter t where
- alignCenter :: t
- alignCenter_ :: Bool -> t
- class CmbAlignRight t where
- alignRight :: t
- alignRight_ :: Bool -> t
- class CmbAlignTop t where
- class CmbAlignMiddle t where
- alignMiddle :: t
- alignMiddle_ :: Bool -> t
- class CmbAlignBottom t where
- alignBottom :: t
- alignBottom_ :: Bool -> t
- class CmbPadding t where
- class CmbPaddingL t where
- class CmbPaddingR t where
- class CmbPaddingT t where
- class CmbPaddingB t where
- class CmbBorder t where
- class CmbBorderL t where
- class CmbBorderR t where
- class CmbBorderT t where
- class CmbBorderB t where
- class CmbRadius t where
- class CmbRadiusTL t where
- class CmbRadiusTR t where
- class CmbRadiusBL t where
- class CmbRadiusBR t where
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
CmbMergeRequired (BoxCfg s e) s Source # | |
Defined in Monomer.Widgets.Containers.Box Methods mergeRequired :: (s -> s -> Bool) -> BoxCfg s e Source # | |
CmbMergeRequired (SelectListCfg s e a) (Seq a) Source # | |
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 # | |
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
class CmbResizeOnChange t where Source #
Defines whether a widget changes its size when the model changes.
Minimal complete definition
class CmbAutoStart t where Source #
Defines whether animation should start automatically.
Minimal complete definition
class CmbDuration t a | t -> a where Source #
Defines the animation length.
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.
class CmbMaxValue t a | t -> a where Source #
Maximum value of a widget, usually numeric.
class CmbDragRate t a | t -> a where Source #
Drag rate of a widget, usually numeric.
class CmbWheelRate t a | t -> a where Source #
Wheel rate of a widget, usually numeric or scrollable.
class CmbIgnoreEmptyArea t where Source #
Whether to ignore pointer events where no widget exists.
Minimal complete definition
Instances
CmbIgnoreEmptyArea (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbDecimals t where Source #
How many decimals a numeric widget accepts.
class CmbMaxLength t where Source #
Max length a widget accepts.
class CmbMaxLines t where Source #
Max lines a widget accepts.
Instances
CmbMaxLines (LabelCfg s e) Source # | |
class CmbMultiline t where Source #
Whether a text based widget is multiline.
Minimal complete definition
Instances
CmbMultiline (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label |
class CmbTrimSpaces t where Source #
Whether to trim spaces or not.
Minimal complete definition
Instances
CmbTrimSpaces (LabelCfg s e) Source # | |
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
Instances
CmbSelectOnBlur (SelectListCfg s e a) Source # | |
Defined in Monomer.Widgets.Containers.SelectList Methods selectOnBlur :: SelectListCfg s e a Source # selectOnBlur_ :: Bool -> SelectListCfg s e a Source # |
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.
class CmbTextFont t where Source #
Text font.
Instances
CmbTextFont TextStyle Source # | |
CmbTextFont StyleState Source # | |
Defined in Monomer.Core.Style Methods textFont :: Font -> StyleState Source # |
class CmbTextSize t where Source #
Text size.
Instances
CmbTextSize TextStyle Source # | |
CmbTextSize StyleState Source # | |
Defined in Monomer.Core.Style Methods textSize :: Double -> StyleState Source # |
class CmbTextSpaceH t where Source #
Horizontal text spacing.
Methods
textSpaceH :: Double -> t Source #
Instances
CmbTextSpaceH TextStyle Source # | |
Defined in Monomer.Core.Style Methods textSpaceH :: Double -> TextStyle Source # | |
CmbTextSpaceH StyleState Source # | |
Defined in Monomer.Core.Style Methods textSpaceH :: Double -> StyleState Source # |
class CmbTextSpaceV t where Source #
Vertical text spacing.
Methods
textSpaceV :: Double -> t Source #
Instances
CmbTextSpaceV TextStyle Source # | |
Defined in Monomer.Core.Style Methods textSpaceV :: Double -> TextStyle Source # | |
CmbTextSpaceV StyleState Source # | |
Defined in Monomer.Core.Style Methods textSpaceV :: Double -> StyleState Source # |
class CmbTextColor t where Source #
Text color.
Instances
CmbTextColor TextStyle Source # | |
CmbTextColor StyleState Source # | |
Defined in Monomer.Core.Style Methods textColor :: Color -> StyleState Source # |
class CmbTextLeft t where Source #
Align text to the left.
Minimal complete definition
Instances
CmbTextLeft TextStyle Source # | |
CmbTextLeft StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextCenter t where Source #
Align text to the center.
Minimal complete definition
Instances
CmbTextCenter TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextCenter StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextRight t where Source #
Align text to the right.
Minimal complete definition
Instances
CmbTextRight TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextRight StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextTop t where Source #
Align text to the top.
Minimal complete definition
Instances
CmbTextTop TextStyle Source # | |
CmbTextTop StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextMiddle t where Source #
Align text to the vertical middle based on the line height.
Minimal complete definition
Instances
CmbTextMiddle TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextMiddle StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextAscender t where Source #
Align text to the vertical middle based on the ascender.
Minimal complete definition
Instances
CmbTextAscender TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextAscender StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextLowerX t where Source #
Align text to the vertical middle based on the x height.
Minimal complete definition
Instances
CmbTextLowerX TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextLowerX StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextBottom t where Source #
Align text to the bottom.
Minimal complete definition
Instances
CmbTextBottom TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextBottom StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextBaseline t where Source #
Align text to the baseline.
Minimal complete definition
Instances
CmbTextBaseline TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextBaseline StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextUnderline t where Source #
Display a line under the text.
Minimal complete definition
Instances
CmbTextUnderline TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextUnderline StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextOverline t where Source #
Display a line above the text.
Minimal complete definition
Instances
CmbTextOverline TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextOverline StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextThroughline t where Source #
Display a line over the text.
Minimal complete definition
Instances
CmbTextThroughline TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextThroughline StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbFitNone t where Source #
Does not apply any kind of resizing to fit to container.
class CmbFitWidth t where Source #
Fits to use all the container's width.
class CmbFitHeight t where Source #
Fits to use all the container's height.
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.
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.
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
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
class CmbIgnoreChildrenEvts t where Source #
Whether to ignore children events.
Minimal complete definition
class CmbOnInit t e | t -> e where Source #
On init event.
Instances
CmbOnInit (CompositeCfg s e sp ep) e Source # | |
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.
Instances
CmbOnDispose (CompositeCfg s e sp ep) e Source # | |
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.
Instances
CmbOnResize (CompositeCfg s e sp ep) e Rect Source # | |
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.
Instances
WidgetEvent e => CmbOnFocus (CheckboxCfg s e) e Path Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods onFocus :: (Path -> e) -> CheckboxCfg s e Source # | |
WidgetEvent e => CmbOnFocus (BoxCfg s e) e Path Source # | |
WidgetEvent e => CmbOnFocus (RadioCfg s e a) e Path Source # | |
WidgetEvent e => CmbOnFocus (SelectListCfg s e a) e Path Source # | |
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 # | |
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
CmbOnFocusReq (CheckboxCfg s e) s e Path Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods onFocusReq :: (Path -> WidgetRequest s e) -> CheckboxCfg s e Source # | |
CmbOnFocusReq (BoxCfg s e) s e Path Source # | |
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 # | |
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 # | |
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 # | |
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.
Instances
WidgetEvent e => CmbOnBlur (CheckboxCfg s e) e Path Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods onBlur :: (Path -> e) -> CheckboxCfg s e Source # | |
WidgetEvent e => CmbOnBlur (BoxCfg s e) e Path Source # | |
WidgetEvent e => CmbOnBlur (RadioCfg s e a) e Path Source # | |
WidgetEvent e => CmbOnBlur (SelectListCfg s e a) e Path Source # | |
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 # | |
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
CmbOnBlurReq (CheckboxCfg s e) s e Path Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods onBlurReq :: (Path -> WidgetRequest s e) -> CheckboxCfg s e Source # | |
CmbOnBlurReq (BoxCfg s e) s e Path Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbOnBlurReq (RadioCfg s e a) s e Path Source # | |
Defined in Monomer.Widgets.Singles.Radio | |
CmbOnBlurReq (SelectListCfg s e a) s e Path Source # | |
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 # | |
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.
Instances
WidgetEvent e => CmbOnEnter (BoxCfg s e) e Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbOnEnterReq t s e | t -> s e where Source #
On enter WidgetRequest.
Methods
onEnterReq :: WidgetRequest s e -> t Source #
Instances
CmbOnEnterReq (BoxCfg s e) s e Source # | |
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.
Instances
WidgetEvent e => CmbOnLeave (BoxCfg s e) e Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbOnLeaveReq t s e | t -> s e where Source #
On leave WidgetRequest.
Methods
onLeaveReq :: WidgetRequest s e -> t Source #
Instances
CmbOnLeaveReq (BoxCfg s e) s e Source # | |
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.
Instances
WidgetEvent e => CmbOnClick (BoxCfg s e) e Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbOnClickReq t s e | t -> s e where Source #
On click WidgetRequest.
Methods
onClickReq :: WidgetRequest s e -> t Source #
Instances
CmbOnClickReq (BoxCfg s e) s e Source # | |
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
WidgetEvent e => CmbOnClickEmpty (BoxCfg s e) e Source # | |
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).
Methods
onClickEmptyReq :: WidgetRequest s e -> t Source #
Instances
CmbOnClickEmptyReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box Methods onClickEmptyReq :: WidgetRequest s e -> BoxCfg s e Source # |
class CmbOnBtnPressed t e | t -> e where Source #
On button pressed event.
Methods
onBtnPressed :: (Button -> Int -> e) -> t Source #
Instances
WidgetEvent e => CmbOnBtnPressed (BoxCfg s e) e Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbOnBtnPressedReq t s e | t -> s e where Source #
On button pressed WidgetRequest.
Methods
onBtnPressedReq :: (Button -> Int -> WidgetRequest s e) -> t Source #
Instances
CmbOnBtnPressedReq (BoxCfg s e) s e Source # | |
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
WidgetEvent e => CmbOnBtnReleased (BoxCfg s e) e Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbOnBtnReleasedReq t s e | t -> s e where Source #
On button released WidgetRequest.
Methods
onBtnReleasedReq :: (Button -> Int -> WidgetRequest s e) -> t Source #
Instances
CmbOnBtnReleasedReq (BoxCfg s e) s e Source # | |
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
CmbOnEnabledChange (CompositeCfg s e sp ep) e Source # | |
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
CmbOnVisibleChange (CompositeCfg s e sp ep) e Source # | |
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.
Instances
WidgetEvent e => CmbOnChange (CheckboxCfg s e) Bool e Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods onChange :: (Bool -> e) -> CheckboxCfg s e Source # | |
WidgetEvent e => CmbOnChange (RadioCfg s e a) a e Source # | |
Defined in Monomer.Widgets.Singles.Radio | |
WidgetEvent e => CmbOnChange (SelectListCfg s e a) a e Source # | |
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 # | |
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 # | |
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
WidgetEvent e => CmbOnChangeIdx (SelectListCfg s e a) e a Source # | |
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 # | |
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
CmbOnChangeReq (CheckboxCfg s e) s e Bool Source # | |
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 # | |
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 # | |
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 # | |
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 # | |
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
CmbOnChangeIdxReq (SelectListCfg s e a) s e a Source # | |
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 # | |
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.
Instances
CmbWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods width :: Double -> StyleState Source # | |
CmbWidth SizeReq Source # | |
CmbWidth (CheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods width :: Double -> CheckboxCfg s e Source # | |
CmbWidth (RadioCfg s e a) Source # | |
class CmbHeight t where Source #
Height combinator.
Instances
CmbHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods height :: Double -> StyleState Source # | |
CmbHeight SizeReq Source # | |
class CmbFlexWidth t where Source #
Flex width combinator.
Instances
CmbFlexWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods flexWidth :: Double -> StyleState Source # | |
CmbFlexWidth SizeReq Source # | |
class CmbFlexHeight t where Source #
Flex height combinator.
Methods
flexHeight :: Double -> t Source #
Instances
CmbFlexHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods flexHeight :: Double -> StyleState Source # | |
CmbFlexHeight SizeReq Source # | |
Defined in Monomer.Core.Style Methods flexHeight :: Double -> SizeReq Source # |
class CmbMinWidth t where Source #
Min width combinator.
Instances
CmbMinWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods minWidth :: Double -> StyleState Source # | |
CmbMinWidth SizeReq Source # | |
class CmbMinHeight t where Source #
Min height combinator.
Instances
CmbMinHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods minHeight :: Double -> StyleState Source # | |
CmbMinHeight SizeReq Source # | |
class CmbMaxWidth t where Source #
Max width combinator.
Instances
CmbMaxWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods maxWidth :: Double -> StyleState Source # | |
CmbMaxWidth SizeReq Source # | |
class CmbMaxHeight t where Source #
Max height combinator.
Instances
CmbMaxHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods maxHeight :: Double -> StyleState Source # | |
CmbMaxHeight SizeReq Source # | |
CmbMaxHeight (DropdownCfg s e a) Source # | |
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
CmbExpandWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods expandWidth :: Double -> StyleState Source # | |
CmbExpandWidth SizeReq Source # | |
Defined in Monomer.Core.Style Methods expandWidth :: Double -> SizeReq Source # |
class CmbExpandHeight t where Source #
Expand height combinator.
Methods
expandHeight :: Double -> t Source #
Instances
CmbExpandHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods expandHeight :: Double -> StyleState Source # | |
CmbExpandHeight SizeReq Source # | |
Defined in Monomer.Core.Style Methods expandHeight :: Double -> SizeReq Source # |
class CmbRangeWidth t where Source #
Range width combinator.
Methods
rangeWidth :: Double -> Double -> t Source #
Instances
CmbRangeWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods rangeWidth :: Double -> Double -> StyleState Source # | |
CmbRangeWidth SizeReq Source # | |
Defined in Monomer.Core.Style |
class CmbRangeHeight t where Source #
Range height combinator.
Methods
rangeHeight :: Double -> Double -> t Source #
Instances
CmbRangeHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods rangeHeight :: Double -> Double -> StyleState Source # | |
CmbRangeHeight SizeReq Source # | |
Defined in Monomer.Core.Style |
class CmbSizeReqW t where Source #
Custom SizeReq width combinator.
Instances
CmbSizeReqW StyleState Source # | |
Defined in Monomer.Core.Style Methods sizeReqW :: SizeReq -> StyleState Source # |
class CmbSizeReqH t where Source #
Custom SizeReq height combinator.
Instances
CmbSizeReqH StyleState Source # | |
Defined in Monomer.Core.Style Methods sizeReqH :: SizeReq -> StyleState Source # |
class CmbSizeReqUpdater t where Source #
SizeReq updater. Useful to make modifications to widget SizeReqs without completely overriding them.
Instances
CmbSizeReqUpdater (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbResizeFactor t where Source #
Resize factor combinator.
Methods
resizeFactor :: Double -> t Source #
Instances
CmbResizeFactor (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label Methods resizeFactor :: Double -> LabelCfg s e Source # |
class CmbResizeFactorDim t where Source #
Resize factor combinator for individual w and h components.
Instances
CmbResizeFactorDim (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label Methods resizeFactorW :: Double -> LabelCfg s e Source # resizeFactorH :: Double -> LabelCfg s e Source # |
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
CmbStyleBasic Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleBasic :: Style -> [StyleState] -> Style Source # | |
CmbStyleBasic (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleBasic :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
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
CmbStyleHover Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleHover :: Style -> [StyleState] -> Style Source # | |
CmbStyleHover (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleHover :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
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
CmbStyleFocus Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocus :: Style -> [StyleState] -> Style Source # | |
CmbStyleFocus (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocus :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
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
CmbStyleFocusHover Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocusHover :: Style -> [StyleState] -> Style Source # | |
CmbStyleFocusHover (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocusHover :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
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
CmbStyleActive Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleActive :: Style -> [StyleState] -> Style Source # | |
CmbStyleActive (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleActive :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
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
CmbStyleDisabled Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleDisabled :: Style -> [StyleState] -> Style Source # | |
CmbStyleDisabled (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleDisabled :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbIgnoreTheme t where Source #
Ignore theme settings and start with blank style.
Minimal complete definition
Instances
CmbIgnoreTheme (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label |
class CmbBgColor t where Source #
Background color.
Instances
CmbBgColor StyleState Source # | |
Defined in Monomer.Core.Style Methods bgColor :: Color -> StyleState Source # |
class CmbFgColor t where Source #
Foreground color.
Instances
CmbFgColor StyleState Source # | |
Defined in Monomer.Core.Style Methods fgColor :: Color -> StyleState Source # |
class CmbSndColor t where Source #
Secondary color.
Instances
CmbSndColor StyleState Source # | |
Defined in Monomer.Core.Style Methods sndColor :: Color -> StyleState Source # |
class CmbHlColor t where Source #
Highlight color.
Instances
CmbHlColor StyleState Source # | |
Defined in Monomer.Core.Style Methods hlColor :: Color -> StyleState Source # |
class CmbTransparency t where Source #
Transparency level.
Methods
transparency :: Double -> t Source #
class CmbCursorIcon t where Source #
Cursor icons.
Minimal complete definition
Methods
cursorArrow :: t Source #
cursorHand :: t Source #
cursorIBeam :: t Source #
cursorInvalid :: t Source #
cursorSizeH :: t Source #
cursorSizeV :: t Source #
cursorDiagTL :: t Source #
cursorDiagTR :: t Source #
cursorIcon :: CursorIcon -> t Source #
Instances
CmbCursorIcon StyleState Source # | |
Defined in Monomer.Core.Style Methods cursorArrow :: StyleState Source # cursorHand :: StyleState Source # cursorIBeam :: StyleState Source # cursorInvalid :: StyleState Source # cursorSizeH :: StyleState Source # cursorSizeV :: StyleState Source # cursorDiagTL :: StyleState Source # cursorDiagTR :: StyleState Source # cursorIcon :: CursorIcon -> StyleState Source # |
class CmbItemBasicStyle t s | t -> s where Source #
Basic style for each item of a list.
Methods
itemBasicStyle :: s -> t Source #
Instances
CmbItemBasicStyle (SelectListCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.SelectList Methods itemBasicStyle :: Style -> SelectListCfg s e a Source # | |
CmbItemBasicStyle (DropdownCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.Dropdown Methods itemBasicStyle :: Style -> DropdownCfg s e a Source # |
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 #
Instances
CmbItemSelectedStyle (SelectListCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.SelectList Methods itemSelectedStyle :: Style -> SelectListCfg s e a Source # | |
CmbItemSelectedStyle (DropdownCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.Dropdown Methods itemSelectedStyle :: Style -> DropdownCfg s e a Source # |
class CmbAlignLeft t where Source #
Align object to the left (not text).
Minimal complete definition
Instances
CmbAlignLeft (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbAlignCenter t where Source #
Align object to the center (not text).
Minimal complete definition
Instances
CmbAlignCenter (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbAlignRight t where Source #
Align object to the right (not text).
Minimal complete definition
Instances
CmbAlignRight (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbAlignMiddle t where Source #
Align object to the middle (not text).
Minimal complete definition
Instances
CmbAlignMiddle (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbAlignBottom t where Source #
Align object to the bottom (not text).
Minimal complete definition
Instances
CmbAlignBottom (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbPadding t where Source #
Set padding to the same size on all sides.
Instances
CmbPadding Padding Source # | |
CmbPadding StyleState Source # | |
Defined in Monomer.Core.Style Methods padding :: Double -> StyleState Source # |
class CmbPaddingL t where Source #
Set padding for the left side.
Instances
CmbPaddingL Padding Source # | |
CmbPaddingL StyleState Source # | |
Defined in Monomer.Core.Style Methods paddingL :: Double -> StyleState Source # |
class CmbPaddingR t where Source #
Set padding for the right side.
Instances
CmbPaddingR Padding Source # | |
CmbPaddingR StyleState Source # | |
Defined in Monomer.Core.Style Methods paddingR :: Double -> StyleState Source # |
class CmbPaddingT t where Source #
Set padding for the top side.
Instances
CmbPaddingT Padding Source # | |
CmbPaddingT StyleState Source # | |
Defined in Monomer.Core.Style Methods paddingT :: Double -> StyleState Source # |
class CmbPaddingB t where Source #
Set padding for the bottom side.
Instances
CmbPaddingB Padding Source # | |
CmbPaddingB StyleState Source # | |
Defined in Monomer.Core.Style Methods paddingB :: Double -> StyleState Source # |
class CmbBorderL t where Source #
Set border for the left side.
Instances
CmbBorderL Border Source # | |
CmbBorderL StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbBorderR t where Source #
Set border for the right side.
Instances
CmbBorderR Border Source # | |
CmbBorderR StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbBorderT t where Source #
Set border for the top side.
Instances
CmbBorderT Border Source # | |
CmbBorderT StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbBorderB t where Source #
Set border for the bottom side.
Instances
CmbBorderB Border Source # | |
CmbBorderB StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbRadius t where Source #
Set radius to the same size on all corners.
Instances
CmbRadius Radius Source # | |
CmbRadius StyleState Source # | |
Defined in Monomer.Core.Style Methods radius :: Double -> StyleState Source # |
class CmbRadiusTL t where Source #
Set radius for the top left corner.
Instances
CmbRadiusTL Radius Source # | |
CmbRadiusTL StyleState Source # | |
Defined in Monomer.Core.Style Methods radiusTL :: Double -> StyleState Source # |
class CmbRadiusTR t where Source #
Set radius for the top right corner.
Instances
CmbRadiusTR Radius Source # | |
CmbRadiusTR StyleState Source # | |
Defined in Monomer.Core.Style Methods radiusTR :: Double -> StyleState Source # |
class CmbRadiusBL t where Source #
Set radius for the bottom left corner.
Instances
CmbRadiusBL Radius Source # | |
CmbRadiusBL StyleState Source # | |
Defined in Monomer.Core.Style Methods radiusBL :: Double -> StyleState Source # |
class CmbRadiusBR t where Source #
Set radius for the bottom right corner.
Instances
CmbRadiusBR Radius Source # | |
CmbRadiusBR StyleState Source # | |
Defined in Monomer.Core.Style Methods radiusBR :: Double -> StyleState Source # |