clay-0.15.0: CSS preprocessor as embedded Haskell.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Clay

Synopsis

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.

pretty :: Config Source #

Configuration to print to a pretty human readable CSS output.

compact :: Config Source #

Configuration to print to a compacted unreadable CSS output.

renderSelector :: Selector -> Text Source #

Render a single CSS Selector.

The Css monad for collecting style rules.

type Css = StyleM () Source #

The Css context is used to collect style rules which are mappings from selectors to style properties. The Css type is a computation in the StyleM monad that just collects and doesn't return anything.

(?) :: 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.

root :: Selector -> Css -> Css Source #

Root is used to add style rules to the top scope.

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

Instances details
IsString Refinement Source # 
Instance details

Defined in Clay.Selector

Monoid Refinement Source # 
Instance details

Defined in Clay.Selector

Semigroup Refinement Source # 
Instance details

Defined in Clay.Selector

Show Refinement Source # 
Instance details

Defined in Clay.Selector

Elements selectors.

star :: Selector Source #

The star selector applies to all elements. Maps to * in CSS.

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.

fontFace :: Css -> Css Source #

Define a new font-face.

!important

important :: Css -> Css Source #

Indicate the supplied css should override css declarations that would otherwise take precedence.

Use sparingly.

Import other CSS files

importUrl :: Text -> Css Source #

Import a CSS file from a URL

Pseudo elements and classes.

HTML5 attribute and element names.

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.

Embedded style properties.

module Clay.Box

data Overflow Source #

Instances

Instances details
Auto Overflow Source # 
Instance details

Defined in Clay.Display

Methods

auto :: Overflow Source #

Hidden Overflow Source # 
Instance details

Defined in Clay.Display

Inherit Overflow Source # 
Instance details

Defined in Clay.Display

Other Overflow Source # 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Overflow Source #

Visible Overflow Source # 
Instance details

Defined in Clay.Display

Val Overflow Source # 
Instance details

Defined in Clay.Display

Methods

value :: Overflow -> Value Source #

data Display Source #

Instances

Instances details
Inherit Display Source # 
Instance details

Defined in Clay.Display

None Display Source # 
Instance details

Defined in Clay.Display

Methods

none :: Display Source #

Other Display Source # 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Display Source #

Val Display Source # 
Instance details

Defined in Clay.Display

Methods

value :: Display -> Value Source #

data FloatStyle Source #

Instances

Instances details
Inherit FloatStyle Source # 
Instance details

Defined in Clay.Display

None FloatStyle Source # 
Instance details

Defined in Clay.Display

Val FloatStyle Source # 
Instance details

Defined in Clay.Display

data Clear Source #

Instances

Instances details
Inherit Clear Source # 
Instance details

Defined in Clay.Display

Methods

inherit :: Clear Source #

None Clear Source # 
Instance details

Defined in Clay.Display

Methods

none :: Clear Source #

Other Clear Source # 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Clear Source #

Val Clear Source # 
Instance details

Defined in Clay.Display

Methods

value :: Clear -> Value Source #

data Position Source #

Instances

Instances details
Inherit Position Source # 
Instance details

Defined in Clay.Display

Other Position Source # 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Position Source #

Val Position Source # 
Instance details

Defined in Clay.Display

Methods

value :: Position -> Value Source #

data Visibility Source #

Instances

Instances details
Hidden Visibility Source # 
Instance details

Defined in Clay.Display

Inherit Visibility Source # 
Instance details

Defined in Clay.Display

Other Visibility Source # 
Instance details

Defined in Clay.Display

Unset Visibility Source # 
Instance details

Defined in Clay.Display

Visible Visibility Source # 
Instance details

Defined in Clay.Display

Val Visibility Source # 
Instance details

Defined in Clay.Display

data Clip Source #

Instances

Instances details
Auto Clip Source # 
Instance details

Defined in Clay.Display

Methods

auto :: Clip Source #

Inherit Clip Source # 
Instance details

Defined in Clay.Display

Methods

inherit :: Clip Source #

Other Clip Source # 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Clip Source #

Val Clip Source # 
Instance details

Defined in Clay.Display

Methods

value :: Clip -> Value Source #

data PointerEvents Source #

Instances

