language-css-0.0.3: CSS 2.1 syntax

Safe HaskellSafe-Infered

Language.Css.Build

Contents

Description

Combinators to build AST

Example :

import Language.Css.Syntax
import Language.Css.Build
import Language.Css.Pretty
import Language.Css.Build.Idents
import Language.Css.Build.Tags hiding (center)

res = ruleSets [
         body [
             margin <:> int 0,
             border <:> int 0 ],
            
         h1 [ textAlign <:> center],

         p [ 
            backgroundColor <:> black, 
            color <:> white,
            padding <:> spaces [pct 5, pct 5, pct 10, pct 10]  ],

         (star /. "warning") [ color <:> red ] 
       ]
 
main = print $ pretty res

Synopsis

Classes

StyleSheet

rules :: [StyleBody] -> StyleSheetSource

construct StyleSheet from list of AtRule 's or RuleSet 's

ruleSets :: [RuleSet] -> StyleSheetSource

construct StyleSheet from list of RuleSet 's

AtRules

media :: [String] -> [RuleSet] -> StyleBodySource

@media

fontFace :: [Decl] -> StyleBodySource

@font-face

RuleSets

Selectors

type Sel' = [Decl] -> RuleSetSource

RuleSet constructor

star :: Sel'Source

* selector

sels :: [Sel'] -> Sel'Source

groups selectors

(/>) :: Sel' -> Sel' -> Sel'Source

Child

> in css

(/-) :: Sel' -> Sel' -> Sel'Source

Descendant

space in css

(/#) :: Sel' -> String -> Sel'Source

set id

(/.) :: Sel' -> String -> Sel'Source

set class

(/:) :: Sel' -> PseudoVal -> Sel'Source

set pseudo classes/elements

class Attrs a whereSource

attribute selector

Methods

attr :: String -> aSource

(!) :: Sel' -> Attr -> Sel'Source

set attributes

(.=) :: AttrIdent -> AttrVal -> AttrSource

element's attribute is

(~=) :: AttrIdent -> AttrVal -> AttrSource

element's attribute includes

(|=) :: AttrIdent -> AttrVal -> AttrSource

element's attribute begins with

Declarations

(<:>) :: String -> Expr -> DeclSource

declaration constructor

important :: Decl -> DeclSource

set !important

space :: Expr -> Expr -> ExprSource

space separated values

slash :: Expr -> Expr -> ExprSource

slash separated values

comma :: Expr -> Expr -> ExprSource

comma separated values

spaces :: [Expr] -> ExprSource

space on list of values

slashes :: [Expr] -> ExprSource

slash on list of values

commas :: [Expr] -> ExprSource

comma on lists of values

Primitive values

fun :: ToExpr a => Ident -> a -> FuncSource

Func constructor

deg :: Double -> ExprSource

<angle>

rad :: Double -> ExprSource

<angle>

grad :: Double -> ExprSource

<angle>

cword :: String -> ExprSource

<color>

rgb :: Int -> Int -> Int -> ExprSource

<color>

hz :: Double -> ExprSource

<frequency>

khz :: Double -> ExprSource

<frequency>

em :: Double -> ExprSource

<length>

ex :: Double -> ExprSource

<length>

px :: Int -> ExprSource

<length>

in' :: Double -> ExprSource

<length>

cm :: Double -> ExprSource

<length>

mm :: Double -> ExprSource

<length>

pc :: Double -> ExprSource

<length>

pt :: Int -> ExprSource

<length>

pct :: Double -> ExprSource

<percentage>

ms :: Double -> ExprSource

<time>

s :: Double -> ExprSource

<time>

url :: String -> ExprSource

<uri>

Colors