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

340 lines
14 KiB
Haskell
Raw Normal View History

{- 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.Foundation where
2016-02-13 12:35:30 +09:00
2016-05-02 19:03:29 +09:00
import Prelude (init, last)
2016-05-27 01:25:23 +09:00
import Control.Monad.Trans.Maybe
2016-02-13 12:35:30 +09:00
import Database.Persist.Sql (ConnectionPool, runSqlPool)
import Text.Hamlet (hamletFile)
--import Text.Jasmine (minifym)
import Yesod.Auth.HashDB (authHashDB)
import Yesod.Auth.Message (AuthMessage (IdentifierNotFound))
2016-02-13 12:35:30 +09:00
import Yesod.Default.Util (addStaticContentExternal)
import Yesod.Core.Types (Logger)
import qualified Yesod.Core.Unsafe as Unsafe
2016-02-18 22:35:38 +09:00
--import qualified Data.CaseInsensitive as CI
import Data.Text as T (pack, intercalate)
2016-02-18 22:35:38 +09:00
--import qualified Data.Text.Encoding as TE
2016-02-13 12:35:30 +09:00
import Text.Jasmine.Local (discardm)
2016-05-02 23:16:51 +09:00
import Vervis.Import.NoFoundation hiding (last)
2016-05-27 01:25:23 +09:00
import Vervis.Model.Group
import Vervis.Model.Ident
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
}
-- 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 _ =
-- sslOnlySessions $
Just <$>
defaultClientSessionBackend 120 "config/client_session_key.aes"
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 =
-- defaultCsrfMiddleware .
-- sslOnlyMiddleware 120 .
defaultYesodMiddleware
2016-02-13 12:35:30 +09:00
defaultLayout widget = do
master <- getYesod
mmsg <- getMessage
2016-02-18 01:43:23 +09:00
mperson <- maybeAuth
(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
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
2016-05-27 01:25:23 +09:00
(GroupsR , True) -> personAny
(GroupNewR , _ ) -> personAny
(GroupMembersR grp , True) -> groupRole (== GRAdmin) grp
(GroupMemberNewR grp , _ ) -> groupRole (== GRAdmin) grp
(GroupMemberR grp _memb , True) -> groupRole (== GRAdmin) grp
(KeysR , _ ) -> personAny
(KeyR _key , _ ) -> personAny
(KeyNewR , _ ) -> personAny
(ReposR shar , True) -> person shar
(RepoNewR user , _ ) -> person user
(RepoR shar _ , True) -> person shar
(ProjectsR shar , True) -> person shar
(ProjectNewR user , _ ) -> person user
(TicketsR shar _ , True) -> person shar
(TicketNewR _ _ , _ ) -> personAny
(TicketR user _ _ , True) -> person user
(TicketEditR user _ _ , _ ) -> person user
(TicketDiscussionR _ _ _ , True) -> personAny
(TicketMessageR _ _ _ _ , True) -> personAny
(TicketTopReplyR _ _ _ , _ ) -> personAny
(TicketReplyR _ _ _ _ , _ ) -> personAny
2016-05-26 06:58:22 +09:00
_ -> return Authorized
2016-05-27 01:25:23 +09:00
where
personAnd
:: (Entity Person -> Handler AuthResult) -> Handler AuthResult
personAnd f = do
mp <- maybeAuth
case mp of
Nothing -> return AuthenticationRequired
Just p -> f p
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"
groupRole :: (GroupRole -> Bool) -> ShrIdent -> Handler AuthResult
groupRole role grp = personAnd $ \ (Entity pid _p) -> do
mrole <- runDB $ runMaybeT $ do
Entity sid _s <- MaybeT $ getBy $ UniqueSharer grp
Entity gid _g <- MaybeT $ getBy $ UniqueGroup sid
Entity _mid m <- MaybeT $ getBy $ UniqueGroupMember pid gid
return $ groupMemberRole m
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
-- 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.
shouldLog app _source level =
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 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
authenticate creds = 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 _ = [authHashDB $ Just . UniquePersonLogin]
2016-02-13 12:35:30 +09:00
authHttpManager = getHttpManager
instance YesodAuthPersist App
-- 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.
2016-02-13 12:35:30 +09:00
instance HasHttpManager App where
getHttpManager = appHttpManager
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
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)
2016-05-02 19:03:29 +09:00
HomeR -> ("Home", 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)
PersonNewR -> ("New", Just PeopleR)
PersonR shar -> (shr2text shar, Just PeopleR)
2016-05-02 19:03:29 +09:00
GroupsR -> ("Groups", Just HomeR)
GroupNewR -> ("New", Just GroupsR)
GroupR shar -> (shr2text shar, Just GroupsR)
GroupMembersR shar -> ("Members", Just $ GroupR shar)
KeysR -> ("Keys", Just HomeR)
KeyNewR -> ("New", Just KeysR)
KeyR key -> (ky2text key, Just KeysR)
2016-05-02 19:03:29 +09:00
ReposR shar -> ("Repos", Just $ PersonR shar)
RepoNewR shar -> ("New", Just $ ReposR shar)
RepoR shar repo -> (rp2text repo, Just $ ReposR shar)
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
)
2016-05-02 19:03:29 +09:00
2016-05-25 06:48:21 +09:00
DarcsDownloadR _ _ _ -> ("", Nothing)
GitRefDiscoverR _ _ -> ("", Nothing)
2016-05-02 19:03:29 +09:00
ProjectsR shar -> ("Projects", Just $ PersonR shar)
ProjectNewR shar -> ("New", Just $ ProjectsR shar)
ProjectR shar proj -> ( prj2text proj
, Just $ ProjectsR shar
)
2016-05-02 19:03:29 +09:00
TicketsR shar proj -> ( "Tickets"
, Just $ ProjectR shar proj
)
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-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
)