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/Course.hs

526 lines
25 KiB
Haskell

{-# LANGUAGE RecordWildCards, NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE PartialTypeSignatures #-}
{-# LANGUAGE RecordWildCards, NamedFieldPuns, TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleContexts #-}
module Handler.Course where
import Import
import Control.Lens
import Utils.Lens
import Utils.TH
import Handler.Utils
import Handler.Utils.Table.Cells
-- import Data.Time
import qualified Data.Text as T
import Data.Function ((&))
-- import Yesod.Form.Bootstrap3
import qualified Data.Set as Set
import qualified Data.Map as Map
import Colonnade hiding (fromMaybe,bool)
-- import Yesod.Colonnade
import qualified Database.Esqueleto as E
import qualified Data.UUID.Cryptographic as UUID
-- NOTE: Outdated way to use dbTable; see ProfileDataR Handler for a more recent method.
type CourseTableData = DBRow (Entity Course, Int64, Bool, Entity School)
colCourse :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colCourse = sortable (Just "course") (i18nCell MsgCourse)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } ->
anchorCell (CourseR courseTerm courseSchool courseShorthand CShowR)
[whamlet|#{display courseName}|]
colCourseDescr :: IsDBTable m a => Colonnade Sortable CourseTableData (DBCell m a)
colCourseDescr = sortable (Just "course") (i18nCell MsgCourse) $ do
course <- view $ _dbrOutput . _1 . _entityVal
return $ courseCell course
colDescription :: IsDBTable m a => Colonnade Sortable CourseTableData (DBCell m a)
colDescription = sortable Nothing (i18nCell MsgCourseDescription)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } ->
case courseDescription of
Nothing -> mempty
(Just descr) -> cell $ modalStatic descr
colCShort :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colCShort = sortable (Just "cshort") (i18nCell MsgCourseShort)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } ->
anchorCell (CourseR courseTerm courseSchool courseShorthand CShowR) [whamlet|#{display courseShorthand}|]
colCShortDescr :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colCShortDescr = sortable (Just "cshort") (i18nCell MsgCourseShort)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } -> mappend
( anchorCell (CourseR courseTerm courseSchool courseShorthand CShowR) [whamlet|#{display courseShorthand}|] )
( case courseDescription of
Nothing -> mempty
(Just descr) -> cell
[whamlet|<span style="float:right"> ^{modalStatic descr} |]
)
colTerm :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colTerm = sortable (Just "term") (i18nCell MsgTerm)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } ->
anchorCell (TermCourseListR courseTerm) [whamlet|#{display courseTerm}|]
colSchool :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colSchool = sortable (Just "school") (i18nCell MsgCourseSchool)
$ \DBRow{ dbrOutput=(Entity _ Course{..}, _, _, Entity _ School{..}) } ->
anchorCell (TermSchoolCourseListR courseTerm courseSchool) [whamlet|#{display schoolName}|]
colSchoolShort :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colSchoolShort = sortable (Just "schoolshort") (i18nCell MsgCourseSchoolShort)
$ \DBRow{ dbrOutput=(Entity _ Course{..}, _, _, Entity _ School{..}) } ->
anchorCell (TermSchoolCourseListR courseTerm courseSchool) [whamlet|#{display schoolShorthand}|]
colRegFrom :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colRegFrom = sortable (Just "register-from") (i18nCell MsgRegisterFrom)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } ->
maybe mempty timeCell courseRegisterFrom
-- cell $ traverse (formatTime SelFormatDateTime) courseRegisterFrom >>= maybe mempty toWidget
colRegTo :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colRegTo = sortable (Just "register-to") (i18nCell MsgRegisterTo)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, _, _) } ->
cell $ traverse (formatTime SelFormatDateTime) courseRegisterTo >>= maybe mempty toWidget
colParticipants :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colParticipants = sortable (Just "participants") (i18nCell MsgCourseMembers)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, currentParticipants, _, _) } -> textCell $ case courseCapacity of
Nothing -> MsgCourseMembersCount currentParticipants
Just max -> MsgCourseMembersCountLimited currentParticipants max
colRegistered :: IsDBTable m a => Colonnade _ CourseTableData (DBCell m a)
colRegistered = sortable (Just "registered") (i18nCell MsgRegistered)
$ \DBRow{ dbrOutput=(Entity cid Course{..}, _, registered, _) } -> tickmarkCell registered
type CourseTableExpr = E.SqlExpr (Entity Course) `E.InnerJoin` E.SqlExpr (Entity School)
course2Participants :: CourseTableExpr -> E.SqlExpr (E.Value Int64)
course2Participants (course `E.InnerJoin` _school) = E.sub_select . E.from $ \courseParticipant -> do
E.where_ $ courseParticipant E.^. CourseParticipantCourse E.==. course E.^. CourseId
return (E.countRows :: E.SqlExpr (E.Value Int64))
course2Registered :: Maybe UserId -> CourseTableExpr -> E.SqlExpr (E.Value Bool)
course2Registered muid (course `E.InnerJoin` _school) = E.exists . E.from $ \courseParticipant -> do
E.where_ $ courseParticipant E.^. CourseParticipantCourse E.==. course E.^. CourseId
E.&&. E.just (courseParticipant E.^. CourseParticipantUser) E.==. E.val muid
makeCourseTable :: ( IsDBTable m x, ToSortable h, Functor h )
=> _ -> Colonnade h CourseTableData (DBCell m x) -> PSValidator m x -> Handler (DBResult m x)
makeCourseTable whereClause colChoices psValidator = do
muid <- maybeAuthId
let dbtSQLQuery :: CourseTableExpr -> E.SqlQuery _
dbtSQLQuery qin@(course `E.InnerJoin` school) = do
E.on $ course E.^. CourseSchool E.==. school E.^. SchoolId
let participants = course2Participants qin
let registered = course2Registered muid qin
E.where_ $ whereClause (course, participants, registered)
return (course, participants, registered, school)
dbtProj :: DBRow _ -> MaybeT (ReaderT SqlBackend (HandlerT UniWorX IO)) CourseTableData
dbtProj = traverse $ \(course, E.Value participants, E.Value registered, school) -> return (course, participants, registered, school)
dbTable psValidator $ DBTable
{ dbtSQLQuery
, dbtColonnade = colChoices
, dbtProj
, dbtSorting = Map.fromList -- OverloadedLists does not work with the templates here
[ ( "course", SortColumn $ \(course `E.InnerJoin` _school) -> course E.^. CourseName)
, ( "cshort", SortColumn $ \(course `E.InnerJoin` _school) -> course E.^. CourseShorthand)
, ( "term" , SortColumn $ \(course `E.InnerJoin` _school) -> course E.^. CourseTerm)
, ( "school", SortColumn $ \(_course `E.InnerJoin` school) -> school E.^. SchoolName)
, ( "schoolshort", SortColumn $ \(_course `E.InnerJoin` school) -> school E.^. SchoolShorthand)
, ( "register-from", SortColumn $ \(course `E.InnerJoin` _school) -> course E.^. CourseRegisterFrom)
, ( "register-to", SortColumn $ \(course `E.InnerJoin` _school) -> course E.^. CourseRegisterTo)
, ( "participants", SortColumn $ course2Participants )
, ( "registered", SortColumn $ course2Registered muid)
]
, dbtFilter = Map.fromList -- OverloadedLists does not work with the templates here
[ ( "course", FilterColumn $ \(course `E.InnerJoin` _school:: CourseTableExpr) criterias -> if
| Set.null criterias -> E.val True :: E.SqlExpr (E.Value Bool)
| otherwise -> course E.^. CourseName `E.in_` E.valList (Set.toList criterias)
)
, ( "cshort", FilterColumn $ \(course `E.InnerJoin` _school :: CourseTableExpr) criterias -> if
| Set.null criterias -> E.val True :: E.SqlExpr (E.Value Bool)
| otherwise -> course E.^. CourseShorthand `E.in_` E.valList (Set.toList criterias)
)
, ( "term" , FilterColumn $ \(course `E.InnerJoin` _school :: CourseTableExpr) criterias -> if
| Set.null criterias -> E.val True :: E.SqlExpr (E.Value Bool)
| otherwise -> course E.^. CourseTerm `E.in_` E.valList (Set.toList criterias)
)
-- , ( "school", FilterColumn $ \(_course `E.InnerJoin` school :: CourseTableExpr) criterias -> if
-- | Set.null criterias -> E.val True :: E.SqlExpr (E.Value Bool)
-- | otherwise -> school E.^. SchoolName `E.in_` E.valList (Set.toList criterias)
-- )
, ( "school", FilterColumn $ \(_course `E.InnerJoin` school :: CourseTableExpr) ->
emptyOrIn $ school E.^. SchoolName -- TODO: Refactor all?!
)
, ( "schoolshort", FilterColumn $ \(_course `E.InnerJoin` school :: CourseTableExpr) criterias -> if
| Set.null criterias -> E.val True :: E.SqlExpr (E.Value Bool)
| otherwise -> school E.^. SchoolShorthand `E.in_` E.valList (Set.toList criterias)
)
]
, dbtStyle = def
, dbtIdent = "courses" :: Text
}
getCourseListR :: Handler Html
getCourseListR = do -- TODO: Suchfunktion für Kurse und Kürzel!!!
muid <- maybeAuthId
let colonnade = widgetColonnade $ mconcat
[ colCourseDescr
, colCShort
, colTerm
, maybe mempty (const colRegistered) muid
, colSchool
]
whereClause = const $ E.val True
validator = def
& defaultSorting [("course", SortAsc), ("term", SortDesc)]
((), coursesTable) <- makeCourseTable whereClause colonnade validator
defaultLayout $ do
setTitleI MsgCourseListTitle
[whamlet|TODO: Such-/Filterfunktion hier einbauen|] -- TODO
$(widgetFile "courses")
getTermCurrentR :: Handler Html
getTermCurrentR = do
termIds <- runDB $ selectKeysList [TermActive ==. True] [Desc TermName]
case fromNullable termIds of
Nothing -> notFound
(Just (maximum -> tid)) -> -- getTermCourseListR tid
redirect $ TermCourseListR tid -- redirect avoids problematic breadcrumbs, headings, etc.
getTermSchoolCourseListR :: TermId -> SchoolId -> Handler Html
getTermSchoolCourseListR tid ssh = do
void . runDB $ get404 tid -- Just ensure the term exists
School{schoolName=school} <- runDB $ get404 ssh -- Just ensure the term exists
muid <- maybeAuthId
let colonnade = widgetColonnade $ mconcat
[ dbRow
, colCShortDescr
, colRegFrom
, colRegTo
, colParticipants
, maybe mempty (const colRegistered) muid
]
whereClause = \(course, _, _) ->
course E.^. CourseTerm E.==. E.val tid
E.&&. course E.^. CourseSchool E.==. E.val ssh
validator = def
& defaultSorting [("cshort", SortAsc)]
((), coursesTable) <- makeCourseTable whereClause colonnade validator
defaultLayout $ do
setTitleI $ MsgTermSchoolCourseListTitle tid school
$(widgetFile "courses")
getTermCourseListR :: TermId -> Handler Html
getTermCourseListR tid = do
void . runDB $ get404 tid -- Just ensure the term exists
muid <- maybeAuthId
let colonnade = widgetColonnade $ mconcat
[ dbRow
, colCShortDescr
, colSchoolShort
, colRegFrom
, colRegTo
, colParticipants
, maybe mempty (const colRegistered) muid
]
whereClause = \(course, _, _) -> course E.^. CourseTerm E.==. E.val tid
validator = def
& defaultSorting [("cshort", SortAsc)]
((), coursesTable) <- makeCourseTable whereClause colonnade validator
defaultLayout $ do
setTitleI . MsgTermCourseListTitle $ tid
$(widgetFile "courses")
getCShowR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
getCShowR tid ssh csh = do
mbAid <- maybeAuthId
(courseEnt,(schoolMB,participants,registered),lecturers) <- runDB $ do
courseEnt@(Entity cid course) <- getBy404 $ TermSchoolCourseShort tid ssh csh
dependent <- (,,)
<$> get (courseSchool course) -- join -- just fetch full school name here
<*> count [CourseParticipantCourse ==. cid] -- join
<*> (case mbAid of -- TODO: Someone please refactor this late-night mess here!
Nothing -> return False
(Just aid) -> do regL <- getBy (UniqueParticipant aid cid)
return $ isJust regL)
lecturers <- E.select $ E.from $ \(lecturer `E.InnerJoin` user) -> do
E.on $ lecturer E.^. LecturerUser E.==. user E.^. UserId
E.where_ $ lecturer E.^. LecturerCourse E.==. E.val cid
return $ user E.^. UserDisplayName
return $ (courseEnt,dependent,E.unValue <$> lecturers)
let course = entityVal courseEnt
(regWidget, regEnctype) <- generateFormPost $ identifyForm "registerBtn" $ registerForm registered $ courseRegisterSecret course
registrationOpen <- (==Authorized) <$> isAuthorized (CourseR tid ssh csh CRegisterR) True
mRegFrom <- traverse (formatTime SelFormatDateTime) $ courseRegisterFrom course
mRegTo <- traverse (formatTime SelFormatDateTime) $ courseRegisterTo course
defaultLayout $ do
setTitle $ [shamlet| #{toPathPiece tid} - #{csh}|]
$(widgetFile "course")
registerForm :: Bool -> Maybe Text -> Form Bool
registerForm registered msecret extra = do
(msecretRes', msecretView) <- case msecret of
(Just _) | not registered -> bimap Just Just <$> (mreq textField (fslpI MsgCourseSecret "Code") Nothing)
_ -> return (Nothing,Nothing)
(btnRes, btnView) <- mreq (buttonField $ bool BtnRegister BtnDeregister registered) "buttonField ignores settings anyway" Nothing
let widget = $(widgetFile "widgets/registerForm")
let msecretRes | Just res <- msecretRes' = Just <$> res
| otherwise = FormSuccess Nothing
return (btnRes *> ((==msecret) <$> msecretRes), widget) -- checks that correct button was pressed, and ignores result of btnRes
postCRegisterR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
postCRegisterR tid ssh csh = do
aid <- requireAuthId
(cid, course, registered) <- runDB $ do
(Entity cid course) <- getBy404 $ TermSchoolCourseShort tid ssh csh
registered <- isJust <$> (getBy $ UniqueParticipant aid cid)
return (cid, course, registered)
((regResult,_), _) <- runFormPost $ identifyForm "registerBtn" $ registerForm registered $ courseRegisterSecret course
case regResult of
(FormSuccess codeOk)
| registered -> do
runDB $ deleteBy $ UniqueParticipant aid cid
addMessageI "info" MsgCourseDeregisterOk
| codeOk -> do
actTime <- liftIO $ getCurrentTime
regOk <- runDB $ insertUnique $ CourseParticipant cid aid actTime
when (isJust regOk) $ addMessageI "success" MsgCourseRegisterOk
| otherwise -> addMessageI "danger" MsgCourseSecretWrong
(_other) -> return () -- TODO check this!
redirect $ CourseR tid ssh csh CShowR
getCourseNewR :: Handler Html
getCourseNewR = do
-- TODO: Defaults für Semester hier ermitteln und übergeben
courseEditHandler True Nothing
postCourseNewR :: Handler Html
postCourseNewR = courseEditHandler False Nothing
getCEditR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
getCEditR tid ssh csh = do
course <- runDB $ getBy $ TermSchoolCourseShort tid ssh csh
courseEditHandler True course
postCEditR :: TermId -> SchoolId -> CourseShorthand -> Handler Html
postCEditR tid ssh csh = do
course <- runDB $ getBy $ TermSchoolCourseShort tid ssh csh
courseEditHandler False course
courseDeleteHandler :: Handler Html -- not called anywhere yet
courseDeleteHandler = undefined
{- TODO
| False -- DELETE -- TODO: This no longer works that way!!! See new way in Handler.Term.termEditHandler
, Just cid <- cfCourseId res -> do
runDB $ deleteCascade cid -- TODO Sicherheitsabfrage einbauen!
let cti = toPathPiece $ cfTerm res
addMessage "info" [shamlet| Kurs #{cti}/#{cfShort res} wurde gelöscht!|]
redirect $ TermCourseListR $ cfTerm res
-}
courseEditHandler :: Bool -> Maybe (Entity Course) -> Handler Html
courseEditHandler isGet course = do
$logDebug "€€€€€€ courseEditHandler started"
aid <- requireAuthId -- TODO: Verify that Editor is owner of the Course to be Edited!!!
((result, formWidget), formEnctype) <- runFormPost . newCourseForm =<< for course courseToForm
case result of
(FormSuccess res@(
CourseForm { cfCourseId = Nothing
, cfShort = csh
, cfSchool = ssh
, cfTerm = tid
})) -> do -- create new course
now <- liftIO getCurrentTime
insertOkay <- runDB $ insertUnique $ Course
{ courseName = cfName res
, courseDescription = cfDesc res
, courseLinkExternal = cfLink res
, courseShorthand = cfShort res
, courseTerm = cfTerm res
, courseSchool = cfSchool res
, courseCapacity = cfCapacity res
, courseRegisterSecret = cfSecret res
, courseMaterialFree = cfMatFree res
, courseRegisterFrom = cfRegFrom res
, courseRegisterTo = cfRegTo res
, courseDeregisterUntil = cfDeRegUntil res
}
case insertOkay of
(Just cid) -> do
runDB $ do
insert_ $ CourseEdit aid now cid
insert_ $ Lecturer aid cid
addMessageI "info" $ MsgCourseNewOk tid ssh csh
redirect $ TermCourseListR tid
Nothing ->
addMessageI "danger" $ MsgCourseNewDupShort tid ssh csh
(FormSuccess res@(
CourseForm { cfCourseId = Just cid
, cfShort = csh
, cfSchool = ssh
, cfTerm = tid
})) -> do -- edit existing course
now <- liftIO getCurrentTime
-- addMessage "debug" [shamlet| #{show res}|]
success <- runDB $ do
old <- get cid
case old of
Nothing -> addMessageI "error" MsgInvalidInput $> False
(Just oldCourse) -> do
updOkay <- myReplaceUnique cid ( -- replaceUnique requires Eq Course, which we cannot have
Course { courseName = cfName res
, courseDescription = cfDesc res
, courseLinkExternal = cfLink res
, courseShorthand = cfShort res
, courseTerm = cfTerm res
, courseSchool = cfSchool res
, courseCapacity = cfCapacity res
, courseRegisterSecret = cfSecret res
, courseMaterialFree = cfMatFree res
, courseRegisterFrom = cfRegFrom res
, courseRegisterTo = cfRegTo res
, courseDeregisterUntil = cfDeRegUntil res
}
)
case updOkay of
(Just _) -> addMessageI "danger" (MsgCourseEditDupShort tid ssh csh) $> False
Nothing -> do
insert_ $ CourseEdit aid now cid
addMessageI "success" $ MsgCourseEditOk tid ssh csh
return True
when success $ redirect $ CourseR tid ssh csh CShowR
(FormFailure _) -> addMessageI "warning" MsgInvalidInput
(FormMissing) -> return ()
actionUrl <- fromMaybe CourseNewR <$> getCurrentRoute
defaultLayout $ do
setTitleI MsgCourseEditTitle
$(widgetFile "formPage")
data CourseForm = CourseForm
{ cfCourseId :: Maybe CourseId
, cfName :: CourseName
, cfDesc :: Maybe Html
, cfLink :: Maybe Text
, cfShort :: CourseShorthand
, cfTerm :: TermId
, cfSchool :: SchoolId
, cfCapacity :: Maybe Int64
, cfSecret :: Maybe Text
, cfMatFree :: Bool
, cfRegFrom :: Maybe UTCTime
, cfRegTo :: Maybe UTCTime
, cfDeRegUntil :: Maybe UTCTime
}
courseToForm :: MonadCrypto m => Entity Course -> m CourseForm
courseToForm (Entity cid Course{..}) = do
return $ CourseForm
{ cfCourseId = Just cid
, cfName = courseName
, cfDesc = courseDescription
, cfLink = courseLinkExternal
, cfShort = courseShorthand
, cfTerm = courseTerm
, cfSchool = courseSchool
, cfCapacity = courseCapacity
, cfSecret = courseRegisterSecret
, cfMatFree = courseMaterialFree
, cfRegFrom = courseRegisterFrom
, cfRegTo = courseRegisterTo
, cfDeRegUntil = courseDeregisterUntil
}
newCourseForm :: Maybe CourseForm -> Form CourseForm
newCourseForm template = identForm FIDcourse $ \html -> do
userSchools <- liftHandlerT . runDB $ do
userId <- liftHandlerT requireAuthId
(fmap concat . sequence)
[ map (userLecturerSchool . entityVal) <$> selectList [UserLecturerUser ==. userId] []
, map (userAdminSchool . entityVal) <$> selectList [UserAdminUser ==. userId] []
]
(result, widget) <- flip (renderAForm FormStandard) html $ CourseForm
<$> pure (cfCourseId =<< template)
<*> areq (ciField textField) (fslI MsgCourseName) (cfName <$> template)
<*> aopt htmlField (fslI MsgCourseDescription
& setTooltip MsgCourseDescriptionTip) (cfDesc <$> template)
<*> aopt urlField (fslI MsgCourseHomepage) (cfLink <$> template)
<*> areq (ciField textField) (fslI MsgCourseShorthand
-- & addAttr "disabled" "disabled"
& setTooltip MsgCourseShorthandUnique)
(cfShort <$> template)
<*> areq termActiveField (fslI MsgCourseSemester) (cfTerm <$> template)
<*> areq (schoolFieldFor userSchools) (fslI MsgCourseSchool) (cfSchool <$> template)
<*> aopt (natField "Kapazität") (fslI MsgCourseCapacity
& setTooltip MsgCourseCapacityTip) (cfCapacity <$> template)
<*> aopt textField (fslpI MsgCourseSecret "beliebige Zeichenkette"
& setTooltip MsgCourseSecretTip) (cfSecret <$> template)
<*> areq checkBoxField (fslI MsgMaterialFree) (cfMatFree <$> template)
<*> aopt utcTimeField (fslpI MsgRegisterFrom "Datum"
& setTooltip MsgCourseRegisterFromTip) (cfRegFrom <$> template)
<*> aopt utcTimeField (fslpI MsgRegisterTo "Datum"
& setTooltip MsgCourseRegisterToTip) (cfRegTo <$> template)
<*> aopt utcTimeField (fslpI MsgDeRegUntil "Datum"
& setTooltip MsgCourseDeregisterUntilTip) (cfDeRegUntil <$> template)
<* submitButton
return $ case result of
FormSuccess courseResult
| errorMsgs <- validateCourse courseResult
, not $ null errorMsgs ->
(FormFailure errorMsgs,
[whamlet|
<div class="alert alert-danger">
<div class="alert__content">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
^{widget}
|]
)
_ -> (result, widget)
validateCourse :: CourseForm -> [Text]
validateCourse (CourseForm{..}) =
[ msg | (False, msg) <-
[
( NTop cfRegFrom <= NTop cfRegTo
, "Ende des Anmeldezeitraums muss nach dem Anfang liegen"
)
,
( NTop cfRegFrom <= NTop cfDeRegUntil
, "Ende des Abmeldezeitraums muss nach dem Anfang liegen"
)
-- No starting date is okay: effective immediately
-- ( cfHasReg <= (isNothing cfRegFrom)
-- , "Beginn der Anmeldung angeben oder Anmeldungen deaktivieren"
-- )
-- ,
] ]