This repository has been archived on 2024-10-24. You can view files and clone it, but cannot push or open issues or pull requests.
fradrive-old/src/Handler/Profile.hs
2018-07-03 09:20:43 +02:00

132 lines
5.3 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 ((^.))
data SettingsForm = SettingsForm
{ stgMaxFavourties :: Int
, stgTheme :: Theme
}
makeSettingForm :: Maybe SettingsForm -> Form SettingsForm
makeSettingForm template = identForm FIDsettings $ \html -> do
let themeList = [(display t,t) | t <- allThemes]
(result, widget) <- flip (renderAForm FormStandard) html $ SettingsForm
<$> areq (natFieldI $ MsgNatField "Favoriten") -- TODO: natFieldI not working here
(fslpI MsgFavoriten "Anzahl Favoriten") (stgMaxFavourties <$> template)
<*> areq (selectFieldList themeList)
(fslpI MsgTheme "theme-select" ) (stgTheme <$> template) -- TODO: pass theme-select as id-attribute or similar.
<* submitButton
return (result, widget) -- no validation required here
getProfileR :: Handler Html
getProfileR = do
(uid, User{..}) <- requireAuthPair
let settingsTemplate = Just $ SettingsForm
{ stgMaxFavourties = userMaxFavourites
, stgTheme = userTheme
}
((res,formWidget), formEnctype) <- runFormPost $ makeSettingForm settingsTemplate
case res of
(FormSuccess SettingsForm{..}) -> do
runDB $ do
update uid [ UserMaxFavourites =. stgMaxFavourties
, UserTheme =. stgTheme
]
when (stgMaxFavourties < userMaxFavourites) $ do
-- prune Favourites to user-defined size
oldFavs <- selectKeysList [ CourseFavouriteUser ==. uid]
[ Desc CourseFavouriteTime
, OffsetBy $ stgMaxFavourties
]
mapM_ delete oldFavs
addMessageI "info" $ MsgSettingsUpdate
redirect ProfileR -- TODO: them change does not happen without redirect
(FormFailure msgs) -> forM_ msgs $ (addMessage "warning") . toHtml
_ -> return ()
(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 $ \(sheet `E.InnerJoin` corrector `E.InnerJoin` course) -> do
E.on $ sheet ^. SheetCourse E.==. course ^. CourseId
E.on $ sheet ^. SheetId E.==. corrector ^. SheetCorrectorSheet
E.where_ $ corrector ^. SheetCorrectorUser E.==. E.val uid
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)
)
let formText = Just MsgSettings
actionUrl = ProfileR
settingsForm = $(widgetFile "formPageI18n")
defaultLayout $ do
setTitle . toHtml $ userIdent <> "'s User page"
$(widgetFile "profile")
$(widgetFile "dsgvDisclaimer")
postProfileR :: Handler Html
postProfileR = do
-- TODO
getProfileR
getProfileDataR :: Handler Html
getProfileDataR = do
(uid, User{..}) <- requireAuthPair
-- mr <- getMessageRender
defaultLayout $ do
$(widgetFile "profileData")
$(widgetFile "dsgvDisclaimer")