Instances details
Auto PointerEvents Source # 
Instance details

Defined in Clay.Display

Inherit PointerEvents Source # 
Instance details

Defined in Clay.Display

None PointerEvents Source # 
Instance details

Defined in Clay.Display

Other PointerEvents Source # 
Instance details

Defined in Clay.Display

Visible PointerEvents Source # 
Instance details

Defined in Clay.Display

Val PointerEvents Source # 
Instance details

Defined in Clay.Display

class Val a => VerticalAlign a where Source #

Minimal complete definition

Nothing

Methods

verticalAlign :: a -> Css Source #

Instances

Instances details
VerticalAlign (Size a) Source # 
Instance details

Defined in Clay.Display

Methods

verticalAlign :: Size a -> Css Source #

class Val a => Cursor a where Source #

Minimal complete definition

Nothing

Methods

cursor :: a -> Css Source #

rect :: Size a -> Size a -> Size a -> Size a -> Clip Source #

middle :: VerticalAlignValue Source #

vAlignSub :: VerticalAlignValue Source #

vAlignSuper :: VerticalAlignValue Source #

textTop :: VerticalAlignValue Source #

textBottom :: VerticalAlignValue Source #

vAlignTop :: VerticalAlignValue Source #

vAlignBottom :: VerticalAlignValue Source #

vAlignBaseline :: VerticalAlignValue Source #

cursorUrl :: Text -> CursorValue Value Source #

cursorDefault :: CursorValue Value Source #

contextMenu :: CursorValue Value Source #

help :: CursorValue Value Source #

pointer :: CursorValue Value Source #

cursorProgress :: CursorValue Value Source #

wait :: CursorValue Value Source #

cell :: CursorValue Value Source #

crosshair :: CursorValue Value Source #

cursorText :: CursorValue Value Source #

vText :: CursorValue Value Source #

alias :: CursorValue Value Source #

cursorCopy :: CursorValue Value Source #

move :: CursorValue Value Source #

noDrop :: CursorValue Value Source #

notAllowed :: CursorValue Value Source #

grab :: CursorValue Value Source #

grabbing :: CursorValue Value Source #

allScroll :: CursorValue Value Source #

colResize :: CursorValue Value Source #

rowResize :: CursorValue Value Source #

nResize :: CursorValue Value Source #

eResize :: CursorValue Value Source #

sResize :: CursorValue Value Source #

wResize :: CursorValue Value Source #

neResize :: CursorValue Value Source #

nwResize :: CursorValue Value Source #

seResize :: CursorValue Value Source #

swResize :: CursorValue Value Source #

ewResize :: CursorValue Value Source #

nsResize :: CursorValue Value Source #

neswResize :: CursorValue Value Source #

nwseResize :: CursorValue Value Source #

zoomIn :: CursorValue Value Source #

zoomOut :: CursorValue Value Source #

class FlexEnd a where Source #

Methods

flexEnd :: a Source #

Instances

Instances details
FlexEnd AlignContentValue Source # 
Instance details

Defined in Clay.Flexbox

FlexEnd AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

FlexEnd AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

FlexEnd JustifyContentValue Source # 
Instance details

Defined in Clay.Flexbox

FlexEnd Value Source # 
Instance details

Defined in Clay.Flexbox

Methods

flexEnd :: Value Source #

class FlexStart a where Source #

Methods

flexStart :: a Source #

Instances

Instances details
FlexStart AlignContentValue Source # 
Instance details

Defined in Clay.Flexbox

FlexStart AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

FlexStart AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

FlexStart JustifyContentValue Source # 
Instance details

Defined in Clay.Flexbox

FlexStart Value Source # 
Instance details

Defined in Clay.Flexbox

class SpaceAround a where Source #

Methods

spaceAround :: a Source #

Instances

Instances details
SpaceAround AlignContentValue Source # 
Instance details

Defined in Clay.Flexbox

SpaceAround JustifyContentValue Source # 
Instance details

Defined in Clay.Flexbox

SpaceAround Value Source # 
Instance details

Defined in Clay.Flexbox

class SpaceBetween a where Source #

Methods

spaceBetween :: a Source #

Instances

Instances details
SpaceBetween AlignContentValue Source # 
Instance details

