{-# OPTIONS_GHC -F -pgmF trhsx #-} module DarcsDen.Pages.Util where import Control.Monad.Trans ( liftIO ) import HSP import DarcsDen.Settings (issuetrackers) import DarcsDen.State.Repository ( Repository(..), repoURL, getRepositoryByID, getRepositoryForks ) repoForkSourceDescription :: Repository -> HSP XML repoForkSourceDescription repo = do f <- liftIO $ getForkedFromRepo repo case f of Nothing -> Just f' -> <% cdata " " %> (fork of <% rOwner f' %>'s <% rName f' %>) getForkedFromRepo :: Repository -> IO (Maybe Repository) getForkedFromRepo (Repository { rForkOf = Nothing }) = return Nothing getForkedFromRepo (Repository { rForkOf = Just id' }) = getRepositoryByID id' links :: Repository -> Bool -> HSP XML links r True = links' r [
  • repository settings
  • ,
  • delete
  • ] links r False = links' r [] links' :: Repository -> [HSP XML] -> HSP XML links' r exls = where patchesButton = do forks <- liftIO $ case (rID r, rRev r) of (Just id', Just _) -> getRepositoryForks id' _ -> return [] if null forks && rForkOf r == Nothing then
    else
  • branches
  • issuesButton r' = <% if issuetrackers && rIssueTracker r' then <%
  • issues
  • %> else <% "" %> %> packsTimeStamp Nothing =
    packsTimeStamp (Just ts) =
    Packs built at <% show ts %>