Copyright | (c) 2018 Francisco Vallarino |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | fjvallarino@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
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 w s | t -> w s where
- mergeRequired :: (w -> 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 CmbReadOnly t where
- 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 CmbTextLineBreak t where
- textLineBreak :: LineBreak -> 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 CmbFitEither t where
- fitEither :: 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 CmbThumbMinSize t where
- thumbMinSize :: Double -> t
- class CmbShowAlpha t where
- showAlpha :: t
- showAlpha_ :: Bool -> t
- class CmbIgnoreChildrenEvts t where
- ignoreChildrenEvts :: t
- ignoreChildrenEvts_ :: Bool -> t
- class CmbIgnoreParentEvts t where
- ignoreParentEvts :: t
- ignoreParentEvts_ :: Bool -> t
- class CmbOnInit t e | t -> e where
- onInit :: e -> t
- class CmbOnInitReq t s e | t -> s e where
- onInitReq :: WidgetRequest s e -> t
- class CmbOnDispose t e | t -> e where
- onDispose :: e -> t
- class CmbOnDisposeReq t s e | t -> s e where
- onDisposeReq :: WidgetRequest s 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
- styleBasicSet :: t -> [StyleState] -> t
- class CmbStyleHover t where
- styleHover :: t -> [StyleState] -> t
- styleHoverSet :: t -> [StyleState] -> t
- class CmbStyleFocus t where
- styleFocus :: t -> [StyleState] -> t
- styleFocusSet :: t -> [StyleState] -> t
- class CmbStyleFocusHover t where
- styleFocusHover :: t -> [StyleState] -> t
- styleFocusHoverSet :: t -> [StyleState] -> t
- class CmbStyleActive t where
- styleActive :: t -> [StyleState] -> t
- styleActiveSet :: t -> [StyleState] -> t
- class CmbStyleDisabled t where
- styleDisabled :: t -> [StyleState] -> t
- styleDisabledSet :: 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
- class CmbChildSpacing t where
- childSpacing :: t
- childSpacing_ :: Double -> t
Documentation
class CmbMergeRequired t w s | t -> w s where Source #
Given two values, usually model, checks if merge is required for a given widget.
The first parameter usually corresponds to the current WidgetEnv
, the second
to the old valuemodel, and the third to the newmodel.
This is used, for example, by _composite_ and _box_.
Methods
mergeRequired :: (w -> s -> s -> Bool) -> t Source #
Instances
CmbMergeRequired (BoxCfg s e) (WidgetEnv s e) s Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbMergeRequired (DropdownCfg s e a) (WidgetEnv s e) (Seq a) Source # | |
Defined in Monomer.Widgets.Containers.Dropdown Methods mergeRequired :: (WidgetEnv s e -> Seq a -> Seq a -> Bool) -> DropdownCfg s e a Source # | |
CmbMergeRequired (SelectListCfg s e a) (WidgetEnv s e) (Seq a) Source # | |
Defined in Monomer.Widgets.Containers.SelectList Methods mergeRequired :: (WidgetEnv s e -> Seq a -> Seq a -> Bool) -> SelectListCfg s e a Source # | |
CmbMergeRequired (CompositeCfg s e sp ep) (WidgetEnv s e) s Source # | |
Defined in Monomer.Widgets.Composite Methods mergeRequired :: (WidgetEnv s e -> s -> s -> Bool) -> CompositeCfg s e sp ep Source # |
class CmbValidInput t s | t -> s where Source #
Listener for the validation status of a user input field using a lens.
Allows associating a flag to know if the input of a field with validation settings is valid. This can be used with _textField_, _numericField_, _dateField_ and _timeField_.
The flag can be used for styling the component according to the current status.
Beyond styling, its usage is needed for validation purposes. Taking
_numericField_ as an example, one can bind a Double
record field to it and set
a valid range from 0 to 100. When the user inputs 100, the record field will
reflect the correct value. If the user adds a 0 (the numericField showing 1000),
the record field will still have 100 because it's the last valid value. Since
there is not a way of indicating errors when using primitive types (a Double
is just a number), we can rely on the flag to check its validity.
Methods
validInput :: ALens' s Bool -> t Source #
Instances
CmbValidInput (TextFieldCfg s e) s Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods validInput :: ALens' s Bool -> TextFieldCfg s e Source # | |
CmbValidInput (DateFieldCfg s e a) s Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods validInput :: ALens' s Bool -> DateFieldCfg s e a Source # | |
CmbValidInput (NumericFieldCfg s e a) s Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods validInput :: ALens' s Bool -> NumericFieldCfg s e a Source # | |
CmbValidInput (TimeFieldCfg s e a) s Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods validInput :: ALens' s Bool -> TimeFieldCfg s e a Source # |
class CmbValidInputV t e | t -> e where Source #
Listener for the validation status of a user input field using an event handler, avoiding the need of a lens.
Check CmbValidInput
for details.
Methods
validInputV :: (Bool -> e) -> t Source #
Instances
CmbValidInputV (TextFieldCfg s e) e Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods validInputV :: (Bool -> e) -> TextFieldCfg s e Source # | |
CmbValidInputV (DateFieldCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods validInputV :: (Bool -> e) -> DateFieldCfg s e a Source # | |
CmbValidInputV (NumericFieldCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods validInputV :: (Bool -> e) -> NumericFieldCfg s e a Source # | |
CmbValidInputV (TimeFieldCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods validInputV :: (Bool -> e) -> TimeFieldCfg s e a Source # |
class CmbSelectOnFocus t where Source #
Defines whether a widget selects all its content when receiving focus.
Minimal complete definition
Instances
CmbSelectOnFocus (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea | |
CmbSelectOnFocus (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods selectOnFocus :: TextFieldCfg s e Source # selectOnFocus_ :: Bool -> TextFieldCfg s e Source # | |
CmbSelectOnFocus (DateFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods selectOnFocus :: DateFieldCfg s e a Source # selectOnFocus_ :: Bool -> DateFieldCfg s e a Source # | |
CmbSelectOnFocus (NumericFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods selectOnFocus :: NumericFieldCfg s e a Source # selectOnFocus_ :: Bool -> NumericFieldCfg s e a Source # | |
CmbSelectOnFocus (TimeFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods selectOnFocus :: TimeFieldCfg s e a Source # selectOnFocus_ :: Bool -> TimeFieldCfg s e a Source # |
class CmbReadOnly t where Source #
Defines whether a widget prevents the user changing the value. Note that, in contrast to a disabled widget, a read-only widget can still be focused and still allows selecting and copying the value.
Minimal complete definition
Instances
CmbReadOnly (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea | |
CmbReadOnly (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField | |
CmbReadOnly (DateFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.DateField | |
CmbReadOnly (NumericFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods readOnly :: NumericFieldCfg s e a Source # readOnly_ :: Bool -> NumericFieldCfg s e a Source # | |
CmbReadOnly (TimeFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.TimeField |
class CmbResizeOnChange t where Source #
Defines whether a widget changes its size when the model changes.
Minimal complete definition
Instances
CmbResizeOnChange (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods resizeOnChange :: TextFieldCfg s e Source # resizeOnChange_ :: Bool -> TextFieldCfg s e Source # | |
CmbResizeOnChange (DateFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods resizeOnChange :: DateFieldCfg s e a Source # resizeOnChange_ :: Bool -> DateFieldCfg s e a Source # | |
CmbResizeOnChange (NumericFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods resizeOnChange :: NumericFieldCfg s e a Source # resizeOnChange_ :: Bool -> NumericFieldCfg s e a Source # | |
CmbResizeOnChange (TimeFieldCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods resizeOnChange :: TimeFieldCfg s e a Source # resizeOnChange_ :: Bool -> TimeFieldCfg s e a Source # |
class CmbAutoStart t where Source #
Defines whether animation should start automatically.
Minimal complete definition
Instances
CmbAutoStart (FadeCfg e) Source # | |
Defined in Monomer.Widgets.Animation.Fade | |
CmbAutoStart (SlideCfg e) Source # | |
Defined in Monomer.Widgets.Animation.Slide |
class CmbDuration t a | t -> a where Source #
Defines the animation length.
Instances
CmbDuration (FadeCfg e) Millisecond Source # | |
Defined in Monomer.Widgets.Animation.Fade Methods duration :: Millisecond -> FadeCfg e Source # | |
CmbDuration (SlideCfg e) Millisecond Source # | |
Defined in Monomer.Widgets.Animation.Slide Methods duration :: Millisecond -> SlideCfg e Source # |
class CmbTitleCaption t where Source #
Title caption of a widget, usually a dialog.
Methods
titleCaption :: Text -> t Source #
Instances
CmbTitleCaption AlertCfg Source # | |
Defined in Monomer.Widgets.Containers.Alert Methods titleCaption :: Text -> AlertCfg Source # | |
CmbTitleCaption ConfirmCfg Source # | |
Defined in Monomer.Widgets.Containers.Confirm Methods titleCaption :: Text -> ConfirmCfg Source # |
class CmbAcceptCaption t where Source #
Accept caption of a widget, usually a button.
Methods
acceptCaption :: Text -> t Source #
Instances
CmbAcceptCaption ConfirmCfg Source # | |
Defined in Monomer.Widgets.Containers.Confirm Methods acceptCaption :: Text -> ConfirmCfg Source # |
class CmbCancelCaption t where Source #
Cancel caption of a widget, usually a button.
Methods
cancelCaption :: Text -> t Source #
Instances
CmbCancelCaption ConfirmCfg Source # | |
Defined in Monomer.Widgets.Containers.Confirm Methods cancelCaption :: Text -> ConfirmCfg Source # |
class CmbCloseCaption t where Source #
Close caption of a widget, usually a button.
Methods
closeCaption :: Text -> t Source #
Instances
CmbCloseCaption AlertCfg Source # | |
Defined in Monomer.Widgets.Containers.Alert Methods closeCaption :: Text -> AlertCfg Source # |
class CmbMinValue t a | t -> a where Source #
Minimum value of a widget, usually numeric.
Instances
FormattableDate a => CmbMinValue (DateFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods minValue :: a -> DateFieldCfg s e a Source # | |
FormattableNumber a => CmbMinValue (NumericFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods minValue :: a -> NumericFieldCfg s e a Source # | |
FormattableTime a => CmbMinValue (TimeFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods minValue :: a -> TimeFieldCfg s e a Source # |
class CmbMaxValue t a | t -> a where Source #
Maximum value of a widget, usually numeric.
Instances
FormattableDate a => CmbMaxValue (DateFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods maxValue :: a -> DateFieldCfg s e a Source # | |
FormattableNumber a => CmbMaxValue (NumericFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods maxValue :: a -> NumericFieldCfg s e a Source # | |
FormattableTime a => CmbMaxValue (TimeFieldCfg s e a) a Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods maxValue :: a -> TimeFieldCfg s e a Source # |
class CmbDragRate t a | t -> a where Source #
Drag rate of a widget, usually numeric.
Instances
CmbDragRate (DateFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods dragRate :: Double -> DateFieldCfg s e a Source # | |
CmbDragRate (DialCfg s e a) Rational Source # | |
CmbDragRate (NumericFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods dragRate :: Double -> NumericFieldCfg s e a Source # | |
CmbDragRate (SliderCfg s e a) Rational Source # | |
CmbDragRate (TimeFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods dragRate :: Double -> TimeFieldCfg 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 (DateFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods wheelRate :: Double -> DateFieldCfg s e a Source # | |
CmbWheelRate (DialCfg s e a) Rational Source # | |
CmbWheelRate (NumericFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods wheelRate :: Double -> NumericFieldCfg s e a Source # | |
CmbWheelRate (SliderCfg s e a) Rational Source # | |
CmbWheelRate (TimeFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods wheelRate :: Double -> TimeFieldCfg s e a Source # |
class CmbIgnoreEmptyArea t where Source #
Whether to ignore pointer events where no widget exists.
Minimal complete definition
Instances
CmbIgnoreEmptyArea StackCfg Source # | |
Defined in Monomer.Widgets.Containers.Stack | |
CmbIgnoreEmptyArea (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box |
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 Methods decimals :: Int -> NumericFieldCfg s e a Source # |
class CmbMaxLength t where Source #
Max length a widget accepts.
Instances
CmbMaxLength (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea Methods maxLength :: Int -> TextAreaCfg s e Source # | |
CmbMaxLength (TextFieldCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods maxLength :: Int -> TextFieldCfg s e Source # |
class CmbMaxLines t where Source #
Max lines a widget accepts.
Instances
CmbMaxLines (ButtonCfg s e) Source # | |
CmbMaxLines (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink Methods maxLines :: Int -> ExternalLinkCfg s e Source # | |
CmbMaxLines (LabelCfg s e) Source # | |
CmbMaxLines (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods maxLines :: Int -> LabeledCheckboxCfg s e Source # | |
CmbMaxLines (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea Methods maxLines :: Int -> TextAreaCfg s e Source # | |
CmbMaxLines (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods maxLines :: Int -> LabeledRadioCfg s e a Source # | |
CmbMaxLines (OptionButtonCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods maxLines :: Int -> OptionButtonCfg s e a Source # |
class CmbAcceptTab t where Source #
Whether a widget accepts tab key.
Minimal complete definition
Instances
CmbAcceptTab (TextAreaCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.TextArea |
class CmbMultiline t where Source #
Whether a text based widget is multiline.
Minimal complete definition
Instances
CmbMultiline (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button | |
CmbMultiline (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink | |
CmbMultiline (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label | |
CmbMultiline (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods multiline :: LabeledCheckboxCfg s e Source # multiline_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbMultiline (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods multiline :: LabeledRadioCfg s e a Source # multiline_ :: Bool -> LabeledRadioCfg s e a Source # | |
CmbMultiline (OptionButtonCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods multiline :: OptionButtonCfg s e a Source # multiline_ :: Bool -> OptionButtonCfg s e a Source # |
class CmbEllipsis t where Source #
Whether to use ellipsis or not.
Minimal complete definition
Instances
CmbEllipsis (ButtonCfg s e) Source # | |
CmbEllipsis (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink | |
CmbEllipsis (LabelCfg s e) Source # | |
CmbEllipsis (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods ellipsis :: LabeledCheckboxCfg s e Source # ellipsis_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbEllipsis (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods ellipsis :: LabeledRadioCfg s e a Source # ellipsis_ :: Bool -> LabeledRadioCfg s e a Source # | |
CmbEllipsis (OptionButtonCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods ellipsis :: OptionButtonCfg s e a Source # ellipsis_ :: Bool -> OptionButtonCfg s e a Source # |
class CmbTrimSpaces t where Source #
Whether to trim spaces or not.
Minimal complete definition
Instances
CmbTrimSpaces (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button | |
CmbTrimSpaces (ExternalLinkCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ExternalLink Methods trimSpaces :: ExternalLinkCfg s e Source # trimSpaces_ :: Bool -> ExternalLinkCfg s e Source # | |
CmbTrimSpaces (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label | |
CmbTrimSpaces (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods trimSpaces :: LabeledCheckboxCfg s e Source # trimSpaces_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTrimSpaces (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods trimSpaces :: LabeledRadioCfg s e a Source # trimSpaces_ :: Bool -> LabeledRadioCfg s e a Source # | |
CmbTrimSpaces (OptionButtonCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods trimSpaces :: OptionButtonCfg s e a Source # trimSpaces_ :: Bool -> OptionButtonCfg s e a Source # |
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 #
Instances
CmbPlaceholder (TextFieldCfg s e) Text Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods placeholder :: Text -> TextFieldCfg s e Source # |
class CmbCaretWidth t a | t -> a where Source #
Width of the caret in a text widget.
Methods
caretWidth :: a -> t Source #
Instances
CmbCaretWidth (TextAreaCfg s e) Double Source # | |
Defined in Monomer.Widgets.Singles.TextArea Methods caretWidth :: Double -> TextAreaCfg s e Source # | |
CmbCaretWidth (TextFieldCfg s e) Double Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods caretWidth :: Double -> TextFieldCfg s e Source # | |
CmbCaretWidth (DateFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods caretWidth :: Double -> DateFieldCfg s e a Source # | |
CmbCaretWidth (NumericFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods caretWidth :: Double -> NumericFieldCfg s e a Source # | |
CmbCaretWidth (TimeFieldCfg s e a) Double Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods caretWidth :: Double -> TimeFieldCfg s e a Source # |
class CmbCaretMs t a | t -> a where Source #
Blink period of the caret in a text widget.
Instances
CmbCaretMs (TextAreaCfg s e) Millisecond Source # | |
Defined in Monomer.Widgets.Singles.TextArea Methods caretMs :: Millisecond -> TextAreaCfg s e Source # | |
CmbCaretMs (TextFieldCfg s e) Millisecond Source # | |
Defined in Monomer.Widgets.Singles.TextField Methods caretMs :: Millisecond -> TextFieldCfg s e Source # | |
CmbCaretMs (DateFieldCfg s e a) Millisecond Source # | |
Defined in Monomer.Widgets.Singles.DateField Methods caretMs :: Millisecond -> DateFieldCfg s e a Source # | |
CmbCaretMs (NumericFieldCfg s e a) Millisecond Source # | |
Defined in Monomer.Widgets.Singles.NumericField Methods caretMs :: Millisecond -> NumericFieldCfg s e a Source # | |
CmbCaretMs (TimeFieldCfg s e a) Millisecond Source # | |
Defined in Monomer.Widgets.Singles.TimeField Methods caretMs :: Millisecond -> TimeFieldCfg s e a Source # |
class CmbTextFont t where Source #
Text font.
Instances
CmbTextFont StyleState Source # | |
Defined in Monomer.Core.Style Methods textFont :: Font -> StyleState Source # | |
CmbTextFont TextStyle Source # | |
class CmbTextSize t where Source #
Text size.
Instances
CmbTextSize StyleState Source # | |
Defined in Monomer.Core.Style Methods textSize :: Double -> StyleState Source # | |
CmbTextSize TextStyle Source # | |
class CmbTextSpaceH t where Source #
Horizontal text spacing.
Methods
textSpaceH :: Double -> t Source #
Instances
CmbTextSpaceH StyleState Source # | |
Defined in Monomer.Core.Style Methods textSpaceH :: Double -> StyleState Source # | |
CmbTextSpaceH TextStyle Source # | |
Defined in Monomer.Core.Style Methods textSpaceH :: Double -> TextStyle Source # |
class CmbTextSpaceV t where Source #
Vertical text spacing.
Methods
textSpaceV :: Double -> t Source #
Instances
CmbTextSpaceV StyleState Source # | |
Defined in Monomer.Core.Style Methods textSpaceV :: Double -> StyleState Source # | |
CmbTextSpaceV TextStyle Source # | |
Defined in Monomer.Core.Style Methods textSpaceV :: Double -> TextStyle Source # |
class CmbTextColor t where Source #
Text color.
Instances
CmbTextColor StyleState Source # | |
Defined in Monomer.Core.Style Methods textColor :: Color -> StyleState Source # | |
CmbTextColor TextStyle Source # | |
class CmbTextLeft t where Source #
Align text to the left.
Minimal complete definition
Instances
CmbTextLeft StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextLeft TextStyle Source # | |
CmbTextLeft (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods textLeft :: LabeledCheckboxCfg s e Source # textLeft_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextLeft (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods textLeft :: LabeledRadioCfg s e a Source # textLeft_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextCenter t where Source #
Align text to the center.
Minimal complete definition
Instances
CmbTextCenter StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextCenter TextStyle Source # | |
Defined in Monomer.Core.Style |
class CmbTextRight t where Source #
Align text to the right.
Minimal complete definition
Instances
CmbTextRight StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextRight TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextRight (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods textRight :: LabeledCheckboxCfg s e Source # textRight_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextRight (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods textRight :: LabeledRadioCfg s e a Source # textRight_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextTop t where Source #
Align text to the top.
Minimal complete definition
Instances
CmbTextTop StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextTop TextStyle Source # | |
CmbTextTop (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods textTop :: LabeledCheckboxCfg s e Source # textTop_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextTop (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio |
class CmbTextMiddle t where Source #
Align text to the vertical middle based on the line height.
Minimal complete definition
Instances
CmbTextMiddle StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextMiddle TextStyle 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 StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextAscender TextStyle 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 StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextLowerX TextStyle Source # | |
Defined in Monomer.Core.Style |
class CmbTextBottom t where Source #
Align text to the bottom.
Minimal complete definition
Instances
CmbTextBottom StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextBottom TextStyle Source # | |
Defined in Monomer.Core.Style | |
CmbTextBottom (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods textBottom :: LabeledCheckboxCfg s e Source # textBottom_ :: Bool -> LabeledCheckboxCfg s e Source # | |
CmbTextBottom (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods textBottom :: LabeledRadioCfg s e a Source # textBottom_ :: Bool -> LabeledRadioCfg s e a Source # |
class CmbTextBaseline t where Source #
Align text to the baseline.
Minimal complete definition
Instances
CmbTextBaseline StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextBaseline TextStyle Source # | |
Defined in Monomer.Core.Style |
class CmbTextUnderline t where Source #
Display a line under the text.
Minimal complete definition
Instances
CmbTextUnderline StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextUnderline TextStyle Source # | |
Defined in Monomer.Core.Style |
class CmbTextOverline t where Source #
Display a line above the text.
Minimal complete definition
Instances
CmbTextOverline StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextOverline TextStyle Source # | |
Defined in Monomer.Core.Style |
class CmbTextThroughline t where Source #
Display a line over the text.
Minimal complete definition
Instances
CmbTextThroughline StyleState Source # | |
Defined in Monomer.Core.Style | |
CmbTextThroughline TextStyle Source # | |
Defined in Monomer.Core.Style |
class CmbTextLineBreak t where Source #
How to break texts into lines.
Methods
textLineBreak :: LineBreak -> t Source #
Instances
CmbTextLineBreak StyleState Source # | |
Defined in Monomer.Core.Style Methods textLineBreak :: LineBreak -> StyleState Source # | |
CmbTextLineBreak TextStyle Source # | |
Defined in Monomer.Core.Style Methods textLineBreak :: LineBreak -> TextStyle Source # |
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 CmbFitEither t where Source #
Either fitWidth or fitHeight such that image does not overflow viewport
Instances
CmbFitEither (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image |
class CmbImageNearest t where Source #
Applies nearest filtering when stretching an image.
Methods
imageNearest :: t Source #
Instances
CmbImageNearest (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image Methods imageNearest :: ImageCfg e Source # |
class CmbImageRepeatX t where Source #
Applies horizontal repetition when stretching an image.
Methods
imageRepeatX :: t Source #
Instances
CmbImageRepeatX (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image Methods imageRepeatX :: ImageCfg e Source # |
class CmbImageRepeatY t where Source #
Applies vertical repetition when stretching an image.
Methods
imageRepeatY :: t Source #
Instances
CmbImageRepeatY (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image Methods 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.
Methods
barHoverColor :: Color -> t Source #
Instances
CmbBarHoverColor (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll Methods 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.
Methods
thumbColor :: Color -> t Source #
Instances
CmbThumbColor (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll Methods thumbColor :: Color -> ScrollCfg s e Source # |
class CmbThumbHoverColor t where Source #
The hover color of a thumb, for example in a scroll.
Methods
thumbHoverColor :: Color -> t Source #
Instances
CmbThumbHoverColor (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll Methods 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.
Methods
thumbFactor :: Double -> t Source #
Instances
CmbThumbFactor (SliderCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.Slider Methods thumbFactor :: Double -> SliderCfg s e a Source # |
class CmbThumbRadius t where Source #
The radius of a thumb's rect, for example in a scroll.
Methods
thumbRadius :: Double -> t Source #
Instances
CmbThumbRadius (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll Methods thumbRadius :: Double -> ScrollCfg s e Source # |
class CmbThumbVisible t where Source #
Whether the thumb is visible, for example in a scroll.
Minimal complete definition
Instances
CmbThumbVisible (SliderCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.Slider |
class CmbThumbWidth t where Source #
The width of a thumb, for example in a scroll.
Methods
thumbWidth :: Double -> t Source #
Instances
CmbThumbWidth (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll Methods thumbWidth :: Double -> ScrollCfg s e Source # |
class CmbThumbMinSize t where Source #
The minimum size of a thumb, for example in a scroll.
Methods
thumbMinSize :: Double -> t Source #
Instances
CmbThumbMinSize (ScrollCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Scroll Methods thumbMinSize :: Double -> ScrollCfg s e Source # |
class CmbShowAlpha t where Source #
Whether to show an alpha channel, for instance in color selector.
Minimal complete definition
Instances
CmbShowAlpha (ColorPickerCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.ColorPicker |
class CmbIgnoreChildrenEvts t where Source #
Whether to ignore children events.
By default low-level events (keyboard, mouse, clipboard, etc) traverse the whole branch where the target widget is located in the widget tree, giving the chance to each widget along the line to respond to the event.
In some cases it is desirable to restrict which widgets can handle an event. Two
different WidgetRequest
s, which can be returned during event handling, exist
for this:
IgnoreChildrenEvents
: parent widgets always have the priority. If a widget returns thisWidgetRequest
during event handling, its children widgets response will be ignored. For example, the _keystroke_ widget can be configured to return this when a keystroke combination matches.IgnoreParentEvents
: if no parent widget requestedIgnoreChildrenEvents
, a widget can respond withIgnoreParentEvents
to have its response being the only one taking place. This is used, for example, by the _textArea_ widget to handle the tab key; without this, the default handler would pass focus to the next widget down the line.
Some of the stock widgets allow configuring this behavior (e.g, keystroke and button).
Minimal complete definition
Instances
CmbIgnoreChildrenEvts KeystrokeCfg Source # | |
Defined in Monomer.Widgets.Containers.Keystroke Methods |
class CmbIgnoreParentEvts t where Source #
Whether to ignore parent events. Check CmbIgnoreChildrenEvts
.
Minimal complete definition
Instances
CmbIgnoreParentEvts (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button Methods ignoreParentEvts :: ButtonCfg s e Source # ignoreParentEvts_ :: Bool -> ButtonCfg s e Source # |
class CmbOnInit t e | t -> e where Source #
On init event.
Instances
WidgetEvent e => CmbOnInit (CompositeCfg s e sp ep) e Source # | |
Defined in Monomer.Widgets.Composite Methods onInit :: e -> CompositeCfg s e sp ep Source # |
class CmbOnInitReq t s e | t -> s e where Source #
On init WidgetRequest.
Methods
onInitReq :: WidgetRequest s e -> t Source #
Instances
CmbOnInitReq (CompositeCfg s e sp ep) s e Source # | |
Defined in Monomer.Widgets.Composite Methods onInitReq :: WidgetRequest s e -> CompositeCfg s e sp ep Source # |
class CmbOnDispose t e | t -> e where Source #
On dispose event.
Instances
WidgetEvent e => CmbOnDispose (CompositeCfg s e sp ep) e Source # | |
Defined in Monomer.Widgets.Composite Methods onDispose :: e -> CompositeCfg s e sp ep Source # |
class CmbOnDisposeReq t s e | t -> s e where Source #
On dispose WidgetRequest.
Methods
onDisposeReq :: WidgetRequest s e -> t Source #
Instances
CmbOnDisposeReq (CompositeCfg s e sp ep) s e Source # | |
Defined in Monomer.Widgets.Composite Methods onDisposeReq :: WidgetRequest s 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
class CmbOnFocusReq t s e a | t -> s e a where Source #
On focus WidgetRequest.
Methods
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.
Methods
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.
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 | |
WidgetEvent e => CmbOnClick (ButtonCfg s e) e Source # | |
Defined in Monomer.Widgets.Singles.Button | |
WidgetEvent e => CmbOnClick (OptionButtonCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods onClick :: e -> OptionButtonCfg s e a Source # | |
WidgetEvent e => CmbOnClick (RadioCfg s e a) e Source # | |
Defined in Monomer.Widgets.Singles.Radio |
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 # | |
CmbOnClickReq (ButtonCfg s e) s e Source # | |
Defined in Monomer.Widgets.Singles.Button Methods onClickReq :: WidgetRequest s e -> ButtonCfg s e Source # | |
CmbOnClickReq (OptionButtonCfg s e a) s e Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods onClickReq :: WidgetRequest s e -> OptionButtonCfg s e a Source # | |
CmbOnClickReq (RadioCfg s e a) s e Source # | |
Defined in Monomer.Widgets.Singles.Radio Methods onClickReq :: WidgetRequest s e -> RadioCfg s e a 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
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 (DropdownCfg s e a) e a Source # | |
Defined in Monomer.Widgets.Containers.Dropdown Methods onChangeIdx :: (Int -> a -> e) -> DropdownCfg s e a Source # | |
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 # |
class CmbOnChangeReq t s e a | t -> s e a where Source #
On change WidgetRequest.
Methods
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.
Methods
onChangeIdxReq :: (Int -> a -> WidgetRequest s e) -> t Source #
Instances
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 # | |
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 # |
class CmbOnLoadError t e a | t -> e a where Source #
On load error event.
Methods
onLoadError :: (a -> e) -> t Source #
Instances
CmbOnLoadError (ImageCfg e) e ImageLoadError Source # | |
Defined in Monomer.Widgets.Singles.Image Methods onLoadError :: (ImageLoadError -> e) -> ImageCfg e Source # |
class CmbOnFinished t e | t -> e where Source #
On finished event.
Methods
onFinished :: e -> t Source #
Instances
CmbOnFinished (FadeCfg e) e Source # | |
Defined in Monomer.Widgets.Animation.Fade Methods onFinished :: e -> FadeCfg e Source # | |
CmbOnFinished (SlideCfg e) e Source # | |
Defined in Monomer.Widgets.Animation.Slide Methods onFinished :: e -> SlideCfg e Source # |
class CmbWidth t where Source #
Width combinator.
Instances
CmbWidth SizeReq Source # | |
CmbWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods width :: Double -> StyleState Source # | |
CmbWidth IconCfg Source # | |
CmbWidth SeparatorLineCfg Source # | |
Defined in Monomer.Widgets.Singles.SeparatorLine Methods width :: Double -> SeparatorLineCfg Source # | |
CmbWidth SpacerCfg Source # | |
CmbWidth (CheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Checkbox Methods width :: Double -> CheckboxCfg s e Source # | |
CmbWidth (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods width :: Double -> LabeledCheckboxCfg s e Source # | |
CmbWidth (DialCfg s e a) Source # | |
CmbWidth (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods width :: Double -> LabeledRadioCfg s e a Source # | |
CmbWidth (RadioCfg s e a) Source # | |
CmbWidth (SliderCfg s e a) Source # | |
class CmbHeight t where Source #
Height combinator.
Instances
CmbHeight SizeReq Source # | |
CmbHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods height :: Double -> StyleState Source # |
class CmbFlexWidth t where Source #
Flex width combinator.
Instances
CmbFlexWidth SizeReq Source # | |
CmbFlexWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods flexWidth :: Double -> StyleState Source # |
class CmbFlexHeight t where Source #
Flex height combinator.
Methods
flexHeight :: Double -> t Source #
Instances
CmbFlexHeight SizeReq Source # | |
Defined in Monomer.Core.Style Methods flexHeight :: Double -> SizeReq Source # | |
CmbFlexHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods flexHeight :: Double -> StyleState Source # |
class CmbMinWidth t where Source #
Min width combinator.
Instances
CmbMinWidth SizeReq Source # | |
CmbMinWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods minWidth :: Double -> StyleState Source # |
class CmbMinHeight t where Source #
Min height combinator.
Instances
CmbMinHeight SizeReq Source # | |
CmbMinHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods minHeight :: Double -> StyleState Source # |
class CmbMaxWidth t where Source #
Max width combinator.
Instances
CmbMaxWidth SizeReq Source # | |
CmbMaxWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods maxWidth :: Double -> StyleState Source # | |
CmbMaxWidth TooltipCfg Source # | |
Defined in Monomer.Widgets.Containers.Tooltip Methods maxWidth :: Double -> TooltipCfg Source # |
class CmbMaxHeight t where Source #
Max height combinator.
Instances
CmbMaxHeight SizeReq Source # | |
CmbMaxHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods maxHeight :: Double -> StyleState Source # | |
CmbMaxHeight TooltipCfg Source # | |
Defined in Monomer.Widgets.Containers.Tooltip Methods maxHeight :: Double -> TooltipCfg 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 SizeReq Source # | |
Defined in Monomer.Core.Style Methods expandWidth :: Double -> SizeReq Source # | |
CmbExpandWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods expandWidth :: Double -> StyleState Source # |
class CmbExpandHeight t where Source #
Expand height combinator.
Methods
expandHeight :: Double -> t Source #
Instances
CmbExpandHeight SizeReq Source # | |
Defined in Monomer.Core.Style Methods expandHeight :: Double -> SizeReq Source # | |
CmbExpandHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods expandHeight :: Double -> StyleState Source # |
class CmbRangeWidth t where Source #
Range width combinator.
Methods
rangeWidth :: Double -> Double -> t Source #
Instances
CmbRangeWidth SizeReq Source # | |
Defined in Monomer.Core.Style | |
CmbRangeWidth StyleState Source # | |
Defined in Monomer.Core.Style Methods rangeWidth :: Double -> Double -> StyleState Source # |
class CmbRangeHeight t where Source #
Range height combinator.
Methods
rangeHeight :: Double -> Double -> t Source #
Instances
CmbRangeHeight SizeReq Source # | |
Defined in Monomer.Core.Style | |
CmbRangeHeight StyleState Source # | |
Defined in Monomer.Core.Style Methods rangeHeight :: Double -> Double -> StyleState Source # |
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 GridCfg Source # | |
Defined in Monomer.Widgets.Containers.Grid | |
CmbSizeReqUpdater StackCfg Source # | |
Defined in Monomer.Widgets.Containers.Stack | |
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.
Methods
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.
Instances
class CmbStyleBasic t where Source #
Basic style combinator, mainly used infix with widgets.
Represents the default style of a widget. It serves as the base for all the other style states when an attribute is not overriden.
Methods
styleBasic :: t -> [StyleState] -> t infixl 5 Source #
Merges the new basic style states with the existing ones.
styleBasicSet :: t -> [StyleState] -> t infixl 5 Source #
Sets the new basic style states overriding the existing ones.
Instances
CmbStyleBasic Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleBasic :: Style -> [StyleState] -> Style Source # styleBasicSet :: Style -> [StyleState] -> Style Source # | |
CmbStyleBasic (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleBasic :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # styleBasicSet :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbStyleHover t where Source #
Hover style combinator, mainly used infix with widgets.
Used when the widget is hovered with a pointing device.
Methods
styleHover :: t -> [StyleState] -> t infixl 5 Source #
Merges the new hover style states with the existing ones.
styleHoverSet :: t -> [StyleState] -> t infixl 5 Source #
Sets the new hover style states overriding the existing ones.
Instances
CmbStyleHover Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleHover :: Style -> [StyleState] -> Style Source # styleHoverSet :: Style -> [StyleState] -> Style Source # | |
CmbStyleHover (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleHover :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # styleHoverSet :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbStyleFocus t where Source #
Focus style combinator, mainly used infix with widgets.
Used when the widget has keyboard focus.
Methods
styleFocus :: t -> [StyleState] -> t infixl 5 Source #
Merges the new focus style states with the existing ones.
styleFocusSet :: t -> [StyleState] -> t infixl 5 Source #
Sets the new focus style states overriding the existing ones.
Instances
CmbStyleFocus Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocus :: Style -> [StyleState] -> Style Source # styleFocusSet :: Style -> [StyleState] -> Style Source # | |
CmbStyleFocus (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocus :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # styleFocusSet :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbStyleFocusHover t where Source #
Focus Hover style combinator, mainly used infix with widgets.
Used when the widget is both focused and hovered. In this situation the attributes defined in focus and hover will be combined, with focus attributes taking precedence. This style state allows for better control in cases when the combination of focus and hover styles do not match expectations.
Methods
styleFocusHover :: t -> [StyleState] -> t infixl 5 Source #
Merges the new focus hover style states with the existing ones.
styleFocusHoverSet :: t -> [StyleState] -> t infixl 5 Source #
Sets the new focus hover style states overriding the existing ones.
Instances
CmbStyleFocusHover Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocusHover :: Style -> [StyleState] -> Style Source # styleFocusHoverSet :: Style -> [StyleState] -> Style Source # | |
CmbStyleFocusHover (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleFocusHover :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # styleFocusHoverSet :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbStyleActive t where Source #
Active style combinator, mainly used infix with widgets.
Used when a mouse press was started in the widget and the pointer is inside its boundaries.
Methods
styleActive :: t -> [StyleState] -> t infixl 5 Source #
Merges the new active style states with the existing ones.
styleActiveSet :: t -> [StyleState] -> t infixl 5 Source #
Sets the new active style states overriding the existing ones.
Instances
CmbStyleActive Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleActive :: Style -> [StyleState] -> Style Source # styleActiveSet :: Style -> [StyleState] -> Style Source # | |
CmbStyleActive (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleActive :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # styleActiveSet :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # |
class CmbStyleDisabled t where Source #
Disabled style combinator, mainly used infix with widgets.
Used when the _nodeEnabled_ attribute has been set to False.
Methods
styleDisabled :: t -> [StyleState] -> t infixl 5 Source #
Merges the new disabled style states with the existing ones.
styleDisabledSet :: t -> [StyleState] -> t infixl 5 Source #
Sets the new disabled style states overriding the existing ones.
Instances
CmbStyleDisabled Style Source # | |
Defined in Monomer.Core.StyleUtil Methods styleDisabled :: Style -> [StyleState] -> Style Source # styleDisabledSet :: Style -> [StyleState] -> Style Source # | |
CmbStyleDisabled (WidgetNode s e) Source # | |
Defined in Monomer.Core.StyleUtil Methods styleDisabled :: WidgetNode s e -> [StyleState] -> WidgetNode s e Source # styleDisabledSet :: 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 (ButtonCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Button | |
CmbIgnoreTheme (LabelCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.Label | |
CmbIgnoreTheme (OptionButtonCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.OptionButton Methods ignoreTheme :: OptionButtonCfg s e a Source # ignoreTheme_ :: Bool -> OptionButtonCfg s e a Source # |
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 #
Instances
CmbTransparency (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image Methods transparency :: Double -> ImageCfg e Source # | |
CmbTransparency (DraggableCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Draggable Methods transparency :: Double -> DraggableCfg s e 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 (DropdownCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.Dropdown Methods itemBasicStyle :: Style -> DropdownCfg s e a Source # | |
CmbItemBasicStyle (SelectListCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.SelectList Methods itemBasicStyle :: Style -> SelectListCfg 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 (DropdownCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.Dropdown Methods itemSelectedStyle :: Style -> DropdownCfg s e a Source # | |
CmbItemSelectedStyle (SelectListCfg s e a) Style Source # | |
Defined in Monomer.Widgets.Containers.SelectList Methods itemSelectedStyle :: Style -> SelectListCfg s e a Source # |
class CmbAlignLeft t where Source #
Align object to the left (not text).
Minimal complete definition
Instances
CmbAlignLeft BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow | |
CmbAlignLeft (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image | |
CmbAlignLeft (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbAlignLeft (PopupCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Popup |
class CmbAlignCenter t where Source #
Align object to the center (not text).
Minimal complete definition
Instances
CmbAlignCenter BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow | |
CmbAlignCenter (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image | |
CmbAlignCenter (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbAlignCenter (PopupCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Popup |
class CmbAlignRight t where Source #
Align object to the right (not text).
Minimal complete definition
Instances
CmbAlignRight BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow | |
CmbAlignRight (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image | |
CmbAlignRight (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbAlignRight (PopupCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Popup |
class CmbAlignTop t where Source #
Align object to the top (not text).
Minimal complete definition
Instances
CmbAlignTop BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow | |
CmbAlignTop (ImageCfg e) Source # | |
CmbAlignTop (BoxCfg s e) Source # | |
CmbAlignTop (PopupCfg s e) Source # | |
class CmbAlignMiddle t where Source #
Align object to the middle (not text).
Minimal complete definition
Instances
CmbAlignMiddle BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow | |
CmbAlignMiddle (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image | |
CmbAlignMiddle (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbAlignMiddle (PopupCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Popup |
class CmbAlignBottom t where Source #
Align object to the bottom (not text).
Minimal complete definition
Instances
CmbAlignBottom BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow | |
CmbAlignBottom (ImageCfg e) Source # | |
Defined in Monomer.Widgets.Singles.Image | |
CmbAlignBottom (BoxCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Box | |
CmbAlignBottom (PopupCfg s e) Source # | |
Defined in Monomer.Widgets.Containers.Popup |
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 # | |
CmbRadius BoxShadowCfg Source # | |
Defined in Monomer.Widgets.Containers.BoxShadow Methods radius :: Double -> BoxShadowCfg Source # | |
CmbRadius (SliderCfg s e a) 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 # |
class CmbChildSpacing t where Source #
Set the spacing between the children of the container.
Minimal complete definition
Methods
childSpacing :: t Source #
Set the spacing to the default amount (may vary by container).
childSpacing_ :: Double -> t Source #
Set the spacing to the specified amount.
Instances
CmbChildSpacing GridCfg Source # | |
Defined in Monomer.Widgets.Containers.Grid | |
CmbChildSpacing StackCfg Source # | |
Defined in Monomer.Widgets.Containers.Stack | |
CmbChildSpacing (LabeledCheckboxCfg s e) Source # | |
Defined in Monomer.Widgets.Singles.LabeledCheckbox Methods childSpacing :: LabeledCheckboxCfg s e Source # childSpacing_ :: Double -> LabeledCheckboxCfg s e Source # | |
CmbChildSpacing (LabeledRadioCfg s e a) Source # | |
Defined in Monomer.Widgets.Singles.LabeledRadio Methods childSpacing :: LabeledRadioCfg s e a Source # childSpacing_ :: Double -> LabeledRadioCfg s e a Source # |