module Text.CxML.Types where -- | contextual markup - generates HTML as a function of a context of type a. -- also keep track of static CSS and JavaScript newtype CxML a = CxML (a->[HElem],[String],[StyleDecl],[JSDecl]) -- non-contextual equivalent useful mainly for making type checker happy occasionally type NonCxML = CxML () -- | HTML elements data HElem = HTag {- tagName -} String [Attr] [HElem] | HText String type Attr = (String,String) -- | how to declare CSS & JavaScript type CssInlineDecl = (String {-id without prefix . -}, [(String,String)] {- css rules -}) data StyleDecl = CSSRule [String] [(String,String)] | CSSLink String -- specify a dependency on a CSS file (mostly hosted by Yahoo or us) data JSDecl = OnLoad String | JSLink String -- specify a dependency on a JS file (mostly hosted by Yahoo or us) -- use a context to turn contextual into non-contextual markup runCxML :: CxML a -> a -> NonCxML runCxML (CxML (h,ts,c,j)) cx = CxML (\_->h cx,ts, c, j) -- concatenate two bits of contextual marker infixr 2 +++ -- combining Html (+++) :: 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 -- | empty tag noElem = CxML (\_->[],[],[],[]) -- | set the HTML children 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), [], [], []) -- the non-overloaded withChildren operator infixl 5 /- (/-) :: CxML b -> [CxML b] -> CxML b (/-) p c = withChildren p c -- | access title parts titleParts (CxML (_,ts,_,_))= ts -- | access JavaScript ( static) part js (CxML (_,_,_,j))= j -- | access CSS ( static ) part css (CxML (_,_,c,_))= c -- | access html (dynamic) part 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])