{-# LANGUAGE PatternGuards, CPP #-} {-# OPTIONS_GHC -F -pgmF trhsx #-} module DarcsDen.Pages.Base where import Data.Char (toLower) import Data.List (sortBy) import Data.Maybe (fromMaybe) import Data.Ord (comparing) import HSP import DarcsDen.Pages.HSPage ( HSPage ) import DarcsDen.State.Session import DarcsDen.Settings import DarcsDen.State.User base :: String -> Bool -> HSP XML -> HSP XML -> HSP XML -> HSPage base title indexable crumb pagenav content sess = <% title %><% if not (null title) then " :: " else "" %><% hostname %> <% if indexable then <% "" %> else <% %> %> -- -- #ifdef HIGHLIGHTER #endif
<% sitenav (sUser sess) %>

<% siteLink %> <% cdata " :: " %> <% crumb %>

<% map notification (sNotifications sess) %> <% content %>
where sitenav (Just u) = sitenav Nothing = notification :: Notification -> HSP XML notification (Success msg) =
<% msg %>
notification (Message msg) =
<% msg %>
notification (Warning msg) =
<% msg %>
frontpage :: [User] -> HSPage frontpage us = base "" True home

users

repos

<% frontPageContent %>
where us' :: [User] us' = sortBy (comparing (map toLower . uName)) us userlink :: User -> HSP XML userlink User{uName=u} =
  • <% u %>
  • field :: HSP XML -> String -> String -> HSP XML field f l n =
    <% f %> -- TODO: for= <% if n /= "" then <% n %> else
    %>
    input :: String -> String -> HSP XML input n v = inputWith :: String -> String -> [(String,String)] -> HSP XML inputWith n v attrs = a := b) attrs) /> textarea :: Int -> String -> String -> HSP XML textarea r n v = input' :: [(String, String)] -> String -> HSP XML input' is n = input n (fromMaybe "" (lookup n is)) inputWith' :: [(String, String)] -> String -> [(String,String)] -> HSP XML inputWith' is n attrs = inputWith n (fromMaybe "" (lookup n is)) attrs checkbox' :: [(String, String)] -> String -> HSP XML checkbox' is n | n `elem` (map fst is) =
    <% box `set` ("checked" := "checked") %>
    | otherwise =
    <% box %>
    where box = checkbox :: Bool -> [(String, String)] -> String -> HSP XML checkbox False = checkbox' checkbox True = \is n -> checkbox' ((n, "1"):is) n password' :: [(String, String)] -> String -> HSP XML password' is n = passwordWith' :: [(String, String)] -> String -> [(String, String)] -> HSP XML passwordWith' is n attrs = a := b) attrs) /> textarea' :: [(String, String)] -> Int -> String -> HSP XML textarea' is r n = textarea r n (fromMaybe "" (lookup n is)) submit :: String -> HSP XML submit l =

    paginate :: String -> Int -> Int -> HSP XML paginate _ _ 1 =
    paginate url page totalpages =
    where prev = next = spacer =