cascading-0.1.0: DSL for HTML CSS (Cascading Style Sheets)

MaintainerErtugrul Soeylemez <es@ertes.de>
Safe HaskellNone

Data.CSS.Types

Contents

Description

 

Synopsis

Style sheets

data CSS Source

Cascading style sheets.

Constructors

CSS 

Fields

_cssImports :: Map Text (Set MediaType)

External stylesheets (url, media-type).

_cssProps :: Map (Set MediaType) [Property]

Properties.

data Property Source

Style properties.

Constructors

Property 

Fields

_propSelector :: [Selector]

Selector for this property.

_propName :: PropName

Property name.

_propValue :: PropValue

Property value.

_propImportant :: Bool

!important property?

CSS building

data BuildCfg Source

CSS builder configuration.

Constructors

BuildCfg 

Fields

_bcMedia :: Set MediaType

Current media type.

_bcSelector :: [Selector]

Current selector.

type SetProp = forall m. SetPropM mSource

Property setter.

type SetPropM m = (MonadReader BuildCfg m, MonadWriter CSS m) => m ()Source

Parametric property setter.

Auxiliary types

newtype MediaType Source

Media types, e.g. all or print.

Constructors

MediaType 

newtype PropName Source

Property names, e.g. font-family.

Constructors

PropName 

newtype Selector Source

Selectors, e.g. * or #content p.

Constructors

Selector 

Type classes

class ToPropValue a whereSource

Types that feature a conversion function to PropValue.

Instances

ToPropValue Char 
ToPropValue Double 
ToPropValue Float 
ToPropValue Int 
ToPropValue Int8 
ToPropValue Int16 
ToPropValue Int32 
ToPropValue Int64 
ToPropValue Integer 
ToPropValue Word 
ToPropValue Word8 
ToPropValue Word16 
ToPropValue Word32 
ToPropValue Word64 
ToPropValue Text 
ToPropValue Text 
ToPropValue ByteString 
ToPropValue ByteString 
ToPropValue PropValue 
ToPropValue VisibilityMode 
ToPropValue UnicodeBidiMode 
ToPropValue TextWrapMode 
ToPropValue TextTransform 
ToPropValue TextDirection 
ToPropValue TextDecoration 
ToPropValue TextAlign 
ToPropValue TableLayout 
ToPropValue PositionMode 
ToPropValue OverflowMode 
ToPropValue ListStyle 
ToPropValue ListPosition 
ToPropValue FontWeight 
ToPropValue FontVariant 
ToPropValue FontStyle 
ToPropValue FontFamily 
ToPropValue FloatEdge 
ToPropValue DisplayMode 
ToPropValue CaptionSide 
ToPropValue BorderStyle 
ToPropValue BackgroundRepeat 
ToPropValue BackgroundAttachment 
ToPropValue [Char] 
ToPropValue a => ToPropValue [a] 
Integral a => ToPropValue (Ratio a) 
(Floating a, RealFrac a) => ToPropValue (Colour a) 
(Floating a, RealFrac a) => ToPropValue (AlphaColour a) 
Real a => ToPropValue (VerticalAlign a) 
ToPropValue (PageBreak a) 
Real a => ToPropValue (Length a) 
Real a => ToPropValue (FontSize a) 
ToPropValue url => ToPropValue (Cursor url) 
ToPropValue (CssUrl Text) 
ToPropValue (CssString Text) 
ToPropValue url => ToPropValue (ContentPart url) 
Real a => ToPropValue (ClipMode a) 
Real a => ToPropValue (BorderWidth a) 
(ToPropValue a, ToPropValue b) => ToPropValue (a, b) 
(Real a, ToPropValue (len a)) => ToPropValue (FactorLen len a) 
ToPropValue (len a) => ToPropValue (AutoLen len a) 
(ToPropValue a, ToPropValue b, ToPropValue c) => ToPropValue (a, b, c)