module Text.CxML.Types where
newtype CxML a = CxML (a->[HElem],[String],[StyleDecl],[JSDecl])
type NonCxML = CxML ()
data HElem = HTag String [Attr] [HElem]
| HText String
type Attr = (String,String)
type CssInlineDecl = (String , [(String,String)] )
data StyleDecl = CSSRule [String] [(String,String)]
| CSSLink String
data JSDecl = OnLoad String
| JSLink String
runCxML :: CxML a -> a -> NonCxML
runCxML (CxML (h,ts,c,j)) cx = CxML (\_->h cx,ts, c, j)
infixr 2 +++
(+++) :: CxML a -> CxML a -> CxML a
(CxML (h1,ts1,c1,j1)) +++ (CxML (h2,ts2,c2,j2)) = CxML (\ctx->((h1 ctx)++(h2 ctx)), ts1++ts2, c1++c2, j1++j2)
concatCxML :: [CxML a] -> CxML a
concatCxML= foldr (+++) noElem
noElem = CxML (\_->[],[],[],[])
withChildren :: CxML a-> [CxML a]-> CxML a
withChildren prnt chs = CxML (\ctx->addch ((htm prnt) ctx) $ concatMap (($ctx) . htm) chs,
(titleParts prnt),
(css prnt)++(concatMap css chs),
(js prnt)++(concatMap js chs))
where addch ((HTag tn ats oldch):_) newch = [HTag tn ats (oldch++newch)]
withCtx :: (a->CxML a)->CxML a
withCtx cxLam = CxML (\ctx->(htm (cxLam ctx) ctx), [], [], [])
infixl 5 /-
(/-) :: CxML b -> [CxML b] -> CxML b
(/-) p c = withChildren p c
titleParts (CxML (_,ts,_,_))= ts
js (CxML (_,_,_,j))= j
css (CxML (_,_,c,_))= c
htm (CxML (h,_,_,_))= h
htmlPart cxml = CxML (\ctx->(htm cxml) ctx,[],[],[])
modCx :: (b -> a) -> CxML a -> CxML b
modCx f (CxML (h,ts,c,j)) = CxML (h . f, ts, c, j)
modTitleParts :: ([String] -> [String]) -> CxML a -> CxML a
modTitleParts f (CxML (h,ts,c,j)) = CxML (h, f ts, c, j)
setTitle, addTitle :: String -> CxML a -> CxML a
setTitle t = modTitleParts (\_ -> [t])
addTitle t = modTitleParts (\ts -> ts ++ [t])