{-# LANGUAGE OverloadedStrings #-}
module Miso.Style
(
Style
, Styles
, StyleSheet
, style_
, styleInline_
, sheet_
, (=:)
, renderStyleSheet
, alignContent
, alignItems
, alignSelf
, animationDelay
, animationDirection
, animationDuration
, animationFillMode
, animationIterationCount
, animation
, animationName
, animationPlayState
, animationTimingFunction
, aspectRatio
, backgroundClip
, backgroundColor
, backgroundImage
, background
, backgroundOrigin
, backgroundPosition
, backgroundRepeat
, backgroundSize
, borderBottomColor
, borderBottomLeftRadius
, borderBottom
, borderBottomRightRadius
, borderBottomStyle
, borderBottomWidth
, borderColor
, borderEndEndRadius
, borderEndStartRadius
, borderInlineEndColor
, borderInlineEndStyle
, borderInlineEndWidth
, borderInlineStartColor
, borderInlineStartStyle
, borderInlineStartWidth
, borderLeftColor
, borderLeft
, borderLeftStyle
, borderLeftWidth
, border
, borderRadius
, borderRightColor
, borderRight
, borderRightStyle
, borderRightWidth
, borderStartEndRadius
, borderStartStartRadius
, borderStyle
, borderTopColor
, borderTopLeftRadius
, borderTop
, borderTopRightRadius
, borderTopStyle
, borderTopWidth
, borderWidth
, bottom
, boxShadow
, boxSizing
, clipPath
, color
, columnGap
, cssVariable
, direction
, display
, filter
, flexBasis
, flexDirection
, flexFlow
, flexGrow
, flex
, flexShrink
, flexWrap
, fontFamily
, fontSize
, fontStyle
, fontWeight
, gap
, gridAutoColumns
, gridAutoFlow
, gridAutoRows
, gridColumnEnd
, gridColumnSpan
, gridColumnStart
, gridRowEnd
, gridRowSpan
, gridRowStart
, gridTemplateColumns
, gridTemplateRows
, height
, imageRendering
, insetInlineEnd
, insetInlineStart
, justifyContent
, justifyItems
, justifySelf
, left
, letterSpacing
, linearCrossGravity
, linearDirection
, linearGravity
, linearLayoutGravity
, linearWeight
, linearWeightSum
, lineHeight
, marginBottom
, marginInlineEnd
, marginInlineStart
, marginLeft
, margin
, marginRight
, marginTop
, maskImage
, mask
, maxHeight
, maxWidth
, minHeight
, minWidth
, opacity
, order
, overflow
, overflowX
, overflowY
, paddingBottom
, paddingInlineEnd
, paddingInlineStart
, paddingLeft
, padding
, paddingRight
, paddingTop
, perspective
, position
, relativeAlignBottom
, relativeAlignInlineEnd
, relativeAlignInlineStart
, relativeAlignLeft
, relativeAlignRight
, relativeAlignTop
, relativeBottomOf
, relativeCenter
, relativeId
, relativeInlineEndOf
, relativeInlineStartOf
, relativeLayoutOnce
, relativeLeftOf
, relativeRightOf
, relativeTopOf
, right
, rowGap
, textAlign
, textDecoration
, textIndent
, textOverflow
, textShadow
, textStrokeColor
, textStroke
, textStrokeWidth
, top
, transform
, transformOrigin
, transitionDelay
, transitionDuration
, transition
, transitionProperty
, transitionTimingFunction
, verticalAlign
, visibility
, whiteSpace
, width
, wordBreak
, xAutoFontSize
, xAutoFontSizePresetSizes
, xHandleColor
, xHandleSize
, zIndex
, module Miso.Style.Color
) where
import Data.Map (Map)
import qualified Data.Map as M
import Miso.String (MisoString)
import qualified Miso.String as MS
import Miso.Style.Color
import Miso.Property
import Miso.Types (Attribute)
import qualified Miso.Types as MT
import Prelude hiding (filter)
(=:) :: k -> v -> (k, v)
k
k =: :: forall k v. k -> v -> (k, v)
=: v
v = (k
k,v
v)
type Style = (MisoString, MisoString)
type Styles = Map MisoString MisoString
newtype StyleSheet = StyleSheet { StyleSheet -> Map Text Styles
getStyleSheet :: Map MisoString Styles }
sheet_ :: [(MisoString, Styles)] -> StyleSheet
sheet_ :: [(Text, Styles)] -> StyleSheet
sheet_ = Map Text Styles -> StyleSheet
StyleSheet (Map Text Styles -> StyleSheet)
-> ([(Text, Styles)] -> Map Text Styles)
-> [(Text, Styles)]
-> StyleSheet
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Text, Styles)] -> Map Text Styles
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
style_ :: [Style] -> Attribute action
style_ :: forall action. [Style] -> Attribute action
style_ = Styles -> Attribute action
forall action. Styles -> Attribute action
MT.Styles (Styles -> Attribute action)
-> ([Style] -> Styles) -> [Style] -> Attribute action
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Style] -> Styles
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
styleInline_ :: MisoString -> Attribute action
styleInline_ :: forall action. Text -> Attribute action
styleInline_ = Text -> Text -> Attribute action
forall action. Text -> Text -> Attribute action
textProp Text
"style"
renderStyles :: Styles -> MisoString
renderStyles :: Styles -> Text
renderStyles Styles
m = [Text] -> Text
MS.unlines
[ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [ Text
spaced, Text
k, Text
":", Text
v, Text
";" ]
| (Text
k,Text
v) <- Styles -> [Style]
forall k a. Map k a -> [(k, a)]
M.toList Styles
m
, let spaced :: Text
spaced = Text
" "
]
renderStyleSheet :: StyleSheet -> MisoString
renderStyleSheet :: StyleSheet -> Text
renderStyleSheet StyleSheet
styleSheet = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
[ [Text] -> Text
MS.unlines
[ Text
selector
, Text
"{"
, Styles -> Text
renderStyles Styles
styles Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
]
| (Text
selector, Styles
styles) <- Map Text Styles -> [(Text, Styles)]
forall k a. Map k a -> [(k, a)]
M.toList (StyleSheet -> Map Text Styles
getStyleSheet StyleSheet
styleSheet)
]
alignContent :: MisoString -> Style
alignContent :: Text -> Style
alignContent Text
x = Text
"align-content" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
alignItems :: MisoString -> Style
alignItems :: Text -> Style
alignItems Text
x = Text
"align-items" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
alignSelf :: MisoString -> Style
alignSelf :: Text -> Style
alignSelf Text
x = Text
"align-self" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationDelay :: MisoString -> Style
animationDelay :: Text -> Style
animationDelay Text
x = Text
"animation-delay" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationDirection :: MisoString -> Style
animationDirection :: Text -> Style
animationDirection Text
x = Text
"animation-direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationDuration :: MisoString -> Style
animationDuration :: Text -> Style
animationDuration Text
x = Text
"animation-duration" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationFillMode :: MisoString -> Style
animationFillMode :: Text -> Style
animationFillMode Text
x = Text
"animation-fill-mode" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationIterationCount :: MisoString -> Style
animationIterationCount :: Text -> Style
animationIterationCount Text
x = Text
"animation-iteration-count" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animation :: MisoString -> Style
animation :: Text -> Style
animation Text
x = Text
"animation" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationName :: MisoString -> Style
animationName :: Text -> Style
animationName Text
x = Text
"animation-name" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationPlayState :: MisoString -> Style
animationPlayState :: Text -> Style
animationPlayState Text
x = Text
"animation-play-state" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
animationTimingFunction :: MisoString -> Style
animationTimingFunction :: Text -> Style
animationTimingFunction Text
x = Text
"animation-timing-function" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
aspectRatio :: MisoString -> Style
aspectRatio :: Text -> Style
aspectRatio Text
x = Text
"aspect-ratio" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
backgroundClip :: MisoString -> Style
backgroundClip :: Text -> Style
backgroundClip Text
x = Text
"background-clip" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
backgroundColor :: Color -> Style
backgroundColor :: Color -> Style
backgroundColor Color
x = Text
"background-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
backgroundImage :: MisoString -> Style
backgroundImage :: Text -> Style
backgroundImage Text
x = Text
"background-image" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
background :: MisoString -> Style
background :: Text -> Style
background Text
x = Text
"background" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
backgroundOrigin :: MisoString -> Style
backgroundOrigin :: Text -> Style
backgroundOrigin Text
x = Text
"background-origin" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
backgroundPosition :: MisoString -> Style
backgroundPosition :: Text -> Style
backgroundPosition Text
x = Text
"background-position" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
backgroundRepeat :: MisoString -> Style
backgroundRepeat :: Text -> Style
backgroundRepeat Text
x = Text
"background-repeat" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
backgroundSize :: MisoString -> Style
backgroundSize :: Text -> Style
backgroundSize Text
x = Text
"background-size" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderBottomColor :: Color -> Style
borderBottomColor :: Color -> Style
borderBottomColor Color
x = Text
"border-bottom-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderBottomLeftRadius :: MisoString -> Style
borderBottomLeftRadius :: Text -> Style
borderBottomLeftRadius Text
x = Text
"border-bottom-left-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderBottom :: MisoString -> Style
borderBottom :: Text -> Style
borderBottom Text
x = Text
"border-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderBottomRightRadius :: MisoString -> Style
borderBottomRightRadius :: Text -> Style
borderBottomRightRadius Text
x = Text
"border-bottom-right-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderBottomStyle :: MisoString -> Style
borderBottomStyle :: Text -> Style
borderBottomStyle Text
x = Text
"border-bottom-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderBottomWidth :: MisoString -> Style
borderBottomWidth :: Text -> Style
borderBottomWidth Text
x = Text
"border-bottom-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderColor :: Color -> Style
borderColor :: Color -> Style
borderColor Color
x = Text
"border-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderEndEndRadius :: MisoString -> Style
borderEndEndRadius :: Text -> Style
borderEndEndRadius Text
x = Text
"border-end-end-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderEndStartRadius :: MisoString -> Style
borderEndStartRadius :: Text -> Style
borderEndStartRadius Text
x = Text
"border-end-start-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderInlineEndColor :: Color -> Style
borderInlineEndColor :: Color -> Style
borderInlineEndColor Color
x = Text
"border-inline-end-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderInlineEndStyle :: MisoString -> Style
borderInlineEndStyle :: Text -> Style
borderInlineEndStyle Text
x = Text
"border-inline-end-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderInlineEndWidth :: MisoString -> Style
borderInlineEndWidth :: Text -> Style
borderInlineEndWidth Text
x = Text
"border-inline-end-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderInlineStartColor :: Color -> Style
borderInlineStartColor :: Color -> Style
borderInlineStartColor Color
x = Text
"border-inline-start-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderInlineStartStyle :: MisoString -> Style
borderInlineStartStyle :: Text -> Style
borderInlineStartStyle Text
x = Text
"border-inline-start-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderInlineStartWidth :: MisoString -> Style
borderInlineStartWidth :: Text -> Style
borderInlineStartWidth Text
x = Text
"border-inline-start-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderLeftColor :: Color -> Style
borderLeftColor :: Color -> Style
borderLeftColor Color
x = Text
"border-left-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderLeft :: MisoString -> Style
borderLeft :: Text -> Style
borderLeft Text
x = Text
"border-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderLeftStyle :: MisoString -> Style
borderLeftStyle :: Text -> Style
borderLeftStyle Text
x = Text
"border-left-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderLeftWidth :: MisoString -> Style
borderLeftWidth :: Text -> Style
borderLeftWidth Text
x = Text
"border-left-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
border :: MisoString -> Style
border :: Text -> Style
border Text
x = Text
"border" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderRadius :: MisoString -> Style
borderRadius :: Text -> Style
borderRadius Text
x = Text
"border-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderRightColor :: Color -> Style
borderRightColor :: Color -> Style
borderRightColor Color
x = Text
"border-right-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderRight :: MisoString -> Style
borderRight :: Text -> Style
borderRight Text
x = Text
"border-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderRightStyle :: MisoString -> Style
borderRightStyle :: Text -> Style
borderRightStyle Text
x = Text
"border-right-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderRightWidth :: MisoString -> Style
borderRightWidth :: Text -> Style
borderRightWidth Text
x = Text
"border-right-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderStartEndRadius :: MisoString -> Style
borderStartEndRadius :: Text -> Style
borderStartEndRadius Text
x = Text
"border-start-end-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderStartStartRadius :: MisoString -> Style
borderStartStartRadius :: Text -> Style
borderStartStartRadius Text
x = Text
"border-start-start-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderStyle :: MisoString -> Style
borderStyle :: Text -> Style
borderStyle Text
x = Text
"border-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderTopColor :: Color -> Style
borderTopColor :: Color -> Style
borderTopColor Color
x = Text
"border-top-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
borderTopLeftRadius :: MisoString -> Style
borderTopLeftRadius :: Text -> Style
borderTopLeftRadius Text
x = Text
"border-top-left-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderTop :: MisoString -> Style
borderTop :: Text -> Style
borderTop Text
x = Text
"border-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderTopRightRadius :: MisoString -> Style
borderTopRightRadius :: Text -> Style
borderTopRightRadius Text
x = Text
"border-top-right-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderTopStyle :: MisoString -> Style
borderTopStyle :: Text -> Style
borderTopStyle Text
x = Text
"border-top-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderTopWidth :: MisoString -> Style
borderTopWidth :: Text -> Style
borderTopWidth Text
x = Text
"border-top-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
borderWidth :: MisoString -> Style
borderWidth :: Text -> Style
borderWidth Text
x = Text
"border-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
bottom :: MisoString -> Style
bottom :: Text -> Style
bottom Text
x = Text
"bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
boxShadow :: MisoString -> Style
boxShadow :: Text -> Style
boxShadow Text
x = Text
"box-shadow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
boxSizing :: MisoString -> Style
boxSizing :: Text -> Style
boxSizing Text
x = Text
"box-sizing" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
clipPath :: MisoString -> Style
clipPath :: Text -> Style
clipPath Text
x = Text
"clip-path" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
color :: Color -> Style
color :: Color -> Style
color Color
x = Text
"color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
columnGap :: MisoString -> Style
columnGap :: Text -> Style
columnGap Text
x = Text
"column-gap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
cssVariable :: MisoString -> Style
cssVariable :: Text -> Style
cssVariable Text
x = Text
"css-variable" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
direction :: MisoString -> Style
direction :: Text -> Style
direction Text
x = Text
"direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
display :: MisoString -> Style
display :: Text -> Style
display Text
x = Text
"display" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
filter :: MisoString -> Style
filter :: Text -> Style
filter Text
x = Text
"filter" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flexBasis :: MisoString -> Style
flexBasis :: Text -> Style
flexBasis Text
x = Text
"flex-basis" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flexDirection :: MisoString -> Style
flexDirection :: Text -> Style
flexDirection Text
x = Text
"flex-direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flexFlow :: MisoString -> Style
flexFlow :: Text -> Style
flexFlow Text
x = Text
"flex-flow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flexGrow :: MisoString -> Style
flexGrow :: Text -> Style
flexGrow Text
x = Text
"flex-grow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flex :: MisoString -> Style
flex :: Text -> Style
flex Text
x = Text
"flex" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flexShrink :: MisoString -> Style
flexShrink :: Text -> Style
flexShrink Text
x = Text
"flex-shrink" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
flexWrap :: MisoString -> Style
flexWrap :: Text -> Style
flexWrap Text
x = Text
"flex-wrap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
fontFamily :: MisoString -> Style
fontFamily :: Text -> Style
fontFamily Text
x = Text
"font-family" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
fontSize :: MisoString -> Style
fontSize :: Text -> Style
fontSize Text
x = Text
"font-size" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
fontStyle :: MisoString -> Style
fontStyle :: Text -> Style
fontStyle Text
x = Text
"font-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
fontWeight :: MisoString -> Style
fontWeight :: Text -> Style
fontWeight Text
x = Text
"font-weight" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gap :: MisoString -> Style
gap :: Text -> Style
gap Text
x = Text
"gap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridAutoColumns :: MisoString -> Style
gridAutoColumns :: Text -> Style
gridAutoColumns Text
x = Text
"grid-auto-columns" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridAutoFlow :: MisoString -> Style
gridAutoFlow :: Text -> Style
gridAutoFlow Text
x = Text
"grid-auto-flow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridAutoRows :: MisoString -> Style
gridAutoRows :: Text -> Style
gridAutoRows Text
x = Text
"grid-auto-rows" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridColumnEnd :: MisoString -> Style
gridColumnEnd :: Text -> Style
gridColumnEnd Text
x = Text
"grid-column-end" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridColumnSpan :: MisoString -> Style
gridColumnSpan :: Text -> Style
gridColumnSpan Text
x = Text
"grid-column-span" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridColumnStart :: MisoString -> Style
gridColumnStart :: Text -> Style
gridColumnStart Text
x = Text
"grid-column-start" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridRowEnd :: MisoString -> Style
gridRowEnd :: Text -> Style
gridRowEnd Text
x = Text
"grid-row-end" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridRowSpan :: MisoString -> Style
gridRowSpan :: Text -> Style
gridRowSpan Text
x = Text
"grid-row-span" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridRowStart :: MisoString -> Style
gridRowStart :: Text -> Style
gridRowStart Text
x = Text
"grid-row-start" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridTemplateColumns :: MisoString -> Style
gridTemplateColumns :: Text -> Style
gridTemplateColumns Text
x = Text
"grid-template-columns" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
gridTemplateRows :: MisoString -> Style
gridTemplateRows :: Text -> Style
gridTemplateRows Text
x = Text
"grid-template-rows" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
height :: MisoString -> Style
height :: Text -> Style
height Text
x = Text
"height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
imageRendering :: MisoString -> Style
imageRendering :: Text -> Style
imageRendering Text
x = Text
"image-rendering" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
insetInlineEnd :: MisoString -> Style
insetInlineEnd :: Text -> Style
insetInlineEnd Text
x = Text
"inset-inline-end" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
insetInlineStart :: MisoString -> Style
insetInlineStart :: Text -> Style
insetInlineStart Text
x = Text
"inset-inline-start" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
justifyContent :: MisoString -> Style
justifyContent :: Text -> Style
justifyContent Text
x = Text
"justify-content" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
justifyItems :: MisoString -> Style
justifyItems :: Text -> Style
justifyItems Text
x = Text
"justify-items" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
justifySelf :: MisoString -> Style
justifySelf :: Text -> Style
justifySelf Text
x = Text
"justify-self" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
left :: MisoString -> Style
left :: Text -> Style
left Text
x = Text
"left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
letterSpacing :: MisoString -> Style
letterSpacing :: Text -> Style
letterSpacing Text
x = Text
"letter-spacing" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
linearCrossGravity :: MisoString -> Style
linearCrossGravity :: Text -> Style
linearCrossGravity Text
x = Text
"linear-cross-gravity" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
linearDirection :: MisoString -> Style
linearDirection :: Text -> Style
linearDirection Text
x = Text
"linear-direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
linearGravity :: MisoString -> Style
linearGravity :: Text -> Style
linearGravity Text
x = Text
"linear-gravity" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
linearLayoutGravity :: MisoString -> Style
linearLayoutGravity :: Text -> Style
linearLayoutGravity Text
x = Text
"linear-layout-gravity" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
linearWeight :: MisoString -> Style
linearWeight :: Text -> Style
linearWeight Text
x = Text
"linear-weight" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
linearWeightSum :: MisoString -> Style
linearWeightSum :: Text -> Style
linearWeightSum Text
x = Text
"linear-weight-sum" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
lineHeight :: MisoString -> Style
lineHeight :: Text -> Style
lineHeight Text
x = Text
"line-height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
marginBottom :: MisoString -> Style
marginBottom :: Text -> Style
marginBottom Text
x = Text
"margin-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
marginInlineEnd :: MisoString -> Style
marginInlineEnd :: Text -> Style
marginInlineEnd Text
x = Text
"margin-inline-end" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
marginInlineStart :: MisoString -> Style
marginInlineStart :: Text -> Style
marginInlineStart Text
x = Text
"margin-inline-start" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
marginLeft :: MisoString -> Style
marginLeft :: Text -> Style
marginLeft Text
x = Text
"margin-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
margin :: MisoString -> Style
margin :: Text -> Style
margin Text
x = Text
"margin" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
marginRight :: MisoString -> Style
marginRight :: Text -> Style
marginRight Text
x = Text
"margin-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
marginTop :: MisoString -> Style
marginTop :: Text -> Style
marginTop Text
x = Text
"margin-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
maskImage :: MisoString -> Style
maskImage :: Text -> Style
maskImage Text
x = Text
"mask-image" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
mask :: MisoString -> Style
mask :: Text -> Style
mask Text
x = Text
"mask" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
maxHeight :: MisoString -> Style
maxHeight :: Text -> Style
maxHeight Text
x = Text
"max-height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
maxWidth :: MisoString -> Style
maxWidth :: Text -> Style
maxWidth Text
x = Text
"max-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
minHeight :: MisoString -> Style
minHeight :: Text -> Style
minHeight Text
x = Text
"min-height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
minWidth :: MisoString -> Style
minWidth :: Text -> Style
minWidth Text
x = Text
"min-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
opacity :: MisoString -> Style
opacity :: Text -> Style
opacity Text
x = Text
"opacity" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
order :: MisoString -> Style
order :: Text -> Style
order Text
x = Text
"order" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
overflow :: MisoString -> Style
overflow :: Text -> Style
overflow Text
x = Text
"overflow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
overflowX :: MisoString -> Style
overflowX :: Text -> Style
overflowX Text
x = Text
"overflow-x" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
overflowY :: MisoString -> Style
overflowY :: Text -> Style
overflowY Text
x = Text
"overflow-y" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
paddingBottom :: MisoString -> Style
paddingBottom :: Text -> Style
paddingBottom Text
x = Text
"padding-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
paddingInlineEnd :: MisoString -> Style
paddingInlineEnd :: Text -> Style
paddingInlineEnd Text
x = Text
"padding-inline-end" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
paddingInlineStart :: MisoString -> Style
paddingInlineStart :: Text -> Style
paddingInlineStart Text
x = Text
"padding-inline-start" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
paddingLeft :: MisoString -> Style
paddingLeft :: Text -> Style
paddingLeft Text
x = Text
"padding-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
padding :: MisoString -> Style
padding :: Text -> Style
padding Text
x = Text
"padding" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
paddingRight :: MisoString -> Style
paddingRight :: Text -> Style
paddingRight Text
x = Text
"padding-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
paddingTop :: MisoString -> Style
paddingTop :: Text -> Style
paddingTop Text
x = Text
"padding-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
perspective :: MisoString -> Style
perspective :: Text -> Style
perspective Text
x = Text
"perspective" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
position :: MisoString -> Style
position :: Text -> Style
position Text
x = Text
"position" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeAlignBottom :: MisoString -> Style
relativeAlignBottom :: Text -> Style
relativeAlignBottom Text
x = Text
"relative-align-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeAlignInlineEnd :: MisoString -> Style
relativeAlignInlineEnd :: Text -> Style
relativeAlignInlineEnd Text
x = Text
"relative-align-inline-end" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeAlignInlineStart :: MisoString -> Style
relativeAlignInlineStart :: Text -> Style
relativeAlignInlineStart Text
x = Text
"relative-align-inline-start" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeAlignLeft :: MisoString -> Style
relativeAlignLeft :: Text -> Style
relativeAlignLeft Text
x = Text
"relative-align-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeAlignRight :: MisoString -> Style
relativeAlignRight :: Text -> Style
relativeAlignRight Text
x = Text
"relative-align-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeAlignTop :: MisoString -> Style
relativeAlignTop :: Text -> Style
relativeAlignTop Text
x = Text
"relative-align-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeBottomOf :: MisoString -> Style
relativeBottomOf :: Text -> Style
relativeBottomOf Text
x = Text
"relative-bottom-of" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeCenter :: MisoString -> Style
relativeCenter :: Text -> Style
relativeCenter Text
x = Text
"relative-center" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeId :: MisoString -> Style
relativeId :: Text -> Style
relativeId Text
x = Text
"relative-id" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeInlineEndOf :: MisoString -> Style
relativeInlineEndOf :: Text -> Style
relativeInlineEndOf Text
x = Text
"relative-inline-end-of" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeInlineStartOf :: MisoString -> Style
relativeInlineStartOf :: Text -> Style
relativeInlineStartOf Text
x = Text
"relative-inline-start-of" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeLayoutOnce :: MisoString -> Style
relativeLayoutOnce :: Text -> Style
relativeLayoutOnce Text
x = Text
"relative-layout-once" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeLeftOf :: MisoString -> Style
relativeLeftOf :: Text -> Style
relativeLeftOf Text
x = Text
"relative-left-of" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeRightOf :: MisoString -> Style
relativeRightOf :: Text -> Style
relativeRightOf Text
x = Text
"relative-right-of" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
relativeTopOf :: MisoString -> Style
relativeTopOf :: Text -> Style
relativeTopOf Text
x = Text
"relative-top-of" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
right :: MisoString -> Style
right :: Text -> Style
right Text
x = Text
"right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
rowGap :: MisoString -> Style
rowGap :: Text -> Style
rowGap Text
x = Text
"row-gap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textAlign :: MisoString -> Style
textAlign :: Text -> Style
textAlign Text
x = Text
"text-align" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textDecoration :: MisoString -> Style
textDecoration :: Text -> Style
textDecoration Text
x = Text
"text-decoration" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textIndent :: MisoString -> Style
textIndent :: Text -> Style
textIndent Text
x = Text
"text-indent" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textOverflow :: MisoString -> Style
textOverflow :: Text -> Style
textOverflow Text
x = Text
"text-overflow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textShadow :: MisoString -> Style
textShadow :: Text -> Style
textShadow Text
x = Text
"text-shadow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textStrokeColor :: Color -> Style
textStrokeColor :: Color -> Style
textStrokeColor Color
x = Text
"text-stroke-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
textStroke :: MisoString -> Style
textStroke :: Text -> Style
textStroke Text
x = Text
"text-stroke" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
textStrokeWidth :: MisoString -> Style
textStrokeWidth :: Text -> Style
textStrokeWidth Text
x = Text
"text-stroke-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
top :: MisoString -> Style
top :: Text -> Style
top Text
x = Text
"top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transform :: MisoString -> Style
transform :: Text -> Style
transform Text
x = Text
"transform" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transformOrigin :: MisoString -> Style
transformOrigin :: Text -> Style
transformOrigin Text
x = Text
"transform-origin" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transitionDelay :: MisoString -> Style
transitionDelay :: Text -> Style
transitionDelay Text
x = Text
"transition-delay" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transitionDuration :: MisoString -> Style
transitionDuration :: Text -> Style
transitionDuration Text
x = Text
"transition-duration" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transition :: MisoString -> Style
transition :: Text -> Style
transition Text
x = Text
"transition" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transitionProperty :: MisoString -> Style
transitionProperty :: Text -> Style
transitionProperty Text
x = Text
"transition-property" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
transitionTimingFunction :: MisoString -> Style
transitionTimingFunction :: Text -> Style
transitionTimingFunction Text
x = Text
"transition-timing-function" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
verticalAlign :: MisoString -> Style
verticalAlign :: Text -> Style
verticalAlign Text
x = Text
"vertical-align" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
visibility :: MisoString -> Style
visibility :: Text -> Style
visibility Text
x = Text
"visibility" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
whiteSpace :: MisoString -> Style
whiteSpace :: Text -> Style
whiteSpace Text
x = Text
"white-space" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
width :: MisoString -> Style
width :: Text -> Style
width Text
x = Text
"width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
wordBreak :: MisoString -> Style
wordBreak :: Text -> Style
wordBreak Text
x = Text
"word-break" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
xAutoFontSize :: MisoString -> Style
xAutoFontSize :: Text -> Style
xAutoFontSize Text
x = Text
"-x-auto-font-size" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
xAutoFontSizePresetSizes :: MisoString -> Style
xAutoFontSizePresetSizes :: Text -> Style
xAutoFontSizePresetSizes Text
x = Text
"-x-auto-font-size-preset-sizes" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
xHandleColor :: Color -> Style
xHandleColor :: Color -> Style
xHandleColor Color
x = Text
"-x-handle-color" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Color -> Text
renderColor Color
x
xHandleSize :: MisoString -> Style
xHandleSize :: Text -> Style
xHandleSize Text
x = Text
"-x-handle-size" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
zIndex :: MisoString -> Style
zIndex :: Text -> Style
zIndex Text
x = Text
"z-index" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x