{-# OPTIONS_GHC -F -pgmF trhsx #-} module DarcsDen.Pages.User where import HSP import Data.Maybe (fromMaybe, isJust) import DarcsDen.Pages.Base import DarcsDen.Pages.HSPage ( HSPage ) import DarcsDen.Pages.Util ( repoForkSourceDescription ) import DarcsDen.State.Repository import DarcsDen.State.User import DarcsDen.State.Session import DarcsDen.Settings user :: User -> [Repository] -> HSPage user u repos sess = base (uName u) True <% uName u %>

<% uName u %>'s repositories

<% repositories repos %>
sess where createlink =
  • new repo
  • repositories :: [Repository] -> HSP XML repositories [] =

    nothing to see here, move along!

    repositories rs = repo :: Repository -> HSP XML repo r =
  • <% rName r %> <% if rDescription r /= "" then <% <% cdata " — " %><% rDescription r %> %> else <% "" %> %> <% repoForkSourceDescription r %> <% if rWebsite r /= "" then <% (<% rWebsite r %>) %> else <% "" %> %>
  • register :: [(String, String)] -> HSPage register is = base "register" False register

    sign up

    <% field (input'' is "name") "username" "" %> <% field (input'' is "email") "email" "" %> <% field (password'' is "password1") "password" (convert is "oauth" "optional" "") %> <% field (password'' is "password2") "password, again" "" %> <% field (textarea' is 10 "keys") "ssh public key(s) (required for push)" "" %> <% field (security is "security_question") (convert is "oauth" "" "what RCS is hosted here ? (anti-spam)") "" %> <% submit "sign me up" %>
    <% submit "Sign up with Github" %>
    <% submit "Sign up with Google" %>
    where convert js i f nf = fromMaybe nf (fmap (const f) (lookup i js)) input'' js n = inputWith' js n [("autocomplete","off")] security js n = password'' js n = passwordWith' js n [("autocomplete","off")] login :: [(String, String)] -> HSPage login is = base "login" False login

    log in

    <% field (input' is "name") "name" "" %> <% field (password' is "password") "password" "" %> <% submit "log me in" %>
    <% submit "Sign in using Github" %>
    <% submit "Sign in using Google" %>
    Forgot Password?
    settings :: User -> HSPage settings u = base "settings" False settings

    account settings

    <% field (input "full_name" (uFullName u)) "full name" "" %> <% field (input "website" (uWebsite u)) "website" "" %>

    change password?

    <% if isJust (uPaS u) then field (password' [] "password") "current password" "" else
    %> <% field (password' [] "password1") "new password" "" %> <% field (password' [] "password2") "(again)" "" %>
    <% field (textarea 10 "keys" (unlines (uKeys u))) "pubkeys" "" %> <% submit "update settings" %>
    <% submit "Link with Github" %>
    <% submit "Link with Google" %>
    forgotPassword :: [(String, String)] -> HSPage forgotPassword is = base "forgot password" False forgot password

    forgot password

    <% field (input' is "username") "username" "" %> <% submit "submit" %>
    resetPassword :: [(String, String)] -> HSPage resetPassword _ = base "reset password" False reset password

    reset password

    <% field (password' [] "password1") "new password" "" %> <% field (password' [] "password2") "(again)" "" %> <% submit "submit" %>