Safe Haskell | None |
---|---|
Language | Haskell98 |
- Rendering stylesheets to CSS.
- The
Css
monad for collecting style rules. - The selector language.
- Apply media queries.
- Apply key-frame animation.
- Define font-faces.
- !important
- Import other CSS files
- Pseudo elements and classes.
- HTML5 attribute and element names.
- Commonly used value types.
- Values shared between multiple properties.
- Embedded style properties.
- Writing your own properties.
Synopsis
- render :: Css -> Text
- renderWith :: Config -> [App] -> Css -> Text
- putCss :: Css -> IO ()
- pretty :: Config
- compact :: Config
- renderSelector :: Selector -> Text
- type Css = StyleM ()
- (?) :: Selector -> Css -> Css
- (<?) :: Selector -> Css -> Css
- (&) :: Refinement -> Css -> Css
- root :: Selector -> Css -> Css
- pop :: Int -> Css -> Css
- (-:) :: Key Text -> Text -> Css
- commenting :: CommentText -> Css -> Css
- type Selector = Fix SelectorF
- data Refinement
- star :: Selector
- element :: Text -> Selector
- (**) :: Selector -> Selector -> Selector
- (|>) :: Selector -> Selector -> Selector
- (#) :: Selector -> Refinement -> Selector
- (|+) :: Selector -> Selector -> Selector
- byId :: Text -> Refinement
- byClass :: Text -> Refinement
- pseudo :: Text -> Refinement
- func :: Text -> [Text] -> Refinement
- attr :: Text -> Refinement
- (@=) :: Text -> Text -> Refinement
- (^=) :: Text -> Text -> Refinement
- ($=) :: Text -> Text -> Refinement
- (*=) :: Text -> Text -> Refinement
- (~=) :: Text -> Text -> Refinement
- (|=) :: Text -> Text -> Refinement
- query :: MediaType -> [Feature] -> Css -> Css
- queryNot :: MediaType -> [Feature] -> Css -> Css
- queryOnly :: MediaType -> [Feature] -> Css -> Css
- keyframes :: Text -> [(Double, Css)] -> Css
- keyframesFromTo :: Text -> Css -> Css -> Css
- fontFace :: Css -> Css
- important :: Css -> Css
- importUrl :: Text -> Css
- after :: Refinement
- before :: Refinement
- firstLetter :: Refinement
- firstLine :: Refinement
- selection :: Refinement
- backdrop :: Refinement
- link :: Refinement
- visited :: Refinement
- active :: Refinement
- hover :: Refinement
- focus :: Refinement
- firstChild :: Refinement
- lastChild :: Refinement
- checked :: Refinement
- disabled :: Refinement
- empty :: Refinement
- enabled :: Refinement
- firstOfType :: Refinement
- indeterminate :: Refinement
- inRange :: Refinement
- invalid :: Refinement
- lastOfType :: Refinement
- onlyChild :: Refinement
- onlyOfType :: Refinement
- optional :: Refinement
- outOfRange :: Refinement
- target :: Refinement
- valid :: Refinement
- nthChild :: Text -> Refinement
- nthLastChild :: Text -> Refinement
- nthLastOfType :: Text -> Refinement
- nthOfType :: Text -> Refinement
- not :: Selector -> Refinement
- accept :: Refinement
- acceptCharset :: Refinement
- accesskey :: Refinement
- action :: Refinement
- alt :: Refinement
- async :: Refinement
- autocomplete :: Refinement
- autofocus :: Refinement
- autoplay :: Refinement
- challenge :: Refinement
- charset :: Refinement
- cols :: Refinement
- colspan :: Refinement
- contenteditable :: Refinement
- contextmenu :: Refinement
- controls :: Refinement
- coords :: Refinement
- crossorigin :: Refinement
- datetime :: Refinement
- default_ :: Refinement
- defer :: Refinement
- dir :: Refinement
- dirname :: Refinement
- download :: Refinement
- draggable :: Refinement
- dropzone :: Refinement
- enctype :: Refinement
- for :: Refinement
- formaction :: Refinement
- formenctype :: Refinement
- formmethod :: Refinement
- formnovalidate :: Refinement
- formtarget :: Refinement
- headers :: Refinement
- high :: Refinement
- href :: Refinement
- hreflang :: Refinement
- httpEquiv :: Refinement
- icon :: Refinement
- id :: Refinement
- inert :: Refinement
- inputmode :: Refinement
- ismap :: Refinement
- itemid :: Refinement
- itemprop :: Refinement
- itemref :: Refinement
- itemscope :: Refinement
- itemtype :: Refinement
- keytype :: Refinement
- kind :: Refinement
- lang :: Refinement
- list :: Refinement
- loop :: Refinement
- low :: Refinement
- manifest :: Refinement
- max :: Refinement
- maxlength :: Refinement
- media :: Refinement
- mediagroup :: Refinement
- method :: Refinement
- min :: Refinement
- multiple :: Refinement
- muted :: Refinement
- name :: Refinement
- novalidate :: Refinement
- open :: Refinement
- optimum :: Refinement
- pattern :: Refinement
- ping :: Refinement
- placeholder :: Refinement
- poster :: Refinement
- preload :: Refinement
- radiogroup :: Refinement
- readonly :: Refinement
- rel :: Refinement
- required :: Refinement
- reversed :: Refinement
- rows :: Refinement
- rowspan :: Refinement
- sandbox :: Refinement
- scope :: Refinement
- scoped :: Refinement
- seamless :: Refinement
- selected :: Refinement
- shape :: Refinement
- sizes :: Refinement
- spellcheck :: Refinement
- src :: Refinement
- srcdoc :: Refinement
- srclang :: Refinement
- srcset :: Refinement
- step :: Refinement
- tabindex :: Refinement
- type_ :: Refinement
- typemustmatch :: Refinement
- usemap :: Refinement
- wrap :: Refinement
- abbr :: IsString a => a
- cite :: IsString a => a
- command :: IsString a => a
- data_ :: IsString a => a
- form :: IsString a => a
- label :: IsString a => a
- span :: IsString a => a
- style :: IsString a => a
- title :: IsString a => a
- a :: Selector
- address :: Selector
- area :: Selector
- article :: Selector
- aside :: Selector
- audio :: Selector
- b :: Selector
- base :: Selector
- bdi :: Selector
- bdo :: Selector
- blockquote :: Selector
- body :: Selector
- br :: Selector
- button :: Selector
- canvas :: Selector
- caption :: Selector
- code :: Selector
- col :: Selector
- colgroup :: Selector
- datalist :: Selector
- dd :: Selector
- del :: Selector
- details :: Selector
- dfn :: Selector
- dialog :: Selector
- div :: Selector
- dl :: Selector
- dt :: Selector
- embed :: Selector
- fieldset :: Selector
- figcaption :: Selector
- figure :: Selector
- footer :: Selector
- h1 :: Selector
- h2 :: Selector
- h3 :: Selector
- h4 :: Selector
- h5 :: Selector
- h6 :: Selector
- head :: Selector
- header :: Selector
- hgroup :: Selector
- hr :: Selector
- html :: Selector
- i :: Selector
- iframe :: Selector
- img :: Selector
- input :: Selector
- ins :: Selector
- kbd :: Selector
- keygen :: Selector
- legend :: Selector
- li :: Selector
- main_ :: Selector
- map :: Selector
- mark :: Selector
- menu :: Selector
- meta :: Selector
- meter :: Selector
- math :: Selector
- nav :: Selector
- noscript :: Selector
- object :: Selector
- ol :: Selector
- optgroup :: Selector
- option :: Selector
- output :: Selector
- p :: Selector
- param :: Selector
- pre :: Selector
- progress :: Selector
- q :: Selector
- rp :: Selector
- rt :: Selector
- ruby :: Selector
- s :: Selector
- samp :: Selector
- script :: Selector
- section :: Selector
- select :: Selector
- small :: Selector
- source :: Selector
- strong :: Selector
- sub :: Selector
- summary :: Selector
- sup :: Selector
- svg :: Selector
- table :: Selector
- tbody :: Selector
- td :: Selector
- template :: Selector
- textarea :: Selector
- tfoot :: Selector
- th :: Selector
- thead :: Selector
- time :: Selector
- tr :: Selector
- track :: Selector
- u :: Selector
- ul :: Selector
- var :: Selector
- video :: Selector
- wbr :: Selector
- module Clay.Size
- module Clay.Color
- module Clay.Time
- module Clay.Common
- module Clay.Background
- module Clay.Border
- module Clay.Box
- class Val a => Cursor a where
- class Val a => VerticalAlign a where
- verticalAlign :: a -> Css
- data PointerEvents
- data Clip
- data Visibility
- data Overflow
- data Display
- data Position
- data Clear
- data FloatStyle
- float :: FloatStyle -> Css
- floatLeft :: FloatStyle
- floatRight :: FloatStyle
- both :: Clear
- clearLeft :: Clear
- clearRight :: Clear
- clear :: Clear -> Css
- static :: Position
- absolute :: Position
- fixed :: Position
- relative :: Position
- sticky :: Position
- position :: Position -> Css
- inline :: Display
- block :: Display
- listItem :: Display
- runIn :: Display
- inlineBlock :: Display
- displayTable :: Display
- inlineTable :: Display
- tableRowGroup :: Display
- tableHeaderGroup :: Display
- tableFooterGroup :: Display
- tableRow :: Display
- tableColumnGroup :: Display
- tableColumn :: Display
- tableCell :: Display
- tableCaption :: Display
- displayNone :: Display
- displayInherit :: Display
- flex :: Display
- inlineFlex :: Display
- grid :: Display
- inlineGrid :: Display
- display :: Display -> Css
- scroll :: Overflow
- overflow :: Overflow -> Css
- overflowX :: Overflow -> Css
- overflowY :: Overflow -> Css
- collapse :: Visibility
- separate :: Visibility
- visibility :: Visibility -> Css
- clip :: Clip -> Css
- rect :: Size a -> Size a -> Size a -> Size a -> Clip
- opacity :: Double -> Css
- zIndex :: Integer -> Css
- visiblePainted :: PointerEvents
- visibleFill :: PointerEvents
- visibleStroke :: PointerEvents
- painted :: PointerEvents
- fillEvents :: PointerEvents
- strokeEvents :: PointerEvents
- allEvents :: PointerEvents
- pointerEvents :: PointerEvents -> Css
- middle :: VerticalAlignValue
- vAlignSub :: VerticalAlignValue
- vAlignBaseline :: VerticalAlignValue
- vAlignSuper :: VerticalAlignValue
- textTop :: VerticalAlignValue
- textBottom :: VerticalAlignValue
- vAlignTop :: VerticalAlignValue
- vAlignBottom :: VerticalAlignValue
- cursorUrl :: Text -> CursorValue Value
- cursorDefault :: CursorValue Value
- contextMenu :: CursorValue Value
- help :: CursorValue Value
- pointer :: CursorValue Value
- cursorProgress :: CursorValue Value
- wait :: CursorValue Value
- cell :: CursorValue Value
- crosshair :: CursorValue Value
- cursorText :: CursorValue Value
- vText :: CursorValue Value
- alias :: CursorValue Value
- cursorCopy :: CursorValue Value
- move :: CursorValue Value
- noDrop :: CursorValue Value
- notAllowed :: CursorValue Value
- grab :: CursorValue Value
- grabbing :: CursorValue Value
- allScroll :: CursorValue Value
- colResize :: CursorValue Value
- rowResize :: CursorValue Value
- nResize :: CursorValue Value
- eResize :: CursorValue Value
- sResize :: CursorValue Value
- wResize :: CursorValue Value
- neResize :: CursorValue Value
- nwResize :: CursorValue Value
- seResize :: CursorValue Value
- swResize :: CursorValue Value
- ewResize :: CursorValue Value
- nsResize :: CursorValue Value
- neswResize :: CursorValue Value
- nwseResize :: CursorValue Value
- zoomIn :: CursorValue Value
- zoomOut :: CursorValue Value
- module Clay.Dynamic
- newtype JustifyContentValue = JustifyContentValue Value
- newtype FlexWrap = FlexWrap Value
- newtype FlexDirection = FlexDirection Value
- newtype AlignSelfValue = AlignSelfValue Value
- newtype AlignItemsValue = AlignItemValue Value
- newtype AlignContentValue = AlignContentValue Value
- class Stretch a where
- stretch :: a
- class SpaceBetween a where
- spaceBetween :: a
- class SpaceAround a where
- spaceAround :: a
- class FlexStart a where
- flexStart :: a
- class FlexEnd a where
- flexEnd :: a
- alignContent :: AlignContentValue -> Css
- alignItems :: AlignItemsValue -> Css
- alignSelf :: AlignSelfValue -> Css
- flexBasis :: Size a -> Css
- row :: FlexDirection
- rowReverse :: FlexDirection
- column :: FlexDirection
- columnReverse :: FlexDirection
- flexDirection :: FlexDirection -> Css
- flexFlow :: FlexDirection -> FlexWrap -> Css
- flexGrow :: Int -> Css
- flexShrink :: Int -> Css
- wrapReverse :: FlexWrap
- flexWrap :: FlexWrap -> Css
- justifyContent :: JustifyContentValue -> Css
- order :: Int -> Css
- data NamedFont
- data FontWeight
- data FontVariant
- data FontStyle
- data FontSize
- data Required a = Required (Size a) (Maybe (Size a)) [Text] [GenericFontFamily]
- data Optional = Optional (Maybe FontWeight) (Maybe FontVariant) (Maybe FontStyle)
- class Val a => Font a where
- fontColor :: Color -> Css
- color :: Color -> Css
- sansSerif :: GenericFontFamily
- serif :: GenericFontFamily
- monospace :: GenericFontFamily
- cursive :: GenericFontFamily
- fantasy :: GenericFontFamily
- fontFamily :: [Text] -> [GenericFontFamily] -> Css
- xxSmall :: FontSize
- xSmall :: FontSize
- medium :: FontSize
- large :: FontSize
- xLarge :: FontSize
- xxLarge :: FontSize
- smaller :: FontSize
- larger :: FontSize
- fontSize :: Size a -> Css
- fontSizeCustom :: FontSize -> Css
- italic :: FontStyle
- oblique :: FontStyle
- fontStyle :: FontStyle -> Css
- smallCaps :: FontVariant
- fontVariant :: FontVariant -> Css
- bold :: FontWeight
- bolder :: FontWeight
- lighter :: FontWeight
- weight :: Integer -> FontWeight
- fontWeight :: FontWeight -> Css
- messageBox :: NamedFont
- smallCaption :: NamedFont
- statusBar :: NamedFont
- lineHeight :: Size a -> Css
- module Clay.FontFace
- module Clay.Geometry
- module Clay.Gradient
- module Clay.List
- data Content
- data TextOverflow
- data OverflowWrap
- data WordBreak
- data TextTransform
- data TextDecoration
- data WhiteSpace
- data TextAlign
- data TextDirection
- data TextIndent
- data TextRendering
- letterSpacing :: Size a -> Css
- wordSpacing :: Size a -> Css
- optimizeSpeed :: TextRendering
- optimizeLegibility :: TextRendering
- geometricPrecision :: TextRendering
- textRendering :: TextRendering -> Css
- textShadow :: Size a -> Size a -> Size a -> Color -> Css
- eachLine :: TextIndent -> TextIndent
- hanging :: TextIndent -> TextIndent
- indent :: Size a -> TextIndent
- textIndent :: TextIndent -> Css
- ltr :: TextDirection
- rtl :: TextDirection
- direction :: TextDirection -> Css
- justify :: TextAlign
- matchParent :: TextAlign
- start :: TextAlign
- end :: TextAlign
- alignSide :: Side -> TextAlign
- alignString :: Char -> TextAlign
- textAlign :: TextAlign -> Css
- whiteSpace :: WhiteSpace -> Css
- nowrap :: WhiteSpace
- preWrap :: WhiteSpace
- preLine :: WhiteSpace
- underline :: TextDecoration
- overline :: TextDecoration
- lineThrough :: TextDecoration
- blink :: TextDecoration
- textDecorationLine :: TextDecoration -> Css
- textDecorationColor :: Color -> Css
- textDecoration :: TextDecoration -> Css
- textDecorationStyle :: Stroke -> Css
- capitalize :: TextTransform
- uppercase :: TextTransform
- lowercase :: TextTransform
- fullWidth :: TextTransform
- textTransform :: TextTransform -> Css
- breakAll :: WordBreak
- keepAll :: WordBreak
- wordBreak :: WordBreak -> Css
- breakWord :: OverflowWrap
- wordWrap :: OverflowWrap -> Css
- overflowWrap :: OverflowWrap -> Css
- overflowClip :: TextOverflow
- overflowEllipsis :: TextOverflow
- textOverflow :: TextOverflow -> Css
- attrContent :: Text -> Content
- stringContent :: Text -> Content
- uriContent :: Text -> Content
- urlContent :: Text -> Content
- openQuote :: Content
- closeQuote :: Content
- noOpenQuote :: Content
- noCloseQuote :: Content
- content :: Content -> Css
- contents :: [Content] -> Css
- module Clay.Transform
- module Clay.Transition
- module Clay.Animation
- data MaskComposite
- class Val a => Mask a where
- copy :: MaskComposite
- sourceOver :: MaskComposite
- sourceIn :: MaskComposite
- sourceOut :: MaskComposite
- sourceAtop :: MaskComposite
- destinationOver :: MaskComposite
- destinationIn :: MaskComposite
- destinationOut :: MaskComposite
- destinationAtop :: MaskComposite
- xor :: MaskComposite
- maskComposite :: MaskComposite -> Css
- maskComposites :: [MaskComposite] -> Css
- maskPosition :: BackgroundPosition -> Css
- maskPositions :: [BackgroundPosition] -> Css
- maskSize :: BackgroundSize -> Css
- maskSizes :: [BackgroundSize] -> Css
- maskRepeat :: BackgroundRepeat -> Css
- maskRepeats :: [BackgroundRepeat] -> Css
- maskImage :: BackgroundImage -> Css
- maskImages :: [BackgroundImage] -> Css
- maskOrigin :: BackgroundOrigin -> Css
- maskOrigins :: [BackgroundOrigin] -> Css
- maskClip :: BackgroundClip -> Css
- maskClips :: [BackgroundClip] -> Css
- maskAttachment :: BackgroundAttachment -> Css
- maskAttachments :: [BackgroundAttachment] -> Css
- data Filter
- filter :: Filter -> Css
- filters :: [Filter] -> Css
- blur :: Size LengthUnit -> Filter
- brightness :: Double -> Filter
- contrast :: Size Percentage -> Filter
- dropShadow :: Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Color -> Filter
- grayscale :: Size Percentage -> Filter
- hueRotate :: Angle a -> Filter
- invert :: Size Percentage -> Filter
- saturate :: Size Percentage -> Filter
- sepia :: Size Percentage -> Filter
- module Clay.Property
Rendering stylesheets to CSS.
render :: Css -> Text Source #
Render a stylesheet with the default configuration. The pretty printer is used by default.
renderWith :: Config -> [App] -> Css -> Text Source #
Render a stylesheet with a custom configuration and an optional outer scope.
putCss :: Css -> IO () Source #
Render to CSS using the default configuration (pretty
) and directly
print to the standard output.
The Css
monad for collecting style rules.
(?) :: Selector -> Css -> Css infixr 5 Source #
Assign a stylesheet to a selector. When the selector is nested inside an
outer scope it will be composed with deep
.
(<?) :: Selector -> Css -> Css infixr 5 Source #
Assign a stylesheet to a selector. When the selector is nested inside an
outer scope it will be composed with |>
.
(&) :: Refinement -> Css -> Css infixr 5 Source #
Assign a stylesheet to a filter selector. When the selector is nested
inside an outer scope it will be composed with the with
selector.
pop :: Int -> Css -> Css Source #
Pop is used to add style rules to selectors defined in an outer scope. The counter specifies how far up the scope stack we want to add the rules.
(-:) :: Key Text -> Text -> Css infix 4 Source #
The colon operator can be used to add style rules to the current context for which there is no embedded version available. Both the key and the value are plain text values and rendered as is to the output CSS.
Comments
It is occasionally useful to output comments in the generated css.
commenting
appends comments (surrounded by ' /*
' and ' */
') to the
values of the supplied Css
as
key: value /* comment */;
Placing the comments before the semicolon ensures they are obviously grouped with the preceding value when rendered compactly.
Note that every generated line in the generated content will feature the comment.
An empty comment generates '* *
'.
commenting :: CommentText -> Css -> Css infixl 3 Source #
Annotate the supplied Css
with the supplied comment.
Comments work with OverloadedStrings
. This will annotate every non-nested
value.
The selector language.
data Refinement Source #
Instances
Show Refinement Source # | |
Defined in Clay.Selector showsPrec :: Int -> Refinement -> ShowS # show :: Refinement -> String # showList :: [Refinement] -> ShowS # | |
IsString Refinement Source # | |
Defined in Clay.Selector fromString :: String -> Refinement # | |
Semigroup Refinement Source # | |
Defined in Clay.Selector (<>) :: Refinement -> Refinement -> Refinement # sconcat :: NonEmpty Refinement -> Refinement # stimes :: Integral b => b -> Refinement -> Refinement # | |
Monoid Refinement Source # | |
Defined in Clay.Selector mempty :: Refinement # mappend :: Refinement -> Refinement -> Refinement # mconcat :: [Refinement] -> Refinement # |
Elements selectors.
element :: Text -> Selector Source #
Select elements by name. The preferred syntax is to enable
OverloadedStrings
and actually just use "element-name"
or use one of
the predefined elements from Clay.Elements.
(**) :: Selector -> Selector -> Selector Source #
The deep selector composer. Maps to sel1 sel2
in CSS.
(|>) :: Selector -> Selector -> Selector Source #
The child selector composer. Maps to sel1 > sel2
in CSS.
(#) :: Selector -> Refinement -> Selector Source #
The filter selector composer, adds a filter to a selector. Maps to
something like sel#filter
or sel.filter
in CSS, depending on the filter.
(|+) :: Selector -> Selector -> Selector Source #
The adjacent selector composer. Maps to sel1 + sel2
in CSS.
Refining selectors.
byId :: Text -> Refinement Source #
Filter elements by id. The preferred syntax is to enable
OverloadedStrings
and use "#id-name"
.
byClass :: Text -> Refinement Source #
Filter elements by class. The preferred syntax is to enable
OverloadedStrings
and use ".class-name"
.
pseudo :: Text -> Refinement Source #
Filter elements by pseudo selector or pseudo class. The preferred syntax
is to enable OverloadedStrings
and use ":pseudo-selector"
or use one
of the predefined ones from Clay.Pseudo.
func :: Text -> [Text] -> Refinement Source #
Filter elements by pseudo selector functions. The preferred way is to use one of the predefined functions from Clay.Pseudo.
Attribute based refining.
attr :: Text -> Refinement Source #
Filter elements based on the presence of a certain attribute. The
preferred syntax is to enable OverloadedStrings
and use
"@attr"
or use one of the predefined ones from Clay.Attributes.
(@=) :: Text -> Text -> Refinement Source #
Filter elements based on the presence of a certain attribute with the specified value.
(^=) :: Text -> Text -> Refinement Source #
Filter elements based on the presence of a certain attribute that begins with the selected value.
($=) :: Text -> Text -> Refinement Source #
Filter elements based on the presence of a certain attribute that ends with the specified value.
(*=) :: Text -> Text -> Refinement Source #
Filter elements based on the presence of a certain attribute that contains the specified value as a substring.
(~=) :: Text -> Text -> Refinement Source #
Filter elements based on the presence of a certain attribute that have the specified value contained in a space separated list.
(|=) :: Text -> Text -> Refinement Source #
Filter elements based on the presence of a certain attribute that have the specified value contained in a hyphen separated list.
Apply media queries.
Because a large part of the names export by Clay.Media clash with names export by other modules we don't re-export it here and recommend you to import the module qualified.
query :: MediaType -> [Feature] -> Css -> Css Source #
Apply a set of style rules when the media type and feature queries apply.
queryNot :: MediaType -> [Feature] -> Css -> Css Source #
Apply a set of style rules when the media type and feature queries do not apply.
queryOnly :: MediaType -> [Feature] -> Css -> Css Source #
Apply a set of style rules only when the media type and feature queries apply.
Apply key-frame animation.
Define font-faces.
!important
important :: Css -> Css Source #
Indicate the supplied css should override css declarations that would otherwise take precedence.
Use sparingly.
Import other CSS files
Pseudo elements and classes.
after :: Refinement Source #
before :: Refinement Source #
link :: Refinement Source #
visited :: Refinement Source #
active :: Refinement Source #
hover :: Refinement Source #
focus :: Refinement Source #
checked :: Refinement Source #
empty :: Refinement Source #
enabled :: Refinement Source #
inRange :: Refinement Source #
invalid :: Refinement Source #
target :: Refinement Source #
valid :: Refinement Source #
nthChild :: Text -> Refinement Source #
nthLastChild :: Text -> Refinement Source #
nthLastOfType :: Text -> Refinement Source #
nthOfType :: Text -> Refinement Source #
not :: Selector -> Refinement Source #
HTML5 attribute and element names.
accept :: Refinement Source #
action :: Refinement Source #
alt :: Refinement Source #
async :: Refinement Source #
charset :: Refinement Source #
cols :: Refinement Source #
colspan :: Refinement Source #
coords :: Refinement Source #
defer :: Refinement Source #
dir :: Refinement Source #
dirname :: Refinement Source #
enctype :: Refinement Source #
for :: Refinement Source #
headers :: Refinement Source #
high :: Refinement Source #
href :: Refinement Source #
icon :: Refinement Source #
id :: Refinement Source #
inert :: Refinement Source #
ismap :: Refinement Source #
itemid :: Refinement Source #
itemref :: Refinement Source #
keytype :: Refinement Source #
kind :: Refinement Source #
lang :: Refinement Source #
list :: Refinement Source #
loop :: Refinement Source #
low :: Refinement Source #
max :: Refinement Source #
media :: Refinement Source #
method :: Refinement Source #
min :: Refinement Source #
muted :: Refinement Source #
name :: Refinement Source #
open :: Refinement Source #
optimum :: Refinement Source #
pattern :: Refinement Source #
ping :: Refinement Source #
poster :: Refinement Source #
preload :: Refinement Source #
rel :: Refinement Source #
rows :: Refinement Source #
rowspan :: Refinement Source #
sandbox :: Refinement Source #
scope :: Refinement Source #
scoped :: Refinement Source #
shape :: Refinement Source #
sizes :: Refinement Source #
src :: Refinement Source #
srcdoc :: Refinement Source #
srclang :: Refinement Source #
srcset :: Refinement Source #
step :: Refinement Source #
type_ :: Refinement Source #
usemap :: Refinement Source #
wrap :: Refinement Source #
abbr :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
cite :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
command :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
data_ :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
form :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
label :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
span :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
style :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
title :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
Commonly used value types.
module Clay.Size
module Clay.Color
module Clay.Time
Values shared between multiple properties.
module Clay.Common
Embedded style properties.
module Clay.Background
module Clay.Border
module Clay.Box
class Val a => VerticalAlign a where Source #
Nothing
verticalAlign :: a -> Css Source #
Instances
VerticalAlign (Size a) Source # | |
Defined in Clay.Display verticalAlign :: Size a -> Css Source # |
data PointerEvents Source #
Instances
Val PointerEvents Source # | |
Defined in Clay.Display value :: PointerEvents -> Value Source # | |
Other PointerEvents Source # | |
Defined in Clay.Display other :: Value -> PointerEvents Source # | |
Visible PointerEvents Source # | |
Defined in Clay.Display | |
None PointerEvents Source # | |
Defined in Clay.Display none :: PointerEvents Source # | |
Inherit PointerEvents Source # | |
Defined in Clay.Display | |
Auto PointerEvents Source # | |
Defined in Clay.Display auto :: PointerEvents Source # |
data Visibility Source #
Instances
Val Visibility Source # | |
Defined in Clay.Display value :: Visibility -> Value Source # | |
Other Visibility Source # | |
Defined in Clay.Display other :: Value -> Visibility Source # | |
Hidden Visibility Source # | |
Defined in Clay.Display hidden :: Visibility Source # | |
Visible Visibility Source # | |
Defined in Clay.Display visible :: Visibility Source # | |
Inherit Visibility Source # | |
Defined in Clay.Display inherit :: Visibility Source # | |
Auto Visibility Source # | |
Defined in Clay.Display auto :: Visibility Source # |
data FloatStyle Source #
Instances
Val FloatStyle Source # | |
Defined in Clay.Display value :: FloatStyle -> Value Source # | |
None FloatStyle Source # | |
Defined in Clay.Display none :: FloatStyle Source # | |
Inherit FloatStyle Source # | |
Defined in Clay.Display inherit :: FloatStyle Source # |
float :: FloatStyle -> Css Source #
clearRight :: Clear Source #
inlineFlex :: Display Source #
inlineGrid :: Display Source #
visibility :: Visibility -> Css Source #
pointerEvents :: PointerEvents -> Css Source #
vAlignBaseline :: VerticalAlignValue Source #
vAlignSuper :: VerticalAlignValue Source #
textBottom :: VerticalAlignValue Source #
vAlignBottom :: VerticalAlignValue Source #
cursorDefault :: CursorValue Value Source #
contextMenu :: CursorValue Value Source #
cursorProgress :: CursorValue Value Source #
cursorText :: CursorValue Value Source #
cursorCopy :: CursorValue Value Source #
notAllowed :: CursorValue Value Source #
neswResize :: CursorValue Value Source #
nwseResize :: CursorValue Value Source #
module Clay.Dynamic
newtype JustifyContentValue Source #
Instances
Val JustifyContentValue Source # | |
Defined in Clay.Flexbox value :: JustifyContentValue -> Value Source # | |
Other JustifyContentValue Source # | |
Defined in Clay.Flexbox other :: Value -> JustifyContentValue Source # | |
Inherit JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
Center JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
SpaceBetween JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
SpaceAround JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
FlexStart JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd JustifyContentValue Source # | |
Defined in Clay.Flexbox |
newtype FlexDirection Source #
Instances
Val FlexDirection Source # | |
Defined in Clay.Flexbox value :: FlexDirection -> Value Source # | |
Other FlexDirection Source # | |
Defined in Clay.Flexbox other :: Value -> FlexDirection Source # |
newtype AlignSelfValue Source #
Instances
Val AlignSelfValue Source # | |
Defined in Clay.Flexbox value :: AlignSelfValue -> Value Source # | |
Other AlignSelfValue Source # | |
Defined in Clay.Flexbox other :: Value -> AlignSelfValue Source # | |
Inherit AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
Center AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
Baseline AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
Auto AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
Stretch AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
FlexStart AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd AlignSelfValue Source # | |
Defined in Clay.Flexbox |
newtype AlignItemsValue Source #
Instances
Val AlignItemsValue Source # | |
Defined in Clay.Flexbox value :: AlignItemsValue -> Value Source # | |
Other AlignItemsValue Source # | |
Defined in Clay.Flexbox other :: Value -> AlignItemsValue Source # | |
Inherit AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
Center AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
Baseline AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
Stretch AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
FlexStart AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd AlignItemsValue Source # | |
Defined in Clay.Flexbox |
newtype AlignContentValue Source #
Instances
Val AlignContentValue Source # | |
Defined in Clay.Flexbox value :: AlignContentValue -> Value Source # | |
Other AlignContentValue Source # | |
Defined in Clay.Flexbox other :: Value -> AlignContentValue Source # | |
Inherit AlignContentValue Source # | |
Defined in Clay.Flexbox | |
Center AlignContentValue Source # | |
Defined in Clay.Flexbox | |
Stretch AlignContentValue Source # | |
Defined in Clay.Flexbox | |
SpaceBetween AlignContentValue Source # | |
Defined in Clay.Flexbox | |
SpaceAround AlignContentValue Source # | |
Defined in Clay.Flexbox | |
FlexStart AlignContentValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd AlignContentValue Source # | |
Defined in Clay.Flexbox |
class Stretch a where Source #
Instances
Stretch Value Source # | |
Defined in Clay.Flexbox | |
Stretch AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
Stretch AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
Stretch AlignContentValue Source # | |
Defined in Clay.Flexbox |
class SpaceBetween a where Source #
spaceBetween :: a Source #
Instances
SpaceBetween Value Source # | |
Defined in Clay.Flexbox spaceBetween :: Value Source # | |
SpaceBetween JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
SpaceBetween AlignContentValue Source # | |
Defined in Clay.Flexbox |
class SpaceAround a where Source #
spaceAround :: a Source #
Instances
SpaceAround Value Source # | |
Defined in Clay.Flexbox spaceAround :: Value Source # | |
SpaceAround JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
SpaceAround AlignContentValue Source # | |
Defined in Clay.Flexbox |
class FlexStart a where Source #
Instances
FlexStart Value Source # | |
Defined in Clay.Flexbox | |
FlexStart JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
FlexStart AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
FlexStart AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
FlexStart AlignContentValue Source # | |
Defined in Clay.Flexbox |
class FlexEnd a where Source #
CSS Flexible Box Layout http://dev.w3.org/csswg/css-flexbox-1
Instances
FlexEnd Value Source # | |
Defined in Clay.Flexbox | |
FlexEnd JustifyContentValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd AlignSelfValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd AlignItemsValue Source # | |
Defined in Clay.Flexbox | |
FlexEnd AlignContentValue Source # | |
Defined in Clay.Flexbox |
alignContent :: AlignContentValue -> Css Source #
alignItems :: AlignItemsValue -> Css Source #
alignSelf :: AlignSelfValue -> Css Source #
row :: FlexDirection Source #
flexDirection :: FlexDirection -> Css Source #
flexShrink :: Int -> Css Source #
data FontWeight Source #
Instances
Val FontWeight Source # | |
Other FontWeight Source # | |
Normal FontWeight Source # | |
Defined in Clay.Font normal :: FontWeight Source # | |
Inherit FontWeight Source # | |
Defined in Clay.Font inherit :: FontWeight Source # |
data FontVariant Source #
Instances
Val FontVariant Source # | |
Other FontVariant Source # | |
Normal FontVariant Source # | |
Defined in Clay.Font normal :: FontVariant Source # | |
Inherit FontVariant Source # | |
Defined in Clay.Font |
class Val a => Font a where Source #
We implement the generic font property as a type class that accepts multiple value types. This allows us to combine different font aspects into a shorthand syntax. Fonts require a mandatory part and have a optional a part.
Nothing
fontFamily :: [Text] -> [GenericFontFamily] -> Css Source #
The fontFamily
style rules takes to lists of font families: zero or more
custom font-families and preferably one or more generic font families.
fontSizeCustom :: FontSize -> Css Source #
fontVariant :: FontVariant -> Css Source #
bold :: FontWeight Source #
bolder :: FontWeight Source #
lighter :: FontWeight Source #
weight :: Integer -> FontWeight Source #
fontWeight :: FontWeight -> Css Source #
lineHeight :: Size a -> Css Source #
module Clay.FontFace
module Clay.Geometry
module Clay.Gradient
module Clay.List
data TextOverflow Source #
Instances
Val TextOverflow Source # | |
Initial TextOverflow Source # | |
Defined in Clay.Text | |
None TextOverflow Source # | |
Defined in Clay.Text none :: TextOverflow Source # | |
Inherit TextOverflow Source # | |
Defined in Clay.Text |
data OverflowWrap Source #
Instances
Val OverflowWrap Source # | |
Unset OverflowWrap Source # | |
Defined in Clay.Text unset :: OverflowWrap Source # | |
Initial OverflowWrap Source # | |
Defined in Clay.Text | |
Normal OverflowWrap Source # | |
Defined in Clay.Text | |
Inherit OverflowWrap Source # | |
Defined in Clay.Text |
data TextTransform Source #
Instances
Val TextTransform Source # | |
None TextTransform Source # | |
Defined in Clay.Text none :: TextTransform Source # | |
Inherit TextTransform Source # | |
Defined in Clay.Text |
data TextDecoration Source #
Instances
Val TextDecoration Source # | |
Other TextDecoration Source # | |
None TextDecoration Source # | |
Defined in Clay.Text | |
Inherit TextDecoration Source # | |
Defined in Clay.Text |
data WhiteSpace Source #
Instances
Val WhiteSpace Source # | |
Other WhiteSpace Source # | |
Normal WhiteSpace Source # | |
Defined in Clay.Text normal :: WhiteSpace Source # | |
Inherit WhiteSpace Source # | |
Defined in Clay.Text inherit :: WhiteSpace Source # |
data TextDirection Source #
Instances
Val TextDirection Source # | |
Other TextDirection Source # | |
Normal TextDirection Source # | |
Defined in Clay.Text | |
Inherit TextDirection Source # | |
Defined in Clay.Text |
data TextIndent Source #
Instances
Val TextIndent Source # | |
Other TextIndent Source # | |
Unset TextIndent Source # | |
Defined in Clay.Text unset :: TextIndent Source # | |
Initial TextIndent Source # | |
Defined in Clay.Text initial :: TextIndent Source # | |
Inherit TextIndent Source # | |
Defined in Clay.Text inherit :: TextIndent Source # |
data TextRendering Source #
Instances
Val TextRendering Source # | |
Other TextRendering Source # | |
Inherit TextRendering Source # | |
Defined in Clay.Text | |
Auto TextRendering Source # | |
Defined in Clay.Text auto :: TextRendering Source # |
letterSpacing :: Size a -> Css Source #
wordSpacing :: Size a -> Css Source #
textRendering :: TextRendering -> Css Source #
eachLine :: TextIndent -> TextIndent Source #
Annotate the supplied TextIndent
with each-line
or hanging
or
both.
eachLine . hanging . indent $ px 3 :: TextIndent
hanging :: TextIndent -> TextIndent Source #
Annotate the supplied TextIndent
with each-line
or hanging
or
both.
eachLine . hanging . indent $ px 3 :: TextIndent
indent :: Size a -> TextIndent Source #
textIndent :: TextIndent -> Css Source #
ltr :: TextDirection Source #
rtl :: TextDirection Source #
direction :: TextDirection -> Css Source #
alignString :: Char -> TextAlign Source #
whiteSpace :: WhiteSpace -> Css Source #
nowrap :: WhiteSpace Source #
preWrap :: WhiteSpace Source #
preLine :: WhiteSpace Source #
textDecorationColor :: Color -> Css Source #
textDecoration :: TextDecoration -> Css Source #
textDecorationStyle :: Stroke -> Css Source #
textTransform :: TextTransform -> Css Source #
wordWrap :: OverflowWrap -> Css Source #
overflowWrap :: OverflowWrap -> Css Source #
textOverflow :: TextOverflow -> Css Source #
attrContent :: Text -> Content Source #
stringContent :: Text -> Content Source #
uriContent :: Text -> Content Source #
urlContent :: Text -> Content Source #
closeQuote :: Content Source #
module Clay.Transform
module Clay.Transition
module Clay.Animation
data MaskComposite Source #
Instances
Val MaskComposite Source # | |
Other MaskComposite Source # | |
None MaskComposite Source # | |
Defined in Clay.Mask none :: MaskComposite Source # | |
Inherit MaskComposite Source # | |
Defined in Clay.Mask | |
Mask MaskComposite Source # | |
class Val a => Mask a where Source #
We implement the generic mask property as a type class that accepts multiple value types. This allows us to combine different mask aspects into a shorthand syntax.
Nothing
Instances
Mask BackgroundAttachment Source # | |
Mask BackgroundClip Source # | |
Mask BackgroundOrigin Source # | |
Mask BackgroundImage Source # | |
Mask BackgroundRepeat Source # | |
Mask BackgroundSize Source # | |
Mask BackgroundPosition Source # | |
Mask MaskComposite Source # | |
Mask a => Mask [a] Source # | |
(Mask a, Mask b) => Mask (a, b) Source # | |
copy :: MaskComposite Source #
xor :: MaskComposite Source #
maskComposite :: MaskComposite -> Css Source #
maskComposites :: [MaskComposite] -> Css Source #
maskPosition :: BackgroundPosition -> Css Source #
maskPositions :: [BackgroundPosition] -> Css Source #
maskSize :: BackgroundSize -> Css Source #
maskSizes :: [BackgroundSize] -> Css Source #
maskRepeat :: BackgroundRepeat -> Css Source #
maskRepeats :: [BackgroundRepeat] -> Css Source #
maskImage :: BackgroundImage -> Css Source #
maskImages :: [BackgroundImage] -> Css Source #
maskOrigin :: BackgroundOrigin -> Css Source #
maskOrigins :: [BackgroundOrigin] -> Css Source #
maskClip :: BackgroundClip -> Css Source #
maskClips :: [BackgroundClip] -> Css Source #
maskAttachments :: [BackgroundAttachment] -> Css Source #
brightness :: Double -> Filter Source #
dropShadow :: Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Color -> Filter Source #
Writing your own properties.
module Clay.Property