Defined in Clay.Flexbox

SpaceBetween JustifyContentValue Source # 
Instance details

Defined in Clay.Flexbox

SpaceBetween Value Source # 
Instance details

Defined in Clay.Flexbox

class SpaceEvenly a where Source #

Methods

spaceEvenly :: a Source #

Instances

Instances details
SpaceEvenly AlignContentValue Source # 
Instance details

Defined in Clay.Flexbox

SpaceEvenly JustifyContentValue Source # 
Instance details

Defined in Clay.Flexbox

SpaceEvenly Value Source # 
Instance details

Defined in Clay.Flexbox

class Stretch a where Source #

Methods

stretch :: a Source #

Instances

Instances details
Stretch AlignContentValue Source # 
Instance details

Defined in Clay.Flexbox

Stretch AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

Stretch AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Stretch Value Source # 
Instance details

Defined in Clay.Flexbox

Methods

stretch :: Value Source #

newtype AlignItemsValue Source #

Constructors

AlignItemValue Value 

Instances

Instances details
Baseline AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

Center AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

Inherit AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

Other AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

FlexEnd AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

FlexStart AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

Stretch AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

Val AlignItemsValue Source # 
Instance details

Defined in Clay.Flexbox

newtype AlignSelfValue Source #

Constructors

AlignSelfValue Value 

Instances

Instances details
Auto AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Baseline AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Center AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Inherit AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Other AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

FlexEnd AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

FlexStart AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Stretch AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

Val AlignSelfValue Source # 
Instance details

Defined in Clay.Flexbox

newtype FlexDirection Source #

Constructors

FlexDirection Value 

Instances

Instances details
Other FlexDirection Source # 
Instance details

Defined in Clay.Flexbox

Val FlexDirection Source # 
Instance details

Defined in Clay.Flexbox

newtype FlexWrap Source #

Constructors

FlexWrap Value 

Instances

Instances details
Other FlexWrap Source # 
Instance details

Defined in Clay.Flexbox

Methods

other :: Value -> FlexWrap Source #

Val FlexWrap Source # 
Instance details

Defined in Clay.Flexbox

Methods

value :: FlexWrap -> Value 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.

http://www.w3.org/TR/css3-fonts/#font-prop

Minimal complete definition

Nothing

Methods

font :: a -> Css Source #

Instances

Instances details
Font (Required a) Source # 
Instance details

Defined in Clay.Font

Methods

font :: Required a -> Css Source #

Font (Optional, Required a) Source # 
Instance details

Defined in Clay.Font

Methods

font :: (Optional, Required a) -> Css Source #

data Optional Source #

Instances

Instances details
Val Optional Source # 
Instance details

Defined in Clay.Font

Methods

value :: Optional -> Value Source #

Font (Optional, Required a) Source # 
Instance details

Defined in Clay.Font

Methods

font :: (Optional, Required a) -> Css Source #

data Required a Source #

Constructors

Required (Size a) (Maybe (Size a)) [Text] [GenericFontFamily] 

Instances

Instances details
Font (Required a) Source # 
Instance details

Defined in Clay.Font

Methods

font :: Required a -> Css Source #

Val (Required a) Source # 
Instance details

Defined in Clay.Font

Methods

value :: Required a -> Value Source #

Font (Optional, Required a) Source # 
Instance details

Defined in Clay.Font

Methods

font :: (Optional, Required a) -> Css Source #

data FontSize Source #

Instances

Instances details
Auto FontSize Source # 
Instance details

Defined in Clay.Font

Methods

auto :: FontSize Source #

Inherit FontSize Source # 
Instance details

Defined in Clay.Font

Other FontSize Source # 
Instance details

Defined in Clay.Font

Methods

other :: Value -> FontSize Source #

Val FontSize Source # 
Instance details

Defined in Clay.Font

Methods

value :: FontSize -> Value Source #

data FontStyle Source #

Instances

Instances details
Inherit FontStyle Source # 
Instance details

Defined in Clay.Font

Normal FontStyle Source # 
Instance details

Defined in Clay.Font

Other FontStyle Source # 
Instance details

Defined in Clay.Font

Val FontStyle Source # 
Instance details

Defined in Clay.Font

data FontVariant Source #

