Experimental changes to Vervis.

[[ 🗃 ^KrXYo vervis ]] :: [📥 Inbox] [📤 Outbox] [🐤 Followers] [🤝 Collaborators] [🛠 Changes]

Clone

HTTPS: darcs clone https://vervis.peers.community/repos/KrXYo

SSH: darcs clone USERNAME@vervis.peers.community:KrXYo

Tags

TODO

src / Vervis / Handler /

Home.hs

{- This file is part of Vervis.
 -
 - Written in 2016 by fr33domlover <fr33domlover@riseup.net>.
 -
 - ♡ Copying is an act of love. Please copy, reuse and share.
 -
 - The author(s) have dedicated all copyright and related and neighboring
 - rights to this software to the public domain worldwide. This software is
 - distributed without any warranty.
 -
 - You should have received a copy of the CC0 Public Domain Dedication along
 - with this software. If not, see
 - <http://creativecommons.org/publicdomain/zero/1.0/>.
 -}

module Vervis.Handler.Home
    ( getHomeR
    )
where

import Vervis.Import hiding (on)

import Database.Esqueleto hiding ((==.))
import Yesod.Auth.Account (newAccountR)
import Data.Time.Clock (diffUTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)
import Time.Types (Elapsed (..), Seconds (..))

import qualified Database.Esqueleto as E ((==.))

import Vervis.Darcs
import Vervis.Model.Ident
import Vervis.Model.Repo
import Vervis.Path

import Data.EventTime.Local
import qualified Vervis.GitOld as G
import qualified Vervis.Darcs as D

intro :: Handler Html
intro = do
    rows <- do
        repos <- runDB $ select $ from $
            \ (repo `LeftOuterJoin` project `InnerJoin` sharer) -> do
                on $ repo ^. RepoSharer E.==. sharer ^. SharerId
                on $ repo ^. RepoProject E.==. project ?. ProjectId
                orderBy
                    [ asc $ sharer ^. SharerIdent
                    , asc $ project ?. ProjectIdent
                    , asc $ repo ^. RepoIdent
                    ]
                return
                    ( sharer ^. SharerIdent
                    , project ?. ProjectIdent
                    , repo ^. RepoIdent
                    , repo ^. RepoVcs
                    )
        now <- liftIO getCurrentTime
        let utc (Seconds i) = posixSecondsToUTCTime $ fromIntegral i
        forM repos $
            \ (Value sharer, Value mproj, Value repo, Value vcs) -> do
                path <- askRepoDir sharer repo
                mlast <- case vcs of
                    VCSDarcs -> liftIO $ D.lastChange path now
                    VCSGit -> do
                        mel <- liftIO $ G.lastChange path
                        return $ Just $ case mel of
                            Nothing -> Never
                            Just (Elapsed t) ->
                                intervalToEventTime $
                                FriendlyConvert $
                                now `diffUTCTime` utc t
                return (sharer, mproj, repo, vcs, mlast)
    defaultLayout $ do
        setTitle "Welcome to Vervis!"
        $(widgetFile "homepage")

personalOverview :: Entity Person -> Handler Html
personalOverview (Entity _pid person) = do
    (ident, projects) <- runDB $ do
        let sid = personIdent person
        sharer <- get404 sid
        projs <- selectList [ProjectSharer ==. sid] [Asc ProjectIdent]
        let pi (Entity _ proj) = projectIdent proj
        return (sharerIdent sharer, map pi projs)
    defaultLayout $ do
        setTitle "Vervis > Overview"
        $(widgetFile "personal-overview")

getHomeR :: Handler Html
getHomeR = do
    mp <- maybeAuth
    case mp of
        Just p  -> personalOverview p
        Nothing -> intro
[See repo JSON]