blizzard-html-0.1.0.0: An HTML and CSS renderer for Haskell
Safe HaskellNone
LanguageHaskell2010

Text.Blizzard.Css3

Synopsis

Documentation

module Clay.Box

module Clay.Color

zoomOut :: CursorValue Value #

zoomIn :: CursorValue Value #

nwseResize :: CursorValue Value #

neswResize :: CursorValue Value #

nsResize :: CursorValue Value #

ewResize :: CursorValue Value #

swResize :: CursorValue Value #

seResize :: CursorValue Value #

nwResize :: CursorValue Value #

neResize :: CursorValue Value #

wResize :: CursorValue Value #

sResize :: CursorValue Value #

eResize :: CursorValue Value #

nResize :: CursorValue Value #

rowResize :: CursorValue Value #

colResize :: CursorValue Value #

allScroll :: CursorValue Value #

grabbing :: CursorValue Value #

grab :: CursorValue Value #

notAllowed :: CursorValue Value #

noDrop :: CursorValue Value #

move :: CursorValue Value #

cursorCopy :: CursorValue Value #

alias :: CursorValue Value #

vText :: CursorValue Value #

cursorText :: CursorValue Value #

crosshair :: CursorValue Value #

cell :: CursorValue Value #

wait :: CursorValue Value #

cursorProgress :: CursorValue Value #

pointer :: CursorValue Value #

help :: CursorValue Value #

contextMenu :: CursorValue Value #

cursorDefault :: CursorValue Value #

cursorUrl :: Text -> CursorValue Value #

vAlignBottom :: VerticalAlignValue #

vAlignTop :: VerticalAlignValue #

textBottom :: VerticalAlignValue #

textTop :: VerticalAlignValue #

vAlignSuper :: VerticalAlignValue #

vAlignBaseline :: VerticalAlignValue #

vAlignSub :: VerticalAlignValue #

middle :: VerticalAlignValue #

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

clip :: Clip -> Css #

data FloatStyle #

Instances

Instances details
Inherit FloatStyle 
Instance details

Defined in Clay.Display

Methods

inherit :: FloatStyle #

None FloatStyle 
Instance details

Defined in Clay.Display

Methods

none :: FloatStyle #

Val FloatStyle 
Instance details

Defined in Clay.Display

Methods

value :: FloatStyle -> Value #

data Clear #

Instances

Instances details
Inherit Clear 
Instance details

Defined in Clay.Display

Methods

inherit :: Clear #

None Clear 
Instance details

Defined in Clay.Display

Methods

none :: Clear #

Other Clear 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Clear #

Val Clear 
Instance details

Defined in Clay.Display

Methods

value :: Clear -> Value #

data Position #

Instances

Instances details
Inherit Position 
Instance details

Defined in Clay.Display

Methods

inherit :: Position #

Other Position 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Position #

Val Position 
Instance details

Defined in Clay.Display

Methods

value :: Position -> Value #

data Display #

Instances

Instances details
Inherit Display 
Instance details

Defined in Clay.Display

Methods

inherit :: Display #

None Display 
Instance details

Defined in Clay.Display

Methods

none :: Display #

Other Display 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Display #

Val Display 
Instance details

Defined in Clay.Display

Methods

value :: Display -> Value #

data Overflow #

Instances

Instances details
Auto Overflow 
Instance details

Defined in Clay.Display

Methods

auto :: Overflow #

Inherit Overflow 
Instance details

Defined in Clay.Display

Methods

inherit :: Overflow #

Visible Overflow 
Instance details

Defined in Clay.Display

Methods

visible :: Overflow #

Hidden Overflow 
Instance details

Defined in Clay.Display

Methods

hidden :: Overflow #

Other Overflow 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Overflow #

Val Overflow 
Instance details

Defined in Clay.Display

Methods

value :: Overflow -> Value #

data Visibility #

Instances

Instances details
Auto Visibility 
Instance details

Defined in Clay.Display

Methods

auto :: Visibility #

Inherit Visibility 
Instance details

Defined in Clay.Display

Methods

inherit :: Visibility #

Visible Visibility 
Instance details

Defined in Clay.Display

Methods

visible :: Visibility #

Hidden Visibility 
Instance details

Defined in Clay.Display

Methods

hidden :: Visibility #

Other Visibility 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Visibility #

Val Visibility 
Instance details

Defined in Clay.Display

Methods

value :: Visibility -> Value #

data Clip #

Instances

Instances details
Auto Clip 
Instance details

