fradrive/src/Handler/Profile.hs

83 lines
3.2 KiB
Haskell

{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
module Handler.Profile where
import Import
import Handler.Utils
-- import Colonnade hiding (fromMaybe, singleton)
-- import Yesod.Colonnade
import qualified Database.Esqueleto as E
import Database.Esqueleto ((^.))
getProfileR :: Handler Html
getProfileR = do
(uid, User{..}) <- requireAuthPair
-- mr <- getMessageRender
(admin_rights,lecturer_rights,lecture_owner,lecture_corrector,participant,studies) <- runDB $ (,,,,,) <$>
(E.select $ E.from $ \(adright `E.InnerJoin` school) -> do
E.where_ $ adright ^. UserAdminUser E.==. E.val uid
E.on $ adright ^. UserAdminSchool E.==. school ^. SchoolId
return (school ^. SchoolShorthand)
)
<*>
(E.select $ E.from $ \(lecright `E.InnerJoin` school) -> do
E.where_ $ lecright ^. UserLecturerUser E.==. E.val uid
E.on $ lecright ^. UserLecturerSchool E.==. school ^. SchoolId
return (school ^. SchoolShorthand)
)
<*>
(E.select $ E.from $ \(lecturer `E.InnerJoin` course) -> do
E.where_ $ lecturer ^. LecturerUser E.==. E.val uid
E.on $ lecturer ^. LecturerCourse E.==. course ^. CourseId
return (course ^. CourseShorthand, course ^. CourseTerm)
)
<*>
(E.select $ E.from $ \(corrector `E.InnerJoin` course) -> do
E.where_ $ corrector ^. CorrectorUser E.==. E.val uid
E.on $ corrector ^. CorrectorCourse E.==. course ^. CourseId
return (course ^. CourseShorthand, course ^. CourseTerm)
)
<*>
(E.select $ E.from $ \(participant `E.InnerJoin` course) -> do
E.where_ $ participant ^. CourseParticipantUser E.==. E.val uid
E.on $ participant ^. CourseParticipantCourse E.==. course ^. CourseId
return (course ^. CourseShorthand, course ^. CourseTerm, participant ^. CourseParticipantRegistration)
)
<*>
(E.select $ E.from $ \(studydegree `E.InnerJoin` studyfeat `E.InnerJoin` studyterms) -> do
E.where_ $ studyfeat ^. StudyFeaturesUser E.==. E.val uid
E.on $ studyfeat ^. StudyFeaturesField E.==. studyterms ^. StudyTermsId
E.on $ studyfeat ^. StudyFeaturesDegree E.==. studydegree ^. StudyDegreeId
return (studydegree ^. StudyDegreeName
,studyterms ^. StudyTermsName
,studyfeat ^. StudyFeaturesType
,studyfeat ^. StudyFeaturesSemester)
)
defaultLayout $ do
setTitle . toHtml $ userIdent <> "'s User page"
$(widgetFile "profile")
postProfileR :: Handler Html
postProfileR = do
-- TODO
getProfileR
getProfileDataR :: Handler Html
getProfileDataR = do
(uid, User{..}) <- requireAuthPair
-- mr <- getMessageRender
defaultLayout $ do
$(widgetFile "profileData")