Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Clay
Contents
- 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
- (|~) :: 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 -> [(Number, Css)] -> Css
- keyframesFromTo :: Text -> Css -> Css -> Css
- fontFace :: Css -> Css
- important :: Css -> Css
- importUrl :: Text -> Css
- inRange :: Refinement
- not :: Selector -> Refinement
- empty :: Refinement
- optional :: Refinement
- link :: Refinement
- valid :: Refinement
- target :: Refinement
- checked :: Refinement
- disabled :: Refinement
- after :: Refinement
- before :: Refinement
- firstLetter :: Refinement
- firstLine :: Refinement
- selection :: Refinement
- backdrop :: Refinement
- visited :: Refinement
- active :: Refinement
- hover :: Refinement
- focus :: Refinement
- firstChild :: Refinement
- lastChild :: Refinement
- enabled :: Refinement
- firstOfType :: Refinement
- indeterminate :: Refinement
- invalid :: Refinement
- lastOfType :: Refinement
- onlyChild :: Refinement
- onlyOfType :: Refinement
- outOfRange :: Refinement
- nthChild :: Text -> Refinement
- nthLastChild :: Text -> Refinement
- nthLastOfType :: Text -> Refinement
- nthOfType :: Text -> Refinement
- id :: Refinement
- for :: Refinement
- loop :: Refinement
- max :: Refinement
- min :: Refinement
- step :: Refinement
- list :: Refinement
- pattern :: Refinement
- default_ :: Refinement
- required :: Refinement
- lang :: Refinement
- wrap :: Refinement
- icon :: 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
- defer :: Refinement
- dir :: Refinement
- dirname :: Refinement
- download :: Refinement
- draggable :: Refinement
- dropzone :: Refinement
- enctype :: Refinement
- formaction :: Refinement
- formenctype :: Refinement
- formmethod :: Refinement
- formnovalidate :: Refinement
- formtarget :: Refinement
- headers :: Refinement
- high :: Refinement
- href :: Refinement
- hreflang :: Refinement
- httpEquiv :: Refinement
- inert :: Refinement
- inputmode :: Refinement
- ismap :: Refinement
- itemid :: Refinement
- itemprop :: Refinement
- itemref :: Refinement
- itemscope :: Refinement
- itemtype :: Refinement
- keytype :: Refinement
- kind :: Refinement
- low :: Refinement
- manifest :: Refinement
- maxlength :: Refinement
- media :: Refinement
- mediagroup :: Refinement
- method :: Refinement
- multiple :: Refinement
- muted :: Refinement
- name :: Refinement
- novalidate :: Refinement
- open :: Refinement
- optimum :: Refinement
- ping :: Refinement
- placeholder :: Refinement
- poster :: Refinement
- preload :: Refinement
- radiogroup :: Refinement
- readonly :: Refinement
- rel :: 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
- tabindex :: Refinement
- type_ :: Refinement
- typemustmatch :: Refinement
- usemap :: Refinement
- base :: Selector
- time :: Selector
- head :: Selector
- map :: Selector
- span :: IsString a => a
- div :: Selector
- option :: Selector
- label :: IsString a => a
- select :: Selector
- style :: IsString a => a
- table :: Selector
- menu :: Selector
- caption :: Selector
- small :: Selector
- pre :: Selector
- a :: Selector
- abbr :: IsString a => a
- cite :: IsString a => a
- command :: IsString a => a
- data_ :: IsString a => a
- form :: IsString a => a
- title :: IsString a => a
- s :: Selector
- p :: Selector
- b :: Selector
- u :: Selector
- i :: Selector
- q :: Selector
- code :: Selector
- h1 :: Selector
- address :: Selector
- area :: Selector
- article :: Selector
- aside :: Selector
- audio :: Selector
- bdi :: Selector
- bdo :: Selector
- blockquote :: Selector
- body :: Selector
- br :: Selector
- button :: Selector
- canvas :: Selector
- col :: Selector
- colgroup :: Selector
- datalist :: Selector
- dd :: Selector
- del :: Selector
- details :: Selector
- dfn :: Selector
- dialog :: Selector
- dl :: Selector
- dt :: Selector
- embed :: Selector
- fieldset :: Selector
- figcaption :: Selector
- figure :: Selector
- footer :: Selector
- h2 :: Selector
- h3 :: Selector
- h4 :: Selector
- h5 :: Selector
- h6 :: Selector
- header :: Selector
- hgroup :: Selector
- hr :: Selector
- html :: Selector
- iframe :: Selector
- img :: Selector
- input :: Selector
- ins :: Selector
- kbd :: Selector
- keygen :: Selector
- legend :: Selector
- li :: Selector
- main_ :: Selector
- mark :: Selector
- math :: Selector
- meta :: Selector
- meter :: Selector
- nav :: Selector
- noscript :: Selector
- object :: Selector
- ol :: Selector
- optgroup :: Selector
- output :: Selector
- param :: Selector
- progress :: Selector
- rp :: Selector
- rt :: Selector
- ruby :: Selector
- samp :: Selector
- script :: Selector
- section :: Selector
- source :: Selector
- strong :: Selector
- sub :: Selector
- summary :: Selector
- sup :: Selector
- svg :: Selector
- tbody :: Selector
- td :: Selector
- template :: Selector
- textarea :: Selector
- tfoot :: Selector
- th :: Selector
- thead :: Selector
- tr :: Selector
- track :: 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
- data Overflow
- data Display
- data FloatStyle
- data Clear
- data Position
- data Visibility
- data Clip
- data PointerEvents
- class Val a => VerticalAlign a where
- verticalAlign :: a -> Css
- class Val a => Cursor a where
- inline :: Display
- clear :: Clear -> Css
- float :: FloatStyle -> Css
- static :: Position
- flex :: Display
- opacity :: Number -> Css
- floatLeft :: FloatStyle
- floatRight :: FloatStyle
- both :: Clear
- clearLeft :: Clear
- clearRight :: Clear
- position :: Position -> Css
- absolute :: Position
- fixed :: Position
- relative :: Position
- sticky :: Position
- display :: Display -> Css
- 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
- inlineFlex :: Display
- grid :: Display
- inlineGrid :: Display
- 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
- zIndex :: Integer -> Css
- pointerEvents :: PointerEvents -> Css
- visiblePainted :: PointerEvents
- visibleFill :: PointerEvents
- visibleStroke :: PointerEvents
- painted :: PointerEvents
- fillEvents :: PointerEvents
- strokeEvents :: PointerEvents
- allEvents :: PointerEvents
- middle :: VerticalAlignValue
- vAlignSub :: VerticalAlignValue
- vAlignSuper :: VerticalAlignValue
- textTop :: VerticalAlignValue
- textBottom :: VerticalAlignValue
- vAlignTop :: VerticalAlignValue
- vAlignBottom :: VerticalAlignValue
- vAlignBaseline :: 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
- class FlexEnd a where
- flexEnd :: a
- class FlexStart a where
- flexStart :: a
- class SpaceAround a where
- spaceAround :: a
- class SpaceBetween a where
- spaceBetween :: a
- class SpaceEvenly a where
- spaceEvenly :: a
- class Stretch a where
- stretch :: a
- newtype AlignContentValue = AlignContentValue Value
- newtype AlignItemsValue = AlignItemValue Value
- newtype AlignSelfValue = AlignSelfValue Value
- newtype FlexDirection = FlexDirection Value
- newtype FlexWrap = FlexWrap Value
- newtype JustifyContentValue = JustifyContentValue Value
- 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
- class Val a => Font a where
- data Optional = Optional (Maybe FontWeight) (Maybe FontVariant) (Maybe FontStyle)
- data Required a = Required (Size a) (Maybe (Size a)) [Text] [GenericFontFamily]
- data FontSize
- data FontStyle
- data FontVariant
- data FontWeight
- data NamedFont
- smaller :: FontSize
- larger :: FontSize
- fontColor :: Color -> Css
- color :: Color -> Css
- fontFamily :: [Text] -> [GenericFontFamily] -> Css
- sansSerif :: GenericFontFamily
- serif :: GenericFontFamily
- monospace :: GenericFontFamily
- cursive :: GenericFontFamily
- fantasy :: GenericFontFamily
- fontSize :: Size a -> Css
- fontSizeCustom :: FontSize -> Css
- xxSmall :: FontSize
- xSmall :: FontSize
- medium :: FontSize
- large :: FontSize
- xLarge :: FontSize
- xxLarge :: FontSize
- fontStyle :: FontStyle -> Css
- italic :: FontStyle
- oblique :: FontStyle
- fontVariant :: FontVariant -> Css
- smallCaps :: FontVariant
- fontWeight :: FontWeight -> Css
- bold :: FontWeight
- bolder :: FontWeight
- lighter :: FontWeight
- weight :: Integer -> FontWeight
- messageBox :: NamedFont
- smallCaption :: NamedFont
- statusBar :: NamedFont
- lineHeight :: Size a -> Css
- module Clay.FontFace
- module Clay.Geometry
- module Clay.Gradient
- module Clay.Grid
- module Clay.List
- data TextRendering
- data TextIndent
- data TextDirection
- data TextAlign
- data WhiteSpace
- data TextDecoration
- data TextTransform
- data TextOverflow
- data WordBreak
- data OverflowWrap
- data Hyphens
- data HyphenateCharacter
- data HyphenateLimit
- data Content
- indent :: Size a -> TextIndent
- content :: Content -> Css
- start :: TextAlign
- nowrap :: WhiteSpace
- letterSpacing :: Size a -> Css
- wordSpacing :: Size a -> Css
- textRendering :: TextRendering -> Css
- optimizeSpeed :: TextRendering
- optimizeLegibility :: TextRendering
- geometricPrecision :: TextRendering
- textShadow :: Size a -> Size a -> Size a -> Color -> Css
- textIndent :: TextIndent -> Css
- eachLine :: TextIndent -> TextIndent
- hanging :: TextIndent -> TextIndent
- direction :: TextDirection -> Css
- ltr :: TextDirection
- rtl :: TextDirection
- textAlign :: TextAlign -> Css
- textAlignLast :: TextAlign -> Css
- justify :: TextAlign
- matchParent :: TextAlign
- end :: TextAlign
- alignSide :: Side -> TextAlign
- alignString :: Char -> TextAlign
- whiteSpace :: WhiteSpace -> Css
- preWrap :: WhiteSpace
- preLine :: WhiteSpace
- textDecoration :: TextDecoration -> Css
- textDecorationStyle :: Stroke -> Css
- textDecorationLine :: TextDecoration -> Css
- textDecorationColor :: Color -> Css
- underline :: TextDecoration
- overline :: TextDecoration
- lineThrough :: TextDecoration
- blink :: TextDecoration
- textTransform :: TextTransform -> Css
- capitalize :: TextTransform
- uppercase :: TextTransform
- lowercase :: TextTransform
- fullWidth :: TextTransform
- textOverflow :: TextOverflow -> Css
- overflowClip :: TextOverflow
- overflowEllipsis :: TextOverflow
- wordBreak :: WordBreak -> Css
- breakAll :: WordBreak
- keepAll :: WordBreak
- overflowWrap :: OverflowWrap -> Css
- wordWrap :: OverflowWrap -> Css
- breakWord :: OverflowWrap
- hyphens :: Hyphens -> Css
- hyphenateCharacter :: HyphenateCharacter -> Css
- hyphenateLimitChars :: HyphenateLimit -> HyphenateLimit -> HyphenateLimit -> Css
- manual :: Hyphens
- contents :: [Content] -> Css
- attrContent :: Text -> Content
- stringContent :: Text -> Content
- uriContent :: Text -> Content
- urlContent :: Text -> Content
- openQuote :: Content
- closeQuote :: Content
- noOpenQuote :: Content
- noCloseQuote :: Content
- module Clay.Transform
- module Clay.Transition
- module Clay.Animation
- class Val a => Mask a where
- data MaskComposite
- xor :: MaskComposite
- copy :: MaskComposite
- sourceOver :: MaskComposite
- sourceIn :: MaskComposite
- sourceOut :: MaskComposite
- sourceAtop :: MaskComposite
- destinationOver :: MaskComposite
- destinationIn :: MaskComposite
- destinationOut :: MaskComposite
- destinationAtop :: 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
- maskOrigin :: BackgroundOrigin -> Css
- maskOrigins :: [BackgroundOrigin] -> Css
- maskClip :: BackgroundClip -> Css
- maskClips :: [BackgroundClip] -> Css
- maskAttachment :: BackgroundAttachment -> Css
- maskAttachments :: [BackgroundAttachment] -> Css
- maskImage :: BackgroundImage -> Css
- maskImages :: [BackgroundImage] -> Css
- data Filter
- filter :: Filter -> Css
- filters :: [Filter] -> Css
- blur :: Size LengthUnit -> Filter
- brightness :: Number -> 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
IsString Refinement Source # | |
Defined in Clay.Selector Methods fromString :: String -> Refinement # | |
Monoid Refinement Source # | |
Defined in Clay.Selector Methods mempty :: Refinement # mappend :: Refinement -> Refinement -> Refinement # mconcat :: [Refinement] -> Refinement # | |
Semigroup Refinement Source # | |
Defined in Clay.Selector Methods (<>) :: Refinement -> Refinement -> Refinement # sconcat :: NonEmpty Refinement -> Refinement # stimes :: Integral b => b -> Refinement -> Refinement # | |
Show Refinement Source # | |
Defined in Clay.Selector Methods showsPrec :: Int -> Refinement -> ShowS # show :: Refinement -> String # showList :: [Refinement] -> ShowS # |
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.
(|~) :: Selector -> Selector -> Selector Source #
The general sibling 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.
inRange :: Refinement Source #
not :: Selector -> Refinement Source #
empty :: Refinement Source #
link :: Refinement Source #
valid :: Refinement Source #
target :: Refinement Source #
checked :: Refinement Source #
after :: Refinement Source #
before :: Refinement Source #
visited :: Refinement Source #
active :: Refinement Source #
hover :: Refinement Source #
focus :: Refinement Source #
enabled :: Refinement Source #
invalid :: Refinement Source #
nthChild :: Text -> Refinement Source #
nthLastChild :: Text -> Refinement Source #
nthLastOfType :: Text -> Refinement Source #
nthOfType :: Text -> Refinement Source #
HTML5 attribute and element names.
id :: Refinement Source #
for :: Refinement Source #
loop :: Refinement Source #
max :: Refinement Source #
min :: Refinement Source #
step :: Refinement Source #
list :: Refinement Source #
pattern :: Refinement Source #
lang :: Refinement Source #
wrap :: Refinement Source #
icon :: Refinement Source #
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 #
headers :: Refinement Source #
high :: Refinement Source #
href :: Refinement Source #
inert :: Refinement Source #
ismap :: Refinement Source #
itemid :: Refinement Source #
itemref :: Refinement Source #
keytype :: Refinement Source #
kind :: Refinement Source #
low :: Refinement Source #
media :: Refinement Source #
method :: Refinement Source #
muted :: Refinement Source #
name :: Refinement Source #
open :: Refinement Source #
optimum :: 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 #
type_ :: Refinement Source #
usemap :: Refinement Source #
span :: 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.
style :: IsString a => a Source #
Special cases, these items occur both as an HTML tag and an HTML attribute. We keep them polymorph.
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.
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
data FloatStyle Source #
Instances
Inherit FloatStyle Source # | |
Defined in Clay.Display Methods inherit :: FloatStyle Source # | |
None FloatStyle Source # | |
Defined in Clay.Display Methods none :: FloatStyle Source # | |
Val FloatStyle Source # | |
Defined in Clay.Display Methods value :: FloatStyle -> Value Source # |
data Visibility Source #
Instances
Hidden Visibility Source # | |
Defined in Clay.Display Methods hidden :: Visibility Source # | |
Inherit Visibility Source # | |
Defined in Clay.Display Methods inherit :: Visibility Source # | |
Other Visibility Source # | |
Defined in Clay.Display Methods other :: Value -> Visibility Source # | |
Unset Visibility Source # | |
Defined in Clay.Display Methods unset :: Visibility Source # | |
Visible Visibility Source # | |
Defined in Clay.Display Methods visible :: Visibility Source # | |
Val Visibility Source # | |
Defined in Clay.Display Methods value :: Visibility -> Value Source # |
data PointerEvents Source #
Instances
Auto PointerEvents Source # | |
Defined in Clay.Display Methods auto :: PointerEvents Source # | |
Inherit PointerEvents Source # | |
Defined in Clay.Display Methods | |
None PointerEvents Source # | |
Defined in Clay.Display Methods none :: PointerEvents Source # | |
Other PointerEvents Source # | |
Defined in Clay.Display Methods other :: Value -> PointerEvents Source # | |
Visible PointerEvents Source # | |
Defined in Clay.Display Methods | |
Val PointerEvents Source # | |
Defined in Clay.Display Methods value :: PointerEvents -> Value Source # |
class Val a => VerticalAlign a where Source #
Minimal complete definition
Nothing
Methods
verticalAlign :: a -> Css Source #
Instances
VerticalAlign (Size a) Source # | |
Defined in Clay.Display Methods verticalAlign :: Size a -> Css Source # |
float :: FloatStyle -> Css Source #
clearRight :: Clear Source #
inlineFlex :: Display Source #
inlineGrid :: Display Source #
visibility :: Visibility -> Css Source #
pointerEvents :: PointerEvents -> Css Source #
vAlignSuper :: VerticalAlignValue Source #
textBottom :: VerticalAlignValue Source #
vAlignBottom :: VerticalAlignValue Source #
vAlignBaseline :: 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
class FlexEnd a where Source #
CSS Flexible Box Layout http://dev.w3.org/csswg/css-flexbox-1
Instances
FlexEnd AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexEnd AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexEnd AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexEnd JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexEnd Value Source # | |
Defined in Clay.Flexbox |
class FlexStart a where Source #
Instances
FlexStart AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart Value Source # | |
Defined in Clay.Flexbox |
class SpaceAround a where Source #
Methods
spaceAround :: a Source #
Instances
SpaceAround AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceAround JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceAround Value Source # | |
Defined in Clay.Flexbox Methods spaceAround :: Value Source # |
class SpaceBetween a where Source #
Methods
spaceBetween :: a Source #
Instances
SpaceBetween AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceBetween JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceBetween Value Source # | |
Defined in Clay.Flexbox Methods spaceBetween :: Value Source # |
class SpaceEvenly a where Source #
Methods
spaceEvenly :: a Source #
Instances
SpaceEvenly AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceEvenly JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceEvenly Value Source # | |
Defined in Clay.Flexbox Methods spaceEvenly :: Value Source # |
class Stretch a where Source #
Instances
Stretch AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Stretch AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
Stretch AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Stretch Value Source # | |
Defined in Clay.Flexbox |
newtype AlignContentValue Source #
Constructors
AlignContentValue Value |
Instances
Center AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Inherit AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Other AlignContentValue Source # | |
Defined in Clay.Flexbox Methods other :: Value -> AlignContentValue Source # | |
FlexEnd AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceAround AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceBetween AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceEvenly AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Stretch AlignContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Val AlignContentValue Source # | |
Defined in Clay.Flexbox Methods value :: AlignContentValue -> Value Source # |
newtype AlignItemsValue Source #
Constructors
AlignItemValue Value |
Instances
Baseline AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
Center AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
Inherit AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
Other AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods other :: Value -> AlignItemsValue Source # | |
FlexEnd AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
Stretch AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods | |
Val AlignItemsValue Source # | |
Defined in Clay.Flexbox Methods value :: AlignItemsValue -> Value Source # |
newtype AlignSelfValue Source #
Constructors
AlignSelfValue Value |
Instances
Auto AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Baseline AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Center AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Inherit AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Other AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods other :: Value -> AlignSelfValue Source # | |
FlexEnd AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Stretch AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods | |
Val AlignSelfValue Source # | |
Defined in Clay.Flexbox Methods value :: AlignSelfValue -> Value Source # |
newtype FlexDirection Source #
Constructors
FlexDirection Value |
Instances
Other FlexDirection Source # | |
Defined in Clay.Flexbox Methods other :: Value -> FlexDirection Source # | |
Val FlexDirection Source # | |
Defined in Clay.Flexbox Methods value :: FlexDirection -> Value Source # |
newtype JustifyContentValue Source #
Constructors
JustifyContentValue Value |
Instances
Center JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Inherit JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Other JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods other :: Value -> JustifyContentValue Source # | |
FlexEnd JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
FlexStart JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceAround JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceBetween JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
SpaceEvenly JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods | |
Val JustifyContentValue Source # | |
Defined in Clay.Flexbox Methods value :: JustifyContentValue -> Value Source # |
alignContent :: AlignContentValue -> Css Source #
alignItems :: AlignItemsValue -> Css Source #
alignSelf :: AlignSelfValue -> Css Source #
row :: FlexDirection Source #
flexDirection :: FlexDirection -> Css Source #
flexShrink :: Int -> Css Source #
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.
Minimal complete definition
Nothing
Constructors
Optional (Maybe FontWeight) (Maybe FontVariant) (Maybe FontStyle) |
Instances
data FontVariant Source #
Instances
Inherit FontVariant Source # | |
Defined in Clay.Font Methods | |
Normal FontVariant Source # | |
Defined in Clay.Font Methods normal :: FontVariant Source # | |
Other FontVariant Source # | |
Val FontVariant Source # | |
data FontWeight Source #
Instances
Inherit FontWeight Source # | |
Defined in Clay.Font Methods inherit :: FontWeight Source # | |
Normal FontWeight Source # | |
Defined in Clay.Font Methods normal :: FontWeight Source # | |
Other FontWeight Source # | |
Val FontWeight Source # | |
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 #
fontWeight :: FontWeight -> Css Source #
bold :: FontWeight Source #
bolder :: FontWeight Source #
lighter :: FontWeight Source #
weight :: Integer -> FontWeight Source #
lineHeight :: Size a -> Css Source #
module Clay.FontFace
module Clay.Geometry
module Clay.Gradient
module Clay.Grid
module Clay.List
data TextRendering Source #
Instances
Auto TextRendering Source # | |
Defined in Clay.Text Methods auto :: TextRendering Source # | |
Inherit TextRendering Source # | |
Defined in Clay.Text Methods | |
Other TextRendering Source # | |
Val TextRendering Source # | |
data TextIndent Source #
Instances
Inherit TextIndent Source # | |
Defined in Clay.Text Methods inherit :: TextIndent Source # | |
Initial TextIndent Source # | |
Defined in Clay.Text Methods initial :: TextIndent Source # | |
Other TextIndent Source # | |
Unset TextIndent Source # | |
Defined in Clay.Text Methods unset :: TextIndent Source # | |
Val TextIndent Source # | |
data TextDirection Source #
Instances
Inherit TextDirection Source # | |
Defined in Clay.Text Methods | |
Normal TextDirection Source # | |
Defined in Clay.Text Methods | |
Other TextDirection Source # | |
Val TextDirection Source # | |
data WhiteSpace Source #
Instances
Inherit WhiteSpace Source # | |
Defined in Clay.Text Methods inherit :: WhiteSpace Source # | |
Normal WhiteSpace Source # | |
Defined in Clay.Text Methods normal :: WhiteSpace Source # | |
Other WhiteSpace Source # | |
Val WhiteSpace Source # | |
data TextDecoration Source #
Instances
Inherit TextDecoration Source # | |
Defined in Clay.Text Methods | |
None TextDecoration Source # | |
Defined in Clay.Text Methods | |
Other TextDecoration Source # | |
Val TextDecoration Source # | |
data TextTransform Source #
Instances
Inherit TextTransform Source # | |
Defined in Clay.Text Methods | |
None TextTransform Source # | |
Defined in Clay.Text Methods none :: TextTransform Source # | |
Val TextTransform Source # | |
data TextOverflow Source #
Instances
Inherit TextOverflow Source # | |
Defined in Clay.Text Methods | |
Initial TextOverflow Source # | |
Defined in Clay.Text Methods | |
None TextOverflow Source # | |
Defined in Clay.Text Methods none :: TextOverflow Source # | |
Val TextOverflow Source # | |
data OverflowWrap Source #
Instances
Inherit OverflowWrap Source # | |
Defined in Clay.Text Methods | |
Initial OverflowWrap Source # | |
Defined in Clay.Text Methods | |
Normal OverflowWrap Source # | |
Defined in Clay.Text Methods | |
Unset OverflowWrap Source # | |
Defined in Clay.Text Methods unset :: OverflowWrap Source # | |
Val OverflowWrap Source # | |
Type for values which can be provided to hyphens
.
data HyphenateCharacter Source #
Type for values which can be provided to hyphenateCharacter
.
Instances
IsString HyphenateCharacter Source # | |
Defined in Clay.Text Methods fromString :: String -> HyphenateCharacter # | |
Auto HyphenateCharacter Source # | |
Defined in Clay.Text Methods | |
Inherit HyphenateCharacter Source # | |
Defined in Clay.Text Methods | |
Initial HyphenateCharacter Source # | |
Defined in Clay.Text Methods | |
Other HyphenateCharacter Source # | |
Unset HyphenateCharacter Source # | |
Defined in Clay.Text Methods | |
Val HyphenateCharacter Source # | |
data HyphenateLimit Source #
Type for values which can be provded to hyphenateLimitChars
.
Instances
Num HyphenateLimit Source # | |
Defined in Clay.Text Methods (+) :: HyphenateLimit -> HyphenateLimit -> HyphenateLimit # (-) :: HyphenateLimit -> HyphenateLimit -> HyphenateLimit # (*) :: HyphenateLimit -> HyphenateLimit -> HyphenateLimit # negate :: HyphenateLimit -> HyphenateLimit # abs :: HyphenateLimit -> HyphenateLimit # signum :: HyphenateLimit -> HyphenateLimit # fromInteger :: Integer -> HyphenateLimit # | |
Auto HyphenateLimit Source # | |
Defined in Clay.Text Methods | |
Inherit HyphenateLimit Source # | |
Defined in Clay.Text Methods | |
Initial HyphenateLimit Source # | |
Defined in Clay.Text Methods | |
Other HyphenateLimit Source # | |
Unset HyphenateLimit Source # | |
Defined in Clay.Text Methods | |
Val HyphenateLimit Source # | |
indent :: Size a -> TextIndent Source #
nowrap :: WhiteSpace Source #
letterSpacing :: Size a -> Css Source #
wordSpacing :: Size a -> Css Source #
textRendering :: TextRendering -> Css Source #
textIndent :: TextIndent -> 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
direction :: TextDirection -> Css Source #
ltr :: TextDirection Source #
rtl :: TextDirection Source #
textAlignLast :: TextAlign -> Css Source #
alignString :: Char -> TextAlign Source #
whiteSpace :: WhiteSpace -> Css Source #
preWrap :: WhiteSpace Source #
preLine :: WhiteSpace Source #
textDecoration :: TextDecoration -> Css Source #
textDecorationStyle :: Stroke -> Css Source #
textDecorationColor :: Color -> Css Source #
textTransform :: TextTransform -> Css Source #
textOverflow :: TextOverflow -> Css Source #
overflowWrap :: OverflowWrap -> Css Source #
wordWrap :: OverflowWrap -> Css Source #
hyphens :: Hyphens -> Css Source #
Specifies how words should be hyphenated.
Possible values are:
none
- No hyphenation. Words will not be hyphenated even if it is explicitly suggested for a word.
manual
- Manual hyphenation.
Specific characters such as
­
in a word will suggest break points. This is the default. auto
- Automatic hyphenation. The browser is free to hyphenate words as it sees fit. However, explicitly suggested break points will take precedence.
For example,
>>>
hyphens auto
The hyphenation rules depend on the language,
which must be specified by the lang
attribute.
For reference, see
hyphens
.
hyphenateCharacter :: HyphenateCharacter -> Css Source #
Customizes the character used for hyphenation.
For example,
>>>
hyphenateCharacter "~"
For reference, see
hyphenate-character
.
Arguments
:: HyphenateLimit | Minimum length of a word which can be hyphenated. |
-> HyphenateLimit | Minimum number of characters allowed before a break point. |
-> HyphenateLimit | Minimum number of characters allowed after a break point. |
-> Css |
Adjusts the minumum number of characters involved in hyphenation.
I.e., specifies the minumum number of characters allowed in a breakable word, before a break point, and after a break point when hyphenating a word.
For example,
>>>
hyphenateLimitChars 14 auto auto
For reference, see
hyphenate-limit-chars
.
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
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.
Minimal complete definition
Nothing
Instances
Mask BackgroundAttachment Source # | |
Mask BackgroundClip Source # | |
Mask BackgroundImage Source # | |
Mask BackgroundOrigin Source # | |
Mask BackgroundPosition Source # | |
Mask BackgroundRepeat Source # | |
Mask BackgroundSize Source # | |
Mask MaskComposite Source # | |
Mask a => Mask [a] Source # | |
(Mask a, Mask b) => Mask (a, b) Source # | |
data MaskComposite Source #
Instances
Inherit MaskComposite Source # | |
Defined in Clay.Mask Methods | |
None MaskComposite Source # | |
Defined in Clay.Mask Methods none :: MaskComposite Source # | |
Other MaskComposite Source # | |
Mask MaskComposite Source # | |
Val MaskComposite Source # | |
xor :: MaskComposite Source #
copy :: 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 #
maskOrigin :: BackgroundOrigin -> Css Source #
maskOrigins :: [BackgroundOrigin] -> Css Source #
maskClip :: BackgroundClip -> Css Source #
maskClips :: [BackgroundClip] -> Css Source #
maskAttachments :: [BackgroundAttachment] -> Css Source #
maskImage :: BackgroundImage -> Css Source #
maskImages :: [BackgroundImage] -> Css Source #
brightness :: Number -> Filter Source #
dropShadow :: Size LengthUnit -> Size LengthUnit -> Size LengthUnit -> Color -> Filter Source #
Writing your own properties.
module Clay.Property