Defined in Clay.Display

Methods

auto :: Clip #

Inherit Clip 
Instance details

Defined in Clay.Display

Methods

inherit :: Clip #

Other Clip 
Instance details

Defined in Clay.Display

Methods

other :: Value -> Clip #

Val Clip 
Instance details

Defined in Clay.Display

Methods

value :: Clip -> Value #

data PointerEvents #

Instances

Instances details
Auto PointerEvents 
Instance details

Defined in Clay.Display

Methods

auto :: PointerEvents #

Inherit PointerEvents 
Instance details

Defined in Clay.Display

None PointerEvents 
Instance details

Defined in Clay.Display

Methods

none :: PointerEvents #

Visible PointerEvents 
Instance details

Defined in Clay.Display

Other PointerEvents 
Instance details

Defined in Clay.Display

Methods

other :: Value -> PointerEvents #

Val PointerEvents 
Instance details

Defined in Clay.Display

Methods

value :: PointerEvents -> Value #

class Val a => VerticalAlign a where #

Minimal complete definition

Nothing

Methods

verticalAlign :: a -> Css #

Instances

Instances details
VerticalAlign VerticalAlignValue 
Instance details

Defined in Clay.Display

Methods

verticalAlign :: VerticalAlignValue -> Css #

VerticalAlign (Size a) 
Instance details

Defined in Clay.Display

Methods

verticalAlign :: Size a -> Css #

class Val a => Cursor a where #

Minimal complete definition

Nothing

Methods

cursor :: a -> Css #

Instances

Instances details
Cursor (CursorValue a) 
Instance details

Defined in Clay.Display

Methods

cursor :: CursorValue a -> Css #

order :: Int -> Css #

class FlexEnd a where #

Methods

flexEnd :: a #

Instances

Instances details
FlexEnd AlignContentValue 
Instance details

Defined in Clay.Flexbox

FlexEnd AlignItemsValue 
Instance details

Defined in Clay.Flexbox

FlexEnd AlignSelfValue 
Instance details

Defined in Clay.Flexbox

FlexEnd JustifyContentValue 
Instance details

Defined in Clay.Flexbox

FlexEnd Value 
Instance details

Defined in Clay.Flexbox

Methods

flexEnd :: Value #

class FlexStart a where #

Methods

flexStart :: a #

Instances

Instances details
FlexStart AlignContentValue 
Instance details

Defined in Clay.Flexbox

FlexStart AlignItemsValue 
Instance details

Defined in Clay.Flexbox

FlexStart AlignSelfValue 
Instance details

Defined in Clay.Flexbox

FlexStart JustifyContentValue 
Instance details

Defined in Clay.Flexbox

FlexStart Value 
Instance details

Defined in Clay.Flexbox

Methods

flexStart :: Value #

class SpaceAround a where #

Methods

spaceAround :: a #

Instances

Instances details
SpaceAround AlignContentValue 
Instance details

Defined in Clay.Flexbox

SpaceAround JustifyContentValue 
Instance details

Defined in Clay.Flexbox

SpaceAround Value 
Instance details

Defined in Clay.Flexbox

Methods

spaceAround :: Value #

class SpaceBetween a where #

Methods

spaceBetween :: a #

Instances

Instances details
SpaceBetween AlignContentValue 
Instance details

Defined in Clay.Flexbox

SpaceBetween JustifyContentValue 
Instance details

Defined in Clay.Flexbox

SpaceBetween Value 
Instance details

Defined in Clay.Flexbox

Methods

spaceBetween :: Value #

class Stretch a where #

Methods

stretch :: a #

Instances

Instances details
Stretch AlignContentValue 
Instance details

Defined in Clay.Flexbox

Stretch AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Stretch AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Stretch Value 
Instance details

Defined in Clay.Flexbox

Methods

stretch :: Value #

newtype AlignContentValue #

Constructors

AlignContentValue Value 

Instances

Instances details
FlexEnd AlignContentValue 
Instance details

Defined in Clay.Flexbox

FlexStart AlignContentValue 
Instance details

Defined in Clay.Flexbox

SpaceAround AlignContentValue 
Instance details

Defined in Clay.Flexbox

SpaceBetween AlignContentValue 
Instance details

Defined in Clay.Flexbox

Stretch AlignContentValue 
Instance details

Defined in Clay.Flexbox

Center AlignContentValue 
Instance details

Defined in Clay.Flexbox

Inherit AlignContentValue 
Instance details

