module Monomer.Core.Style (
module Monomer.Core.StyleTypes,
module Monomer.Core.ThemeTypes,
paddingH,
paddingV,
fixedSize,
flexSize,
expandSize,
minSize,
maxSize,
rangeSize
) where
import Control.Lens ((&), (.~), (?~), non)
import Data.Default
import Monomer.Core.Combinators
import Monomer.Core.StyleTypes
import Monomer.Core.ThemeTypes
import Monomer.Graphics.Types
import qualified Monomer.Core.Lens as L
paddingH :: (Semigroup a, CmbPaddingL a, CmbPaddingR a) => Double -> a
paddingH :: Double -> a
paddingH Double
p = Double -> a
forall t. CmbPaddingL t => Double -> t
paddingL Double
p a -> a -> a
forall a. Semigroup a => a -> a -> a
<> Double -> a
forall t. CmbPaddingR t => Double -> t
paddingR Double
p
paddingV :: (Semigroup a, CmbPaddingT a, CmbPaddingB a) => Double -> a
paddingV :: Double -> a
paddingV Double
p = Double -> a
forall t. CmbPaddingT t => Double -> t
paddingT Double
p a -> a -> a
forall a. Semigroup a => a -> a -> a
<> Double -> a
forall t. CmbPaddingB t => Double -> t
paddingB Double
p
fixedSize :: Double -> SizeReq
fixedSize :: Double -> SizeReq
fixedSize Double
s = SizeReq
forall a. Default a => a
def
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFixed s a => Lens' s a
L.fixed ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
flexSize :: Double -> Double -> SizeReq
flexSize :: Double -> Double -> SizeReq
flexSize Double
s Double
f = SizeReq
forall a. Default a => a
def
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFlex s a => Lens' s a
L.flex ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFactor s a => Lens' s a
L.factor ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
f
expandSize :: Double -> Double -> SizeReq
expandSize :: Double -> Double -> SizeReq
expandSize Double
s Double
f = SizeReq
forall a. Default a => a
def
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFlex s a => Lens' s a
L.flex ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasExtra s a => Lens' s a
L.extra ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFactor s a => Lens' s a
L.factor ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
f
minSize :: Double -> Double -> SizeReq
minSize :: Double -> Double -> SizeReq
minSize Double
s Double
f = SizeReq
forall a. Default a => a
def
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFixed s a => Lens' s a
L.fixed ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasExtra s a => Lens' s a
L.extra ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFactor s a => Lens' s a
L.factor ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
f
maxSize :: Double -> Double -> SizeReq
maxSize :: Double -> Double -> SizeReq
maxSize Double
s Double
f = SizeReq
forall a. Default a => a
def
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFlex s a => Lens' s a
L.flex ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFactor s a => Lens' s a
L.factor ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
f
rangeSize :: Double -> Double -> Double -> SizeReq
rangeSize :: Double -> Double -> Double -> SizeReq
rangeSize Double
s1 Double
s2 Double
f = SizeReq
forall a. Default a => a
def
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFixed s a => Lens' s a
L.fixed ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s1
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFlex s a => Lens' s a
L.flex ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
s2 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
s1
SizeReq -> (SizeReq -> SizeReq) -> SizeReq
forall a b. a -> (a -> b) -> b
& (Double -> Identity Double) -> SizeReq -> Identity SizeReq
forall s a. HasFactor s a => Lens' s a
L.factor ((Double -> Identity Double) -> SizeReq -> Identity SizeReq)
-> Double -> SizeReq -> SizeReq
forall s t a b. ASetter s t a b -> b -> s -> t
.~ Double
f
instance CmbWidth SizeReq where
width :: Double -> SizeReq
width Double
w = Double -> SizeReq
fixedSize Double
w
instance CmbHeight SizeReq where
height :: Double -> SizeReq
height Double
h = Double -> SizeReq
fixedSize Double
h
instance CmbFlexWidth SizeReq where
flexWidth :: Double -> SizeReq
flexWidth Double
w = Double -> Double -> SizeReq
expandSize Double
w Double
1
instance CmbFlexHeight SizeReq where
flexHeight :: Double -> SizeReq
flexHeight Double
h = Double -> Double -> SizeReq
expandSize Double
h Double
1
instance CmbMinWidth SizeReq where
minWidth :: Double -> SizeReq
minWidth Double
w = Double -> Double -> SizeReq
minSize Double
w Double
1
instance CmbMinHeight SizeReq where
minHeight :: Double -> SizeReq
minHeight Double
h = Double -> Double -> SizeReq
minSize Double
h Double
1
instance CmbMaxWidth SizeReq where
maxWidth :: Double -> SizeReq
maxWidth Double
w = Double -> Double -> SizeReq
maxSize Double
w Double
1
instance CmbMaxHeight SizeReq where
maxHeight :: Double -> SizeReq
maxHeight Double
h = Double -> Double -> SizeReq
maxSize Double
h Double
1
instance CmbExpandWidth SizeReq where
expandWidth :: Double -> SizeReq
expandWidth Double
w = Double -> Double -> SizeReq
expandSize Double
w Double
1
instance CmbExpandHeight SizeReq where
expandHeight :: Double -> SizeReq
expandHeight Double
h = Double -> Double -> SizeReq
expandSize Double
h Double
1
instance CmbRangeWidth SizeReq where
rangeWidth :: Double -> Double -> SizeReq
rangeWidth Double
w1 Double
w2 = Double -> Double -> Double -> SizeReq
rangeSize Double
w1 Double
w2 Double
1
instance CmbRangeHeight SizeReq where
rangeHeight :: Double -> Double -> SizeReq
rangeHeight Double
h1 Double
h2 = Double -> Double -> Double -> SizeReq
rangeSize Double
h1 Double
h2 Double
1
instance CmbTextFont TextStyle where
textFont :: Font -> TextStyle
textFont Font
font = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe Font -> Identity (Maybe Font))
-> TextStyle -> Identity TextStyle
forall s a. HasFont s a => Lens' s a
L.font ((Maybe Font -> Identity (Maybe Font))
-> TextStyle -> Identity TextStyle)
-> Font -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Font
font
instance CmbTextSize TextStyle where
textSize :: Double -> TextStyle
textSize Double
size = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe FontSize -> Identity (Maybe FontSize))
-> TextStyle -> Identity TextStyle
forall s a. HasFontSize s a => Lens' s a
L.fontSize ((Maybe FontSize -> Identity (Maybe FontSize))
-> TextStyle -> Identity TextStyle)
-> FontSize -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> FontSize
FontSize Double
size
instance CmbTextSpaceH TextStyle where
textSpaceH :: Double -> TextStyle
textSpaceH Double
space = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe FontSpace -> Identity (Maybe FontSpace))
-> TextStyle -> Identity TextStyle
forall s a. HasFontSpaceH s a => Lens' s a
L.fontSpaceH ((Maybe FontSpace -> Identity (Maybe FontSpace))
-> TextStyle -> Identity TextStyle)
-> FontSpace -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> FontSpace
FontSpace Double
space
instance CmbTextSpaceV TextStyle where
textSpaceV :: Double -> TextStyle
textSpaceV Double
space = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe FontSpace -> Identity (Maybe FontSpace))
-> TextStyle -> Identity TextStyle
forall s a. HasFontSpaceV s a => Lens' s a
L.fontSpaceV ((Maybe FontSpace -> Identity (Maybe FontSpace))
-> TextStyle -> Identity TextStyle)
-> FontSpace -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> FontSpace
FontSpace Double
space
instance CmbTextColor TextStyle where
textColor :: Color -> TextStyle
textColor Color
col = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe Color -> Identity (Maybe Color))
-> TextStyle -> Identity TextStyle
forall s a. HasFontColor s a => Lens' s a
L.fontColor ((Maybe Color -> Identity (Maybe Color))
-> TextStyle -> Identity TextStyle)
-> Color -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Color
col
instance CmbTextLeft TextStyle where
textLeft_ :: Bool -> TextStyle
textLeft_ Bool
False = TextStyle
forall a. Default a => a
def
textLeft_ Bool
True = AlignTH -> TextStyle
textAlignH AlignTH
ATLeft
instance CmbTextCenter TextStyle where
textCenter_ :: Bool -> TextStyle
textCenter_ Bool
False = TextStyle
forall a. Default a => a
def
textCenter_ Bool
True = AlignTH -> TextStyle
textAlignH AlignTH
ATCenter
instance CmbTextRight TextStyle where
textRight_ :: Bool -> TextStyle
textRight_ Bool
False = TextStyle
forall a. Default a => a
def
textRight_ Bool
True = AlignTH -> TextStyle
textAlignH AlignTH
ATRight
instance CmbTextTop TextStyle where
textTop_ :: Bool -> TextStyle
textTop_ Bool
False = TextStyle
forall a. Default a => a
def
textTop_ Bool
True = AlignTV -> TextStyle
textAlignV AlignTV
ATTop
instance CmbTextMiddle TextStyle where
textMiddle_ :: Bool -> TextStyle
textMiddle_ Bool
False = TextStyle
forall a. Default a => a
def
textMiddle_ Bool
True = AlignTV -> TextStyle
textAlignV AlignTV
ATMiddle
instance CmbTextAscender TextStyle where
textAscender_ :: Bool -> TextStyle
textAscender_ Bool
False = TextStyle
forall a. Default a => a
def
textAscender_ Bool
True = AlignTV -> TextStyle
textAlignV AlignTV
ATAscender
instance CmbTextLowerX TextStyle where
textLowerX_ :: Bool -> TextStyle
textLowerX_ Bool
False = TextStyle
forall a. Default a => a
def
textLowerX_ Bool
True = AlignTV -> TextStyle
textAlignV AlignTV
ATLowerX
instance CmbTextBottom TextStyle where
textBottom_ :: Bool -> TextStyle
textBottom_ Bool
False = TextStyle
forall a. Default a => a
def
textBottom_ Bool
True = AlignTV -> TextStyle
textAlignV AlignTV
ATBottom
instance CmbTextBaseline TextStyle where
textBaseline_ :: Bool -> TextStyle
textBaseline_ Bool
False = TextStyle
forall a. Default a => a
def
textBaseline_ Bool
True = AlignTV -> TextStyle
textAlignV AlignTV
ATBaseline
instance CmbTextUnderline TextStyle where
textUnderline_ :: Bool -> TextStyle
textUnderline_ Bool
under = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe Bool -> Identity (Maybe Bool))
-> TextStyle -> Identity TextStyle
forall s a. HasUnderline s a => Lens' s a
L.underline ((Maybe Bool -> Identity (Maybe Bool))
-> TextStyle -> Identity TextStyle)
-> Bool -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Bool
under
instance CmbTextOverline TextStyle where
textOverline_ :: Bool -> TextStyle
textOverline_ Bool
over = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe Bool -> Identity (Maybe Bool))
-> TextStyle -> Identity TextStyle
forall s a. HasOverline s a => Lens' s a
L.overline ((Maybe Bool -> Identity (Maybe Bool))
-> TextStyle -> Identity TextStyle)
-> Bool -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Bool
over
instance CmbTextThroughline TextStyle where
textThroughline_ :: Bool -> TextStyle
textThroughline_ Bool
through = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe Bool -> Identity (Maybe Bool))
-> TextStyle -> Identity TextStyle
forall s a. HasThroughline s a => Lens' s a
L.throughline ((Maybe Bool -> Identity (Maybe Bool))
-> TextStyle -> Identity TextStyle)
-> Bool -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Bool
through
instance CmbPadding Padding where
padding :: Double -> Padding
padding Double
padd = Maybe Double
-> Maybe Double -> Maybe Double -> Maybe Double -> Padding
Padding Maybe Double
jp Maybe Double
jp Maybe Double
jp Maybe Double
jp where
jp :: Maybe Double
jp = Double -> Maybe Double
forall a. a -> Maybe a
Just Double
padd
instance CmbPaddingL Padding where
paddingL :: Double -> Padding
paddingL Double
padd = Padding
forall a. Default a => a
def Padding -> (Padding -> Padding) -> Padding
forall a b. a -> (a -> b) -> b
& (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasLeft s a => Lens' s a
L.left ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> Double -> Padding -> Padding
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbPaddingR Padding where
paddingR :: Double -> Padding
paddingR Double
padd = Padding
forall a. Default a => a
def Padding -> (Padding -> Padding) -> Padding
forall a b. a -> (a -> b) -> b
& (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasRight s a => Lens' s a
L.right ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> Double -> Padding -> Padding
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbPaddingT Padding where
paddingT :: Double -> Padding
paddingT Double
padd = Padding
forall a. Default a => a
def Padding -> (Padding -> Padding) -> Padding
forall a b. a -> (a -> b) -> b
& (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasTop s a => Lens' s a
L.top ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> Double -> Padding -> Padding
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbPaddingB Padding where
paddingB :: Double -> Padding
paddingB Double
padd = Padding
forall a. Default a => a
def Padding -> (Padding -> Padding) -> Padding
forall a b. a -> (a -> b) -> b
& (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasBottom s a => Lens' s a
L.bottom ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> Double -> Padding -> Padding
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbBorder Border where
border :: Double -> Color -> Border
border Double
w Color
col = Maybe BorderSide
-> Maybe BorderSide
-> Maybe BorderSide
-> Maybe BorderSide
-> Border
Border Maybe BorderSide
bs Maybe BorderSide
bs Maybe BorderSide
bs Maybe BorderSide
bs where
bs :: Maybe BorderSide
bs = BorderSide -> Maybe BorderSide
forall a. a -> Maybe a
Just (Double -> Color -> BorderSide
BorderSide Double
w Color
col)
instance CmbBorderL Border where
borderL :: Double -> Color -> Border
borderL Double
w Color
col = Border
forall a. Default a => a
def Border -> (Border -> Border) -> Border
forall a b. a -> (a -> b) -> b
& (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasLeft s a => Lens' s a
L.left ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> BorderSide -> Border -> Border
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbBorderR Border where
borderR :: Double -> Color -> Border
borderR Double
w Color
col = Border
forall a. Default a => a
def Border -> (Border -> Border) -> Border
forall a b. a -> (a -> b) -> b
& (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasRight s a => Lens' s a
L.right ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> BorderSide -> Border -> Border
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbBorderT Border where
borderT :: Double -> Color -> Border
borderT Double
w Color
col = Border
forall a. Default a => a
def Border -> (Border -> Border) -> Border
forall a b. a -> (a -> b) -> b
& (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasTop s a => Lens' s a
L.top ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> BorderSide -> Border -> Border
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbBorderB Border where
borderB :: Double -> Color -> Border
borderB Double
w Color
col = Border
forall a. Default a => a
def Border -> (Border -> Border) -> Border
forall a b. a -> (a -> b) -> b
& (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasBottom s a => Lens' s a
L.bottom ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> BorderSide -> Border -> Border
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbRadius Radius where
radius :: Double -> Radius
radius Double
rad = Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Maybe RadiusCorner
-> Radius
Radius Maybe RadiusCorner
jrad Maybe RadiusCorner
jrad Maybe RadiusCorner
jrad Maybe RadiusCorner
jrad where
jrad :: Maybe RadiusCorner
jrad = RadiusCorner -> Maybe RadiusCorner
forall a. a -> Maybe a
Just (RadiusCorner -> Maybe RadiusCorner)
-> RadiusCorner -> Maybe RadiusCorner
forall a b. (a -> b) -> a -> b
$ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusTL Radius where
radiusTL :: Double -> Radius
radiusTL Double
rad = Radius
forall a. Default a => a
def Radius -> (Radius -> Radius) -> Radius
forall a b. a -> (a -> b) -> b
& (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasTopLeft s a => Lens' s a
L.topLeft ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> RadiusCorner -> Radius -> Radius
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusTR Radius where
radiusTR :: Double -> Radius
radiusTR Double
rad = Radius
forall a. Default a => a
def Radius -> (Radius -> Radius) -> Radius
forall a b. a -> (a -> b) -> b
& (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasTopRight s a => Lens' s a
L.topRight ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> RadiusCorner -> Radius -> Radius
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusBL Radius where
radiusBL :: Double -> Radius
radiusBL Double
rad = Radius
forall a. Default a => a
def Radius -> (Radius -> Radius) -> Radius
forall a b. a -> (a -> b) -> b
& (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasBottomLeft s a => Lens' s a
L.bottomLeft ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> RadiusCorner -> Radius -> Radius
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusBR Radius where
radiusBR :: Double -> Radius
radiusBR Double
rad = Radius
forall a. Default a => a
def Radius -> (Radius -> Radius) -> Radius
forall a b. a -> (a -> b) -> b
& (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasBottomRight s a => Lens' s a
L.bottomRight ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> RadiusCorner -> Radius -> Radius
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbWidth StyleState where
width :: Double -> StyleState
width Double
w = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbWidth t => Double -> t
width Double
w
instance CmbHeight StyleState where
height :: Double -> StyleState
height Double
h = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbHeight t => Double -> t
height Double
h
instance CmbFlexWidth StyleState where
flexWidth :: Double -> StyleState
flexWidth Double
w = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbFlexWidth t => Double -> t
flexWidth Double
w
instance CmbFlexHeight StyleState where
flexHeight :: Double -> StyleState
flexHeight Double
h = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbFlexHeight t => Double -> t
flexHeight Double
h
instance CmbMinWidth StyleState where
minWidth :: Double -> StyleState
minWidth Double
w = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbMinWidth t => Double -> t
minWidth Double
w
instance CmbMinHeight StyleState where
minHeight :: Double -> StyleState
minHeight Double
h = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbMinHeight t => Double -> t
minHeight Double
h
instance CmbMaxWidth StyleState where
maxWidth :: Double -> StyleState
maxWidth Double
w = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbMaxWidth t => Double -> t
maxWidth Double
w
instance CmbMaxHeight StyleState where
maxHeight :: Double -> StyleState
maxHeight Double
h = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbMaxHeight t => Double -> t
maxHeight Double
h
instance CmbExpandWidth StyleState where
expandWidth :: Double -> StyleState
expandWidth Double
w = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbExpandWidth t => Double -> t
expandWidth Double
w
instance CmbExpandHeight StyleState where
expandHeight :: Double -> StyleState
expandHeight Double
h = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> SizeReq
forall t. CmbExpandHeight t => Double -> t
expandHeight Double
h
instance CmbRangeWidth StyleState where
rangeWidth :: Double -> Double -> StyleState
rangeWidth Double
w1 Double
w2 = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Double -> SizeReq
forall t. CmbRangeWidth t => Double -> Double -> t
rangeWidth Double
w1 Double
w2
instance CmbRangeHeight StyleState where
rangeHeight :: Double -> Double -> StyleState
rangeHeight Double
h1 Double
h2 = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Double -> SizeReq
forall t. CmbRangeHeight t => Double -> Double -> t
rangeHeight Double
h1 Double
h2
instance CmbSizeReqW StyleState where
sizeReqW :: SizeReq -> StyleState
sizeReqW SizeReq
srW = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqW s a => Lens' s a
L.sizeReqW ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ SizeReq
srW
instance CmbSizeReqH StyleState where
sizeReqH :: SizeReq -> StyleState
sizeReqH SizeReq
srH = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState
forall s a. HasSizeReqH s a => Lens' s a
L.sizeReqH ((Maybe SizeReq -> Identity (Maybe SizeReq))
-> StyleState -> Identity StyleState)
-> SizeReq -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ SizeReq
srH
instance CmbBgColor StyleState where
bgColor :: Color -> StyleState
bgColor Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState
forall s a. HasBgColor s a => Lens' s a
L.bgColor ((Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState)
-> Color -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Color
col
instance CmbFgColor StyleState where
fgColor :: Color -> StyleState
fgColor Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState
forall s a. HasFgColor s a => Lens' s a
L.fgColor ((Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState)
-> Color -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Color
col
instance CmbSndColor StyleState where
sndColor :: Color -> StyleState
sndColor Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState
forall s a. HasSndColor s a => Lens' s a
L.sndColor ((Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState)
-> Color -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Color
col
instance CmbHlColor StyleState where
hlColor :: Color -> StyleState
hlColor Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState
forall s a. HasHlColor s a => Lens' s a
L.hlColor ((Maybe Color -> Identity (Maybe Color))
-> StyleState -> Identity StyleState)
-> Color -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Color
col
instance CmbCursorIcon StyleState where
cursorIcon :: CursorIcon -> StyleState
cursorIcon CursorIcon
icon = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe CursorIcon -> Identity (Maybe CursorIcon))
-> StyleState -> Identity StyleState
forall s a. HasCursorIcon s a => Lens' s a
L.cursorIcon ((Maybe CursorIcon -> Identity (Maybe CursorIcon))
-> StyleState -> Identity StyleState)
-> CursorIcon -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ CursorIcon
icon
instance CmbTextFont StyleState where
textFont :: Font -> StyleState
textFont Font
font = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Font -> TextStyle
forall t. CmbTextFont t => Font -> t
textFont Font
font
instance CmbTextSize StyleState where
textSize :: Double -> StyleState
textSize Double
size = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> TextStyle
forall t. CmbTextSize t => Double -> t
textSize Double
size
instance CmbTextSpaceH StyleState where
textSpaceH :: Double -> StyleState
textSpaceH Double
space = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> TextStyle
forall t. CmbTextSpaceH t => Double -> t
textSpaceH Double
space
instance CmbTextSpaceV StyleState where
textSpaceV :: Double -> StyleState
textSpaceV Double
space = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> TextStyle
forall t. CmbTextSpaceV t => Double -> t
textSpaceV Double
space
instance CmbTextColor StyleState where
textColor :: Color -> StyleState
textColor Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Color -> TextStyle
forall t. CmbTextColor t => Color -> t
textColor Color
col
instance CmbTextLeft StyleState where
textLeft_ :: Bool -> StyleState
textLeft_ Bool
False = StyleState
forall a. Default a => a
def
textLeft_ Bool
True = AlignTH -> StyleState
styleTextAlignH AlignTH
ATLeft
instance CmbTextCenter StyleState where
textCenter_ :: Bool -> StyleState
textCenter_ Bool
False = StyleState
forall a. Default a => a
def
textCenter_ Bool
True = AlignTH -> StyleState
styleTextAlignH AlignTH
ATCenter
instance CmbTextRight StyleState where
textRight_ :: Bool -> StyleState
textRight_ Bool
False = StyleState
forall a. Default a => a
def
textRight_ Bool
True = AlignTH -> StyleState
styleTextAlignH AlignTH
ATRight
instance CmbTextTop StyleState where
textTop_ :: Bool -> StyleState
textTop_ Bool
False = StyleState
forall a. Default a => a
def
textTop_ Bool
True = AlignTV -> StyleState
styleTextAlignV AlignTV
ATTop
instance CmbTextMiddle StyleState where
textMiddle_ :: Bool -> StyleState
textMiddle_ Bool
False = StyleState
forall a. Default a => a
def
textMiddle_ Bool
True = AlignTV -> StyleState
styleTextAlignV AlignTV
ATMiddle
instance CmbTextAscender StyleState where
textAscender_ :: Bool -> StyleState
textAscender_ Bool
False = StyleState
forall a. Default a => a
def
textAscender_ Bool
True = AlignTV -> StyleState
styleTextAlignV AlignTV
ATAscender
instance CmbTextLowerX StyleState where
textLowerX_ :: Bool -> StyleState
textLowerX_ Bool
False = StyleState
forall a. Default a => a
def
textLowerX_ Bool
True = AlignTV -> StyleState
styleTextAlignV AlignTV
ATLowerX
instance CmbTextBottom StyleState where
textBottom_ :: Bool -> StyleState
textBottom_ Bool
False = StyleState
forall a. Default a => a
def
textBottom_ Bool
True = AlignTV -> StyleState
styleTextAlignV AlignTV
ATBottom
instance CmbTextBaseline StyleState where
textBaseline_ :: Bool -> StyleState
textBaseline_ Bool
False = StyleState
forall a. Default a => a
def
textBaseline_ Bool
True = AlignTV -> StyleState
styleTextAlignV AlignTV
ATBaseline
instance CmbTextUnderline StyleState where
textUnderline_ :: Bool -> StyleState
textUnderline_ Bool
False = StyleState
forall a. Default a => a
def
textUnderline_ Bool
True = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ TextStyle
forall t. CmbTextUnderline t => t
textUnderline
instance CmbTextOverline StyleState where
textOverline_ :: Bool -> StyleState
textOverline_ Bool
False = StyleState
forall a. Default a => a
def
textOverline_ Bool
True = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ TextStyle
forall t. CmbTextOverline t => t
textOverline
instance CmbTextThroughline StyleState where
textThroughline_ :: Bool -> StyleState
textThroughline_ Bool
False = StyleState
forall a. Default a => a
def
textThroughline_ Bool
True = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> TextStyle -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ TextStyle
forall t. CmbTextThroughline t => t
textThroughline
instance CmbPadding StyleState where
padding :: Double -> StyleState
padding Double
padd = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState
forall s a. HasPadding s a => Lens' s a
L.padding ((Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState)
-> Padding -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Padding
forall t. CmbPadding t => Double -> t
padding Double
padd
instance CmbPaddingL StyleState where
paddingL :: Double -> StyleState
paddingL Double
padd = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState
forall s a. HasPadding s a => Lens' s a
L.padding ((Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState)
-> ((Maybe Double -> Identity (Maybe Double))
-> Maybe Padding -> Identity (Maybe Padding))
-> (Maybe Double -> Identity (Maybe Double))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Iso' (Maybe Padding) Padding
forall a. Eq a => a -> Iso' (Maybe a) a
non Padding
forall a. Default a => a
def ((Padding -> Identity Padding)
-> Maybe Padding -> Identity (Maybe Padding))
-> ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> (Maybe Double -> Identity (Maybe Double))
-> Maybe Padding
-> Identity (Maybe Padding)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasLeft s a => Lens' s a
L.left ((Maybe Double -> Identity (Maybe Double))
-> StyleState -> Identity StyleState)
-> Double -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbPaddingR StyleState where
paddingR :: Double -> StyleState
paddingR Double
padd = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState
forall s a. HasPadding s a => Lens' s a
L.padding ((Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState)
-> ((Maybe Double -> Identity (Maybe Double))
-> Maybe Padding -> Identity (Maybe Padding))
-> (Maybe Double -> Identity (Maybe Double))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Iso' (Maybe Padding) Padding
forall a. Eq a => a -> Iso' (Maybe a) a
non Padding
forall a. Default a => a
def ((Padding -> Identity Padding)
-> Maybe Padding -> Identity (Maybe Padding))
-> ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> (Maybe Double -> Identity (Maybe Double))
-> Maybe Padding
-> Identity (Maybe Padding)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasRight s a => Lens' s a
L.right ((Maybe Double -> Identity (Maybe Double))
-> StyleState -> Identity StyleState)
-> Double -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbPaddingT StyleState where
paddingT :: Double -> StyleState
paddingT Double
padd = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState
forall s a. HasPadding s a => Lens' s a
L.padding ((Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState)
-> ((Maybe Double -> Identity (Maybe Double))
-> Maybe Padding -> Identity (Maybe Padding))
-> (Maybe Double -> Identity (Maybe Double))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Iso' (Maybe Padding) Padding
forall a. Eq a => a -> Iso' (Maybe a) a
non Padding
forall a. Default a => a
def ((Padding -> Identity Padding)
-> Maybe Padding -> Identity (Maybe Padding))
-> ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> (Maybe Double -> Identity (Maybe Double))
-> Maybe Padding
-> Identity (Maybe Padding)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasTop s a => Lens' s a
L.top ((Maybe Double -> Identity (Maybe Double))
-> StyleState -> Identity StyleState)
-> Double -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbPaddingB StyleState where
paddingB :: Double -> StyleState
paddingB Double
padd = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState
forall s a. HasPadding s a => Lens' s a
L.padding ((Maybe Padding -> Identity (Maybe Padding))
-> StyleState -> Identity StyleState)
-> ((Maybe Double -> Identity (Maybe Double))
-> Maybe Padding -> Identity (Maybe Padding))
-> (Maybe Double -> Identity (Maybe Double))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Padding -> Iso' (Maybe Padding) Padding
forall a. Eq a => a -> Iso' (Maybe a) a
non Padding
forall a. Default a => a
def ((Padding -> Identity Padding)
-> Maybe Padding -> Identity (Maybe Padding))
-> ((Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding)
-> (Maybe Double -> Identity (Maybe Double))
-> Maybe Padding
-> Identity (Maybe Padding)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe Double -> Identity (Maybe Double))
-> Padding -> Identity Padding
forall s a. HasBottom s a => Lens' s a
L.bottom ((Maybe Double -> Identity (Maybe Double))
-> StyleState -> Identity StyleState)
-> Double -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double
padd
instance CmbBorder StyleState where
border :: Double -> Color -> StyleState
border Double
w Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState
forall s a. HasBorder s a => Lens' s a
L.border ((Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState)
-> Border -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> Border
forall t. CmbBorder t => Double -> Color -> t
border Double
w Color
col
instance CmbBorderL StyleState where
borderL :: Double -> Color -> StyleState
borderL Double
w Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState
forall s a. HasBorder s a => Lens' s a
L.border ((Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState)
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border -> Identity (Maybe Border))
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Border -> Iso' (Maybe Border) Border
forall a. Eq a => a -> Iso' (Maybe a) a
non Border
forall a. Default a => a
def ((Border -> Identity Border)
-> Maybe Border -> Identity (Maybe Border))
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border
-> Identity (Maybe Border)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasLeft s a => Lens' s a
L.left ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState -> Identity StyleState)
-> BorderSide -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbBorderR StyleState where
borderR :: Double -> Color -> StyleState
borderR Double
w Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState
forall s a. HasBorder s a => Lens' s a
L.border ((Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState)
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border -> Identity (Maybe Border))
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Border -> Iso' (Maybe Border) Border
forall a. Eq a => a -> Iso' (Maybe a) a
non Border
forall a. Default a => a
def ((Border -> Identity Border)
-> Maybe Border -> Identity (Maybe Border))
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border
-> Identity (Maybe Border)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasRight s a => Lens' s a
L.right ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState -> Identity StyleState)
-> BorderSide -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbBorderT StyleState where
borderT :: Double -> Color -> StyleState
borderT Double
w Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState
forall s a. HasBorder s a => Lens' s a
L.border ((Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState)
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border -> Identity (Maybe Border))
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Border -> Iso' (Maybe Border) Border
forall a. Eq a => a -> Iso' (Maybe a) a
non Border
forall a. Default a => a
def ((Border -> Identity Border)
-> Maybe Border -> Identity (Maybe Border))
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border
-> Identity (Maybe Border)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasTop s a => Lens' s a
L.top ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState -> Identity StyleState)
-> BorderSide -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbBorderB StyleState where
borderB :: Double -> Color -> StyleState
borderB Double
w Color
col = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState
forall s a. HasBorder s a => Lens' s a
L.border ((Maybe Border -> Identity (Maybe Border))
-> StyleState -> Identity StyleState)
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border -> Identity (Maybe Border))
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Border -> Iso' (Maybe Border) Border
forall a. Eq a => a -> Iso' (Maybe a) a
non Border
forall a. Default a => a
def ((Border -> Identity Border)
-> Maybe Border -> Identity (Maybe Border))
-> ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border)
-> (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Maybe Border
-> Identity (Maybe Border)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe BorderSide -> Identity (Maybe BorderSide))
-> Border -> Identity Border
forall s a. HasBottom s a => Lens' s a
L.bottom ((Maybe BorderSide -> Identity (Maybe BorderSide))
-> StyleState -> Identity StyleState)
-> BorderSide -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Color -> BorderSide
BorderSide Double
w Color
col
instance CmbRadius StyleState where
radius :: Double -> StyleState
radius Double
rad = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState
forall s a. HasRadius s a => Lens' s a
L.radius ((Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState)
-> Radius -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> Radius
forall t. CmbRadius t => Double -> t
radius Double
rad
instance CmbRadiusTL StyleState where
radiusTL :: Double -> StyleState
radiusTL Double
rad = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState
forall s a. HasRadius s a => Lens' s a
L.radius ((Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState)
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius -> Identity (Maybe Radius))
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Radius -> Iso' (Maybe Radius) Radius
forall a. Eq a => a -> Iso' (Maybe a) a
non Radius
forall a. Default a => a
def ((Radius -> Identity Radius)
-> Maybe Radius -> Identity (Maybe Radius))
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius
-> Identity (Maybe Radius)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasTopLeft s a => Lens' s a
L.topLeft ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState -> Identity StyleState)
-> RadiusCorner -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusTR StyleState where
radiusTR :: Double -> StyleState
radiusTR Double
rad = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState
forall s a. HasRadius s a => Lens' s a
L.radius ((Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState)
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius -> Identity (Maybe Radius))
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Radius -> Iso' (Maybe Radius) Radius
forall a. Eq a => a -> Iso' (Maybe a) a
non Radius
forall a. Default a => a
def ((Radius -> Identity Radius)
-> Maybe Radius -> Identity (Maybe Radius))
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius
-> Identity (Maybe Radius)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasTopRight s a => Lens' s a
L.topRight ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState -> Identity StyleState)
-> RadiusCorner -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusBL StyleState where
radiusBL :: Double -> StyleState
radiusBL Double
rad = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState
forall s a. HasRadius s a => Lens' s a
L.radius ((Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState)
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius -> Identity (Maybe Radius))
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Radius -> Iso' (Maybe Radius) Radius
forall a. Eq a => a -> Iso' (Maybe a) a
non Radius
forall a. Default a => a
def ((Radius -> Identity Radius)
-> Maybe Radius -> Identity (Maybe Radius))
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius
-> Identity (Maybe Radius)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasBottomLeft s a => Lens' s a
L.bottomLeft ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState -> Identity StyleState)
-> RadiusCorner -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
instance CmbRadiusBR StyleState where
radiusBR :: Double -> StyleState
radiusBR Double
rad = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState
forall s a. HasRadius s a => Lens' s a
L.radius ((Maybe Radius -> Identity (Maybe Radius))
-> StyleState -> Identity StyleState)
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius -> Identity (Maybe Radius))
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Radius -> Iso' (Maybe Radius) Radius
forall a. Eq a => a -> Iso' (Maybe a) a
non Radius
forall a. Default a => a
def ((Radius -> Identity Radius)
-> Maybe Radius -> Identity (Maybe Radius))
-> ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius)
-> (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Maybe Radius
-> Identity (Maybe Radius)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> Radius -> Identity Radius
forall s a. HasBottomRight s a => Lens' s a
L.bottomRight ((Maybe RadiusCorner -> Identity (Maybe RadiusCorner))
-> StyleState -> Identity StyleState)
-> RadiusCorner -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ Double -> RadiusCorner
radiusCorner Double
rad
radiusCorner :: Double -> RadiusCorner
radiusCorner :: Double -> RadiusCorner
radiusCorner Double
rad = Double -> RadiusCorner
RadiusCorner Double
rad
textAlignH :: AlignTH -> TextStyle
textAlignH :: AlignTH -> TextStyle
textAlignH AlignTH
align = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe AlignTH -> Identity (Maybe AlignTH))
-> TextStyle -> Identity TextStyle
forall s a. HasAlignH s a => Lens' s a
L.alignH ((Maybe AlignTH -> Identity (Maybe AlignTH))
-> TextStyle -> Identity TextStyle)
-> AlignTH -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ AlignTH
align
textAlignV :: AlignTV -> TextStyle
textAlignV :: AlignTV -> TextStyle
textAlignV AlignTV
align = TextStyle
forall a. Default a => a
def TextStyle -> (TextStyle -> TextStyle) -> TextStyle
forall a b. a -> (a -> b) -> b
& (Maybe AlignTV -> Identity (Maybe AlignTV))
-> TextStyle -> Identity TextStyle
forall s a. HasAlignV s a => Lens' s a
L.alignV ((Maybe AlignTV -> Identity (Maybe AlignTV))
-> TextStyle -> Identity TextStyle)
-> AlignTV -> TextStyle -> TextStyle
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ AlignTV
align
styleTextAlignH :: AlignTH -> StyleState
styleTextAlignH :: AlignTH -> StyleState
styleTextAlignH AlignTH
align = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> ((Maybe AlignTH -> Identity (Maybe AlignTH))
-> Maybe TextStyle -> Identity (Maybe TextStyle))
-> (Maybe AlignTH -> Identity (Maybe AlignTH))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextStyle -> Iso' (Maybe TextStyle) TextStyle
forall a. Eq a => a -> Iso' (Maybe a) a
non TextStyle
forall a. Default a => a
def ((TextStyle -> Identity TextStyle)
-> Maybe TextStyle -> Identity (Maybe TextStyle))
-> ((Maybe AlignTH -> Identity (Maybe AlignTH))
-> TextStyle -> Identity TextStyle)
-> (Maybe AlignTH -> Identity (Maybe AlignTH))
-> Maybe TextStyle
-> Identity (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe AlignTH -> Identity (Maybe AlignTH))
-> TextStyle -> Identity TextStyle
forall s a. HasAlignH s a => Lens' s a
L.alignH ((Maybe AlignTH -> Identity (Maybe AlignTH))
-> StyleState -> Identity StyleState)
-> AlignTH -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ AlignTH
align
styleTextAlignV :: AlignTV -> StyleState
styleTextAlignV :: AlignTV -> StyleState
styleTextAlignV AlignTV
align = StyleState
forall a. Default a => a
def StyleState -> (StyleState -> StyleState) -> StyleState
forall a b. a -> (a -> b) -> b
& (Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState
forall s a. HasText s a => Lens' s a
L.text ((Maybe TextStyle -> Identity (Maybe TextStyle))
-> StyleState -> Identity StyleState)
-> ((Maybe AlignTV -> Identity (Maybe AlignTV))
-> Maybe TextStyle -> Identity (Maybe TextStyle))
-> (Maybe AlignTV -> Identity (Maybe AlignTV))
-> StyleState
-> Identity StyleState
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TextStyle -> Iso' (Maybe TextStyle) TextStyle
forall a. Eq a => a -> Iso' (Maybe a) a
non TextStyle
forall a. Default a => a
def ((TextStyle -> Identity TextStyle)
-> Maybe TextStyle -> Identity (Maybe TextStyle))
-> ((Maybe AlignTV -> Identity (Maybe AlignTV))
-> TextStyle -> Identity TextStyle)
-> (Maybe AlignTV -> Identity (Maybe AlignTV))
-> Maybe TextStyle
-> Identity (Maybe TextStyle)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe AlignTV -> Identity (Maybe AlignTV))
-> TextStyle -> Identity TextStyle
forall s a. HasAlignV s a => Lens' s a
L.alignV ((Maybe AlignTV -> Identity (Maybe AlignTV))
-> StyleState -> Identity StyleState)
-> AlignTV -> StyleState -> StyleState
forall s t a b. ASetter s t a (Maybe b) -> b -> s -> t
?~ AlignTV
align