1
0
Fork 0
mirror of https://code.sup39.dev/repos/Wqawg synced 2025-01-08 20:56:47 +09:00
vervis/src/Vervis/Foundation.hs

1204 lines
55 KiB
Haskell
Raw Normal View History

{- This file is part of Vervis.
-
- Written in 2016, 2018, 2019 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.Foundation where
2016-02-13 12:35:30 +09:00
2016-05-02 19:03:29 +09:00
import Prelude (init, last)
import Control.Concurrent.MVar (MVar, newEmptyMVar)
import Control.Concurrent.STM.TVar
import Control.Monad.Logger.CallStack (logWarn)
import Control.Monad.STM (atomically)
import Control.Monad.Trans.Except
2016-05-27 01:25:23 +09:00
import Control.Monad.Trans.Maybe
import Crypto.Error (CryptoFailable (..))
import Crypto.PubKey.Ed25519 (PublicKey, publicKey, signature, verify)
import Data.Either (isRight)
import Data.HashMap.Strict (HashMap)
import Data.Maybe (fromJust)
import Data.PEM (pemContent)
import Data.Text.Encoding (decodeUtf8')
import Data.Time.Interval (TimeInterval, fromTimeUnit, toTimeUnit)
import Data.Time.Units (Second, Minute, Day)
2016-02-13 12:35:30 +09:00
import Database.Persist.Sql (ConnectionPool, runSqlPool)
import Graphics.SVGFonts.ReadFont (PreparedFont)
import Network.HTTP.Client (Manager, HttpException, requestFromURI, responseBody)
import Network.HTTP.Simple (httpJSONEither, setRequestManager, addRequestHeader)
import Network.HTTP.Types.Header (hHost)
import Network.URI (URI, uriAuthority, uriFragment, uriRegName, parseURI)
import Text.Shakespeare.Text (textFile)
2016-02-13 12:35:30 +09:00
import Text.Hamlet (hamletFile)
--import Text.Jasmine (minifym)
import UnliftIO.MVar (withMVar)
import Yesod.Auth.Account
import Yesod.Auth.Account.Message (AccountMsg (MsgUsernameExists))
import Yesod.Auth.Message (AuthMessage (IdentifierNotFound))
2016-02-13 12:35:30 +09:00
import Yesod.Core.Types (Logger)
import Yesod.Default.Util (addStaticContentExternal)
import qualified Data.ByteString.Char8 as BC (unpack)
import qualified Data.ByteString.Lazy as BL (ByteString)
import qualified Data.HashMap.Strict as M (lookup, insert)
import qualified Yesod.Core.Unsafe as Unsafe
--import qualified Data.CaseInsensitive as CI
import Data.Text as T (pack, intercalate, concat)
--import qualified Data.Text.Encoding as TE
import Network.HTTP.Signature hiding (Algorithm (..))
import Yesod.Auth.Unverified
import Yesod.Auth.Unverified.Creds
import Yesod.HttpSignature (YesodHttpSig (..))
import Yesod.Mail.Send
2016-02-13 12:35:30 +09:00
import qualified Network.HTTP.Signature as S (Algorithm (..))
2016-02-13 12:35:30 +09:00
import Network.FedURI
import Web.ActivityPub hiding (PublicKey)
import Text.Email.Local
import Text.Jasmine.Local (discardm)
import Vervis.Access
import Vervis.ActorKey (ActorKey)
import Vervis.Import.NoFoundation hiding (Handler, Day, last, init, logWarn)
2016-05-27 01:25:23 +09:00
import Vervis.Model.Group
import Vervis.Model.Ident
import Vervis.Model.Role
import Vervis.Widget (breadcrumbsW, revisionW)
2016-05-02 23:16:51 +09:00
2016-02-13 12:35:30 +09:00
-- | The foundation datatype for your application. This can be a good place to
-- keep settings and values requiring initialization before your application
-- starts running, such as database connections. Every handler will have
-- access to the data present here.
data App = App
{ appSettings :: AppSettings
, appStatic :: Static -- ^ Settings for static file serving.
, appConnPool :: ConnectionPool -- ^ Database connection pool.
, appHttpManager :: Manager
, appLogger :: Logger
, appMailQueue :: Maybe (Chan (MailRecipe App))
, appSvgFont :: PreparedFont Double
, appActorKeys :: TVar (ActorKey, ActorKey, Bool)
, appInstanceMutex :: TVar (HashMap Text (MVar ()))
, appCapSignKey :: ActorKey
, appHashidEncode :: Int64 -> Text
, appHashidDecode :: Text -> Maybe Int64
, appActivities :: TVar (Vector (UTCTime, Either String (ByteString, BL.ByteString)))
2016-02-13 12:35:30 +09:00
}
-- This is where we define all of the routes in our application. For a full
-- explanation of the syntax, please see:
-- http://www.yesodweb.com/book/routing-and-handlers
--
-- Note that this is really half the story; in Application.hs, mkYesodDispatch
-- generates the rest of the code. Please see the following documentation
-- for an explanation for this split:
-- http://www.yesodweb.com/book/scaffolding-and-the-site-template#scaffolding-and-the-site-template_foundation_and_application_modules
--
-- This function also generates the following type synonyms:
-- type Handler = HandlerT App IO
-- type Widget = WidgetT App IO ()
mkYesodData "App" $(parseRoutesFile "config/routes")
-- | A convenient synonym for creating forms.
type Form a = Html -> MForm (HandlerT App IO) (FormResult a, Widget)
2016-02-13 12:35:30 +09:00
type AppDB = YesodDB App
2016-02-13 12:35:30 +09:00
-- Please see the documentation for the Yesod typeclass. There are a number
-- of settings which can be configured by overriding methods here.
instance Yesod App where
-- Controls the base of generated URLs. For more information on modifying,
-- see: https://github.com/yesodweb/yesod/wiki/Overriding-approot
approot = ApprootRequest $ \app req ->
case appRoot $ appSettings app of
Nothing -> getApprootText guessApproot app req
Just root -> root
-- Store session data on the client in encrypted cookies,
-- default session idle timeout is 120 minutes
makeSessionBackend app =
-- sslOnlySessions $
let s = appSettings app
t = fromIntegral (toTimeUnit $ appClientSessionTimeout s :: Minute)
k = appClientSessionKeyFile s
in Just <$> defaultClientSessionBackend t k
2016-02-13 12:35:30 +09:00
-- Yesod Middleware allows you to run code before and after each handler function.
-- The defaultYesodMiddleware adds the response header "Vary: Accept, Accept-Language" and performs authorization checks.
-- The defaultCsrfMiddleware:
-- a) Sets a cookie with a CSRF token in it.
-- b) Validates that incoming write requests include that token in either a header or POST parameter.
-- For details, see the CSRF documentation in the Yesod.Core.Handler module of the yesod-core package.
yesodMiddleware
-- sslOnlyMiddleware 120 .
= defaultCsrfSetCookieMiddleware
. (\ handler ->
csrfCheckMiddleware
handler
(getCurrentRoute >>= \ mr -> case mr of
Nothing -> return False
Just InboxR -> return False
Just (GitUploadRequestR _ _) -> return False
Just r -> isWriteRequest r
)
defaultCsrfHeaderName
defaultCsrfParamName
)
. defaultYesodMiddleware
2016-02-13 12:35:30 +09:00
defaultLayout widget = do
master <- getYesod
mmsg <- getMessage
mperson <- maybeAuthAllowUnverified
(title, bcs) <- breadcrumbs
2016-02-13 12:35:30 +09:00
-- We break up the default layout into two components:
-- default-layout is the contents of the body tag, and
-- default-layout-wrapper is the entire page. Since the final
-- value passed to hamletToRepHtml cannot be a widget, this allows
-- you to use normal widget features in default-layout.
pc <- widgetToPageContent $ do
setTitle $ toHtml $
T.intercalate "" (map snd bcs) <> "" <> title
let instanceHost = appInstanceHost $ appSettings master
2016-02-13 12:35:30 +09:00
$(widgetFile "default-layout")
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
-- Who can access which pages.
2016-05-25 15:53:22 +09:00
isAuthorized r w = case (r, w) of
(AuthR a , True)
| a == resendVerifyR -> personFromResendForm
(AuthR (PluginR "account" ["verify", u, _]), False) -> personUnver u
(OutboxR , True) -> personAny
(GroupsR , True) -> personAny
(GroupNewR , _ ) -> personAny
(GroupMembersR grp , True) -> groupAdmin grp
(GroupMemberNewR grp , _ ) -> groupAdmin grp
(GroupMemberR grp _memb , True) -> groupAdmin grp
(KeysR , _ ) -> personAny
(KeyR _key , _ ) -> personAny
(KeyNewR , _ ) -> personAny
(ClaimRequestsPersonR , _ ) -> personAny
(ProjectRolesR shr , _ ) -> personOrGroupAdmin shr
(ProjectRoleNewR shr , _ ) -> personOrGroupAdmin shr
(ProjectRoleR shr _rl , _ ) -> personOrGroupAdmin shr
(ProjectRoleOpsR shr _rl , _ ) -> personOrGroupAdmin shr
(ProjectRoleOpNewR shr _rl , _ ) -> personOrGroupAdmin shr
(ReposR shr , True) -> personOrGroupAdmin shr
(RepoNewR shr , _ ) -> personOrGroupAdmin shr
(RepoR shar _ , True) -> person shar
(RepoEditR shr _rp , _ ) -> person shr
(RepoDevsR shr _rp , _ ) -> person shr
(RepoDevNewR shr _rp , _ ) -> person shr
(RepoDevR shr _rp _dev , _ ) -> person shr
(ProjectsR shr , True) -> personOrGroupAdmin shr
(ProjectNewR shr , _ ) -> personOrGroupAdmin shr
(ProjectR shr _prj , True) -> person shr
(ProjectEditR shr _prj , _ ) -> person shr
(ProjectDevsR shr _prj , _ ) -> person shr
(ProjectDevNewR shr _prj , _ ) -> person shr
(ProjectDevR shr _prj _dev , _ ) -> person shr
2016-05-27 01:25:23 +09:00
-- (GlobalWorkflowsR , _ ) -> serverAdmin
-- (GlobalWorkflowNewR , _ ) -> serverAdmin
-- (GlobalWorkflowR _wfl , _ ) -> serverAdmin
(WorkflowsR shr , _ ) -> personOrGroupAdmin shr
(WorkflowNewR shr , _ ) -> personOrGroupAdmin shr
(WorkflowR shr _wfl , _ ) -> personOrGroupAdmin shr
2016-08-08 23:01:06 +09:00
(WorkflowFieldsR shr _ , _ ) -> personOrGroupAdmin shr
(WorkflowFieldNewR shr _ , _ ) -> personOrGroupAdmin shr
(WorkflowFieldR shr _ _ , _ ) -> personOrGroupAdmin shr
(WorkflowEnumsR shr _ , _ ) -> personOrGroupAdmin shr
(WorkflowEnumNewR shr _ , _ ) -> personOrGroupAdmin shr
(WorkflowEnumR shr _ _ , _ ) -> personOrGroupAdmin shr
(WorkflowEnumCtorsR shr _ _ , _ ) -> personOrGroupAdmin shr
(WorkflowEnumCtorNewR shr _ _ , _ ) -> personOrGroupAdmin shr
(WorkflowEnumCtorR shr _ _ _ , _ ) -> personOrGroupAdmin shr
(TicketsR s j , True) -> projOp ProjOpOpenTicket s j
(TicketNewR s j , _ ) -> projOp ProjOpOpenTicket s j
(TicketR user _ _ , True) -> person user
(TicketEditR user _ _ , _ ) -> person user
2016-08-11 16:58:51 +09:00
(TicketAcceptR s j _ , _ ) -> projOp ProjOpAcceptTicket s j
(TicketCloseR s j _ , _ ) -> projOp ProjOpCloseTicket s j
(TicketOpenR s j _ , _ ) -> projOp ProjOpReopenTicket s j
(TicketClaimR s j _ , _ ) -> projOp ProjOpClaimTicket s j
(TicketUnclaimR s j _ , _ ) -> projOp ProjOpUnclaimTicket s j
(TicketAssignR s j _ , _ ) -> projOp ProjOpAssignTicket s j
(TicketUnassignR s j _ , _ ) -> projOp ProjOpUnassignTicket s j
2016-06-08 10:28:18 +09:00
(ClaimRequestsTicketR s j _, True) -> projOp ProjOpRequestTicket s j
(ClaimRequestNewR s j _ , _ ) -> projOp ProjOpRequestTicket s j
(TicketDiscussionR _ _ _ , True) -> personAny
(TicketMessageR _ _ _ _ , True) -> personAny
(TicketTopReplyR _ _ _ , _ ) -> personAny
(TicketReplyR _ _ _ _ , _ ) -> personAny
(TicketDepsR s j _ , True) -> projOp ProjOpAddTicketDep s j
(TicketDepNewR s j _ , _ ) -> projOp ProjOpAddTicketDep s j
(TicketDepR s j _ _ , True) -> projOp ProjOpRemoveTicketDep s j
_ -> return Authorized
2016-05-27 01:25:23 +09:00
where
nobody :: Handler AuthResult
nobody = return $ Unauthorized "This operation is currently disabled"
serverAdmin :: Handler AuthResult
serverAdmin = nobody
2016-05-27 01:25:23 +09:00
personAnd
:: (Entity Person -> Handler AuthResult) -> Handler AuthResult
personAnd f = do
mp <- maybeAuth
case mp of
Nothing -> return AuthenticationRequired
Just p -> f p
personUnverifiedAnd
:: (Entity Person -> Handler AuthResult) -> Handler AuthResult
personUnverifiedAnd f = do
mp <- maybeUnverifiedAuth
case mp of
Nothing -> return AuthenticationRequired
Just p -> f p
2016-05-27 01:25:23 +09:00
personAny :: Handler AuthResult
personAny = personAnd $ \ _p -> return Authorized
person :: ShrIdent -> Handler AuthResult
person ident = personAnd $ \ (Entity _ p) -> do
let sid = personIdent p
sharer <- runDB $ getJust sid
return $ if ident == sharerIdent sharer
then Authorized
else Unauthorized "No access to this operation"
personUnver :: Text -> Handler AuthResult
personUnver uname = personUnverifiedAnd $ \ p ->
if username p == uname
then return Authorized
else do
logWarn $ T.concat
[ "User ", username p, " tried to verify user ", uname
]
return $ Unauthorized "You can't verify other users"
personFromResendForm :: Handler AuthResult
personFromResendForm = personUnverifiedAnd $ \ p -> do
((result, _), _) <-
runFormPost $ renderDivs $ resendVerifyEmailForm ""
case result of
FormSuccess uname ->
if username p == uname
then return Authorized
else do
logWarn $ T.concat
[ "User ", username p, " tried to POST to \
\verification email resend for user ", uname
]
return $
Unauthorized
"You can't do that for other users"
_ -> do
logWarn $ T.concat
[ "User ", username p, " tried to POST to \
\verification email resend for invalid username"
]
return $
Unauthorized "Requesting resend for invalid username"
2016-05-27 01:25:23 +09:00
groupRole :: (GroupRole -> Bool) -> ShrIdent -> Handler AuthResult
groupRole role grp = personAnd $ \ (Entity pid _p) -> runDB $ do
Entity sid _s <- getBy404 $ UniqueSharer grp
Entity gid _g <- getBy404 $ UniqueGroup sid
mem <- getBy $ UniqueGroupMember pid gid
let mrole = groupMemberRole . entityVal <$> mem
2016-05-27 01:25:23 +09:00
return $ case mrole of
Nothing -> Unauthorized "Not a member of the group"
Just r ->
if role r
then Authorized
else Unauthorized "Not the expected group role"
2016-02-13 12:35:30 +09:00
groupAdmin :: ShrIdent -> Handler AuthResult
groupAdmin = groupRole (== GRAdmin)
personOrGroupAdmin :: ShrIdent -> Handler AuthResult
personOrGroupAdmin shr = personAnd $ \ (Entity vpid _vp) -> runDB $ do
Entity sid _ <- getBy404 $ UniqueSharer shr
mep <- getBy $ UniquePersonIdent sid
case mep of
Just (Entity pid _p) ->
return $ if pid == vpid
then Authorized
else Unauthorized "Cant access other peoples roles"
Nothing -> do
meg <- getBy $ UniqueGroup sid
case meg of
Nothing -> do
logWarn $
"Found non-person non-group sharer: " <>
shr2text shr
return $ error "Zombie sharer"
Just (Entity gid _g) -> do
mem <- getBy $ UniqueGroupMember vpid gid
return $ case mem of
Nothing -> Unauthorized "Not a group member"
Just (Entity _mid m) ->
if groupMemberRole m == GRAdmin
then Authorized
else Unauthorized "Not a group admin"
projOp
:: ProjectOperation -> ShrIdent -> PrjIdent -> Handler AuthResult
projOp op shr prj = do
mpid <- maybeAuthId
oas <- runDB $ checkProjectAccess mpid op shr prj
return $
case oas of
ObjectAccessAllowed -> Authorized
_ ->
Unauthorized
"You need a project role with that operation enabled"
2016-02-13 12:35:30 +09:00
-- This function creates static content files in the static folder
-- and names them based on a hash of their content. This allows
-- expiration dates to be set far in the future without worry of
-- users receiving stale content.
addStaticContent ext mime content = do
master <- getYesod
let staticDir = appStaticDir $ appSettings master
addStaticContentExternal
discardm
2016-02-13 12:35:30 +09:00
genFileName
staticDir
(StaticR . flip StaticRoute [])
ext
mime
content
where
-- Generate a unique filename based on the content itself
genFileName lbs = "autogen-" ++ base64md5 lbs
-- What messages should be logged. The following includes all messages when
-- in development, and warnings and errors in production.
2018-12-05 12:41:19 +09:00
shouldLogIO app _source level = pure $
2016-02-13 12:35:30 +09:00
appShouldLogAll (appSettings app)
|| level == LevelWarn
|| level == LevelError
makeLogger = return . appLogger
-- How to run database actions.
instance YesodPersist App where
type YesodPersistBackend App = SqlBackend
runDB action = do
master <- getYesod
runSqlPool action $ appConnPool master
instance YesodPersistRunner App where
getDBRunner = defaultGetDBRunner appConnPool
instance YesodMailSend App where
data MailMessage App
2018-04-01 10:29:50 +09:00
= MailVerifyAccount (Route App)
| MailResetPassphrase (Route App)
formatMailMessage _reply _mname msg =
case msg of
MailVerifyAccount url ->
( "Verify your Vervis account"
, $(textFile "templates/person/email/verify-account.md")
)
MailResetPassphrase url ->
( "Reset your Vervis passphrase"
, $(textFile "templates/person/email/reset-passphrase.md")
)
getMailSettings = getsYesod $ appMail . appSettings
getSubmitMail = do
mchan <- getsYesod appMailQueue
case mchan of
Nothing -> return Nothing
Just chan -> return $ Just $ liftIO . writeChan chan
2016-02-13 12:35:30 +09:00
instance YesodAuth App where
type AuthId App = PersonId
2016-02-13 12:35:30 +09:00
-- Where to send a user after successful login
loginDest _ = HomeR
-- Where to send a user after logout
logoutDest _ = HomeR
-- Override the above two destinations when a Referer: header is present
redirectToReferer _ = True
2018-12-05 12:41:19 +09:00
authenticate creds = liftHandler $ do
let ident = credsIdent creds
mpid <- runDB $ getBy $ UniquePersonLogin $ credsIdent creds
return $ case mpid of
Nothing -> UserError $ IdentifierNotFound ident
Just (Entity pid _) -> Authenticated pid
2016-02-13 12:35:30 +09:00
-- You can add other plugins like BrowserID, email or OAuth here
authPlugins _ = [accountPlugin]
2016-02-13 12:35:30 +09:00
authHttpManager = error "authHttpManager"
2016-02-13 12:35:30 +09:00
onLogout = clearUnverifiedCreds False
2016-02-13 12:35:30 +09:00
instance YesodAuthPersist App
newtype AccountPersistDB' a = AccountPersistDB'
{ unAccountPersistDB' :: Handler a
}
deriving (Functor, Applicative, Monad, MonadIO)
morphAPDB :: AccountPersistDB App Person a -> AccountPersistDB' a
morphAPDB = AccountPersistDB' . runAccountPersistDB
instance AccountDB AccountPersistDB' where
type UserAccount AccountPersistDB' = Entity Person
loadUser = morphAPDB . loadUser
loadUserByEmailAddress = morphAPDB . loadUserByEmailAddress
addNewUser name email key pwd = AccountPersistDB' $ runDB $ do
now <- liftIO getCurrentTime
let sharer = Sharer
{ sharerIdent = text2shr name
, sharerName = Nothing
, sharerCreated = now
}
msid <- insertBy sharer
case msid of
Left _ -> do
mr <- getMessageRender
return $ Left $ mr $ MsgUsernameExists name
Right sid -> do
2018-04-01 12:02:35 +09:00
let defTime = UTCTime (ModifiedJulianDay 0) 0
person = Person
{ personIdent = sid
, personLogin = name
, personPassphraseHash = pwd
, personEmail = email
, personVerified = False
, personVerifiedKey = key
, personVerifiedKeyCreated = now
, personResetPassKey = ""
, personResetPassKeyCreated = defTime
, personAbout = ""
}
pid <- insert person
return $ Right $ Entity pid person
verifyAccount = morphAPDB . verifyAccount
setVerifyKey = (morphAPDB .) . setVerifyKey
setNewPasswordKey = (morphAPDB .) . setNewPasswordKey
setNewPassword = (morphAPDB .) . setNewPassword
instance AccountSendEmail App where
sendVerifyEmail uname email url = do
sent <- sendMail (Address (Just uname) email) (MailVerifyAccount url)
unless sent $ do
2018-04-09 09:38:40 +09:00
setMessage "Mail sending disabled, please contact admin"
2018-04-01 10:29:50 +09:00
ur <- getUrlRender
logWarn $ T.concat
[ "Verification email NOT SENT for user "
, uname, " <", emailText email, ">: "
2018-04-01 10:29:50 +09:00
, ur url
]
sendNewPasswordEmail uname email url = do
sent <- sendMail (Address (Just uname) email) (MailResetPassphrase url)
unless sent $ do
2018-04-09 09:38:40 +09:00
setMessage "Mail sending disabled, please contact admin"
2018-04-01 10:29:50 +09:00
ur <- getUrlRender
logWarn $ T.concat
["Password reset email NOT SENT for user "
, uname, " <", emailText email, ">: "
2018-04-01 10:29:50 +09:00
, ur url
]
instance YesodAuthVerify App where
verificationRoute _ = ResendVerifyEmailR
instance YesodAuthAccount AccountPersistDB' App where
requireEmailVerification = appEmailVerification . appSettings
2018-04-01 12:02:35 +09:00
emailVerifyKeyDuration _ = Just $ fromTimeUnit (1 :: Day)
passphraseResetKeyDuration _ = Just $ fromTimeUnit (1 :: Day)
2018-04-11 20:09:42 +09:00
allowLoginByEmailAddress _ = True
2018-04-01 12:02:35 +09:00
runAccountDB = unAccountPersistDB'
unregisteredLogin u = do
2018-12-05 12:41:19 +09:00
setUnverifiedCreds True $ Creds "account" (username u) []
return mempty
registrationAllowed = do
settings <- getsYesod appSettings
if appRegister settings
then do
room <- case appAccounts settings of
Nothing -> return True
Just cap -> do
current <- runDB $ count ([] :: [Filter Person])
return $ current < cap
return $
if room
then Nothing
else Just $ setMessage "Maximal number of registered users reached"
else return $ Just $ setMessage "User registration disabled"
2016-02-13 12:35:30 +09:00
-- This instance is required to use forms. You can modify renderMessage to
-- achieve customized and internationalized form validation messages.
instance RenderMessage App FormMessage where
renderMessage _ _ = defaultFormMessage
-- Useful when writing code that is re-usable outside of the Handler context.
-- An example is background jobs that send email.
-- This can also be useful for writing code that works across multiple Yesod
-- applications.
--instance HasHttpManager App where
-- getHttpManager = appHttpManager
2016-02-13 12:35:30 +09:00
unsafeHandler :: App -> Handler a -> IO a
unsafeHandler = Unsafe.fakeHandlerGetLogger appLogger
-- Note: Some functionality previously present in the scaffolding has been
-- moved to documentation in the Wiki. Following are some hopefully helpful
-- links:
--
-- https://github.com/yesodweb/yesod/wiki/Sending-email
-- https://github.com/yesodweb/yesod/wiki/Serve-static-files-from-a-separate-domain
-- https://github.com/yesodweb/yesod/wiki/i18n-messages-in-the-scaffolding
2016-02-27 14:41:36 +09:00
-- TODO this is copied from stm-2.5, remove when we upgrade LTS
stateTVar :: TVar s -> (s -> (a, s)) -> STM a
stateTVar var f = do
s <- readTVar var
let (a, s') = f s -- since we destructure this, we are strict in f
writeTVar var s'
return a
withHostLock :: Text -> Handler a -> Handler a
withHostLock host action = do
tvar <- getsYesod appInstanceMutex
mvar <- liftIO $ do
existing <- M.lookup host <$> readTVarIO tvar
case existing of
Just v -> return v
Nothing -> do
v <- newEmptyMVar
atomically $ stateTVar tvar $ \ m ->
case M.lookup host m of
Just v' -> (v', m)
Nothing -> (v, M.insert host v m)
withMVar mvar $ const action
sumUpTo :: Int -> AppDB Int -> AppDB Int -> AppDB Bool
sumUpTo limit action1 action2 = do
n <- action1
if n <= limit
then do
m <- action2
return $ n + m <= limit
else return False
-- | Grab instance and remote sharer IDs from the DB, inserting new ones if
-- they can't be found in the DB. The @Maybe Bool@ indicates whether the IDs
-- are newly inserted record: 'Nothing' means they're both new. @Just True@
-- means the instance record existed but the remote sharer is new. @Just False@
-- means both the instance and remote sharer existed in the DB.
instanceAndActor
:: Text
-> LocalURI
-> LocalURI
-> AppDB (InstanceId, RemoteSharerId, Maybe Bool)
instanceAndActor host luActor luInbox = do
(iid, inew) <- idAndNew <$> insertBy (Instance host)
let rs = RemoteSharer luActor iid luInbox
if inew
then do
rsid <- insert rs
return (iid, rsid, Nothing)
else do
(rsid, rsnew) <- idAndNew <$> insertBy rs
return (iid, rsid, Just rsnew)
where
idAndNew (Left (Entity iid _)) = (iid, False)
idAndNew (Right iid) = (iid, True)
actorRoom :: Int -> RemoteSharerId -> AppDB Bool
actorRoom limit rsid = do
sumUpTo limit
(count [VerifKeySharedUsageUser ==. rsid])
(count [VerifKeySharer ==. Just rsid])
getOldUsageId rsid = fmap entityKey . listToMaybe <$> selectList [VerifKeySharedUsageUser ==. rsid] [Asc VerifKeySharedUsageId, LimitTo 1]
getOldPersonalKeyId rsid = fmap entityKey . listToMaybe <$> selectList [VerifKeySharer ==. Just rsid] [Asc VerifKeyExpires, Asc VerifKeyId, LimitTo 1]
makeActorRoomByPersonal limit rsid vkid = do
room <-
if limit <= 1
then return False
else (< limit-1) <$> count [VerifKeySharer ==. Just rsid, VerifKeyId !=. vkid]
unless room $ delete vkid
makeActorRoomByUsage limit rsid suid = do
room <-
if limit <= 1
then return False
else
sumUpTo (limit-1)
(count [VerifKeySharedUsageUser ==. rsid, VerifKeySharedUsageId !=. suid])
(count [VerifKeySharer ==. Just rsid])
unless room $ delete suid
-- | Checks whether the given actor has room left for a new shared key usage
-- record, and if not, deletes a record to make room for a new one. It prefers
-- to delete a usage record if any exist; otherwise it deletes a personal key.
--
-- The first parameter is the actor key storage limit, and it must be above
-- zero.
makeActorRoomForUsage :: Int -> RemoteSharerId -> AppDB ()
makeActorRoomForUsage limit rsid = do
msuid <- getOldUsageId rsid
case msuid of
Nothing -> do
mvkid <- getOldPersonalKeyId rsid
case mvkid of
Nothing -> return ()
Just vkid -> makeActorRoomByPersonal limit rsid vkid
Just suid -> makeActorRoomByUsage limit rsid suid
-- | Checks whether the given actor has room left for a new personal key
-- record, and if not, deletes a record to make room for a new one. It prefers
-- to delete a personal key if any exist; otherwise it deletes a usage record.
--
-- The first parameter is the actor key storage limit, and it must be above
-- zero.
makeActorRoomForPersonalKey :: Int -> RemoteSharerId -> AppDB ()
makeActorRoomForPersonalKey limit rsid = do
mvkid <- getOldPersonalKeyId rsid
case mvkid of
Nothing -> do
msuid <- getOldUsageId rsid
case msuid of
Nothing -> return ()
Just suid -> makeActorRoomByUsage limit rsid suid
Just vkid -> makeActorRoomByPersonal limit rsid vkid
-- | Checks whether the given instance has room left for a new shared key
-- record, and if not, deletes a record to make room for a new one.
--
-- The first parameter is the actor key storage limit, and it must be above
-- zero.
makeInstanceRoom :: Int -> InstanceId -> AppDB ()
makeInstanceRoom limit iid = do
mvk <- listToMaybe <$> selectList [VerifKeyInstance ==. iid, VerifKeySharer ==. Nothing] [Asc VerifKeyExpires, Asc VerifKeyId, LimitTo 1]
case mvk of
Nothing -> return ()
Just (Entity vkid _) -> do
room <-
if limit <= 1
then return False
else (< limit-1) <$> count [VerifKeyInstance ==. iid, VerifKeySharer ==. Nothing, VerifKeyId !=. vkid]
unless room $ delete vkid
data RoomModeDB
= RoomModeNoLimit
| RoomModeLimit Int
data RoomMode
= RoomModeInstant
| RoomModeCached RoomModeDB
roomModeFromLimit :: Maybe Int -> RoomMode
roomModeFromLimit Nothing = RoomModeCached $ RoomModeNoLimit
roomModeFromLimit (Just limit) =
if limit <= 0
then RoomModeInstant
else RoomModeCached $ RoomModeLimit limit
actorRoomMode :: AppSettings -> RoomMode
actorRoomMode = roomModeFromLimit . appMaxActorKeys
instanceRoomMode :: AppSettings -> RoomMode
instanceRoomMode = roomModeFromLimit . appMaxInstanceKeys
-- | Given a shared key we have in our DB, verify that the given actor lists
-- this key, and update the DB accordingly.
--
-- * If the storage limit on actor keys is zero:
-- - If we're supposed to reject signatures when there's no room, raise
-- an error! We can't store anything with a limit of 0
-- - Otherwise, fetch the actor, store in DB if we don't have it, verify
-- usage via actor JSON. Usage isn't stored in the DB.
-- * If there's no storage limit, or it's above zero:
-- - If we know the actor and we have a record that it lists the key,
-- return success, no other action
-- - If we know the actor but we don't have a record of usage, fetch the
-- actor and verify usage. If the actor already has the maximal number of
-- keys: If we're supposed to reject signatures when there's no room,
-- raise an error. Otherwise, delete an old key/usage and store the new
-- usage in the DB.
-- - If we don't know the actor, fetch actor, verify usage, store actor and
-- usage in DB.
--
-- If we get success, that means the actor lists the key, and both the actor
-- and the usage exist in our DB now (if the storage limit isn't zero).
keyListedByActorShared
:: Manager
-> InstanceId
-> VerifKeyId
-> Text
-> LocalURI
-> LocalURI
-> ExceptT String Handler ()
keyListedByActorShared manager iid vkid host luKey luActor = do
(reject, roomMode) <- do
s <- getsYesod appSettings
return (appRejectOnMaxKeys s, actorRoomMode s)
case roomMode of
RoomModeInstant -> do
when reject $ throwE "Actor key storage limit is 0 and set to reject"
luInbox <- actorInbox <$> ExceptT (keyListedByActor manager host luKey luActor)
_ <- lift $ runDB $ insertUnique $ RemoteSharer luActor iid luInbox
return ()
RoomModeCached m -> do
mresult <- do
ments <- lift $ runDB $ do
mrs <- getBy $ UniqueRemoteSharer iid luActor
for mrs $ \ (Entity rsid _) ->
(rsid,) . isJust <$>
getBy (UniqueVerifKeySharedUsage vkid rsid)
return $
case ments of
Nothing -> Just Nothing
Just (rsid, used) ->
if used
then Nothing
else Just $ Just rsid
for_ mresult $ \ mrsid -> do
luInbox <- actorInbox <$> ExceptT (keyListedByActor manager host luKey luActor)
ExceptT $ runDB $ do
vkExists <- isJust <$> get vkid
case mrsid of
Nothing -> do
rsid <- insert $ RemoteSharer luActor iid luInbox
when vkExists $ insert_ $ VerifKeySharedUsage vkid rsid
return $ Right ()
Just rsid -> runExceptT $ when vkExists $ do
case m of
RoomModeNoLimit -> return ()
RoomModeLimit limit -> do
if reject
then do
room <- lift $ actorRoom limit rsid
unless room $ throwE "Actor key storage limit reached"
else lift $ makeActorRoomForUsage limit rsid
lift $ insert_ $ VerifKeySharedUsage vkid rsid
data VerifKeyDetail = VerifKeyDetail
{ vkdKeyId :: LocalURI
, vkdKey :: PublicKey
, vkdExpires :: Maybe UTCTime
, vkdActorId :: LocalURI
, vkdShared :: Bool
}
instance YesodHttpSig App where
data HttpSigVerResult App = HttpSigVerResult (Either String FedURI)
httpSigVerHeaders = const [hRequestTarget, hHost, hActivityPubActor]
httpSigVerSeconds =
fromIntegral . toSeconds . appHttpSigTimeLimit . appSettings
where
toSeconds :: TimeInterval -> Second
toSeconds = toTimeUnit
httpVerifySig (Verification malgo (KeyId keyid) input (Signature sig)) = fmap HttpSigVerResult $ runExceptT $ do
verifySigAlgo malgo
(host, luKey) <- f2l <$> parseKeyId keyid
signature <- parseSig sig
mluActorHeader <- getActorHeader host
let sigAlgo = isJust malgo
manager <- getsYesod appHttpManager
(inboxOrVkid, vkd) <- do
ments <- lift $ runDB $ do
mvk <- runMaybeT $ do
Entity iid _ <- MaybeT $ getBy $ UniqueInstance host
MaybeT $ getBy $ UniqueVerifKey iid luKey
for mvk $ \ vk@(Entity _ verifkey) -> do
mremote <- traverse getJust $ verifKeySharer verifkey
return (vk, mremote)
case ments of
Just (Entity vkid vk, mremote) -> do
(ua, s) <-
case mremote of
Just remote -> do
let sharer = remoteSharerIdent remote
for_ mluActorHeader $ \ u ->
if sharer == u
then return ()
else throwE "Key's owner doesn't match actor header"
return (sharer, False)
Nothing -> do
ua <- case mluActorHeader of
Nothing -> throwE "Got a sig with an instance key, but actor header not specified!"
Just u -> return u
manager <- getsYesod appHttpManager
let iid = verifKeyInstance vk
withHostLock' host $ keyListedByActorShared manager iid vkid host luKey ua
return (ua, True)
return
( Right (verifKeyInstance vk, vkid)
, VerifKeyDetail
{ vkdKeyId = luKey
, vkdKey = verifKeyPublic vk
, vkdExpires = verifKeyExpires vk
, vkdActorId = ua
, vkdShared = s
}
)
Nothing -> fetched2vkd luKey <$> fetchUnknownKey manager sigAlgo host mluActorHeader luKey
let verify' k = verify k input signature
errSig1 = throwE "Fetched fresh key; Ed25519 sig verification says not valid"
errSig2 = throwE "Used key from DB; Ed25519 sig verification says not valid; fetched fresh key; still not valid"
errTime = throwE "Key expired"
now <- liftIO getCurrentTime
let stillValid Nothing = True
stillValid (Just expires) = expires > now
if verify' (vkdKey vkd) && stillValid (vkdExpires vkd)
then case inboxOrVkid of
Left uinb -> ExceptT $ withHostLock host $ runDB $ addVerifKey host uinb vkd
Right _ids -> return ()
else case inboxOrVkid of
Left _uinb ->
if stillValid $ vkdExpires vkd
then errSig1
else errTime
Right (iid, vkid) -> do
let ua = vkdActorId vkd
listed = withHostLock' host $ keyListedByActorShared manager iid vkid host luKey ua
(newKey, newExp) <-
if vkdShared vkd
then fetchKnownSharedKey manager listed sigAlgo host ua luKey
else fetchKnownPersonalKey manager sigAlgo host ua luKey
if stillValid newExp
then return ()
else errTime
if verify' newKey
then lift $ runDB $ updateVerifKey vkid vkd
{ vkdKey = newKey
, vkdExpires = newExp
}
else errSig2
return $ l2f host $ vkdActorId vkd
where
verifySigAlgo = traverse_ $ \ algo ->
case algo of
S.AlgorithmEd25519 -> return ()
S.AlgorithmOther _ -> throwE "Unsupported algo in Sig header"
parseKeyId k =
case parseFedURI =<< (first displayException . decodeUtf8') k of
Left e -> throwE $ "keyId in Sig header isn't a valid FedURI: " ++ e
Right u -> return u
parseSig b =
case signature b of
CryptoPassed s -> return s
CryptoFailed e -> throwE "Parsing Ed25519 signature failed"
getActorHeader host = do
bs <- lookupHeaders hActivityPubActor
case bs of
[] -> return Nothing
[b] -> fmap Just . ExceptT . pure $ do
t <- first displayException $ decodeUtf8' b
(h, lu) <- f2l <$> parseFedURI t
if h == host
then Right ()
else Left "Key and actor have different hosts"
Right lu
_ -> throwE "Multiple ActivityPub-Actor headers"
fetched2vkd uk (Fetched k mexp ua uinb s) =
( Left uinb
, VerifKeyDetail
{ vkdKeyId = uk
, vkdKey = k
, vkdExpires = mexp
, vkdActorId = ua
, vkdShared = s
}
)
addVerifKey h uinb vkd =
if vkdShared vkd
then addSharedKey h uinb vkd
else addPersonalKey h uinb vkd
where
addSharedKey host luInbox (VerifKeyDetail luKey key mexpires luActor _) = runExceptT $ do
(reject, roomModeA, roomModeI) <- do
s <- getsYesod appSettings
return (appRejectOnMaxKeys s, actorRoomMode s, instanceRoomMode s)
(iid, rsid, inew) <- lift $ instanceAndActor host luActor luInbox
case roomModeI of
RoomModeInstant ->
when reject $ throwE "Instance key storage limit is 0 and set to reject"
RoomModeCached m -> do
case m of
RoomModeNoLimit -> return ()
RoomModeLimit limit ->
if reject
then when (isJust inew) $ do
room <- lift $ instanceRoom limit iid
unless room $ throwE "Instance key storage limit reached"
else when (isJust inew) $ lift $ makeInstanceRoom limit iid
vkid <- lift $ insert $ VerifKey luKey iid mexpires key Nothing
case roomModeA of
RoomModeInstant ->
when reject $ throwE "Actor key storage limit is 0 and set to reject"
RoomModeCached m -> do
case m of
RoomModeNoLimit -> return ()
RoomModeLimit limit ->
if reject
then when (inew == Just False) $ do
room <- lift $ actorRoom limit rsid
unless room $ throwE "Actor key storage limit reached"
else when (inew == Just False) $ lift $ makeActorRoomForUsage limit rsid
lift $ insert_ $ VerifKeySharedUsage vkid rsid
where
instanceRoom n iid =
(< n) <$> count [VerifKeyInstance ==. iid, VerifKeySharer ==. Nothing]
addPersonalKey host luInbox (VerifKeyDetail luKey key mexpires luActor _) = runExceptT $ do
(reject, roomMode) <- do
s <- getsYesod appSettings
return (appRejectOnMaxKeys s, actorRoomMode s)
(iid, rsid, inew) <- lift $ instanceAndActor host luActor luInbox
case roomMode of
RoomModeInstant ->
when reject $ throwE "Actor key storage limit is 0 and set to reject"
RoomModeCached m -> do
case m of
RoomModeNoLimit -> return ()
RoomModeLimit limit ->
if reject
then when (inew == Just False) $ do
room <- lift $ actorRoom limit rsid
unless room $ throwE "Actor key storage limit reached"
else when (inew == Just False) $ lift $ makeActorRoomForPersonalKey limit rsid
lift $ insert_ $ VerifKey luKey iid mexpires key (Just rsid)
updateVerifKey vkid vkd =
update vkid [VerifKeyExpires =. vkdExpires vkd, VerifKeyPublic =. vkdKey vkd]
withHostLock' h = ExceptT . withHostLock h . runExceptT
2016-05-02 19:03:29 +09:00
instance YesodBreadcrumbs App where
breadcrumb route = return $ case route of
2016-05-25 06:48:21 +09:00
StaticR _ -> ("", Nothing)
FaviconR -> ("", Nothing)
RobotsR -> ("", Nothing)
InboxR -> ("Inbox", Nothing)
OutboxR -> ("Outbox", Nothing)
ActorKey1R -> ("Actor Key 1", Nothing)
ActorKey2R -> ("Actor Key 2", Nothing)
2016-05-02 19:03:29 +09:00
HomeR -> ("Home", Nothing)
ResendVerifyEmailR -> ( "Resend verification email"
, Nothing
)
2016-05-25 06:48:21 +09:00
AuthR _ -> ("Auth", Nothing)
SharersR -> ("Sharers", Just HomeR)
SharerR shar -> (shr2text shar, Just SharersR)
2016-05-02 19:03:29 +09:00
PeopleR -> ("People", Just HomeR)
GroupsR -> ("Groups", Just HomeR)
GroupNewR -> ("New", Just GroupsR)
GroupMembersR shar -> ("Members", Just $ SharerR shar)
GroupMemberNewR shar -> ("New", Just $ GroupMembersR shar)
GroupMemberR grp memb -> ( shr2text memb
, Just $ GroupMembersR grp
)
KeysR -> ("Keys", Just HomeR)
KeyNewR -> ("New", Just KeysR)
KeyR key -> (ky2text key, Just KeysR)
2016-05-02 19:03:29 +09:00
ClaimRequestsPersonR -> ( "Ticket Claim Requests"
, Just HomeR
)
ProjectRolesR shr -> ( "Project Roles"
, Just $ SharerR shr
)
ProjectRoleNewR shr -> ("New", Just $ ProjectRolesR shr)
ProjectRoleR shr rl -> ( rl2text rl
, Just $ ProjectRolesR shr
)
ProjectRoleOpsR shr rl -> ( "Operations"
, Just $ ProjectRoleR shr rl
)
ProjectRoleOpNewR shr rl -> ( "New"
, Just $ ProjectRoleOpsR shr rl
)
ReposR shar -> ("Repos", Just $ SharerR shar)
2016-05-02 19:03:29 +09:00
RepoNewR shar -> ("New", Just $ ReposR shar)
RepoR shar repo -> (rp2text repo, Just $ ReposR shar)
RepoEditR shr rp -> ("Edit", Just $ RepoR shr rp)
RepoSourceR shar repo [] -> ("Files", Just $ RepoR shar repo)
RepoSourceR shar repo refdir -> ( last refdir
2016-05-02 19:03:29 +09:00
, Just $
RepoSourceR shar repo $
init refdir
2016-05-02 19:03:29 +09:00
)
RepoHeadChangesR shar repo -> ("Changes", Just $ RepoR shar repo)
RepoChangesR shar repo ref -> ( ref
, Just $ RepoHeadChangesR shar repo
)
2018-05-25 06:44:13 +09:00
RepoPatchR shr rp hash -> ( "Patch " <> hash
, Just $ RepoR shr rp
)
RepoDevsR shr rp -> ( "Collaboratots"
, Just $ RepoR shr rp
)
2016-05-29 23:13:25 +09:00
RepoDevNewR shr rp -> ("New", Just $ RepoDevsR shr rp)
RepoDevR shr rp dev -> ( shr2text dev
, Just $ RepoDevsR shr rp
)
2016-05-02 19:03:29 +09:00
2016-05-25 06:48:21 +09:00
DarcsDownloadR _ _ _ -> ("", Nothing)
GitRefDiscoverR _ _ -> ("", Nothing)
GitUploadRequestR _ _ -> ("", Nothing)
2016-05-25 06:48:21 +09:00
ProjectsR shar -> ("Projects", Just $ SharerR shar)
2016-05-02 19:03:29 +09:00
ProjectNewR shar -> ("New", Just $ ProjectsR shar)
ProjectR shar proj -> ( prj2text proj
, Just $ ProjectsR shar
)
ProjectEditR shr prj -> ("Edit", Just $ ProjectR shr prj)
ProjectDevsR shr prj -> ( "Collaborators"
, Just $ ProjectR shr prj
)
ProjectDevNewR shr prj -> ( "New"
, Just $ ProjectDevsR shr prj
)
ProjectDevR shr prj dev -> ( shr2text dev
, Just $ ProjectDevsR shr prj
)
2016-05-02 19:03:29 +09:00
WorkflowsR shr -> ("Workflows", Just $ SharerR shr)
WorkflowNewR shr -> ("New", Just $ WorkflowsR shr)
WorkflowR shr wfl -> ( wfl2text wfl
, Just $ WorkflowsR shr
)
2016-08-08 23:01:06 +09:00
WorkflowFieldsR shr wfl -> ( "Fields"
, Just $ WorkflowR shr wfl
)
WorkflowFieldNewR shr wfl -> ( "New"
, Just $ WorkflowFieldsR shr wfl
)
WorkflowFieldR shr wfl fld -> ( fld2text fld
, Just $ WorkflowFieldsR shr wfl
)
WorkflowEnumsR shr wfl -> ( "Enums"
, Just $ WorkflowR shr wfl
)
WorkflowEnumNewR shr wfl -> ( "New"
, Just $ WorkflowEnumsR shr wfl
)
WorkflowEnumR shr wfl enm -> ( enm2text enm
, Just $ WorkflowEnumsR shr wfl
)
WorkflowEnumCtorsR shr wfl enm -> ( "Ctors"
, Just $ WorkflowEnumR shr wfl enm
)
WorkflowEnumCtorNewR shr wfl enm -> ( "New"
, Just $
WorkflowEnumCtorsR shr wfl enm
)
WorkflowEnumCtorR shr wfl enm c -> ( c
, Just $
WorkflowEnumCtorsR shr wfl enm
)
2016-05-02 19:03:29 +09:00
TicketsR shar proj -> ( "Tickets"
, Just $ ProjectR shar proj
)
2016-08-04 16:36:24 +09:00
TicketTreeR shr prj -> ( "Tree", Just $ TicketsR shr prj)
2016-05-02 19:03:29 +09:00
TicketNewR shar proj -> ("New", Just $ TicketsR shar proj)
TicketR shar proj num -> ( T.pack $ '#' : show num
, Just $ TicketsR shar proj
)
TicketEditR shar proj num -> ( "Edit"
, Just $ TicketR shar proj num
)
2016-08-11 16:58:51 +09:00
TicketAcceptR _shr _prj _num -> ("", Nothing)
TicketCloseR _shar _proj _num -> ("", Nothing)
TicketOpenR _shar _proj _num -> ("", Nothing)
TicketClaimR _shar _proj _num -> ("", Nothing)
TicketUnclaimR _shar _proj _num -> ("", Nothing)
TicketAssignR shr prj num -> ( "Assign"
, Just $ TicketR shr prj num
)
TicketUnassignR _shr _prj _num -> ("", Nothing)
ClaimRequestsProjectR shr prj -> ( "Ticket Claim Requests"
, Just $ ProjectR shr prj
)
ClaimRequestsTicketR shr prj num -> ( "Ticket Claim Requests"
, Just $ TicketR shr prj num
)
2016-06-08 10:28:18 +09:00
ClaimRequestNewR shr prj num -> ( "New"
, Just $
ClaimRequestsTicketR shr prj num
)
2016-05-25 06:48:21 +09:00
TicketDiscussionR shar proj num -> ( "Discussion"
, Just $ TicketR shar proj num
)
TicketMessageR shar proj t c -> ( T.pack $ '#' : show c
, Just $
TicketDiscussionR shar proj t
)
TicketTopReplyR shar proj num -> ( "New topic"
, Just $
TicketDiscussionR shar proj num
)
TicketReplyR shar proj num cnum -> ( "Reply"
, Just $
TicketMessageR shar proj num cnum
)
TicketDepsR shr prj num -> ( "Dependencies"
, Just $ TicketR shr prj num
)
TicketDepNewR shr prj num -> ( "New dependency"
, Just $ TicketDepsR shr prj num
)
TicketDepR shr prj pnum cnum -> ( T.pack $ '#' : show cnum
, Just $ TicketDepsR shr prj pnum
)
2016-07-27 17:35:50 +09:00
TicketReverseDepsR shr prj num -> ( "Dependants"
, Just $ TicketR shr prj num
)
WikiPageR shr prj _page -> ("Wiki", Just $ ProjectR shr prj)