Defined in Clay.Flexbox

Other AlignContentValue 
Instance details

Defined in Clay.Flexbox

Val AlignContentValue 
Instance details

Defined in Clay.Flexbox

newtype AlignItemsValue #

Constructors

AlignItemValue Value 

Instances

Instances details
FlexEnd AlignItemsValue 
Instance details

Defined in Clay.Flexbox

FlexStart AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Stretch AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Baseline AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Center AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Inherit AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Other AlignItemsValue 
Instance details

Defined in Clay.Flexbox

Val AlignItemsValue 
Instance details

Defined in Clay.Flexbox

newtype AlignSelfValue #

Constructors

AlignSelfValue Value 

Instances

Instances details
FlexEnd AlignSelfValue 
Instance details

Defined in Clay.Flexbox

FlexStart AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Stretch AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Auto AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Baseline AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Center AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Inherit AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Other AlignSelfValue 
Instance details

Defined in Clay.Flexbox

Val AlignSelfValue 
Instance details

Defined in Clay.Flexbox

newtype FlexDirection #

Constructors

FlexDirection Value 

Instances

Instances details
Other FlexDirection 
Instance details

Defined in Clay.Flexbox

Methods

other :: Value -> FlexDirection #

Val FlexDirection 
Instance details

Defined in Clay.Flexbox

Methods

value :: FlexDirection -> Value #

newtype FlexWrap #

Constructors

FlexWrap Value 

Instances

Instances details
Other FlexWrap 
Instance details

Defined in Clay.Flexbox

Methods

other :: Value -> FlexWrap #

Val FlexWrap 
Instance details

Defined in Clay.Flexbox

Methods

value :: FlexWrap -> Value #

newtype JustifyContentValue #

Instances

Instances details
FlexEnd JustifyContentValue 
Instance details

Defined in Clay.Flexbox

FlexStart JustifyContentValue 
Instance details

Defined in Clay.Flexbox

SpaceAround JustifyContentValue 
Instance details

Defined in Clay.Flexbox

SpaceBetween JustifyContentValue 
Instance details

Defined in Clay.Flexbox

Center JustifyContentValue 
Instance details

Defined in Clay.Flexbox

Inherit JustifyContentValue 
Instance details

Defined in Clay.Flexbox

Other JustifyContentValue 
Instance details

Defined in Clay.Flexbox

Val JustifyContentValue 
Instance details

Defined in Clay.Flexbox

fontSize :: Size a -> Css #

fontFamily :: [Text] -> [GenericFontFamily] -> Css #

The fontFamily style rules takes to lists of font families: zero or more custom font-families and preferably one or more generic font families.

fantasy :: GenericFontFamily #

cursive :: GenericFontFamily #

monospace :: GenericFontFamily #

serif :: GenericFontFamily #

sansSerif :: GenericFontFamily #

fontColor :: Color -> Css #

An alias for color.

class Val a => Font a where #

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 #

Instances

Instances details
Font (Required a) 
Instance details

Defined in Clay.Font

Methods

font :: Required a -> Css #

Font (Optional, Required a) 
Instance details

Defined in Clay.Font

Methods

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

data Optional #

Instances

Instances details
Val Optional 
Instance details

Defined in Clay.Font

Methods

value :: Optional -> Value #

Font (Optional, Required a) 
Instance details

Defined in Clay.Font

Methods

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

data Required a #

Constructors

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

Instances

Instances details
Font (Required a) 
Instance details

Defined in Clay.Font

Methods

font :: Required a -> Css #

Val (Required a) 
Instance details

Defined in Clay.Font

Methods

value :: Required a -> Value #

Font (Optional, Required a) 
Instance details

Defined in Clay.Font

Methods

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

data FontSize #

Instances

Instances details
Auto FontSize 
Instance details

Defined in Clay.Font

Methods

auto :: FontSize #

Inherit FontSize 
Instance details

Defined in Clay.Font

Methods

inherit :: FontSize #

Other FontSize 
Instance details

Defined in Clay.Font

Methods

other :: Value -> FontSize #

Val FontSize 
Instance details

Defined in Clay.Font

Methods

value :: FontSize -> Value #

data FontStyle #

Instances

Instances details
Inherit FontStyle 
Instance details

Defined in Clay.Font

Methods

inherit :: FontStyle #

Normal FontStyle 
Instance details

Defined in Clay.Font

Methods

normal :: FontStyle #

Other FontStyle 
Instance details

Defined in Clay.Font

