{-# LANGUAGE OverloadedStrings, GeneralizedNewtypeDeriving #-} module Clay.List ( ListStyleType , listStyleType , disc , armenian , circleListStyle , cjkIdeographic , decimal , decimalLeadingZero , georgian , hebrew , hiragana , hiraganaIroha , katakana , katakanaIroha , lowerAlpha , lowerGreek , lowerLatin , lowerRoman , square , upperAlpha , upperLatin , upperRoman , ListStylePosition , listStylePosition , inside , outside , ListStyleImage , listStyleImage , imageUrl , listStyle ) where import Data.Text (Text) import Clay.Common import Clay.Property import Clay.Stylesheet newtype ListStyleType = ListStyleType Value deriving (ListStyleType -> Value (ListStyleType -> Value) -> Val ListStyleType forall a. (a -> Value) -> Val a value :: ListStyleType -> Value $cvalue :: ListStyleType -> Value Val, ListStyleType ListStyleType -> Initial ListStyleType forall a. a -> Initial a initial :: ListStyleType $cinitial :: ListStyleType Initial, ListStyleType ListStyleType -> Inherit ListStyleType forall a. a -> Inherit a inherit :: ListStyleType $cinherit :: ListStyleType Inherit, ListStyleType ListStyleType -> None ListStyleType forall a. a -> None a none :: ListStyleType $cnone :: ListStyleType None, Value -> ListStyleType (Value -> ListStyleType) -> Other ListStyleType forall a. (Value -> a) -> Other a other :: Value -> ListStyleType $cother :: Value -> ListStyleType Other) disc, armenian, circleListStyle, cjkIdeographic, decimal, decimalLeadingZero, georgian , hebrew, hiragana, hiraganaIroha, katakana, katakanaIroha, lowerAlpha , lowerGreek, lowerLatin, lowerRoman, square, upperAlpha, upperLatin, upperRoman :: ListStyleType disc :: ListStyleType disc = Value -> ListStyleType ListStyleType Value "disc" armenian :: ListStyleType armenian = Value -> ListStyleType ListStyleType Value "armenian" circleListStyle :: ListStyleType circleListStyle = Value -> ListStyleType ListStyleType Value "circle" cjkIdeographic :: ListStyleType cjkIdeographic = Value -> ListStyleType ListStyleType Value "cjk-ideographic" decimal :: ListStyleType decimal = Value -> ListStyleType ListStyleType Value "decimal" decimalLeadingZero :: ListStyleType decimalLeadingZero = Value -> ListStyleType ListStyleType Value "decimal-leading-zero" georgian :: ListStyleType georgian = Value -> ListStyleType ListStyleType Value "georgian" hebrew :: ListStyleType hebrew = Value -> ListStyleType ListStyleType Value "hebrew" hiragana :: ListStyleType hiragana = Value -> ListStyleType ListStyleType Value "hiragana" hiraganaIroha :: ListStyleType hiraganaIroha = Value -> ListStyleType ListStyleType Value "hiragana-iroha" katakana :: ListStyleType katakana = Value -> ListStyleType ListStyleType Value "katakana" katakanaIroha :: ListStyleType katakanaIroha = Value -> ListStyleType ListStyleType Value "katakana-iroha" lowerAlpha :: ListStyleType lowerAlpha = Value -> ListStyleType ListStyleType Value "lower-alpha" lowerGreek :: ListStyleType lowerGreek = Value -> ListStyleType ListStyleType Value "lower-greek" lowerLatin :: ListStyleType lowerLatin = Value -> ListStyleType ListStyleType Value "lower-latin" lowerRoman :: ListStyleType lowerRoman = Value -> ListStyleType ListStyleType Value "lower-roman" square :: ListStyleType square = Value -> ListStyleType ListStyleType Value "square" upperAlpha :: ListStyleType upperAlpha = Value -> ListStyleType ListStyleType Value "upper-alpha" upperLatin :: ListStyleType upperLatin = Value -> ListStyleType ListStyleType Value "upper-latin" upperRoman :: ListStyleType upperRoman = Value -> ListStyleType ListStyleType Value "upper-roman" listStyleType :: ListStyleType -> Css listStyleType :: ListStyleType -> Css listStyleType = Key ListStyleType -> ListStyleType -> Css forall a. Val a => Key a -> a -> Css key Key ListStyleType "list-style-type" newtype ListStylePosition = ListStylePosition Value deriving (ListStylePosition -> Value (ListStylePosition -> Value) -> Val ListStylePosition forall a. (a -> Value) -> Val a value :: ListStylePosition -> Value $cvalue :: ListStylePosition -> Value Val, ListStylePosition ListStylePosition -> Initial ListStylePosition forall a. a -> Initial a initial :: ListStylePosition $cinitial :: ListStylePosition Initial, ListStylePosition ListStylePosition -> Inherit ListStylePosition forall a. a -> Inherit a inherit :: ListStylePosition $cinherit :: ListStylePosition Inherit, Value -> ListStylePosition (Value -> ListStylePosition) -> Other ListStylePosition forall a. (Value -> a) -> Other a other :: Value -> ListStylePosition $cother :: Value -> ListStylePosition Other) inside, outside :: ListStylePosition inside :: ListStylePosition inside = Value -> ListStylePosition ListStylePosition Value "inside" outside :: ListStylePosition outside = Value -> ListStylePosition ListStylePosition Value "outside" listStylePosition :: ListStylePosition -> Css listStylePosition :: ListStylePosition -> Css listStylePosition = Key ListStylePosition -> ListStylePosition -> Css forall a. Val a => Key a -> a -> Css key Key ListStylePosition "list-style-position" newtype ListStyleImage = ListStyleImage Value deriving (ListStyleImage -> Value (ListStyleImage -> Value) -> Val ListStyleImage forall a. (a -> Value) -> Val a value :: ListStyleImage -> Value $cvalue :: ListStyleImage -> Value Val, ListStyleImage ListStyleImage -> Initial ListStyleImage forall a. a -> Initial a initial :: ListStyleImage $cinitial :: ListStyleImage Initial, ListStyleImage ListStyleImage -> Inherit ListStyleImage forall a. a -> Inherit a inherit :: ListStyleImage $cinherit :: ListStyleImage Inherit, ListStyleImage ListStyleImage -> None ListStyleImage forall a. a -> None a none :: ListStyleImage $cnone :: ListStyleImage None, Value -> ListStyleImage (Value -> ListStyleImage) -> Other ListStyleImage forall a. (Value -> a) -> Other a other :: Value -> ListStyleImage $cother :: Value -> ListStyleImage Other) listStyleImage :: ListStyleImage -> Css listStyleImage :: ListStyleImage -> Css listStyleImage = Key ListStyleImage -> ListStyleImage -> Css forall a. Val a => Key a -> a -> Css key Key ListStyleImage "list-style-image" imageUrl :: Text -> ListStyleImage imageUrl :: Text -> ListStyleImage imageUrl Text u = Value -> ListStyleImage ListStyleImage (Value "url(" Value -> Value -> Value forall a. Semigroup a => a -> a -> a <> Literal -> Value forall a. Val a => a -> Value value (Text -> Literal Literal Text u) Value -> Value -> Value forall a. Semigroup a => a -> a -> a <> Value ")") listStyle :: ListStyleType -> ListStylePosition -> ListStyleImage -> Css listStyle :: ListStyleType -> ListStylePosition -> ListStyleImage -> Css listStyle ListStyleType a ListStylePosition b ListStyleImage c = Key (ListStyleType, (ListStylePosition, ListStyleImage)) -> (ListStyleType, (ListStylePosition, ListStyleImage)) -> Css forall a. Val a => Key a -> a -> Css key Key (ListStyleType, (ListStylePosition, ListStyleImage)) "list-style" (ListStyleType a ListStyleType -> (ListStylePosition, ListStyleImage) -> (ListStyleType, (ListStylePosition, ListStyleImage)) forall a b. a -> b -> (a, b) ! ListStylePosition b ListStylePosition -> ListStyleImage -> (ListStylePosition, ListStyleImage) forall a b. a -> b -> (a, b) ! ListStyleImage c)