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 |
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.
mergeRequired :: (s -> s -> Bool) -> t Source #
Instances
CmbMergeRequired (BoxCfg s e) s Source # | |
Defined in Monomer.Widgets.Containers.Box mergeRequired :: (s -> s -> Bool) -> BoxCfg s e Source # | |
CmbMergeRequired (SelectListCfg s e a) (Seq a) Source # | |
Defined in Monomer.Widgets.Containers.SelectList mergeRequired :: (Seq a -> Seq a -> Bool) -> SelectListCfg s e a Source # | |
CmbMergeRequired (CompositeCfg s e sp ep) s Source # | |
Defined in Monomer.Widgets.Composite 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.
validInput :: ALens' s Bool -> t Source #
Instances
CmbValidInput (TextFieldCfg s e) s Source # | |
Defined in Monomer.Widgets.Singles.TextField validInput :: ALens' s Bool -> TextFieldCfg s e Source # | |
CmbValidInput (TimeFieldCfg s e a) s Source # | |
Defined in Monomer.Widgets.Singles.TimeField validInput :: ALens' s Bool -> TimeFieldCfg s e a Source # | |
CmbValidInput (NumericFieldCfg s e a) s Source # | |
Defined in Monomer.Widgets.Singles.NumericField validInput :: ALens' s Bool -> NumericFieldCfg s e a Source # | |
CmbValidInput (DateFieldCfg s e a) s Source # | |
Defined in Monomer.Widgets.Singles.DateField validInput :: ALens' s Bool -> DateFieldCfg s e a Source # |
class CmbValidInputV t e | t -> e where Source #
Listener for the validation status of a field using an event handler.
validInputV :: (Bool -> e) -> t Source #
Instances
CmbValidInputV (TextFieldCfg s e) e Source # | |
Defined in Monomer.Widgets.Singles.TextField validInputV :: (Bool -> e) -> TextFieldCfg s e Source # | |
CmbValidInputV (TimeFieldCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.TimeField validInputV :: (Bool -> e) -> TimeFieldCfg s e a Source # | |
CmbValidInputV (NumericFieldCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.NumericField validInputV :: (Bool -> e) -> NumericFieldCfg s e a Source # | |
CmbValidInputV (DateFieldCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.DateField validInputV :: (Bool -> e) -> DateFieldCfg s e a Source # |
class CmbSelectOnFocus t where Source #
Defines whether a widget selects all its content when receiving focus.
selectOnFocus :: t Source #
selectOnFocus_ :: Bool -> t Source #
Instances
CmbSelectOnFocus (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField selectOnFocus :: TextFieldCfg s e Source # selectOnFocus_ :: Bool -> TextFieldCfg s e Source # | |
CmbSelectOnFocus (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea selectOnFocus :: TextAreaCfg s e Source # selectOnFocus_ :: Bool -> TextAreaCfg s e Source # | |
CmbSelectOnFocus (TimeFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.TimeField selectOnFocus :: TimeFieldCfg s e a Source # selectOnFocus_ :: Bool -> TimeFieldCfg s e a Source # | |
CmbSelectOnFocus (NumericFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.NumericField selectOnFocus :: NumericFieldCfg s e a Source # selectOnFocus_ :: Bool -> NumericFieldCfg s e a Source # | |
CmbSelectOnFocus (DateFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.DateField selectOnFocus :: DateFieldCfg s e a Source # selectOnFocus_ :: Bool -> DateFieldCfg s e a Source # |
class CmbResizeOnChange t where Source #
Defines whether a widget changes its size when the model changes.
resizeOnChange :: t Source #
resizeOnChange_ :: Bool -> t Source #
Instances
CmbResizeOnChange (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField resizeOnChange :: TextFieldCfg s e Source # resizeOnChange_ :: Bool -> TextFieldCfg s e Source # | |
CmbResizeOnChange (TimeFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.TimeField resizeOnChange :: TimeFieldCfg s e a Source # resizeOnChange_ :: Bool -> TimeFieldCfg s e a Source # | |
CmbResizeOnChange (NumericFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.NumericField resizeOnChange :: NumericFieldCfg s e a Source # resizeOnChange_ :: Bool -> NumericFieldCfg s e a Source # | |
CmbResizeOnChange (DateFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.DateField resizeOnChange :: DateFieldCfg s e a Source # resizeOnChange_ :: Bool -> DateFieldCfg s e a Source # |
class CmbAutoStart t where Source #
Defines whether animation should start automatically.
Instances
CmbAutoStart (SlideCfg e) Source # | |
Defined in Monomer.Widgets.Animation.Slide | |
CmbAutoStart (FadeCfg e) Source # | |
Defined in Monomer.Widgets.Animation.Fade |
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.
titleCaption :: Text -> t Source #
Instances
CmbTitleCaption ConfirmCfg Source # | |
Defined in Monomer.Widgets.Containers.Confirm titleCaption :: Text -> ConfirmCfg Source # | |
CmbTitleCaption AlertCfg Source # | |
Defined in Monomer.Widgets.Containers.Alert titleCaption :: Text -> AlertCfg Source # |
class CmbAcceptCaption t where Source #
Accept caption of a widget, usually a button.
acceptCaption :: Text -> t Source #
Instances
CmbAcceptCaption ConfirmCfg Source # | |
Defined in Monomer.Widgets.Containers.Confirm acceptCaption :: Text -> ConfirmCfg Source # |
class CmbCancelCaption t where Source #
Cancel caption of a widget, usually a button.
cancelCaption :: Text -> t Source #
Instances
CmbCancelCaption ConfirmCfg Source # | |
Defined in Monomer.Widgets.Containers.Confirm cancelCaption :: Text -> ConfirmCfg Source # |
class CmbCloseCaption t where Source #
Close caption of a widget, usually a button.
closeCaption :: Text -> t Source #
Instances
CmbCloseCaption AlertCfg Source # | |
Defined in Monomer.Widgets.Containers.Alert closeCaption :: Text -> AlertCfg Source # |
class CmbMinValue t a | t -> a where Source #
Minimum value of a widget, usually numeric.
Instances
FormattableTime a => CmbMinValue (TimeFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.TimeField minValue :: a -> TimeFieldCfg s e a Source # | |
FormattableNumber a => CmbMinValue (NumericFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.NumericField minValue :: a -> NumericFieldCfg s e a Source # | |
FormattableDate a => CmbMinValue (DateFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.DateField minValue :: a -> DateFieldCfg s e a Source # |
class CmbMaxValue t a | t -> a where Source #
Maximum value of a widget, usually numeric.
Instances
FormattableTime a => CmbMaxValue (TimeFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.TimeField maxValue :: a -> TimeFieldCfg s e a Source # | |
FormattableNumber a => CmbMaxValue (NumericFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.NumericField maxValue :: a -> NumericFieldCfg s e a Source # | |
FormattableDate a => CmbMaxValue (DateFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.DateField maxValue :: a -> DateFieldCfg s e a Source # |
class CmbDragRate t a | t -> a where Source #
Drag rate of a widget, usually numeric.
Instances
CmbDragRate (SliderCfg s e a) Rational Source # | |
CmbDragRate (DialCfg s e a) Rational Source # | |
CmbDragRate (TimeFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.TimeField dragRate :: Double -> TimeFieldCfg s e a Source # | |
CmbDragRate (NumericFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.NumericField dragRate :: Double -> NumericFieldCfg s e a Source # | |
CmbDragRate (DateFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.DateField dragRate :: Double -> DateFieldCfg s e a Source # |
class CmbWheelRate t a | t -> a where Source #
Wheel rate of a widget, usually numeric or scrollable.
Instances
CmbWheelRate (ScrollCfg s e) Rational Source # | |
CmbWheelRate (SliderCfg s e a) Rational Source # | |
CmbWheelRate (DialCfg s e a) Rational Source # | |
CmbWheelRate (TimeFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.TimeField wheelRate :: Double -> TimeFieldCfg s e a Source # | |
CmbWheelRate (NumericFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.NumericField wheelRate :: Double -> NumericFieldCfg s e a Source # | |
CmbWheelRate (DateFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.DateField wheelRate :: Double -> DateFieldCfg s e a Source # |
class CmbIgnoreEmptyArea t where Source #
Whether to ignore pointer events where no widget exists.
ignoreEmptyArea :: t Source #
ignoreEmptyArea_ :: Bool -> t Source #
Instances
CmbIgnoreEmptyArea StackCfg Source # | |
Defined in Monomer.Widgets.Containers.Stack | |
CmbIgnoreEmptyArea (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box ignoreEmptyArea :: BoxCfg s e Source # ignoreEmptyArea_ :: Bool -> BoxCfg s e Source # |
class CmbDecimals t where Source #
How many decimals a numeric widget accepts.
Instances
CmbDecimals (NumericFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.NumericField decimals :: Int -> NumericFieldCfg s e a Source # |
class CmbMaxLength t where Source #
Max length a widget accepts.
Instances
CmbMaxLength (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField maxLength :: Int -> TextFieldCfg s e Source # | |
CmbMaxLength (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea maxLength :: Int -> TextAreaCfg s e Source # |
class CmbMaxLines t where Source #
Max lines a widget accepts.
Instances
CmbMaxLines (LabelCfg s e) Source # | |
CmbMaxLines (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink maxLines :: Int -> ExternalLinkCfg s e Source # | |
CmbMaxLines (ButtonCfg s e) Source # | |
CmbMaxLines (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea maxLines :: Int -> TextAreaCfg s e Source # | |
CmbMaxLines (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox maxLines :: Int -> LabeledCheckboxCfg s e Source # | |
CmbMaxLines (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio maxLines :: Int -> LabeledRadioCfg s e a Source # |
class CmbAcceptTab t where Source #
Whether a widget accepts tab key.
Instances
CmbAcceptTab (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea acceptTab :: TextAreaCfg s e Source # acceptTab_ :: Bool -> TextAreaCfg s e Source # |
class CmbMultiline t where Source #
Whether a text based widget is multiline.
Instances
CmbMultiline (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label | |
CmbMultiline (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink multiline :: ExternalLinkCfg s e Source # multiline_ :: Bool -> ExternalLinkCfg s e Source # | |
CmbMultiline (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button | |
CmbMultiline (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox multiline :: LabeledCheckboxCfg s e Source # multiline_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbMultiline (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio multiline :: LabeledRadioCfg s e a Source # multiline_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbEllipsis t where Source #
Whether to use ellipsis or not.
Instances
CmbEllipsis (LabelCfg s e) Source # | |
CmbEllipsis (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink ellipsis :: ExternalLinkCfg s e Source # ellipsis_ :: Bool -> ExternalLinkCfg s e Source # | |
CmbEllipsis (ButtonCfg s e) Source # | |
CmbEllipsis (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox ellipsis :: LabeledCheckboxCfg s e Source # ellipsis_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbEllipsis (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio ellipsis :: LabeledRadioCfg s e a Source # ellipsis_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTrimSpaces t where Source #
Whether to trim spaces or not.
trimSpaces :: t Source #
trimSpaces_ :: Bool -> t Source #
Instances
CmbTrimSpaces (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label trimSpaces :: LabelCfg s e Source # trimSpaces_ :: Bool -> LabelCfg s e Source # | |
CmbTrimSpaces (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink trimSpaces :: ExternalLinkCfg s e Source # trimSpaces_ :: Bool -> ExternalLinkCfg s e Source # | |
CmbTrimSpaces (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button trimSpaces :: ButtonCfg s e Source # trimSpaces_ :: Bool -> ButtonCfg s e Source # | |
CmbTrimSpaces (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox trimSpaces :: LabeledCheckboxCfg s e Source # trimSpaces_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTrimSpaces (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio trimSpaces :: LabeledRadioCfg s e a Source # trimSpaces_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbSelectOnBlur t where Source #
Whether to automatically select a value on blur (for example, dropdown).
selectOnBlur :: t Source #
selectOnBlur_ :: Bool -> t Source #
Instances
CmbSelectOnBlur (SelectListCfg s e a) Source # | |
Defined in Monomer.Widgets.Containers.SelectList 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.
placeholder :: a -> t Source #
Instances
CmbPlaceholder (TextFieldCfg s e) Text Source # | |
Defined in Monomer.Widgets.Singles.TextField placeholder :: Text -> TextFieldCfg s e Source # |
class CmbCaretWidth t a | t -> a where Source #
Width of the caret in a text widget.
caretWidth :: a -> t Source #
Instances
CmbCaretWidth (TextFieldCfg s e) Double Source # | |
Defined in Monomer.Widgets.Singles.TextField caretWidth :: Double -> TextFieldCfg s e Source # | |
CmbCaretWidth (TextAreaCfg s e) Double Source # | |
Defined in Monomer.Widgets.Singles.TextArea caretWidth :: Double -> TextAreaCfg s e Source # | |
CmbCaretWidth (TimeFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.TimeField caretWidth :: Double -> TimeFieldCfg s e a Source # | |
CmbCaretWidth (NumericFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.NumericField caretWidth :: Double -> NumericFieldCfg s e a Source # | |
CmbCaretWidth (DateFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.DateField caretWidth :: Double -> DateFieldCfg s e a Source # |
class CmbCaretMs t a | t -> a where Source #
Blink period of the caret in a text widget.
Instances
CmbCaretMs (TextFieldCfg s e) Int Source # | |
Defined in Monomer.Widgets.Singles.TextField caretMs :: Int -> TextFieldCfg s e Source # | |
CmbCaretMs (TextAreaCfg s e) Int Source # | |
Defined in Monomer.Widgets.Singles.TextArea caretMs :: Int -> TextAreaCfg s e Source # | |
CmbCaretMs (TimeFieldCfg s e a) Int Source # | |
Defined in Monomer.Widgets.Singles.TimeField caretMs :: Int -> TimeFieldCfg s e a Source # | |
CmbCaretMs (NumericFieldCfg s e a) Int Source # | |
Defined in Monomer.Widgets.Singles.NumericField caretMs :: Int -> NumericFieldCfg s e a Source # | |
CmbCaretMs (DateFieldCfg s e a) Int Source # | |
Defined in Monomer.Widgets.Singles.DateField caretMs :: Int -> DateFieldCfg s e a Source # |
class CmbTextFont t where Source #
Text font.
Instances
CmbTextFont TextStyle Source # | |
CmbTextFont StyleState Source # | |
Defined in Monomer.Core.Style textFont :: Font -> StyleState Source # |
class CmbTextSize t where Source #
Text size.
Instances
CmbTextSize TextStyle Source # | |
CmbTextSize StyleState Source # | |
Defined in Monomer.Core.Style textSize :: Double -> StyleState Source # |
class CmbTextSpaceH t where Source #
Horizontal text spacing.
textSpaceH :: Double -> t Source #
Instances
CmbTextSpaceH TextStyle Source # | |
Defined in Monomer.Core.Style textSpaceH :: Double -> TextStyle Source # | |
CmbTextSpaceH StyleState Source # | |
Defined in Monomer.Core.Style textSpaceH :: Double -> StyleState Source # |
class CmbTextSpaceV t where Source #
Vertical text spacing.
textSpaceV :: Double -> t Source #
Instances
CmbTextSpaceV TextStyle Source # | |
Defined in Monomer.Core.Style textSpaceV :: Double -> TextStyle Source # | |
CmbTextSpaceV StyleState Source # | |
Defined in Monomer.Core.Style textSpaceV :: Double -> StyleState Source # |
class CmbTextColor t where Source #
Text color.
Instances
CmbTextColor TextStyle Source # | |
CmbTextColor StyleState Source # | |
Defined in Monomer.Core.Style textColor :: Color -> StyleState Source # |
class CmbTextLeft t where Source #
Align text to the left.
Instances
CmbTextLeft TextStyle Source # | |
CmbTextLeft StyleState Source # | |
Defined in Monomer.Core.Style textLeft :: StyleState Source # textLeft_ :: Bool -> StyleState Source # | |
CmbTextLeft (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox textLeft :: LabeledCheckboxCfg s e Source # textLeft_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextLeft (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio textLeft :: LabeledRadioCfg s e a Source # textLeft_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextCenter t where Source #
Align text to the center.
textCenter :: t Source #
textCenter_ :: Bool -> t Source #
Instances
CmbTextCenter TextStyle Source # | |
Defined in Monomer.Core.Style textCenter :: TextStyle Source # textCenter_ :: Bool -> TextStyle Source # | |
CmbTextCenter StyleState Source # | |
Defined in Monomer.Core.Style textCenter :: StyleState Source # textCenter_ :: Bool -> StyleState Source # |
class CmbTextRight t where Source #
Align text to the right.
Instances
CmbTextRight TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextRight StyleState Source # | |
Defined in Monomer.Core.Style textRight :: StyleState Source # textRight_ :: Bool -> StyleState Source # | |
CmbTextRight (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox textRight :: LabeledCheckboxCfg s e Source # textRight_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextRight (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio textRight :: LabeledRadioCfg s e a Source # textRight_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextTop t where Source #
Align text to the top.
Instances
CmbTextTop TextStyle Source # | |
CmbTextTop StyleState Source # | |
Defined in Monomer.Core.Style textTop :: StyleState Source # textTop_ :: Bool -> StyleState Source # | |
CmbTextTop (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox textTop :: LabeledCheckboxCfg s e Source # textTop_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextTop (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio textTop :: LabeledRadioCfg s e a Source # textTop_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextMiddle t where Source #
Align text to the vertical middle based on the line height.
textMiddle :: t Source #
textMiddle_ :: Bool -> t Source #
Instances
CmbTextMiddle TextStyle Source # | |
Defined in Monomer.Core.Style textMiddle :: TextStyle Source # textMiddle_ :: Bool -> TextStyle Source # | |
CmbTextMiddle StyleState Source # | |
Defined in Monomer.Core.Style textMiddle :: StyleState Source # textMiddle_ :: Bool -> StyleState Source # |
class CmbTextAscender t where Source #
Align text to the vertical middle based on the ascender.
textAscender :: t Source #
textAscender_ :: Bool -> t Source #
Instances
CmbTextAscender TextStyle Source # | |
Defined in Monomer.Core.Style textAscender :: TextStyle Source # textAscender_ :: Bool -> TextStyle Source # | |
CmbTextAscender StyleState Source # | |
Defined in Monomer.Core.Style textAscender :: StyleState Source # textAscender_ :: Bool -> StyleState Source # |
class CmbTextLowerX t where Source #
Align text to the vertical middle based on the x height.
textLowerX :: t Source #
textLowerX_ :: Bool -> t Source #
Instances
CmbTextLowerX TextStyle Source # | |
Defined in Monomer.Core.Style textLowerX :: TextStyle Source # textLowerX_ :: Bool -> TextStyle Source # | |
CmbTextLowerX StyleState Source # | |
Defined in Monomer.Core.Style textLowerX :: StyleState Source # textLowerX_ :: Bool -> StyleState Source # |
class CmbTextBottom t where Source #
Align text to the bottom.
textBottom :: t Source #
textBottom_ :: Bool -> t Source #
Instances
CmbTextBottom TextStyle Source # | |
Defined in Monomer.Core.Style textBottom :: TextStyle Source # textBottom_ :: Bool -> TextStyle Source # | |
CmbTextBottom StyleState Source # | |
Defined in Monomer.Core.Style textBottom :: StyleState Source # textBottom_ :: Bool -> StyleState Source # | |
CmbTextBottom (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox textBottom :: LabeledCheckboxCfg s e Source # textBottom_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextBottom (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio textBottom :: LabeledRadioCfg s e a Source # textBottom_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextBaseline t where Source #
Align text to the baseline.
textBaseline :: t Source #
textBaseline_ :: Bool -> t Source #
Instances
CmbTextBaseline TextStyle Source # | |
Defined in Monomer.Core.Style textBaseline :: TextStyle Source # textBaseline_ :: Bool -> TextStyle Source # | |
CmbTextBaseline StyleState Source # | |
Defined in Monomer.Core.Style textBaseline :: StyleState Source # textBaseline_ :: Bool -> StyleState Source # |
class CmbTextUnderline t where Source #
Display a line under the text.
textUnderline :: t Source #
textUnderline_ :: Bool -> t Source #
Instances
CmbTextUnderline TextStyle Source # | |
Defined in Monomer.Core.Style textUnderline :: TextStyle Source # textUnderline_ :: Bool -> TextStyle Source # | |
CmbTextUnderline StyleState Source # | |
Defined in Monomer.Core.Style |
class CmbTextOverline t where Source #
Display a line above the text.
textOverline :: t Source #
textOverline_ :: Bool -> t Source #
Instances
CmbTextOverline TextStyle Source # | |
Defined in Monomer.Core.Style textOverline :: TextStyle Source # textOverline_ :: Bool -> TextStyle Source # | |
CmbTextOverline StyleState Source # | |
Defined in Monomer.Core.Style textOverline :: StyleState Source # textOverline_ :: Bool -> StyleState Source # |
class CmbTextThroughline t where Source #
Display a line over the text.
textThroughline :: t Source #
textThroughline_ :: Bool -> t Source #
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.
Instances
CmbFitNone (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image |
class CmbFitFill t where Source #
Fits to use all the container's space.
Instances
CmbFitFill (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image |
class CmbFitWidth t where Source #
Fits to use all the container's width.
Instances
CmbFitWidth (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image |
class CmbFitHeight t where Source #
Fits to use all the container's height.
Instances
CmbFitHeight (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image |
class CmbImageNearest t where Source #
Applies nearest filtering when stretching an image.
imageNearest :: t Source #
Instances
CmbImageNearest (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image imageNearest :: ImageCfg e Source # |
class CmbImageRepeatX t where Source #
Applies horizontal repetition when stretching an image.
imageRepeatX :: t Source #
Instances
CmbImageRepeatX (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image imageRepeatX :: ImageCfg e Source # |
class CmbImageRepeatY t where Source #
Applies vertical repetition when stretching an image.
imageRepeatY :: t Source #
Instances
CmbImageRepeatY (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image imageRepeatY :: ImageCfg e Source # |
class CmbBarColor t where Source #
The color of a bar, for example in a scroll.
Instances
CmbBarColor (ScrollCfg s e) Source # | |
class CmbBarHoverColor t where Source #
The hover color of a bar, for example in a scroll.
barHoverColor :: Color -> t Source #
Instances
CmbBarHoverColor (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll barHoverColor :: Color -> ScrollCfg s e Source # |
class CmbBarWidth t where Source #
The width of a bar, for example in a scroll.
Instances
CmbBarWidth (ScrollCfg s e) Source # | |
class CmbThumbColor t where Source #
The color of a thumb, for example in a scroll.
thumbColor :: Color -> t Source #
Instances
CmbThumbColor (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll thumbColor :: Color -> ScrollCfg s e Source # |
class CmbThumbHoverColor t where Source #
The hover color of a thumb, for example in a scroll.
thumbHoverColor :: Color -> t Source #
Instances
CmbThumbHoverColor (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll thumbHoverColor :: Color -> ScrollCfg s e Source # |
class CmbThumbFactor t where Source #
The thumb factor. For example, in slider this makes the thumb proportional to the width of the slider.
thumbFactor :: Double -> t Source #
Instances
CmbThumbFactor (SliderCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.Slider thumbFactor :: Double -> SliderCfg s e a Source # |
class CmbThumbRadius t where Source #
The radius of a thumb's rect, for example in a scroll.
thumbRadius :: Double -> t Source #
Instances
CmbThumbRadius (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll thumbRadius :: Double -> ScrollCfg s e Source # |
class CmbThumbVisible t where Source #
Whether the thumb is visible, for example in a scroll.
thumbVisible :: t Source #
thumbVisible_ :: Bool -> t Source #
Instances
CmbThumbVisible (SliderCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.Slider thumbVisible :: SliderCfg s e a Source # thumbVisible_ :: Bool -> SliderCfg s e a Source # |
class CmbThumbWidth t where Source #
The width color of a thumb, for example in a scroll.
thumbWidth :: Double -> t Source #
Instances
CmbThumbWidth (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll thumbWidth :: Double -> ScrollCfg s e Source # |
class CmbShowAlpha t where Source #
Whether to show an alpha channel, for instance in color selector.
Instances
CmbShowAlpha (ColorPickerCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ColorPicker showAlpha :: ColorPickerCfg s e Source # showAlpha_ :: Bool -> ColorPickerCfg s e Source # |
class CmbIgnoreChildrenEvts t where Source #
Whether to ignore children events.
ignoreChildrenEvts :: t Source #
ignoreChildrenEvts_ :: Bool -> t Source #
Instances
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 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 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 onResize :: (Rect -> e) -> CompositeCfg s e sp ep Source # |
class CmbOnFocus t e a | t -> e a where Source #
On focus event.
Instances
class CmbOnFocusReq t s e a | t -> s e a where Source #
On focus WidgetRequest.
onFocusReq :: (a -> WidgetRequest s e) -> t Source #
Instances
class CmbOnBlur t e a | t -> e a where Source #
On blur event.
Instances
class CmbOnBlurReq t s e a | t -> s e a where Source #
On blur WidgetRequest.
onBlurReq :: (a -> WidgetRequest s e) -> t Source #
Instances
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.
onEnterReq :: WidgetRequest s e -> t Source #
Instances
CmbOnEnterReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box 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.
onLeaveReq :: WidgetRequest s e -> t Source #
Instances
CmbOnLeaveReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box onLeaveReq :: WidgetRequest s e -> BoxCfg s e Source # |
class CmbOnClick t e | t -> e where Source #
On click event.
Instances
WidgetEvent e => CmbOnClick (ButtonCfg s e) e Source # | |
Defined in Monomer.Widgets.Singles.Button | |
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.
onClickReq :: WidgetRequest s e -> t Source #
Instances
CmbOnClickReq (ButtonCfg s e) s e Source # | |
Defined in Monomer.Widgets.Singles.Button onClickReq :: WidgetRequest s e -> ButtonCfg s e Source # | |
CmbOnClickReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box 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).
onClickEmpty :: e -> t Source #
Instances
WidgetEvent e => CmbOnClickEmpty (BoxCfg s e) e Source # | |
Defined in Monomer.Widgets.Containers.Box 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).
onClickEmptyReq :: WidgetRequest s e -> t Source #
Instances
CmbOnClickEmptyReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box onClickEmptyReq :: WidgetRequest s e -> BoxCfg s e Source # |
class CmbOnBtnPressed t e | t -> e where Source #
On button pressed event.
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.
onBtnPressedReq :: (Button -> Int -> WidgetRequest s e) -> t Source #
Instances
CmbOnBtnPressedReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box onBtnPressedReq :: (Button -> Int -> WidgetRequest s e) -> BoxCfg s e Source # |
class CmbOnBtnReleased t e | t -> e where Source #
On button released event.
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.
onBtnReleasedReq :: (Button -> Int -> WidgetRequest s e) -> t Source #
Instances
CmbOnBtnReleasedReq (BoxCfg s e) s e Source # | |
Defined in Monomer.Widgets.Containers.Box onBtnReleasedReq :: (Button -> Int -> WidgetRequest s e) -> BoxCfg s e Source # |
class CmbOnEnabledChange t e | t -> e where Source #
On enabled change event.
onEnabledChange :: e -> t Source #
Instances
CmbOnEnabledChange (CompositeCfg s e sp ep) e Source # | |
Defined in Monomer.Widgets.Composite onEnabledChange :: e -> CompositeCfg s e sp ep Source # |
class CmbOnVisibleChange t e | t -> e where Source #
On visible change event.
onVisibleChange :: e -> t Source #
Instances
CmbOnVisibleChange (CompositeCfg s e sp ep) e Source # | |
Defined in Monomer.Widgets.Composite onVisibleChange :: e -> CompositeCfg s e sp ep Source # |
class CmbOnChange t a e | t -> e where Source #
On change event.
Instances
class CmbOnChangeIdx t e a | t -> e a where Source #
On change event, including index.
onChangeIdx :: (Int -> a -> e) -> t Source #
Instances
WidgetEvent e => CmbOnChangeIdx (SelectListCfg s e a) e a Source # | |
Defined in Monomer.Widgets.Containers.SelectList 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 onChangeIdx :: (Int -> a -> e) -> DropdownCfg s e a Source # |
class CmbOnChangeReq t s e a | t -> s e a where Source #
On change WidgetRequest.
onChangeReq :: (a -> WidgetRequest s e) -> t Source #
Instances
class CmbOnChangeIdxReq t s e a | t -> s e a where Source #
On change WidgetRequest, including index.
onChangeIdxReq :: (Int -> a -> WidgetRequest s e) -> t Source #
Instances
CmbOnChangeIdxReq (SelectListCfg s e a) s e a Source # | |
Defined in Monomer.Widgets.Containers.SelectList 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 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.
onLoadError :: (a -> e) -> t Source #
Instances
CmbOnLoadError (ImageCfg e) e ImageLoadError Source # | |
Defined in Monomer.Widgets.Singles.Image onLoadError :: (ImageLoadError -> e) -> ImageCfg e Source # |
class CmbOnFinished t e | t -> e where Source #
On finished event.
onFinished :: e -> t Source #
Instances
CmbOnFinished (SlideCfg e) e Source # | |
Defined in Monomer.Widgets.Animation.Slide onFinished :: e -> SlideCfg e Source # | |
CmbOnFinished (FadeCfg e) e Source # | |
Defined in Monomer.Widgets.Animation.Fade onFinished :: e -> FadeCfg e Source # |
class CmbWidth t where Source #
Width combinator.
Instances
CmbWidth StyleState Source # | |
Defined in Monomer.Core.Style width :: Double -> StyleState Source # | |
CmbWidth SizeReq Source # | |
CmbWidth SpacerCfg Source # | |
CmbWidth SeparatorLineCfg Source # | |
Defined in Monomer.Widgets.Singles.SeparatorLine width :: Double -> SeparatorLineCfg Source # | |
CmbWidth IconCfg Source # | |
CmbWidth (CheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Checkbox width :: Double -> CheckboxCfg s e Source # | |
CmbWidth (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox width :: Double -> LabeledCheckboxCfg s e Source # | |
CmbWidth (SliderCfg s e a) Source # | |
CmbWidth (RadioCfg s e a) Source # | |
CmbWidth (DialCfg s e a) Source # | |
CmbWidth (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio width :: Double -> LabeledRadioCfg s e a Source # |
class CmbHeight t where Source #
Height combinator.
Instances
CmbHeight StyleState Source # | |
Defined in Monomer.Core.Style height :: Double -> StyleState Source # | |
CmbHeight SizeReq Source # | |
class CmbFlexWidth t where Source #
Flex width combinator.
Instances
CmbFlexWidth StyleState Source # | |
Defined in Monomer.Core.Style flexWidth :: Double -> StyleState Source # | |
CmbFlexWidth SizeReq Source # | |
class CmbFlexHeight t where Source #
Flex height combinator.
flexHeight :: Double -> t Source #
Instances
CmbFlexHeight StyleState Source # | |
Defined in Monomer.Core.Style flexHeight :: Double -> StyleState Source # | |
CmbFlexHeight SizeReq Source # | |
Defined in Monomer.Core.Style flexHeight :: Double -> SizeReq Source # |
class CmbMinWidth t where Source #
Min width combinator.
Instances
CmbMinWidth StyleState Source # | |
Defined in Monomer.Core.Style minWidth :: Double -> StyleState Source # | |
CmbMinWidth SizeReq Source # | |
class CmbMinHeight t where Source #
Min height combinator.
Instances
CmbMinHeight StyleState Source # | |
Defined in Monomer.Core.Style minHeight :: Double -> StyleState Source # | |
CmbMinHeight SizeReq Source # | |
class CmbMaxWidth t where Source #
Max width combinator.
Instances
CmbMaxWidth StyleState Source # | |
Defined in Monomer.Core.Style maxWidth :: Double -> StyleState Source # | |
CmbMaxWidth SizeReq Source # | |
CmbMaxWidth TooltipCfg Source # | |
Defined in Monomer.Widgets.Containers.Tooltip maxWidth :: Double -> TooltipCfg Source # |
class CmbMaxHeight t where Source #
Max height combinator.
Instances
CmbMaxHeight StyleState Source # | |
Defined in Monomer.Core.Style maxHeight :: Double -> StyleState Source # | |
CmbMaxHeight SizeReq Source # | |
CmbMaxHeight TooltipCfg Source # | |
Defined in Monomer.Widgets.Containers.Tooltip maxHeight :: Double -> TooltipCfg Source # | |
CmbMaxHeight (DropdownCfg s e a) Source # | |
Defined in Monomer.Widgets.Containers.Dropdown maxHeight :: Double -> DropdownCfg s e a Source # |
class CmbExpandWidth t where Source #
Expand width combinator.
expandWidth :: Double -> t Source #
Instances
CmbExpandWidth StyleState Source # | |
Defined in Monomer.Core.Style expandWidth :: Double -> StyleState Source # | |
CmbExpandWidth SizeReq Source # | |
Defined in Monomer.Core.Style expandWidth :: Double -> SizeReq Source # |
class CmbExpandHeight t where Source #
Expand height combinator.
expandHeight :: Double -> t Source #
Instances
CmbExpandHeight StyleState Source # | |
Defined in Monomer.Core.Style expandHeight :: Double -> StyleState Source # | |
CmbExpandHeight SizeReq Source # | |
Defined in Monomer.Core.Style expandHeight :: Double -> SizeReq Source # |
class CmbRangeWidth t where Source #
Range width combinator.
rangeWidth :: Double -> Double -> t Source #
Instances
CmbRangeWidth StyleState Source # | |
Defined in Monomer.Core.Style rangeWidth :: Double -> Double -> StyleState Source # | |
CmbRangeWidth SizeReq Source # | |
Defined in Monomer.Core.Style |
class CmbRangeHeight t where Source #
Range height combinator.
rangeHeight :: Double -> Double -> t Source #
Instances
CmbRangeHeight StyleState Source # | |
Defined in Monomer.Core.Style 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 sizeReqW :: SizeReq -> StyleState Source # |
class CmbSizeReqH t where Source #
Custom SizeReq height combinator.
Instances
CmbSizeReqH StyleState Source # | |
Defined in Monomer.Core.Style sizeReqH :: SizeReq -> StyleState Source # |
class CmbSizeReqUpdater t where Source #
SizeReq updater. Useful to make modifications to widget SizeReqs without completely overriding them.
Instances
CmbSizeReqUpdater StackCfg Source # | |
Defined in Monomer.Widgets.Containers.Stack | |
CmbSizeReqUpdater GridCfg Source # | |
Defined in Monomer.Widgets.Containers.Grid | |
CmbSizeReqUpdater (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbResizeFactor t where Source #
Resize factor combinator. A value of 0 represents fixed size.
resizeFactor :: Double -> t Source #
Instances
class CmbResizeFactorDim t where Source #
Resize factor combinator for individual w and h components. A value of 0 represents fixed size.
resizeFactorW :: Double -> t Source #
resizeFactorH :: Double -> t Source #
Instances
class CmbStyleBasic t where Source #
Basic style combinator, used mainly infix for widgets as a list.
styleBasic :: t -> [StyleState] -> t infixl 5 Source #
Instances
CmbStyleBasic Style Source # | |
Defined in Monomer.Core.StyleUtil styleBasic :: Style -> [StyleState] -> Style Source # | |
CmbStyleBasic (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil 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.
styleHover :: t -> [StyleState] -> t infixl 5 Source #
Instances
CmbStyleHover Style Source # | |
Defined in Monomer.Core.StyleUtil styleHover :: Style -> [StyleState] -> Style Source # | |
CmbStyleHover (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil 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.
styleFocus :: t -> [StyleState] -> t infixl 5 Source #
Instances
CmbStyleFocus Style Source # | |
Defined in Monomer.Core.StyleUtil styleFocus :: Style -> [StyleState] -> Style Source # | |
CmbStyleFocus (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil 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.
styleFocusHover :: t -> [StyleState] -> t infixl 5 Source #
Instances
CmbStyleFocusHover Style Source # | |
Defined in Monomer.Core.StyleUtil styleFocusHover :: Style -> [StyleState] -> Style Source # | |
CmbStyleFocusHover (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil 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.
styleActive :: t -> [StyleState] -> t infixl 5 Source #
Instances
CmbStyleActive Style Source # | |
Defined in Monomer.Core.StyleUtil styleActive :: Style -> [StyleState] -> Style Source # | |
CmbStyleActive (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil 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.
styleDisabled :: t -> [StyleState] -> t infixl 5 Source #
Instances
CmbStyleDisabled Style Source # | |
Defined in Monomer.Core.StyleUtil styleDisabled :: Style -> [StyleState] -> Style Source # | |
CmbStyleDisabled (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil styleDisabled :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbIgnoreTheme t where Source #
Ignore theme settings and start with blank style.
ignoreTheme :: t Source #
ignoreTheme_ :: Bool -> t Source #
Instances
CmbIgnoreTheme (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label ignoreTheme :: LabelCfg s e Source # ignoreTheme_ :: Bool -> LabelCfg s e Source # | |
CmbIgnoreTheme (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button ignoreTheme :: ButtonCfg s e Source # ignoreTheme_ :: Bool -> ButtonCfg s e Source # |
class CmbBgColor t where Source #
Background color.
Instances
CmbBgColor StyleState Source # | |
Defined in Monomer.Core.Style bgColor :: Color -> StyleState Source # |
class CmbFgColor t where Source #
Foreground color.
Instances
CmbFgColor StyleState Source # | |
Defined in Monomer.Core.Style fgColor :: Color -> StyleState Source # |
class CmbSndColor t where Source #
Secondary color.
Instances
CmbSndColor StyleState Source # | |
Defined in Monomer.Core.Style sndColor :: Color -> StyleState Source # |
class CmbHlColor t where Source #
Highlight color.
Instances
CmbHlColor StyleState Source # | |
Defined in Monomer.Core.Style hlColor :: Color -> StyleState Source # |
class CmbTransparency t where Source #
Transparency level.
transparency :: Double -> t Source #
Instances
CmbTransparency (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image transparency :: Double -> ImageCfg e Source # | |
CmbTransparency (DraggableCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Draggable transparency :: Double -> DraggableCfg s e Source # |
class CmbCursorIcon t where Source #
Cursor icons.
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
class CmbItemBasicStyle t s | t -> s where Source #
Basic style for each item of a list.
itemBasicStyle :: s -> t Source #
Instances
CmbItemBasicStyle (SelectListCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.SelectList itemBasicStyle :: Style -> SelectListCfg s e a Source # | |
CmbItemBasicStyle (DropdownCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.Dropdown itemBasicStyle :: Style -> DropdownCfg s e a Source # |
class CmbItemHoverStyle t s | t -> s where Source #
Hover style for an item of a list.
itemHoverStyle :: s -> t Source #
class CmbItemSelectedStyle t s | t -> s where Source #
Selected style for an item of a list.
itemSelectedStyle :: s -> t Source #
Instances
CmbItemSelectedStyle (SelectListCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.SelectList itemSelectedStyle :: Style -> SelectListCfg s e a Source # | |
CmbItemSelectedStyle (DropdownCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.Dropdown itemSelectedStyle :: Style -> DropdownCfg s e a Source # |
class CmbAlignLeft t where Source #
Align object to the left (not text).
Instances
CmbAlignLeft (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image | |
CmbAlignLeft (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
class CmbAlignCenter t where Source #
Align object to the center (not text).
alignCenter :: t Source #
alignCenter_ :: Bool -> t Source #
Instances
CmbAlignCenter (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image alignCenter :: ImageCfg e Source # alignCenter_ :: Bool -> ImageCfg e Source # | |
CmbAlignCenter (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box alignCenter :: BoxCfg s e Source # alignCenter_ :: Bool -> BoxCfg s e Source # |
class CmbAlignRight t where Source #
Align object to the right (not text).
alignRight :: t Source #
alignRight_ :: Bool -> t Source #
Instances
CmbAlignRight (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image alignRight :: ImageCfg e Source # alignRight_ :: Bool -> ImageCfg e Source # | |
CmbAlignRight (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box alignRight :: BoxCfg s e Source # alignRight_ :: Bool -> BoxCfg s e Source # |
class CmbAlignMiddle t where Source #
Align object to the middle (not text).
alignMiddle :: t Source #
alignMiddle_ :: Bool -> t Source #
Instances
CmbAlignMiddle (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image alignMiddle :: ImageCfg e Source # alignMiddle_ :: Bool -> ImageCfg e Source # | |
CmbAlignMiddle (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box alignMiddle :: BoxCfg s e Source # alignMiddle_ :: Bool -> BoxCfg s e Source # |
class CmbAlignBottom t where Source #
Align object to the bottom (not text).
alignBottom :: t Source #
alignBottom_ :: Bool -> t Source #
Instances
CmbAlignBottom (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image alignBottom :: ImageCfg e Source # alignBottom_ :: Bool -> ImageCfg e Source # | |
CmbAlignBottom (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box alignBottom :: BoxCfg s e Source # alignBottom_ :: Bool -> BoxCfg s e Source # |
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 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 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 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 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 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.
class CmbRadiusTL t where Source #
Set radius for the top left corner.
Instances
CmbRadiusTL Radius Source # | |
CmbRadiusTL StyleState Source # | |
Defined in Monomer.Core.Style 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 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 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 radiusBR :: Double -> StyleState Source # |