Methods

other :: Value -> FontStyle #

Val FontStyle 
Instance details

Defined in Clay.Font

Methods

value :: FontStyle -> Value #

data FontVariant #

Instances

Instances details
Inherit FontVariant 
Instance details

Defined in Clay.Font

Normal FontVariant 
Instance details

Defined in Clay.Font

Methods

normal :: FontVariant #

Other FontVariant 
Instance details

Defined in Clay.Font

Methods

other :: Value -> FontVariant #

Val FontVariant 
Instance details

Defined in Clay.Font

Methods

value :: FontVariant -> Value #

data FontWeight #

Instances

Instances details
Inherit FontWeight 
Instance details

Defined in Clay.Font

Methods

inherit :: FontWeight #

Normal FontWeight 
Instance details

Defined in Clay.Font

Methods

normal :: FontWeight #

Other FontWeight 
Instance details

Defined in Clay.Font

Methods

other :: Value -> FontWeight #

Val FontWeight 
Instance details

Defined in Clay.Font

Methods

value :: FontWeight -> Value #

data NamedFont #

Instances

Instances details
Other NamedFont 
Instance details

Defined in Clay.Font

Methods

other :: Value -> NamedFont #

Val NamedFont 
Instance details

Defined in Clay.Font

Methods

value :: NamedFont -> Value #

module Clay.List

module Clay.Size

hanging :: TextIndent -> TextIndent #

Annotate the supplied TextIndent with each-line or hanging or both.

eachLine . hanging . indent $ px 3 :: TextIndent

eachLine :: TextIndent -> TextIndent #

Annotate the supplied TextIndent with each-line or hanging or both.

eachLine . hanging . indent $ px 3 :: TextIndent

textShadow :: Size a -> Size a -> Size a -> Color -> Css #

data TextRendering #

Instances

Instances details
Auto TextRendering 
Instance details

Defined in Clay.Text

Methods

auto :: TextRendering #

Inherit TextRendering 
Instance details

Defined in Clay.Text

Other TextRendering 
Instance details

Defined in Clay.Text

Methods

other :: Value -> TextRendering #

Val TextRendering 
Instance details

Defined in Clay.Text

Methods

value :: TextRendering -> Value #

data TextIndent #

Instances

Instances details
Inherit TextIndent 
Instance details

Defined in Clay.Text

Methods

inherit :: TextIndent #

Initial TextIndent 
Instance details

Defined in Clay.Text

Methods

initial :: TextIndent #

Unset TextIndent 
Instance details

Defined in Clay.Text

Methods

unset :: TextIndent #

Other TextIndent 
Instance details

Defined in Clay.Text

Methods

other :: Value -> TextIndent #

Val TextIndent 
Instance details

Defined in Clay.Text

Methods

value :: TextIndent -> Value #

data TextDirection #

Instances

Instances details
Inherit TextDirection 
Instance details

Defined in Clay.Text

Normal TextDirection 
Instance details

Defined in Clay.Text

Other TextDirection 
Instance details

Defined in Clay.Text

Methods

other :: Value -> TextDirection #

Val TextDirection 
Instance details

Defined in Clay.Text

Methods

value :: TextDirection -> Value #

data TextAlign #

Instances

Instances details
Center TextAlign 
Instance details

Defined in Clay.Text

Methods

center :: TextAlign #

Inherit TextAlign 
Instance details

Defined in Clay.Text

Methods

inherit :: TextAlign #

Normal TextAlign 
Instance details

Defined in Clay.Text

Methods

normal :: TextAlign #

Other TextAlign 
Instance details

Defined in Clay.Text

Methods

other :: Value -> TextAlign #

Val TextAlign 
Instance details

Defined in Clay.Text

Methods

value :: TextAlign -> Value #

data WhiteSpace #

Instances

Instances details
Inherit WhiteSpace 
Instance details

Defined in Clay.Text

Methods

inherit :: WhiteSpace #

Normal WhiteSpace 
Instance details

Defined in Clay.Text

Methods

normal :: WhiteSpace #

Other WhiteSpace 
Instance details

Defined in Clay.Text

Methods

other :: Value -> WhiteSpace #

Val WhiteSpace 
Instance details

Defined in Clay.Text

Methods

value :: WhiteSpace -> Value #

data TextDecoration #

Instances

Instances details
Inherit TextDecoration 
Instance details

Defined in Clay.Text

None TextDecoration 
Instance details

Defined in Clay.Text

