{-# LANGUAGE FunctionalDependencies #-}
module Monomer.Core.Combinators where
import Control.Lens (ALens')
import Data.Text (Text)
import Monomer.Common
import Monomer.Core.StyleTypes
import Monomer.Core.WidgetTypes
import Monomer.Event.Types
import Monomer.Graphics.Types
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
forall t. CmbSelectOnFocus t => Bool -> t
selectOnFocus_ Bool
True
selectOnFocus_ :: Bool -> t
class CmbResizeOnChange t where
resizeOnChange :: t
resizeOnChange = Bool -> t
forall t. CmbResizeOnChange t => Bool -> t
resizeOnChange_ Bool
True
resizeOnChange_ :: Bool -> t
class CmbAutoStart t where
autoStart :: t
autoStart = Bool -> t
forall t. CmbAutoStart t => Bool -> t
autoStart_ Bool
True
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
forall t. CmbIgnoreEmptyArea t => Bool -> t
ignoreEmptyArea_ Bool
True
ignoreEmptyArea_ :: Bool -> t
class CmbDecimals t where
decimals :: Int -> t
class CmbMaxLength t where
maxLength :: Int -> t
class CmbMaxLines t where
maxLines :: Int -> t
class CmbAcceptTab t where
acceptTab :: t
acceptTab = Bool -> t
forall t. CmbAcceptTab t => Bool -> t
acceptTab_ Bool
True
acceptTab_ :: Bool -> t
class CmbMultiline t where
multiline :: t
multiline = Bool -> t
forall t. CmbMultiline t => Bool -> t
multiline_ Bool
True
multiline_ :: Bool -> t
class CmbEllipsis t where
ellipsis :: t
ellipsis = Bool -> t
forall t. CmbEllipsis t => Bool -> t
ellipsis_ Bool
True
ellipsis_ :: Bool -> t
class CmbTrimSpaces t where
trimSpaces :: t
trimSpaces = Bool -> t
forall t. CmbTrimSpaces t => Bool -> t
trimSpaces_ Bool
True
trimSpaces_ :: Bool -> t
class CmbSelectOnBlur t where
selectOnBlur :: t
selectOnBlur = Bool -> t
forall t. CmbSelectOnBlur t => Bool -> t
selectOnBlur_ Bool
True
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
textFont :: Font -> t
class CmbTextSize t where
textSize :: Double -> t
class CmbTextSpaceH t where
textSpaceH :: Double -> t
class CmbTextSpaceV t where
textSpaceV :: Double -> t
class CmbTextColor t where
textColor :: Color -> t
class CmbTextLeft t where
textLeft :: t
textLeft = Bool -> t
forall t. CmbTextLeft t => Bool -> t
textLeft_ Bool
True
textLeft_ :: Bool -> t
class CmbTextCenter t where
textCenter :: t
textCenter = Bool -> t
forall t. CmbTextCenter t => Bool -> t
textCenter_ Bool
True
textCenter_ :: Bool -> t
class CmbTextRight t where
textRight :: t
textRight = Bool -> t
forall t. CmbTextRight t => Bool -> t
textRight_ Bool
True
textRight_ :: Bool -> t
class CmbTextTop t where
textTop :: t
textTop = Bool -> t
forall t. CmbTextTop t => Bool -> t
textTop_ Bool
True
textTop_ :: Bool -> t
class CmbTextMiddle t where
textMiddle :: t
textMiddle = Bool -> t
forall t. CmbTextMiddle t => Bool -> t
textMiddle_ Bool
True
textMiddle_ :: Bool -> t
class CmbTextAscender t where
textAscender :: t
textAscender = Bool -> t
forall t. CmbTextAscender t => Bool -> t
textAscender_ Bool
True
textAscender_ :: Bool -> t
class CmbTextLowerX t where
textLowerX :: t
textLowerX = Bool -> t
forall t. CmbTextLowerX t => Bool -> t
textLowerX_ Bool
True
textLowerX_ :: Bool -> t
class CmbTextBottom t where
textBottom :: t
textBottom = Bool -> t
forall t. CmbTextBottom t => Bool -> t
textBottom_ Bool
True
textBottom_ :: Bool -> t
class CmbTextBaseline t where
textBaseline :: t
textBaseline = Bool -> t
forall t. CmbTextBaseline t => Bool -> t
textBaseline_ Bool
True
textBaseline_ :: Bool -> t
class CmbTextUnderline t where
textUnderline :: t
textUnderline = Bool -> t
forall t. CmbTextUnderline t => Bool -> t
textUnderline_ Bool
True
textUnderline_ :: Bool -> t
class CmbTextOverline t where
textOverline :: t
textOverline = Bool -> t
forall t. CmbTextOverline t => Bool -> t
textOverline_ Bool
True
textOverline_ :: Bool -> t
class CmbTextThroughline t where
textThroughline :: t
textThroughline = Bool -> t
forall t. CmbTextThroughline t => Bool -> t
textThroughline_ Bool
True
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
barColor :: Color -> t
class CmbBarHoverColor t where
barHoverColor :: Color -> t
class CmbBarWidth t where
barWidth :: Double -> t
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
forall t. CmbThumbVisible t => Bool -> t
thumbVisible_ Bool
True
thumbVisible_ :: Bool -> t
class CmbThumbWidth t where
thumbWidth :: Double -> t
class CmbShowAlpha t where
showAlpha :: t
showAlpha = Bool -> t
forall t. CmbShowAlpha t => Bool -> t
showAlpha_ Bool
True
showAlpha_ :: Bool -> t
class CmbIgnoreChildrenEvts t where
ignoreChildrenEvts :: t
ignoreChildrenEvts = Bool -> t
forall t. CmbIgnoreChildrenEvts t => Bool -> t
ignoreChildrenEvts_ Bool
True
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
width :: Double -> t
class CmbHeight t where
height :: Double -> t
class CmbFlexWidth t where
flexWidth :: Double -> t
class CmbFlexHeight t where
flexHeight :: Double -> t
class CmbMinWidth t where
minWidth :: Double -> t
class CmbMinHeight t where
minHeight :: Double -> t
class CmbMaxWidth t where
maxWidth :: Double -> t
class CmbMaxHeight t where
maxHeight :: Double -> t
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
sizeReqW :: SizeReq -> t
class CmbSizeReqH t where
sizeReqH :: SizeReq -> t
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
infixl 5 `styleBasic`
infixl 5 `styleHover`
infixl 5 `styleFocus`
infixl 5 `styleFocusHover`
infixl 5 `styleActive`
infixl 5 `styleDisabled`
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
forall t. CmbIgnoreTheme t => Bool -> t
ignoreTheme_ Bool
True
ignoreTheme_ :: Bool -> t
class CmbBgColor t where
bgColor :: Color -> t
class CmbFgColor t where
fgColor :: Color -> t
class CmbSndColor t where
sndColor :: Color -> t
class CmbHlColor t where
hlColor :: Color -> t
class CmbTransparency t where
transparency :: Double -> t
class CmbCursorIcon t where
cursorArrow :: t
cursorArrow = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorArrow
cursorHand :: t
cursorHand = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorHand
cursorIBeam :: t
cursorIBeam = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorIBeam
cursorInvalid :: t
cursorInvalid = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorInvalid
cursorSizeH :: t
cursorSizeH = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorSizeH
cursorSizeV :: t
cursorSizeV = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorSizeV
cursorDiagTL :: t
cursorDiagTL = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorDiagTL
cursorDiagTR :: t
cursorDiagTR = CursorIcon -> t
forall t. CmbCursorIcon t => CursorIcon -> t
cursorIcon CursorIcon
CursorDiagTR
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
forall t. CmbAlignLeft t => Bool -> t
alignLeft_ Bool
True
alignLeft_ :: Bool -> t
class CmbAlignCenter t where
alignCenter :: t
alignCenter = Bool -> t
forall t. CmbAlignCenter t => Bool -> t
alignCenter_ Bool
True
alignCenter_ :: Bool -> t
class CmbAlignRight t where
alignRight :: t
alignRight = Bool -> t
forall t. CmbAlignRight t => Bool -> t
alignRight_ Bool
True
alignRight_ :: Bool -> t
class CmbAlignTop t where
alignTop :: t
alignTop = Bool -> t
forall t. CmbAlignTop t => Bool -> t
alignTop_ Bool
True
alignTop_ :: Bool -> t
class CmbAlignMiddle t where
alignMiddle :: t
alignMiddle = Bool -> t
forall t. CmbAlignMiddle t => Bool -> t
alignMiddle_ Bool
True
alignMiddle_ :: Bool -> t
class CmbAlignBottom t where
alignBottom :: t
alignBottom = Bool -> t
forall t. CmbAlignBottom t => Bool -> t
alignBottom_ Bool
True
alignBottom_ :: Bool -> t
class CmbPadding t where
padding :: Double -> t
class CmbPaddingL t where
paddingL :: Double -> t
class CmbPaddingR t where
paddingR :: Double -> t
class CmbPaddingT t where
paddingT :: Double -> t
class CmbPaddingB t where
paddingB :: Double -> t
class CmbBorder t where
border :: Double -> Color -> t
class CmbBorderL t where
borderL :: Double -> Color -> t
class CmbBorderR t where
borderR :: Double -> Color -> t
class CmbBorderT t where
borderT :: Double -> Color -> t
class CmbBorderB t where
borderB :: Double -> Color -> t
class CmbRadius t where
radius :: Double -> t
class CmbRadiusTL t where
radiusTL :: Double -> t
class CmbRadiusTR t where
radiusTR :: Double -> t
class CmbRadiusBL t where
radiusBL :: Double -> t
class CmbRadiusBR t where
radiusBR :: Double -> t