module Text.CxML.CSS where
-- utility functions for manipulating CSS part

import Text.CxML.Types
import Text.CxML.Tags
import Text.CxML.HTML

-- change a list of CSS declarations to prepend a selector
underSelector :: String -> [StyleDecl] -> [StyleDecl]
underSelector par rls = map (underSelector' par) rls

underSelector' par (CSSRule sel ats) = CSSRule (map prepend sel) ats
    where prepend s = par++" "++s
                      
underSelector' par sd@(_) = sd

(*>) = underSelector

-- | set style 
infixl 8 ^%

(^%) :: CxML a->[StyleDecl]-> CxML a
tag ^% sty = CxML (htm tag, titleParts tag, css tag ++ sty, js tag)

-- | create HTML to link to a CSS file
csslink url = link!("type","text/css")!("rel","stylesheet")^>url


infixl 8 ^^.
(^^.) :: CxML a -> CssInlineDecl -> CxML a
tag^^.(rlsName,rlsBody) = tag^.rlsName ^%[CSSRule ['.':rlsName] rlsBody ]