-----------------------------------------------------------------------------
{-# LANGUAGE OverloadedStrings #-}
-----------------------------------------------------------------------------
-- |
-- Module      :  Miso.Style
-- Copyright   :  (C) 2016-2025 David M. Johnson
-- License     :  BSD3-style (see the file LICENSE)
-- Maintainer  :  David M. Johnson <code@dmj.io>
-- Stability   :  experimental
-- Portability :  non-portable
-----------------------------------------------------------------------------
module Miso.Style
  ( -- *** Types
    module Miso.Style.Types
  -- *** Smart Constructor
  , style_
  , styleInline_
  , sheet_
  , selector_
  , (=:)
    -- *** Render
  , renderStyleSheet
    -- *** Combinators
  , 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
  , cursor
  , 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
  -- *** Colors
  , module Miso.Style.Color
  -- *** Units
  , px
  , ppx
  , pct
  , pt
  , vw
  , vh
  , deg
  , turn
  , rad
  , rpx
  , rem
  , em
  , s
  , ms
  -- *** Animation
  , keyframes_
  -- *** Media Queries
  , media_
  ) where
-----------------------------------------------------------------------------
import qualified Data.Map as M
import           Miso.String (MisoString)
import qualified Miso.String as MS
import           Miso.Style.Color
import           Miso.Style.Types
import           Miso.Property
import           Miso.Types (Attribute)
import qualified Miso.Types as MT
-----------------------------------------------------------------------------
import           Prelude hiding (filter, rem)
-----------------------------------------------------------------------------
pt :: Double -> MisoString
pt :: Double -> Text
pt Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"pt"
-----------------------------------------------------------------------------
px :: Double -> MisoString
px :: Double -> Text
px Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"px"
-----------------------------------------------------------------------------
deg :: Double -> MisoString
deg :: Double -> Text
deg Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"deg"
-----------------------------------------------------------------------------
turn :: Double -> MisoString
turn :: Double -> Text
turn Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"turn"
-----------------------------------------------------------------------------
rad :: Double -> MisoString
rad :: Double -> Text
rad Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"rad"
-----------------------------------------------------------------------------
rpx :: Double -> MisoString
rpx :: Double -> Text
rpx Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"rpx"
-----------------------------------------------------------------------------
rem :: Double -> MisoString
rem :: Double -> Text
rem Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"rem"
-----------------------------------------------------------------------------
em :: Double -> MisoString
em :: Double -> Text
em Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"em"
-----------------------------------------------------------------------------
vh :: Double -> MisoString
vh :: Double -> Text
vh Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"vh"
-----------------------------------------------------------------------------
vw :: Double -> MisoString
vw :: Double -> Text
vw Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"vw"
-----------------------------------------------------------------------------
s :: Double -> MisoString
s :: Double -> Text
s Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"s"
-----------------------------------------------------------------------------
ms :: Double -> MisoString
ms :: Double -> Text
ms Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"ms"
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/percentage
pct :: Double -> MisoString
pct :: Double -> Text
pct Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"%"
-----------------------------------------------------------------------------
ppx :: Double -> MisoString
ppx :: Double -> Text
ppx Double
x = Double -> Text
forall str. ToMisoString str => str -> Text
MS.ms Double
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"ppx"
-----------------------------------------------------------------------------
-- | Smart constructor for Attributes. This function is helpful when
-- constructing 'Style'.
--
-- Example shown below.
--
-- @
-- div_ [ style_  [ "background" =: "red" ] ] []
-- @
--
(=:) :: k -> v -> (k, v)
k
k =: :: forall k v. k -> v -> (k, v)
=: v
v = (k
k,v
v)
-----------------------------------------------------------------------------
-- | Used when constructing a 'StyleSheet'
--
-- @
-- sheet_
--   [ selector_ ".name"
--     [ backgroundColor red
--     , alignContent "top"
--     ]
--   ]
-- @
--
selector_ :: MisoString -> [Style] -> Styles
selector_ :: Text -> [Style] -> Styles
selector_ Text
k [Style]
v = (Text, [Style]) -> Styles
Styles (Text
k,[Style]
v)
-----------------------------------------------------------------------------
sheet_ :: [Styles] -> StyleSheet
sheet_ :: [Styles] -> StyleSheet
sheet_ = [Styles] -> StyleSheet
StyleSheet
-----------------------------------------------------------------------------
-- | @style_@ is an attribute that will set the @style@
-- attribute of the associated DOM node to @attrs@.
--
-- @style@ attributes not contained in @attrs@ will be deleted.
--
-- > import qualified Data.Map as M
-- > div_ [ style_ [ backgroundColor "red" ] [ ]
--
-- <https://developer.mozilla.org/en-US/docs/Web/CSS>
--
style_ :: [Style] -> Attribute action
style_ :: forall action. [Style] -> Attribute action
style_ = Map Text Text -> Attribute action
forall action. Map Text Text -> Attribute action
MT.Styles (Map Text Text -> Attribute action)
-> ([Style] -> Map Text Text) -> [Style] -> Attribute action
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Style] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
-----------------------------------------------------------------------------
-- | Set "style" property
--
-- > view m = div_ [ styleInline_ "background-color:red;color:blue;" ] [ "foo" ]
--
-- https://developer.mozilla.org/en-US/docs/Web/CSS
styleInline_ ::  MisoString -> Attribute action
styleInline_ :: forall action. Text -> Attribute action
styleInline_ = Text -> Text -> Attribute action
forall action. Text -> Text -> Attribute action
textProp Text
"style"
-----------------------------------------------------------------------------
-- | Renders a 'Styles' to a 'MisoString'
renderStyles :: Int -> Styles -> MisoString
renderStyles :: Int -> Styles -> Text
renderStyles Int
indent (Styles (Text
sel,[Style]
styles)) = [Text] -> Text
MS.unlines
  [ Text
sel Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" {" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
MS.replicate Int
indent Text
" "
  , Text -> [Text] -> Text
MS.intercalate Text
"\n"
        [ [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat
          [ Int -> Text -> Text
MS.replicate (Int
indent Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
k
          , Text
" : "
          , Text
v
          , Text
";"
          ]
        | (Text
k,Text
v) <- [Style]
styles
        ]
  , Int -> Text -> Text
MS.replicate Int
indent Text
" " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"}"
  ]
renderStyles Int
indent (KeyFrame Text
name [(Text, [Style])]
frames) = Text -> [Text] -> Text
MS.intercalate Text
" "
  [ Text
"@keyframes"
  , Text
name
  , Text
"{\n"
  , Text -> [Text] -> Text
MS.intercalate Text
"\n  "
    [ Int -> Styles -> Text
renderStyles (Int
indent Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) ((Text, [Style]) -> Styles
Styles (Text, [Style])
frame)
    | (Text, [Style])
frame <- [(Text, [Style])]
frames
    ]
  , Text
"}\n"
  ]
renderStyles Int
indent (Media Text
name [(Text, [Style])]
frames) = Text -> [Text] -> Text
MS.intercalate Text
" "
  [ Text
"@media"
  , Text
name
  , Text
"{\n"
  , Text -> [Text] -> Text
MS.intercalate Text
"\n  "
    [ Int -> Styles -> Text
renderStyles (Int
indent Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
2) ((Text, [Style]) -> Styles
Styles (Text, [Style])
frame)
    | (Text, [Style])
frame <- [(Text, [Style])]
frames
    ]
  , Text
"}\n"
  ]
-----------------------------------------------------------------------------
-- | Render 'StyleSheet' as 'MisoString'
--
renderStyleSheet :: StyleSheet -> MisoString
renderStyleSheet :: StyleSheet -> Text
renderStyleSheet StyleSheet
styleSheet = Text -> [Text] -> Text
MS.intercalate Text
"\n"
  [ Int -> Styles -> Text
renderStyles Int
0 Styles
styles
  | Styles
styles <- StyleSheet -> [Styles]
getStyleSheet StyleSheet
styleSheet
  ]
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/@keyframes
--
-- @
-- testKeyFrame :: Styles
-- testKeyFrame = keyframes "slide-in"
--   [ "from" =:
--       [ transform "translateX(0%)"
--       ]
--   , "to" =:
--       [ transform "translateX(100%)"
--       , backgroundColor red
--       , backgroundSize "10px"
--       , backgroundRepeat "true"
--       ]
--   , pct 10 =:
--     [ "foo" =: "bar"
--     ]
--  ]
-- @
--
keyframes_ :: MisoString -> [(MisoString, [Style])] -> Styles
keyframes_ :: Text -> [(Text, [Style])] -> Styles
keyframes_ = Text -> [(Text, [Style])] -> Styles
KeyFrame
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/@media
--
-- @
-- media_ "screen and (min-width: 480px)"
--   [ "header" =:
--       [ height "auto"
--       ]
--   , "ul" =:
--       [ display "block"
--       ]
--   ]
-- @
--
media_ :: MisoString -> [(MisoString, [Style])] -> Styles
media_ :: Text -> [(Text, [Style])] -> Styles
media_ = Text -> [(Text, [Style])] -> Styles
Media
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/align-content
--
alignContent :: MisoString -> Style
alignContent :: Text -> Style
alignContent Text
x = Text
"align-content" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/align-items
--
alignItems :: MisoString -> Style
alignItems :: Text -> Style
alignItems Text
x = Text
"align-items" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/align-self
--
alignSelf :: MisoString -> Style
alignSelf :: Text -> Style
alignSelf Text
x = Text
"align-self" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation-delay
--
animationDelay :: MisoString -> Style
animationDelay :: Text -> Style
animationDelay Text
x = Text
"animation-delay" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation-direction
--
animationDirection :: MisoString -> Style
animationDirection :: Text -> Style
animationDirection Text
x = Text
"animation-direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation-duration
--
animationDuration :: MisoString -> Style
animationDuration :: Text -> Style
animationDuration Text
x = Text
"animation-duration" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://animation-mozilla.org/en-US/docs/Web/CSS/align-content/animation-fill-mode
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation-iteration-count
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation
--
animation :: MisoString -> Style
animation :: Text -> Style
animation Text
x = Text
"animation" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation-name
--
animationName :: MisoString -> Style
animationName :: Text -> Style
animationName Text
x = Text
"animation-name" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- |  https://developer.mozilla.org/en-US/docs/Web/CSS/animation-play-state
-- > style_ [ animationPlayState =: "value" ]
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/animation-timing-function
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/aspect-ratio
--
aspectRatio :: MisoString -> Style
aspectRatio :: Text -> Style
aspectRatio Text
x = Text
"aspect-ratio" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-clip
--
backgroundClip :: MisoString -> Style
backgroundClip :: Text -> Style
backgroundClip Text
x = Text
"background-clip" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-image
--
backgroundImage :: MisoString -> Style
backgroundImage :: Text -> Style
backgroundImage Text
x = Text
"background-image" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background
--
background :: MisoString -> Style
background :: Text -> Style
background Text
x = Text
"background" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-origin
--
backgroundOrigin :: MisoString -> Style
backgroundOrigin :: Text -> Style
backgroundOrigin Text
x = Text
"background-origin" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-position
--
backgroundPosition :: MisoString -> Style
backgroundPosition :: Text -> Style
backgroundPosition Text
x = Text
"background-position" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-repeat
--
backgroundRepeat :: MisoString -> Style
backgroundRepeat :: Text -> Style
backgroundRepeat Text
x = Text
"background-repeat" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/background-size
--
backgroundSize :: MisoString -> Style
backgroundSize :: Text -> Style
backgroundSize Text
x = Text
"background-size" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-bottom-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-bottom-left-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-bottom
--
borderBottom :: MisoString -> Style
borderBottom :: Text -> Style
borderBottom Text
x = Text
"border-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-bottom-right-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-bottom-style
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-bottom-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-end-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-end-start-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-inline-end-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-inline-end-style
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-inline-end-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-inline-start-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-inline-start-style
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-inline-start-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-left-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-left
--
borderLeft :: MisoString -> Style
borderLeft :: Text -> Style
borderLeft Text
x = Text
"border-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-left-style
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-left-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border
--
border :: MisoString -> Style
border :: Text -> Style
border Text
x = Text
"border" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-radius
--
borderRadius :: MisoString -> Style
borderRadius :: Text -> Style
borderRadius Text
x = Text
"border-radius" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-right-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-right
--
borderRight :: MisoString -> Style
borderRight :: Text -> Style
borderRight Text
x = Text
"border-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-right-style
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-right-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-start-end-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-start-start-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-style
--
borderStyle :: MisoString -> Style
borderStyle :: Text -> Style
borderStyle Text
x = Text
"border-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-top-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-top-left-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-top
--
borderTop :: MisoString -> Style
borderTop :: Text -> Style
borderTop Text
x = Text
"border-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-top-right-radius
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-top-style
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-top-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/border-width
--
borderWidth :: MisoString -> Style
borderWidth :: Text -> Style
borderWidth Text
x = Text
"border-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/bottom
--
bottom :: MisoString -> Style
bottom :: Text -> Style
bottom Text
x = Text
"bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/box-shadow
--
boxShadow :: MisoString -> Style
boxShadow :: Text -> Style
boxShadow Text
x = Text
"box-shadow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/box-sizing
--
boxSizing :: MisoString -> Style
boxSizing :: Text -> Style
boxSizing Text
x = Text
"box-sizing" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/clip-path
--
clipPath :: MisoString -> Style
clipPath :: Text -> Style
clipPath Text
x = Text
"clip-path" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/column-gap
--
columnGap :: MisoString -> Style
columnGap :: Text -> Style
columnGap Text
x = Text
"column-gap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/css-variable
--
cssVariable :: MisoString -> Style
cssVariable :: Text -> Style
cssVariable Text
x = Text
"css-variable" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/direction
--
direction :: MisoString -> Style
direction :: Text -> Style
direction Text
x = Text
"direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/display
--
display :: MisoString -> Style
display :: Text -> Style
display Text
x = Text
"display" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/filter
--
filter :: MisoString -> Style
filter :: Text -> Style
filter Text
x = Text
"filter" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex-basis
--
flexBasis :: MisoString -> Style
flexBasis :: Text -> Style
flexBasis Text
x = Text
"flex-basis" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex-direction
--
flexDirection :: MisoString -> Style
flexDirection :: Text -> Style
flexDirection Text
x = Text
"flex-direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex-flow
--
flexFlow :: MisoString -> Style
flexFlow :: Text -> Style
flexFlow Text
x = Text
"flex-flow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex-grow
--
flexGrow :: MisoString -> Style
flexGrow :: Text -> Style
flexGrow Text
x = Text
"flex-grow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex
--
flex :: MisoString -> Style
flex :: Text -> Style
flex Text
x = Text
"flex" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex-shrink
--
flexShrink :: MisoString -> Style
flexShrink :: Text -> Style
flexShrink Text
x = Text
"flex-shrink" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/flex-wrap
--
flexWrap :: MisoString -> Style
flexWrap :: Text -> Style
flexWrap Text
x = Text
"flex-wrap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/font-family
--
fontFamily :: MisoString -> Style
fontFamily :: Text -> Style
fontFamily Text
x = Text
"font-family" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/font-size
--
fontSize :: MisoString -> Style
fontSize :: Text -> Style
fontSize Text
x = Text
"font-size" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/font-style
--
fontStyle :: MisoString -> Style
fontStyle :: Text -> Style
fontStyle Text
x = Text
"font-style" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/font-weight
--
fontWeight :: MisoString -> Style
fontWeight :: Text -> Style
fontWeight Text
x = Text
"font-weight" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/cursor
--
cursor :: MisoString -> Style
cursor :: Text -> Style
cursor Text
x = Text
"cursor" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/gap
--
gap :: MisoString -> Style
gap :: Text -> Style
gap Text
x = Text
"gap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-auto-columns
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-auto-flow
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-auto-rows
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-column-end
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-column-span
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-column-start
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-row-end
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-row-span
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-row-start
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-template-columns
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/grid-template-rows
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/height
--
height :: MisoString -> Style
height :: Text -> Style
height Text
x = Text
"height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/image-rendering
--
imageRendering :: MisoString -> Style
imageRendering :: Text -> Style
imageRendering Text
x = Text
"image-rendering" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/inset-inline-end
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/inset-inline-start
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/justify-content
--
justifyContent :: MisoString -> Style
justifyContent :: Text -> Style
justifyContent Text
x = Text
"justify-content" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/justify-items
--
justifyItems :: MisoString -> Style
justifyItems :: Text -> Style
justifyItems Text
x = Text
"justify-items" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/justify-self
--
justifySelf :: MisoString -> Style
justifySelf :: Text -> Style
justifySelf Text
x = Text
"justify-self" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/left
--
left :: MisoString -> Style
left :: Text -> Style
left Text
x = Text
"left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/letter-spacing
--
letterSpacing :: MisoString -> Style
letterSpacing :: Text -> Style
letterSpacing Text
x = Text
"letter-spacing" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/linear-cross-gravity
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/linear-direction
--
linearDirection :: MisoString -> Style
linearDirection :: Text -> Style
linearDirection Text
x = Text
"linear-direction" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/linear-gravity
--
linearGravity :: MisoString -> Style
linearGravity :: Text -> Style
linearGravity Text
x = Text
"linear-gravity" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/linear-layout-gravity
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/linear-weight
--
linearWeight :: MisoString -> Style
linearWeight :: Text -> Style
linearWeight Text
x = Text
"linear-weight" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/linear-weight-sum
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/line-height
--
lineHeight :: MisoString -> Style
lineHeight :: Text -> Style
lineHeight Text
x = Text
"line-height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin-bottom
--
marginBottom :: MisoString -> Style
marginBottom :: Text -> Style
marginBottom Text
x = Text
"margin-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin-inline-end
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin-inline-start
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin-left
--
marginLeft :: MisoString -> Style
marginLeft :: Text -> Style
marginLeft Text
x = Text
"margin-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin
--
margin :: MisoString -> Style
margin :: Text -> Style
margin Text
x = Text
"margin" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin-right
--
marginRight :: MisoString -> Style
marginRight :: Text -> Style
marginRight Text
x = Text
"margin-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/margin-top
--
marginTop :: MisoString -> Style
marginTop :: Text -> Style
marginTop Text
x = Text
"margin-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/mask-image
--
maskImage :: MisoString -> Style
maskImage :: Text -> Style
maskImage Text
x = Text
"mask-image" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/mask
--
mask :: MisoString -> Style
mask :: Text -> Style
mask Text
x = Text
"mask" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/max-height
--
maxHeight :: MisoString -> Style
maxHeight :: Text -> Style
maxHeight Text
x = Text
"max-height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/max-width
--
maxWidth :: MisoString -> Style
maxWidth :: Text -> Style
maxWidth Text
x = Text
"max-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/min-height
--
minHeight :: MisoString -> Style
minHeight :: Text -> Style
minHeight Text
x = Text
"min-height" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/min-width
--
minWidth :: MisoString -> Style
minWidth :: Text -> Style
minWidth Text
x = Text
"min-width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/opacity
--
opacity :: MisoString -> Style
opacity :: Text -> Style
opacity Text
x = Text
"opacity" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/order
--
order :: MisoString -> Style
order :: Text -> Style
order Text
x = Text
"order" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/overflow
--
overflow :: MisoString -> Style
overflow :: Text -> Style
overflow Text
x = Text
"overflow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/overflow-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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/overflow-y
--
overflowY :: MisoString -> Style
overflowY :: Text -> Style
overflowY Text
x = Text
"overflow-y" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding-bottom
--
paddingBottom :: MisoString -> Style
paddingBottom :: Text -> Style
paddingBottom Text
x = Text
"padding-bottom" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding-inline-end
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding-inline-start
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding-left
--
paddingLeft :: MisoString -> Style
paddingLeft :: Text -> Style
paddingLeft Text
x = Text
"padding-left" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding
--
padding :: MisoString -> Style
padding :: Text -> Style
padding Text
x = Text
"padding" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding-right
--
paddingRight :: MisoString -> Style
paddingRight :: Text -> Style
paddingRight Text
x = Text
"padding-right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/padding-top
--
paddingTop :: MisoString -> Style
paddingTop :: Text -> Style
paddingTop Text
x = Text
"padding-top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/perspective
--
perspective :: MisoString -> Style
perspective :: Text -> Style
perspective Text
x = Text
"perspective" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/position
--
position :: MisoString -> Style
position :: Text -> Style
position Text
x = Text
"position" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-align-bottom
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-align-inline-end
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-align-inline-start
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-align-left
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-align-right
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-align-top
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-bottom-of
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-center
--
relativeCenter :: MisoString -> Style
relativeCenter :: Text -> Style
relativeCenter Text
x = Text
"relative-center" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-id
--
relativeId :: MisoString -> Style
relativeId :: Text -> Style
relativeId Text
x = Text
"relative-id" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-inline-end-of
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-inline-start-of
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-layout-once
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-left-of
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-right-of
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/relative-top-of
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/right
--
right :: MisoString -> Style
right :: Text -> Style
right Text
x = Text
"right" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/row-gap
--
rowGap :: MisoString -> Style
rowGap :: Text -> Style
rowGap Text
x = Text
"row-gap" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-align
--
textAlign :: MisoString -> Style
textAlign :: Text -> Style
textAlign Text
x = Text
"text-align" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-decoration
--
textDecoration :: MisoString -> Style
textDecoration :: Text -> Style
textDecoration Text
x = Text
"text-decoration" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-indent
--
textIndent :: MisoString -> Style
textIndent :: Text -> Style
textIndent Text
x = Text
"text-indent" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-overflow
--
textOverflow :: MisoString -> Style
textOverflow :: Text -> Style
textOverflow Text
x = Text
"text-overflow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-shadow
--
textShadow :: MisoString -> Style
textShadow :: Text -> Style
textShadow Text
x = Text
"text-shadow" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-stroke-color
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-stroke
--
textStroke :: MisoString -> Style
textStroke :: Text -> Style
textStroke Text
x = Text
"text-stroke" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/text-stroke-width
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/top
--
top :: MisoString -> Style
top :: Text -> Style
top Text
x = Text
"top" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transform
--
transform :: MisoString -> Style
transform :: Text -> Style
transform Text
x = Text
"transform" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transform-origin
--
transformOrigin :: MisoString -> Style
transformOrigin :: Text -> Style
transformOrigin Text
x = Text
"transform-origin" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transition-delay
--
transitionDelay :: MisoString -> Style
transitionDelay :: Text -> Style
transitionDelay Text
x = Text
"transition-delay" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transition-duration
--
transitionDuration :: MisoString -> Style
transitionDuration :: Text -> Style
transitionDuration Text
x = Text
"transition-duration" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transition
--
transition :: MisoString -> Style
transition :: Text -> Style
transition Text
x = Text
"transition" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transition-property
--
transitionProperty :: MisoString -> Style
transitionProperty :: Text -> Style
transitionProperty Text
x = Text
"transition-property" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/transition-timing-function
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/vertical-align
--
verticalAlign :: MisoString -> Style
verticalAlign :: Text -> Style
verticalAlign Text
x = Text
"vertical-align" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/visibility
--
visibility :: MisoString -> Style
visibility :: Text -> Style
visibility Text
x = Text
"visibility" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/white-space
--
whiteSpace :: MisoString -> Style
whiteSpace :: Text -> Style
whiteSpace Text
x = Text
"white-space" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/width
--
width :: MisoString -> Style
width :: Text -> Style
width Text
x = Text
"width" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/word-break
--
wordBreak :: MisoString -> Style
wordBreak :: Text -> Style
wordBreak Text
x = Text
"word-break" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/xAutoFontSize
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/xAutoFontSizePresetSizes
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/xHandleColor
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/xHandleSize
--
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
-----------------------------------------------------------------------------
-- | https://developer.mozilla.org/en-US/docs/Web/CSS/z-index
--
zIndex :: MisoString -> Style
zIndex :: Text -> Style
zIndex Text
x = Text
"z-index" Text -> Text -> Style
forall k v. k -> v -> (k, v)
=: Text
x
-----------------------------------------------------------------------------