Instances

Instances details
Inherit FontVariant Source # 
Instance details

Defined in Clay.Font

Normal FontVariant Source # 
Instance details

Defined in Clay.Font

Other FontVariant Source # 
Instance details

Defined in Clay.Font

Val FontVariant Source # 
Instance details

Defined in Clay.Font

data FontWeight Source #

Instances

Instances details
Inherit FontWeight Source # 
Instance details

Defined in Clay.Font

Normal FontWeight Source # 
Instance details

Defined in Clay.Font

Other FontWeight Source # 
Instance details

Defined in Clay.Font

Val FontWeight Source # 
Instance details

Defined in Clay.Font

data NamedFont Source #

Instances

Instances details
Other NamedFont Source # 
Instance details

Defined in Clay.Font

Val NamedFont Source # 
Instance details

Defined in Clay.Font

fontColor :: Color -> Css Source #

An alias for color.

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.

sansSerif :: GenericFontFamily Source #

serif :: GenericFontFamily Source #

monospace :: GenericFontFamily Source #

cursive :: GenericFontFamily Source #

fantasy :: GenericFontFamily Source #

module Clay.Grid

module Clay.List

data TextRendering Source #

Instances

Instances details
Auto TextRendering Source # 
Instance details

Defined in Clay.Text

Inherit TextRendering Source # 
Instance details

Defined in Clay.Text

Other TextRendering Source # 
Instance details

Defined in Clay.Text

Val TextRendering Source # 
Instance details

Defined in Clay.Text

data TextIndent Source #

Instances

Instances details
Inherit TextIndent Source # 
Instance details

Defined in Clay.Text

Initial TextIndent Source # 
Instance details

Defined in Clay.Text

Other TextIndent Source # 
Instance details

Defined in Clay.Text

Unset TextIndent Source # 
Instance details

Defined in Clay.Text

Val TextIndent Source # 
Instance details

Defined in Clay.Text

data TextDirection Source #

Instances

Instances details
Inherit TextDirection Source # 
Instance details

Defined in Clay.Text

Normal TextDirection Source # 
Instance details

Defined in Clay.Text

Other TextDirection Source # 
Instance details

Defined in Clay.Text

Val TextDirection Source # 
Instance details

Defined in Clay.Text

data TextAlign Source #

Instances

Instances details
Center TextAlign Source # 
Instance details

Defined in Clay.Text

Inherit TextAlign Source # 
Instance details

Defined in Clay.Text

Normal TextAlign Source # 
Instance details

Defined in Clay.Text

Other TextAlign Source # 
Instance details

Defined in Clay.Text

Val TextAlign Source # 
Instance details

Defined in Clay.Text

data WhiteSpace Source #

Instances

Instances details
Inherit WhiteSpace Source # 
Instance details

Defined in Clay.Text

Normal WhiteSpace Source # 
Instance details

Defined in Clay.Text

Other WhiteSpace Source # 
Instance details

Defined in Clay.Text

Val WhiteSpace Source # 
Instance details

Defined in Clay.Text

data TextDecoration Source #

Instances

Instances details
Inherit TextDecoration Source # 
Instance details

Defined in Clay.Text

None TextDecoration Source # 
Instance details

Defined in Clay.Text

Other TextDecoration Source # 
Instance details

Defined in Clay.Text

Val TextDecoration Source # 
Instance details

Defined in Clay.Text

data TextTransform Source #

Instances

Instances details
Inherit TextTransform Source # 
Instance details

Defined in Clay.Text

None TextTransform Source # 
Instance details

Defined in Clay.Text

Val TextTransform Source # 
Instance details

Defined in Clay.Text

data TextOverflow Source #

Instances

Instances details
Inherit TextOverflow Source # 
Instance details

Defined in Clay.Text

Initial TextOverflow Source # 
Instance details

Defined in Clay.Text

None TextOverflow Source # 
Instance details

Defined in Clay.Text

Val TextOverflow Source # 
Instance details

Defined in Clay.Text

data WordBreak Source #

Instances

Instances details
Inherit WordBreak Source # 
Instance details

Defined in Clay.Text

Initial WordBreak Source # 
Instance details

Defined in Clay.Text

