{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedLists #-} {-# LANGUAGE TemplateHaskell, QuasiQuotes #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE PatternGuards #-} {-# LANGUAGE TupleSections #-} {-# LANGUAGE FlexibleInstances, UndecidableInstances #-} 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 Data.CaseInsensitive (CI) 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.List (foldr1) import Data.Set (Set) import qualified Data.Set as Set import Data.Map (Map, (!?)) import qualified Data.Map as Map import Data.Conduit (($$)) import Data.Conduit.List (sourceList) import qualified Database.Esqueleto as E import Control.Monad.Except (MonadError(..), runExceptT) import Control.Monad.Trans.Maybe (MaybeT(..)) import Control.Monad.Trans.Reader (runReader) import System.FilePath import Handler.Utils.Templates import Handler.Utils.StudyFeatures import Control.Lens import Utils.Lens -- infixl 9 :$: -- pattern a :$: b = a b -- | 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") -- | Convenient Type Synonyms: type DB a = YesodDB UniWorX a type Form x = Html -> MForm (HandlerT UniWorX IO) (FormResult x, Widget) type MsgRenderer = MsgRendererS UniWorX -- see Utils -- Pattern Synonyms for convenience pattern CSheetR tid csh shn ptn = CourseR tid csh (SheetR shn ptn) -- Menus and Favourites data MenuItem = MenuItem { menuItemLabel :: Text , menuItemIcon :: Maybe Text , menuItemRoute :: Route UniWorX , menuItemAccessCallback' :: Handler Bool -- Check whether action is shown in ADDITION to authorization (which is always checked) } menuItemAccessCallback :: MenuItem -> Handler Bool menuItemAccessCallback MenuItem{..} = (&&) <$> ((==) Authorized <$> authCheck) <*> menuItemAccessCallback' where authCheck = handleAny (\_ -> return . Unauthorized $ error "authCheck caught exception") $ isAuthorized menuItemRoute False data MenuTypes -- Semantische Rolle: = NavbarAside { menuItem :: MenuItem } -- TODO | NavbarExtra { menuItem :: MenuItem } -- TODO | NavbarRight { menuItem :: MenuItem } -- Generell, nahezu immer sichtbar | NavbarSecondary { menuItem :: MenuItem } -- Generell, nahezu immer sichtbar | PageActionPrime { menuItem :: MenuItem } -- Seitenspezifische Aktion, häufig | PageActionSecondary { menuItem :: MenuItem } -- Seitenspezifische Aktion, selten -- Messages mkMessage "UniWorX" "messages" "de" -- 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 instance RenderMessage UniWorX TermIdentifier where renderMessage foundation ls TermIdentifier{..} = case season of Summer -> renderMessage' $ MsgSummerTerm year Winter -> renderMessage' $ MsgWinterTerm year where renderMessage' = renderMessage foundation ls -- Access Control data AccessPredicate = APPure (Route UniWorX -> Reader MsgRenderer AuthResult) | APHandler (Route UniWorX -> Handler AuthResult) | APDB (Route UniWorX -> DB AuthResult) orAR, andAR :: MsgRenderer -> AuthResult -> AuthResult -> AuthResult orAR _ Authorized _ = Authorized orAR _ _ Authorized = Authorized orAR _ AuthenticationRequired _ = AuthenticationRequired orAR _ _ AuthenticationRequired = AuthenticationRequired orAR mr (Unauthorized x) (Unauthorized y) = Unauthorized . render mr $ MsgUnauthorizedOr x y -- and andAR mr (Unauthorized x) (Unauthorized y) = Unauthorized . render mr $ MsgUnauthorizedAnd x y andAR _ reason@(Unauthorized x) _ = reason andAR _ _ reason@(Unauthorized x) = reason andAR _ Authorized other = other andAR _ AuthenticationRequired _ = AuthenticationRequired orAP,andAP :: AccessPredicate -> AccessPredicate -> AccessPredicate orAP = liftAR orAR (== Authorized) andAP = liftAR andAR (const False) liftAR :: (MsgRenderer -> AuthResult -> AuthResult -> AuthResult) -> (AuthResult -> Bool) -- ^ Predicate to Short-Circuit on first argument -> AccessPredicate -> AccessPredicate -> AccessPredicate -- Ensure to first evaluate Pure conditions, then Handler before DB liftAR op sc (APPure f) (APPure g) = APPure $ \r -> shortCircuitM sc (f r) (g r) . op =<< ask liftAR op sc (APHandler f) (APHandler g) = APHandler $ \r -> shortCircuitM sc (f r) (g r) . op =<< getMsgRenderer liftAR op sc (APDB f) (APDB g) = APDB $ \r -> shortCircuitM sc (f r) (g r) . op =<< getMsgRenderer liftAR op sc (APPure f) apg = liftAR op sc (APHandler $ \r -> runReader (f r) <$> getMsgRenderer) apg liftAR op sc apf apg@(APPure _) = liftAR op sc apg apf liftAR op sc (APHandler f) apdb = liftAR op sc (APDB $ lift . f) apdb liftAR op sc apdb apg@(APHandler _) = liftAR op sc apg apdb trueAP,falseAP :: AccessPredicate trueAP = APPure . const $ return Authorized falseAP = APPure . const $ Unauthorized . ($ MsgUnauthorized) . render <$> ask -- TODO: I believe falseAP := adminAP adminAP :: AccessPredicate -- access for admins (of appropriate school in case of course-routes) adminAP = APDB $ \case -- Courses: access only to school admins CourseR tid csh _ -> exceptT return return $ do authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId [E.Value c] <- lift . E.select . E.from $ \(course `E.InnerJoin` userAdmin) -> do E.on $ course E.^. CourseSchool E.==. userAdmin E.^. UserAdminSchool E.where_ $ userAdmin E.^. UserAdminUser E.==. E.val authId E.&&. course E.^. CourseTerm E.==. E.val tid E.&&. course E.^. CourseShorthand E.==. E.val csh return (E.countRows :: E.SqlExpr (E.Value Int64)) guardMExceptT (c > 0) (unauthorizedI MsgUnauthorizedSchoolAdmin) return Authorized -- other routes: access to any admin is granted here _other -> exceptT return return $ do authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId adrights <- lift $ selectFirst [UserAdminUser ==. authId] [] guardMExceptT (isJust adrights) (unauthorizedI $ MsgUnauthorized) return Authorized knownTags :: Map (CI Text) AccessPredicate knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId [("free", trueAP) ,("deprecated", APHandler $ \r -> do $logWarnS "AccessControl" ("deprecated route: " <> tshow r) addMessageI "error" MsgDeprecatedRoute return Authorized ) ,("lecturer", APDB $ \case CourseR tid csh _ -> exceptT return return $ do authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId [E.Value c] <- lift . E.select . E.from $ \(course `E.InnerJoin` lecturer) -> do E.on $ course E.^. CourseId E.==. lecturer E.^. LecturerCourse E.where_ $ lecturer E.^. LecturerUser E.==. E.val authId E.&&. course E.^. CourseTerm E.==. E.val tid E.&&. course E.^. CourseShorthand E.==. E.val csh return (E.countRows :: E.SqlExpr (E.Value Int64)) guardMExceptT (c>0) (unauthorizedI MsgUnauthorizedLecturer) return Authorized _ -> exceptT return return $ do authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId void . maybeMExceptT (unauthorizedI MsgUnauthorizedSchoolLecturer) $ selectFirst [UserLecturerUser ==. authId] [] return Authorized ) ,("corrector", APDB $ \route -> exceptT return return $ do authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId resList <- lift . E.select . E.from $ \(course `E.InnerJoin` sheet `E.InnerJoin` sheetCorrector) -> do E.on $ sheetCorrector E.^. SheetCorrectorSheet E.==. sheet E.^. SheetId E.on $ sheet E.^. SheetCourse E.==. course E.^. CourseId E.where_ $ sheetCorrector E.^. SheetCorrectorUser E.==. E.val authId return (course E.^. CourseId, sheet E.^. SheetId) let resMap :: Map CourseId (Set SheetId) resMap = Map.fromListWith Set.union [ (cid, Set.singleton sid) | (E.Value cid, E.Value sid) <- resList ] case route of CSheetR _ _ _ (SubmissionR cID) -> maybeT (unauthorizedI MsgUnauthorizedSubmissionCorrector) $ do sid <- catchIfMaybeT (const True :: CryptoIDError -> Bool) $ decrypt cID Submission{..} <- MaybeT . lift $ get sid guard $ maybe False (== authId) submissionRatingBy return Authorized CSheetR tid csh shn _ -> maybeT (unauthorizedI MsgUnauthorizedSheetCorrector) $ do Entity cid _ <- MaybeT . lift . getBy $ CourseTermShort tid csh Entity sid _ <- MaybeT . lift . getBy $ CourseSheet cid shn guard $ sid `Set.member` fromMaybe Set.empty (resMap !? cid) return Authorized CourseR tid csh _ -> maybeT (unauthorizedI MsgUnauthorizedCorrector) $ do Entity cid _ <- MaybeT . lift . getBy $ CourseTermShort tid csh guard $ cid `Set.member` Map.keysSet resMap return Authorized _ -> do guardMExceptT (not $ Map.null resMap) (unauthorizedI MsgUnauthorizedCorrectorAny) return Authorized ) ,("time", APDB $ \case CSheetR tid csh shn subRoute -> maybeT (unauthorizedI MsgUnauthorizedSheetTime) $ do Entity cid _ <- MaybeT . getBy $ CourseTermShort tid csh Entity sid Sheet{..} <- MaybeT . getBy $ CourseSheet cid shn cTime <- liftIO getCurrentTime case subRoute of SFileR SheetExercise _ -> guard $ maybe False (<= cTime) sheetVisibleFrom SFileR SheetHint _ -> guard $ maybe False (<= cTime) sheetHintFrom SFileR SheetSolution _ -> guard $ maybe False (<= cTime) sheetSolutionFrom SFileR SheetMarking _ -> mzero -- only for correctors and lecturers SubmissionNewR -> guard $ sheetActiveFrom <= cTime && cTime <= sheetActiveTo _ -> guard $ maybe False (<= cTime) sheetVisibleFrom return Authorized r -> do $logErrorS "AccessControl" $ "'!time' used on route that doesn't support it: " <> tshow r unauthorizedI MsgUnauthorized ) ,("registered", APDB $ \case CourseR tid csh _ -> exceptT return return $ do authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId [E.Value c] <- lift . E.select . E.from $ \(course `E.InnerJoin` courseParticipant) -> do E.on $ course E.^. CourseId E.==. courseParticipant E.^. CourseParticipantCourse E.where_ $ courseParticipant E.^. CourseParticipantUser E.==. E.val authId E.&&. course E.^. CourseTerm E.==. E.val tid E.&&. course E.^. CourseShorthand E.==. E.val csh return (E.countRows :: E.SqlExpr (E.Value Int64)) guardMExceptT (c > 0) (unauthorizedI MsgUnauthorizedParticipant) return Authorized r -> do $logErrorS "AccessControl" $ "'!registered' used on route that doesn't support it: " <> tshow r unauthorizedI MsgUnauthorized ) ,("materials", APDB $ \case CourseR tid csh _ -> maybeT (unauthorizedI MsgUnfreeMaterials) $ do Entity _ Course{..} <- MaybeT . getBy $ CourseTermShort tid csh guard courseMaterialFree return Authorized r -> do $logErrorS "AccessControl" $ "'!materials' used on route that doesn't support it: " <> tshow r unauthorizedI MsgUnauthorized ) ,("owner", APDB $ \case CSheetR _ _ _ (SubmissionR cID) -> exceptT return return $ do sid <- catchIfMExceptT (const $ unauthorizedI MsgUnauthorizedSubmissionOwner) (const True :: CryptoIDError -> Bool) $ decrypt cID authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId void . maybeMExceptT (unauthorizedI MsgUnauthorizedSubmissionOwner) . getBy $ UniqueSubmissionUser authId sid return Authorized CSheetR _ _ _ SubmissionNewR -> unauthorizedI MsgUnauthorizedSubmissionOwner r -> do $logErrorS "AccessControl" $ "'!owner' used on route that doesn't support it: " <> tshow r unauthorizedI MsgUnauthorized ) ,("isRead", APHandler $ \route -> bool <$> return Authorized <*> unauthorizedI MsgUnauthorizedWrite <*> isWriteRequest route ) ,("isWrite", APHandler $ \route -> do write <- isWriteRequest route if write then return Authorized else unauthorizedI MsgUnauthorized ) ] tag2ap :: Text -> AccessPredicate tag2ap t = case Map.lookup (CI.mk t) knownTags of (Just acp) -> acp Nothing -> APHandler $ \_route -> do -- Can this be pure like falseAP? GK: not if we want to log a message (which we definitely should) $logWarnS "AccessControl" $ "'" <> t <> "' not known to access control" unauthorizedI MsgUnauthorized route2ap :: Route UniWorX -> AccessPredicate route2ap r = foldr orAP adminAP attrsAND -- adminAP causes all to be in DB!!! GK: Due to shortCircuitM this (while still true) is no longer costly (we do a `runDB` but then only actually send off queries, if needed) where attrsAND = map splitAND $ Set.toList $ routeAttrs r splitAND = foldr1 andAP . map tag2ap . Text.splitOn "AND" evalAccessDB :: Route UniWorX -> DB AuthResult -- all requests, regardless of POST/GET, use isWriteRequest otherwise evalAccessDB r = case route2ap r of (APPure p) -> lift $ runReader (p r) <$> getMsgRenderer (APHandler p) -> lift $ p r (APDB p) -> p r evalAccess :: Route UniWorX -> Handler AuthResult evalAccess r = case route2ap r of (APPure p) -> runReader (p r) <$> getMsgRenderer (APHandler p) -> p r (APDB p) -> runDB $ p r -- TODO: isAuthorized = evalAccess' -- 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 handler = do res <- defaultYesodMiddleware handler void . runMaybeT $ do route <- MaybeT getCurrentRoute case route of -- update Course Favourites here CourseR tid csh _ -> do uid <- MaybeT maybeAuthId $(logDebug) "Favourites save" now <- liftIO $ getCurrentTime void . lift . runDB . runMaybeT $ do cid <- MaybeT . getKeyBy $ CourseTermShort tid csh user <- MaybeT $ get uid -- update Favourites void . lift $ upsertBy (UniqueCourseFavourite uid cid) (CourseFavourite uid now cid) [CourseFavouriteTime =. now] -- prune Favourites to user-defined size oldFavs <- lift $ selectKeysList [ CourseFavouriteUser ==. uid] [ Desc CourseFavouriteTime , OffsetBy $ userMaxFavourites user ] lift $ mapM delete oldFavs _other -> return () return res defaultLayout widget = do master <- getYesod mmsgs <- getMessages mcurrentRoute <- getCurrentRoute -- Get the breadcrumbs, as defined in the YesodBreadcrumbs instance. (title, parents) <- breadcrumbs let menu = defaultLinks ++ maybe [] pageActions mcurrentRoute menuTypes <- filterM (menuItemAccessCallback . menuItem) menu -- Lookup Favourites if possible favourites' <- do muid <- maybeAuthId case muid of Nothing -> return [] (Just uid) -> runDB . E.select . E.from $ \(course `E.InnerJoin` courseFavourite) -> do E.on (course E.^. CourseId E.==. courseFavourite E.^. CourseFavouriteCourse) E.where_ (courseFavourite E.^. CourseFavouriteUser E.==. E.val uid) E.orderBy [ E.asc $ course E.^. CourseShorthand ] return course favourites <- forM favourites' $ \(Entity _ c@Course{..}) -> let courseRoute = CourseR courseTerm courseShorthand CShowR in (c, courseRoute, ) <$> filterM (menuItemAccessCallback . menuItem) (pageActions courseRoute) -- 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. let navbar :: Widget navbar = $(widgetFile "widgets/navbar") asidenav :: Widget asidenav = $(widgetFile "widgets/asidenav") contentHeadline :: Maybe Widget contentHeadline = pageHeading =<< mcurrentRoute breadcrumbs :: Widget breadcrumbs = $(widgetFile "widgets/breadcrumbs") pageactionprime :: Widget pageactionprime = $(widgetFile "widgets/pageactionprime") -- functions to determine if there are page-actions isPageActionPrime :: MenuTypes -> Bool isPageActionPrime (PageActionPrime _) = True isPageActionPrime _ = False hasPageActions :: Bool hasPageActions = any isPageActionPrime menuTypes pc <- widgetToPageContent $ do addStylesheetRemote "https://fonts.googleapis.com/css?family=Source+Sans+Pro:300,400,600,800,900" addScript $ StaticR js_zepto_js addScript $ StaticR js_fetchPolyfill_js addScript $ StaticR js_urlPolyfill_js addScript $ StaticR js_featureChecker_js addScript $ StaticR js_flatpickr_js addScript $ StaticR js_tabber_js addStylesheet $ StaticR css_flatpickr_css addStylesheet $ StaticR css_tabber_css addStylesheet $ StaticR css_fonts_css addStylesheet $ StaticR css_icons_css $(widgetFile "default-layout") $(widgetFile "standalone/modal") $(widgetFile "standalone/showHide") $(widgetFile "standalone/inputs") $(widgetFile "standalone/tabber") withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet") -- The page to be redirected to when authentication is required. authRoute _ = Just $ AuthR LoginR isAuthorized route _isWrite = evalAccess route -- 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 -- 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 (TermCourseListR term) = return (toPathPiece term, Just TermShowR) breadcrumb (CourseR term course CShowR) = return (course, Just $ TermCourseListR term) breadcrumb CourseNewR = return ("Neu", Just CourseListR) breadcrumb (CourseR _ _ CEditR) = return ("Editieren", Just CourseListR) breadcrumb (CourseR tid csh SheetListR) = return ("Übungen",Just $ CourseR tid csh CShowR) breadcrumb (CourseR tid csh SheetNewR ) = return ("Neu", Just $ CourseR tid csh SheetListR) breadcrumb (CSheetR tid csh shn SShowR) = return (shn, Just $ CourseR tid csh SheetListR) breadcrumb (CSheetR tid csh shn SEditR) = return ("Edit", Just $ CSheetR tid csh shn SShowR) breadcrumb (CSheetR tid csh shn SDelR ) = return ("DELETE", Just $ CSheetR tid csh shn SShowR) breadcrumb (CSheetR tid csh shn (SubmissionR _)) = return ("Abgabe", Just $ CSheetR tid csh shn SShowR) breadcrumb SubmissionListR = return ("Abgaben", Just HomeR) breadcrumb HomeR = return ("Uniworky", Nothing) breadcrumb (AuthR _) = return ("Login", Just HomeR) breadcrumb ProfileR = return ("Profile", Just HomeR) breadcrumb _ = return ("home", Nothing) pageActions :: Route UniWorX -> [MenuTypes] pageActions (CourseR tid csh CShowR) = [ PageActionPrime $ MenuItem { menuItemLabel = "Übungsblätter" , menuItemIcon = Nothing , menuItemRoute = CourseR tid csh SheetListR , menuItemAccessCallback' = return True } , PageActionPrime $ MenuItem { menuItemLabel = "Kurs Editieren" , menuItemIcon = Nothing , menuItemRoute = CourseR tid csh CEditR , menuItemAccessCallback' = return True } ] pageActions (CourseR tid csh SheetListR) = [ PageActionPrime $ MenuItem { menuItemLabel = "Neues Übungsblatt" , menuItemIcon = Nothing , menuItemRoute = CourseR tid csh SheetNewR , menuItemAccessCallback' = return True } ] pageActions (CSheetR tid csh shn SShowR) = [ PageActionPrime $ MenuItem { menuItemLabel = "Abgabe anlegen" , menuItemIcon = Nothing , menuItemRoute = CSheetR tid csh shn SubmissionNewR , menuItemAccessCallback' = return True -- TODO: check that no submission already exists } , PageActionPrime $ MenuItem { menuItemLabel = "Abgabe" , menuItemIcon = Nothing , menuItemRoute = CSheetR tid csh shn SubmissionOwnR , menuItemAccessCallback' = return True -- TODO: check that a submission already exists } ] pageActions TermShowR = [ PageActionPrime $ MenuItem { menuItemLabel = "Neues Semester" , menuItemIcon = Nothing , menuItemRoute = TermEditR , menuItemAccessCallback' = return True } ] pageActions (TermCourseListR _) = [ PageActionPrime $ MenuItem { menuItemLabel = "Neuer Kurs" , menuItemIcon = Just "book" , menuItemRoute = CourseNewR , menuItemAccessCallback' = return True } ] pageActions _ = [] pageHeading :: Route UniWorX -> Maybe Widget pageHeading HomeR = Just [whamlet|_{MsgHomeHeading}|] pageHeading TermShowR = Just [whamlet|_{MsgTermsHeading}|] pageHeading _ = Nothing defaultLinks :: [MenuTypes] defaultLinks = -- Define the menu items of the header. [ NavbarRight $ MenuItem { menuItemLabel = "Home" , menuItemIcon = Just "home" , menuItemRoute = HomeR , menuItemAccessCallback' = return True } , NavbarRight $ MenuItem { menuItemLabel = "Profile" , menuItemIcon = Just "profile" , menuItemRoute = ProfileR , menuItemAccessCallback' = isJust <$> maybeAuthPair } , NavbarSecondary $ MenuItem { menuItemLabel = "Login" , menuItemIcon = Just "login" , menuItemRoute = AuthR LoginR , menuItemAccessCallback' = isNothing <$> maybeAuthPair } , NavbarSecondary $ MenuItem { menuItemLabel = "Logout" , menuItemIcon = Just "logout" , menuItemRoute = AuthR LogoutR , menuItemAccessCallback' = isJust <$> maybeAuthPair } , NavbarAside $ MenuItem { menuItemLabel = "Veranstaltungen" , menuItemIcon = Just "book" , menuItemRoute = CourseListR -- should be CourseListActiveR or similar in the future , menuItemAccessCallback' = return True } , NavbarAside $ MenuItem { menuItemLabel = "Semester" , menuItemIcon = Nothing , menuItemRoute = CourseListR -- should be TermListR ,,, , menuItemAccessCallback' = return True } , NavbarAside $ MenuItem { menuItemLabel = "Benutzer" , menuItemIcon = Just "user" , menuItemRoute = UsersR , menuItemAccessCallback' = return True -- Creates a LOOP: (Authorized ==) <$> isAuthorized UsersR False } ] -- 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 userMaxFavourites = 12 -- TODO: appDefaultFavourites appSettings 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 -- 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 instance (MonadThrow m, MonadHandler m, HandlerSite m ~ UniWorX) => MonadCrypto m where type MonadCryptoKey m = CryptoIDKey cryptoIDKey f = getsYesod appCryptoIDKey >>= f -- 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