fradrive/src/Foundation.hs

436 lines
18 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternGuards #-}
module Foundation where
import Import.NoFoundation
import Database.Persist.Sql (ConnectionPool, runSqlPool)
import Text.Hamlet (hamletFile)
import Text.Jasmine (minifym)
-- Used only when in "auth-dummy-login" setting is enabled.
import Yesod.Auth.Message
import Yesod.Auth.Dummy
import Yesod.Auth.LDAP
import LDAP.Data (LDAPScope(..))
import LDAP.Search (LDAPEntry(..))
import Yesod.Default.Util (addStaticContentExternal)
import Yesod.Core.Types (Logger)
import qualified Yesod.Core.Unsafe as Unsafe
import qualified Data.CaseInsensitive as CI
import qualified Data.Text.Encoding as TE
import Data.ByteArray (convert)
import Crypto.Hash (Digest, SHAKE256)
import Crypto.Hash.Conduit (sinkHash)
import qualified Data.ByteString.Base64.URL as Base64 (encode)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as Lazy.ByteString
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.Conduit (($$))
import Data.Conduit.List (sourceList)
import Control.Monad.Except (MonadError(..), runExceptT)
import Handler.Utils.StudyFeatures
import qualified Data.UUID.Cryptographic as UUID
import qualified System.FilePath.Cryptographic as FilePath
import System.FilePath
-- | 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 UniWorX = UniWorX
{ appSettings :: AppSettings
, appStatic :: Static -- ^ Settings for static file serving.
, appConnPool :: ConnectionPool -- ^ Database connection pool.
, appHttpManager :: Manager
, appLogger :: Logger
, appCryptoIDKey :: CryptoIDKey
}
-- 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 UniWorX IO
-- type Widget = WidgetT UniWorX IO ()
mkYesodData "UniWorX" $(parseRoutesFile "routes")
data MenuItem = MenuItem
{ menuItemLabel :: Text
, menuItemRoute :: Route UniWorX
, menuItemAccessCallback :: Handler Bool
}
data MenuTypes
= NavbarLeft { menuItem :: MenuItem }
| NavbarRight { menuItem :: MenuItem }
| NavbarExtra { menuItem :: MenuItem }
-- | A convenient synonym for creating forms.
type Form x = Html -> MForm (HandlerT UniWorX IO) (FormResult x, Widget)
-- Please see the documentation for the Yesod typeclass. There are a number
-- of settings which can be configured by overriding methods here.
instance Yesod UniWorX 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 _ = Just <$> defaultClientSessionBackend
120 -- timeout in minutes
"client_session_key.aes"
-- 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.
-- Some users may also want to add the defaultCsrfMiddleware, which:
-- 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.
-- To add it, chain it together with the defaultMiddleware: yesodMiddleware = defaultYesodMiddleware . defaultCsrfMiddleware
-- For details, see the CSRF documentation in the Yesod.Core.Handler module of the yesod-core package.
yesodMiddleware = defaultYesodMiddleware
defaultLayout = defaultLinkLayout []
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
isAuthorized (AuthR _) _ = return Authorized
isAuthorized HomeR _ = return Authorized
isAuthorized FaviconR _ = return Authorized
isAuthorized RobotsR _ = return Authorized
isAuthorized (StaticR _) _ = return Authorized
isAuthorized ProfileR _ = isAuthenticated
isAuthorized TermShowR _ = return Authorized
isAuthorized CourseListR _ = return Authorized
isAuthorized (CourseListTermR _) _ = return Authorized
isAuthorized (CourseShowR _ _) _ = return Authorized
isAuthorized SubmissionListR _ = isAuthenticated
isAuthorized SubmissionDownloadMultiArchiveR _ = isAuthenticated
isAuthorized route isWrite = runDB $ isAuthorizedDB route isWrite
-- 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
minifym
genFileName
staticDir
(StaticR . flip StaticRoute [])
ext
mime
content
where
-- Generate a unique filename based on the content itself, this is used
-- for deduplication so a collision resistant hash function is required
--
-- SHA-3 (SHAKE256) seemed to be a future-proof choice
--
-- Length of hash is 144 bits instead of MD5's 128, so as to avoid
-- padding after base64-conversion
genFileName lbs = Text.unpack
. Text.decodeUtf8
. Base64.encode
. (convert :: Digest (SHAKE256 144) -> ByteString)
. runIdentity
$ sourceList (Lazy.ByteString.toChunks lbs) $$ sinkHash
-- 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
isAuthorizedDB :: Route UniWorX -> Bool -> YesodDB UniWorX AuthResult
isAuthorizedDB (SubmissionR cID) _ = submissionAccess $ Right cID
isAuthorizedDB (SubmissionDownloadSingleR cID _) _ = submissionAccess $ Right cID
isAuthorizedDB (SubmissionDownloadArchiveR (splitExtension -> (baseName, _))) _ = submissionAccess . Left . CryptoID $ CI.mk baseName
isAuthorizedDB TermEditR _ = adminAccess Nothing
isAuthorizedDB (TermEditExistR _) _ = adminAccess Nothing
isAuthorizedDB CourseEditR _ = lecturerAccess Nothing
isAuthorizedDB (CourseEditExistR t c) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort (TermKey t) c)
isAuthorizedDB (CourseEditExistIDR cID) _ = do
cIDKey <- getsYesod appCryptoIDKey
courseId <- UUID.decrypt cIDKey cID
courseLecturerAccess courseId
isAuthorizedDB route isWrite = lift $ isAuthorized route isWrite
submissionAccess :: Either CryptoFileNameSubmission CryptoUUIDSubmission -> YesodDB UniWorX AuthResult
submissionAccess cID = do
authId <- lift requireAuthId
cIDKey <- getsYesod appCryptoIDKey
submissionId <- either (FilePath.decrypt cIDKey) (UUID.decrypt cIDKey) cID
Submission{..} <- get404 submissionId
submissionUsers <- map (submissionUserUserId . entityVal) <$> selectList [SubmissionUserSubmissionId ==. submissionId] []
let auth = authId `elem` submissionUsers || Just authId == submissionRatingBy
return $ case auth of
True -> Authorized
False -> Unauthorized "No access to this submission"
adminAccess :: Maybe (Maybe SchoolId) -- ^ If @Just@, matched exactly against 'userAdminSchool'
-> YesodDB UniWorX AuthResult
adminAccess school = do
authId <- lift requireAuthId
schools <- map (userAdminSchool . entityVal) <$> selectList [UserAdminUser ==. authId] []
return $ case maybe (null schools) (`elem` schools) school of
True -> Authorized
False -> Unauthorized "No admin access"
lecturerAccess :: Maybe SchoolId
-> YesodDB UniWorX AuthResult
lecturerAccess school = do
authId <- lift requireAuthId
schools <- map (userLecturerSchool . entityVal) <$> selectList [UserLecturerUser ==. authId] []
return $ case maybe (null schools) (`elem` schools) school of
True -> Authorized
False -> Unauthorized "No lecturer access"
courseLecturerAccess :: CourseId -> YesodDB UniWorX AuthResult
courseLecturerAccess courseId = do
authId <- lift requireAuthId
users <- map (lecturerUserId . entityVal ) <$> selectList [ LecturerCourseId ==. courseId ] []
return $ case authId `elem` users of
True -> Authorized
False -> Unauthorized "No lecturer access for this course"
isAuthorizedDB' :: Route UniWorX -> Bool -> YesodDB UniWorX Bool
isAuthorizedDB' route isWrite = (== Authorized) <$> isAuthorizedDB route isWrite
isAuthorized' :: Route UniWorX -> Bool -> Handler Bool
isAuthorized' route isWrite = runDB $ isAuthorizedDB' route isWrite
-- Define breadcrumbs.
instance YesodBreadcrumbs UniWorX where
breadcrumb TermShowR = return ("Semester", Just HomeR)
breadcrumb TermEditR = return ("Neu", Just TermShowR)
breadcrumb (TermEditExistR _) = return ("Editieren", Just TermShowR)
breadcrumb CourseListR = return ("Kurs", Just HomeR)
breadcrumb (CourseListTermR term) = return (termToText term, Just TermShowR)
breadcrumb (CourseShowR term course) = return (course, Just $ CourseListTermR term)
breadcrumb CourseEditR = return ("Neu", Just CourseListR)
breadcrumb (CourseEditExistR _ _) = return ("Editieren", Just CourseListR)
breadcrumb SubmissionListR = return ("Abgaben", Just HomeR)
breadcrumb (SubmissionR _) = return ("Abgabe", Just SubmissionListR)
breadcrumb HomeR = return ("ReWorX", Nothing)
breadcrumb (AuthR _) = return ("Login", Just HomeR)
breadcrumb ProfileR = return ("Profile", Just HomeR)
breadcrumb _ = return ("home", Nothing)
defaultLinks :: [MenuTypes]
defaultLinks = -- Define the menu items of the header.
[ NavbarLeft $ MenuItem
{ menuItemLabel = "Home"
, menuItemRoute = HomeR
, menuItemAccessCallback = return True
}
, NavbarLeft $ MenuItem
{ menuItemLabel = "Kurse"
, menuItemRoute = CourseListR
, menuItemAccessCallback = return True
}
, NavbarRight $ MenuItem
{ menuItemLabel = "Profile"
, menuItemRoute = ProfileR
, menuItemAccessCallback = isJust <$> maybeAuthPair
}
, NavbarRight $ MenuItem
{ menuItemLabel = "Login"
, menuItemRoute = AuthR LoginR
, menuItemAccessCallback = isNothing <$> maybeAuthPair
}
, NavbarRight $ MenuItem
{ menuItemLabel = "Logout"
, menuItemRoute = AuthR LogoutR
, menuItemAccessCallback = isJust <$> maybeAuthPair
}
]
defaultLinkLayout :: [MenuTypes] -> Widget -> Handler Html
defaultLinkLayout = defaultMenuLayout . (defaultLinks ++)
defaultMenuLayout :: [MenuTypes] -> Widget -> Handler Html
defaultMenuLayout menu widget = do
master <- getYesod
mmsgs <- getMessages
mcurrentRoute <- getCurrentRoute
-- Get the breadcrumbs, as defined in the YesodBreadcrumbs instance.
(title, parents) <- breadcrumbs
menuTypes <- filterM (menuItemAccessCallback . menuItem) menu
-- 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
addStylesheet $ StaticR css_bootstrap_css
$(widgetFile "default-layout")
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
-- How to run database actions.
instance YesodPersist UniWorX where
type YesodPersistBackend UniWorX = SqlBackend
runDB action = runSqlPool action =<< appConnPool <$> getYesod
instance YesodPersistRunner UniWorX where
getDBRunner = defaultGetDBRunner appConnPool
instance YesodAuth UniWorX where
type AuthId UniWorX = UserId
-- 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@(Creds{..}) = runDB . fmap (either id id) . runExceptT $ do
let (userPlugin, userIdent)
| isDummy
, [dummyPlugin, dummyIdent] <- Text.splitOn ":" credsIdent
= (dummyPlugin, dummyIdent)
| otherwise
= (credsPlugin, credsIdent)
isDummy = credsPlugin == "dummy"
uAuth = UniqueAuthentication userPlugin userIdent
$logDebugS "auth" $ tshow ((userPlugin, userIdent), creds)
when isDummy . (throwError =<<) . lift $
maybe (UserError $ IdentifierNotFound credsIdent) (Authenticated . entityKey) <$> getBy uAuth
let
userMatrikelnummer = lookup "LMU-Stud-Matrikelnummer" credsExtra
userEmail' = lookup "mail" credsExtra
userDisplayName' = lookup "displayName" credsExtra
userEmail <- maybe (throwError $ ServerError "Could not retrieve user email") return userEmail'
userDisplayName <- maybe (throwError $ ServerError "Could not retrieve user name") return userDisplayName'
let
newUser = User{..}
userUpdate = [ UserMatrikelnummer =. userMatrikelnummer
, UserDisplayName =. userDisplayName
, UserEmail =. userEmail
]
userId <- lift $ entityKey <$> upsertBy uAuth newUser userUpdate
let
userStudyFeatures = concat <$> mapM (parseStudyFeatures userId) userStudyFeatures'
userStudyFeatures' = [ v | (k, v) <- credsExtra, k == "dfnEduPersonFeaturesOfStudy" ]
fs <- either (\err -> throwError . ServerError $ "Could not parse features of study: " <> err) return userStudyFeatures
lift $ deleteWhere [StudyFeaturesUser ==. userId]
forM_ fs $ \StudyFeatures{..} -> do
lift . insertMaybe studyFeaturesDegree $ StudyDegree (unStudyDegreeKey studyFeaturesDegree) Nothing Nothing
lift . insertMaybe studyFeaturesField $ StudyTerms (unStudyTermsKey studyFeaturesField) Nothing Nothing
lift $ insertMany_ fs
return $ Authenticated userId
where
insertMaybe key val = get key >>= maybe (insert_ val) (\_ -> return ())
-- You can add other plugins like Google Email, email or OAuth here
authPlugins app = [genericAuthLDAP $ ldapConfig app] ++ extraAuthPlugins
-- Enable authDummy login if enabled.
where extraAuthPlugins = [authDummy | appAuthDummyLogin $ appSettings app]
authHttpManager = getHttpManager
ldapConfig :: UniWorX -> LDAPConfig
ldapConfig app@(appSettings -> settings) = LDAPConfig
{ usernameFilter = \u -> principalName <> "=" <> u
, identifierModifier
, ldapUri = appLDAPURI settings
, initDN = appLDAPDN settings
, initPass = appLDAPPw settings
, baseDN = appLDAPBaseName settings
, ldapScope = LdapScopeSubtree
}
where
principalName :: IsString a => a
principalName = "userPrincipalName"
identifierModifier _ entry = case lookup principalName $ leattrs entry of
Just [n] -> Text.pack n
_ -> error "Could not determine user principal name"
-- | Access function to determine if a user is logged in.
isAuthenticated :: Handler AuthResult
isAuthenticated = do
muid <- maybeAuthId
return $ case muid of
Nothing -> Unauthorized "You must login to access this page"
Just _ -> Authorized
instance YesodAuthPersist UniWorX
-- This instance is required to use forms. You can modify renderMessage to
-- achieve customized and internationalized form validation messages.
instance RenderMessage UniWorX 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 UniWorX where
getHttpManager = appHttpManager
unsafeHandler :: UniWorX -> 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