module Text.CxML.NavList where import Text.CxML.Types import Text.CxML.Tags import Text.CxML.HTML import Text.CxML.CSS -- this should really be renamed CxML.Components -- this module defines a navigation list component which can be used for tabs, left-hand vertical menu or breadcrumbs. -- see " a list apart" on taming lists but I don't like their breadcrumbs solution with nested markup. data NavListStyle = Tabs | Vertical | Breadcrumbs | HoverCols String String | NoUnderline | LinesBetween | AnyCSS StyleDecl | TextCol String | CurrentLinkCSS [(String, String)] | CurrentItemCSS [(String, String)] --navList ::[NavListStyle] -> String -> [(String, String)] -> CxML a navList styls tid (item:items) = ul^#tid^%(('#':tid) *> (concatMap navStyles styls))/- ((litemf item):(map litem items)) where litem (txt,targ) = li /- [a^>targ /- [modHElems processText $ t txt]] litemf (txt,targ) = li^."first" /- [a^>targ /- [t txt]] navStyles Tabs = [] navStyles Vertical = [CSSRule ["li a"] [("padding","4px"), ("font-size", "116%")]] navStyles (CurrentLinkCSS sty) = [CSSRule ["li.current a"] sty] navStyles (CurrentItemCSS sty) = [CSSRule ["li a"] sty] navStyles (TextCol cl) = [CSSRule ["li a"] [("color",cl)]] navStyles (HoverCols tx bg) = [CSSRule ["li:hover"] [("background-color",bg)], CSSRule ["li:hover a"] [("color",tx)]] navStyles NoUnderline = [CSSRule ["li a"] [("text-decoration","none")]] navStyles LinesBetween = [CSSRule ["li"] [("border-top","1px solid #bbbbbb")], CSSRule ["li.first"] [("border-top","none")] ] navStyles Breadcrumbs = [CSSRule ["li","ul"] [("display","inline"), ("margin", "0"),("padding", "0")]] prependChar Breadcrumbs = "» " prependChar _ = "" processText (HText t)= HText ((concatMap prependChar styls )++t) processText h = h vertNav = navList [Vertical, NoUnderline, LinesBetween, TextCol "#000", HoverCols "#f33" "#ccc"] "vertNav" --http://www.sixshootermedia.com/blog/semantic-h1-logo-link/ h1logo txt imgpath = h1^#"h1logo"^%rls /- [t txt] where rls = [CSSRule ["#h1logo"] [("text-indent","-9999px"), ("background", "url("++imgpath++") no-repeat;"), ("width", "100%"),("height","60px") ]] formTo :: String -> [CxML a] -> CxML a formTo actionUrl chs = form!("method","post")!("action",actionUrl) /- chs submitBtn lbl = button!("name","action")!("value","submit") /- [t lbl] {- from formerly RequestCtx.hs -} --yuiMenu = div^."yuimenu" // div^."bd" // [ul^."first-of-type" // "hello world"] --div^."yuimenu" // div^."bd" // ul^."first-of-type" // "hello world" -- yawn -- http://www.alistapart.com/articles/prettyaccessibleforms formSection nm contents = if null nm then fieldset /- [ol /- contents] else fieldset /- [legend /- [t nm], ol /- contents] --setValFromCtx :: (a -> String) -> CxML a -> CxML a --setValFromCtx stLam (CxML (h,c,j))= CxML (\ctx-> map (add_attr "value" (stLam ctx)) $ h ctx, c,j )