Normal WordBreak Source # 
Instance details

Defined in Clay.Text

Unset WordBreak Source # 
Instance details

Defined in Clay.Text

Val WordBreak Source # 
Instance details

Defined in Clay.Text

data OverflowWrap Source #

Instances

Instances details
Inherit OverflowWrap Source # 
Instance details

Defined in Clay.Text

Initial OverflowWrap Source # 
Instance details

Defined in Clay.Text

Normal OverflowWrap Source # 
Instance details

Defined in Clay.Text

Unset OverflowWrap Source # 
Instance details

Defined in Clay.Text

Val OverflowWrap Source # 
Instance details

Defined in Clay.Text

data Hyphens Source #

Type for values which can be provided to hyphens.

Instances

Instances details
Auto Hyphens Source # 
Instance details

Defined in Clay.Text

Methods

auto :: Hyphens Source #

Inherit Hyphens Source # 
Instance details

Defined in Clay.Text

Initial Hyphens Source # 
Instance details

Defined in Clay.Text

None Hyphens Source # 
Instance details

Defined in Clay.Text

Methods

none :: Hyphens Source #

Other Hyphens Source # 
Instance details

Defined in Clay.Text

Methods

other :: Value -> Hyphens Source #

Unset Hyphens Source # 
Instance details

Defined in Clay.Text

Methods

unset :: Hyphens Source #

Val Hyphens Source # 
Instance details

Defined in Clay.Text

Methods

value :: Hyphens -> Value Source #

data HyphenateCharacter Source #

Type for values which can be provided to hyphenateCharacter.

Instances

Instances details
IsString HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

Auto HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

Inherit HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

Initial HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

Other HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

Unset HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

Val HyphenateCharacter Source # 
Instance details

Defined in Clay.Text

data Content Source #

Instances

Instances details
Inherit Content Source # 
Instance details

Defined in Clay.Text

Initial Content Source # 
Instance details

Defined in Clay.Text

None Content Source # 
Instance details

Defined in Clay.Text

Methods

none :: Content Source #

Normal Content Source # 
Instance details

Defined in Clay.Text

Val Content Source # 
Instance details

Defined in Clay.Text

Methods

value :: Content -> Value Source #

textShadow :: Size a -> Size a -> Size a -> Color -> 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

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 &shy; 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.

hyphenateLimitChars Source #

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.

manual :: Hyphens Source #

Value for hyphens specifying that hyphenation be manual.

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

Methods

mask :: a -> Css Source #

Instances

Instances details
Mask BackgroundAttachment Source # 
Instance details

Defined in Clay.Mask

Mask BackgroundClip Source # 
Instance details

Defined in Clay.Mask

Mask BackgroundImage Source # 
Instance details

Defined in Clay.Mask

Mask BackgroundOrigin Source # 
Instance details

Defined in Clay.Mask

Mask BackgroundPosition Source # 
Instance details

Defined in Clay.Mask

Mask BackgroundRepeat Source # 
Instance details

Defined in Clay.Mask

Mask BackgroundSize Source # 
Instance details

Defined in Clay.Mask

Mask MaskComposite Source # 
Instance details

Defined in Clay.Mask

Mask a => Mask [a] Source # 
Instance details

Defined in Clay.Mask

Methods

mask :: [a] -> Css Source #

(Mask a, Mask b) => Mask (a, b) Source # 
Instance details

Defined in Clay.Mask

Methods

mask :: (a, b) -> Css Source #

data MaskComposite Source #

Instances

Instances details
Inherit MaskComposite Source # 
Instance details

Defined in Clay.Mask

None MaskComposite Source # 
Instance details

Defined in Clay.Mask

Other MaskComposite Source # 
Instance details

Defined in Clay.Mask

Mask MaskComposite Source # 
Instance details

Defined in Clay.Mask

Val MaskComposite Source # 
Instance details

Defined in Clay.Mask

data Filter Source #

Instances

Instances details
Inherit Filter Source # 
Instance details

Defined in Clay.Filter

None Filter Source # 
Instance details

Defined in Clay.Filter

Methods

none :: Filter Source #

Val Filter Source # 
Instance details

Defined in Clay.Filter

Methods

value :: Filter -> Value Source #

Writing your own properties.