Other TextDecoration 
Instance details

Defined in Clay.Text

Val TextDecoration 
Instance details

Defined in Clay.Text

data TextTransform #

Instances

Instances details
Inherit TextTransform 
Instance details

Defined in Clay.Text

None TextTransform 
Instance details

Defined in Clay.Text

Methods

none :: TextTransform #

Val TextTransform 
Instance details

Defined in Clay.Text

Methods

value :: TextTransform -> Value #

data WordBreak #

Instances

Instances details
Inherit WordBreak 
Instance details

Defined in Clay.Text

Methods

inherit :: WordBreak #

Normal WordBreak 
Instance details

Defined in Clay.Text

Methods

normal :: WordBreak #

Initial WordBreak 
Instance details

Defined in Clay.Text

Methods

initial :: WordBreak #

Unset WordBreak 
Instance details

Defined in Clay.Text

Methods

unset :: WordBreak #

Val WordBreak 
Instance details

Defined in Clay.Text

Methods

value :: WordBreak -> Value #

data OverflowWrap #

Instances

Instances details
Inherit OverflowWrap 
Instance details

Defined in Clay.Text

Normal OverflowWrap 
Instance details

Defined in Clay.Text

Initial OverflowWrap 
Instance details

Defined in Clay.Text

Unset OverflowWrap 
Instance details

Defined in Clay.Text

Methods

unset :: OverflowWrap #

Val OverflowWrap 
Instance details

Defined in Clay.Text

Methods

value :: OverflowWrap -> Value #

data TextOverflow #

Instances

Instances details
Inherit TextOverflow 
Instance details

Defined in Clay.Text

None TextOverflow 
Instance details

Defined in Clay.Text

Methods

none :: TextOverflow #

Initial TextOverflow 
Instance details

Defined in Clay.Text

Val TextOverflow 
Instance details

Defined in Clay.Text

Methods

value :: TextOverflow -> Value #

data Content #

Instances

Instances details
Inherit Content 
Instance details

Defined in Clay.Text

Methods

inherit :: Content #

None Content 
Instance details

Defined in Clay.Text

Methods

none :: Content #

Normal Content 
Instance details

Defined in Clay.Text

Methods

normal :: Content #

Initial Content 
Instance details

Defined in Clay.Text

Methods

initial :: Content #

Val Content 
Instance details

Defined in Clay.Text

Methods

value :: Content -> Value #

module Clay.Time

class Val a => Mask a where #

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 #

Instances

Instances details
Mask MaskComposite 
Instance details

Defined in Clay.Mask

Methods

mask :: MaskComposite -> Css #

Mask BackgroundPosition 
Instance details

Defined in Clay.Mask

Mask BackgroundSize 
Instance details

Defined in Clay.Mask

Methods

mask :: BackgroundSize -> Css #

Mask BackgroundRepeat 
Instance details

Defined in Clay.Mask

Methods

mask :: BackgroundRepeat -> Css #

Mask BackgroundImage 
Instance details

Defined in Clay.Mask

Methods

mask :: BackgroundImage -> Css #

Mask BackgroundOrigin 
Instance details

Defined in Clay.Mask

Methods

mask :: BackgroundOrigin -> Css #

Mask BackgroundClip 
Instance details

Defined in Clay.Mask

Methods

mask :: BackgroundClip -> Css #

Mask BackgroundAttachment 
Instance details

Defined in Clay.Mask

Mask a => Mask [a] 
Instance details

Defined in Clay.Mask

Methods

mask :: [a] -> Css #

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

Defined in Clay.Mask

Methods

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

data MaskComposite #

Instances

Instances details
Mask MaskComposite 
Instance details

Defined in Clay.Mask

Methods

mask :: MaskComposite -> Css #

Inherit MaskComposite 
Instance details

Defined in Clay.Mask

None MaskComposite 
Instance details

Defined in Clay.Mask

Methods

none :: MaskComposite #

Other MaskComposite 
Instance details

Defined in Clay.Mask

Methods

other :: Value -> MaskComposite #

Val MaskComposite 
Instance details

Defined in Clay.Mask

Methods

value :: MaskComposite -> Value #

data Filter #

Instances

Instances details
Inherit Filter 
Instance details

Defined in Clay.Filter

Methods

inherit :: Filter #

None Filter 
Instance details

Defined in Clay.Filter

Methods

none :: Filter #

Val Filter 
Instance details

Defined in Clay.Filter

Methods

value :: Filter -> Value #