Eventually-decentralized project hosting and management platform

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

Clone

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

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

Tags

TODO

src / Vervis / Form /

Tracker.hs

{- This file is part of Vervis.
 -
 - Written in 2016, 2019, 2022 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.Form.Tracker
    ( NewDeck (..)
    , newDeckForm
    , NewLoom (..)
    , newLoomForm
    --, NewProjectCollab (..)
    --, newProjectCollabForm
    --, editProjectForm
    )
where

import Data.Bifunctor
import Data.Maybe
import Data.Text (Text)
import Database.Persist ((==.))
import Yesod.Form.Fields
import Yesod.Form.Functions
import Yesod.Form.Types
import Yesod.Persist.Core

import qualified Data.Text as T
import qualified Database.Esqueleto as E

import Yesod.Hashids

import Vervis.Foundation
import Vervis.Model

data NewDeck = NewDeck
    { ndName  :: Text
    , ndDesc  :: Text
    }

newDeckForm :: Form NewDeck
newDeckForm = renderDivs $ NewDeck
    <$> areq textField "Name*"       Nothing
    <*> areq textField "Description" Nothing

data NewLoom = NewLoom
    { nlName  :: Text
    , nlDesc  :: Text
    , nlRepo  :: RepoId
    }

newLoomForm :: Form NewLoom
newLoomForm = renderDivs $ NewLoom
    <$> areq textField  "Name*"       Nothing
    <*> areq textField  "Description" Nothing
    <*> areq selectRepo "Repo*"       Nothing
    where
    selectRepo = selectField $ do
        hashRepo <- getEncodeKeyHashid
        l <- runDB $ E.select $
            E.from $ \ (repo `E.InnerJoin` actor) -> do
                E.on $ repo E.^. RepoActor E.==. actor E.^. ActorId
                E.where_ $ E.isNothing $ repo E.^. RepoLoom
                E.orderBy [E.desc $ repo E.^. RepoId]
                return (actor E.^. ActorName, repo E.^. RepoId)
        optionsPairs $ map (option hashRepo) l
        where
        option hashRepo (E.Value name, E.Value repoID) =
            ( T.concat ["^", keyHashidText $ hashRepo repoID, " ", name]
            , repoID
            )

{-
data NewProjectCollab = NewProjectCollab
    { ncPerson :: PersonId
    , ncRole   :: Maybe RoleId
    }

newProjectCollabAForm
    :: SharerId -> ProjectId -> AForm Handler NewProjectCollab
newProjectCollabAForm sid jid = NewProjectCollab
    <$> areq selectPerson "Person*"     Nothing
    <*> aopt selectRole   "Custom role" Nothing
    where
    selectPerson = selectField $ do
        l <- runDB $ E.select $
            E.from $ \ (person `E.InnerJoin` sharer `E.LeftOuterJoin` (recip `E.InnerJoin` topic)) -> do
                E.on $ recip E.^. CollabRecipLocalCollab E.==. topic E.^. CollabTopicLocalProjectCollab E.&&.
                       topic E.^. CollabTopicLocalProjectProject E.==. E.val jid
                E.on $ person E.^. PersonId E.==. recip E.^. CollabRecipLocalPerson
                E.on $ person E.^. PersonIdent E.==. sharer E.^. SharerId
                E.where_ $ E.isNothing $ E.just $ recip E.^. CollabRecipLocalId
                return (sharer E.^. SharerIdent, person E.^. PersonId)
        optionsPairs $ map (bimap (shr2text . E.unValue) E.unValue) l
    selectRole =
        selectField $
        optionsPersistKey [RoleSharer ==. sid] [] $
        rl2text . roleIdent

newProjectCollabForm :: SharerId -> ProjectId -> Form NewProjectCollab
newProjectCollabForm sid jid = renderDivs $ newProjectCollabAForm sid jid

editProjectAForm :: SharerId -> Entity Project -> AForm Handler Project
editProjectAForm sid (Entity jid project) = Project
    <$> pure                         (projectActor project)
    <*> pure                         (projectIdent project)
    <*> pure                         (projectSharer project)
    <*> aopt textField "Name"        (Just $ projectName project)
    <*> aopt textField "Description" (Just $ projectDesc project)
    <*> pure                         (projectWorkflow project)
    <*> pure                         (projectNextTicket project)
    <*> aopt selectWiki "Wiki"       (Just $ projectWiki project)
    <*> aopt selectRole "User role"  (Just $ projectCollabUser project)
    <*> aopt selectRole "Guest role" (Just $ projectCollabAnon project)
    <*> pure                         (projectCreate project)
    where
    selectWiki =
        selectField $
        optionsPersistKey [RepoProject ==. Just jid] [] $
        rp2text . repoIdent
    selectRole =
        selectField $
        optionsPersistKey [RoleSharer ==. sid] [] $
        rl2text . roleIdent

editProjectForm :: SharerId -> Entity Project -> Form Project
editProjectForm s j = renderDivs $ editProjectAForm s j
-}
[See repo JSON]