module Handler.Course.Show ( getCShowR , getCRegisterTemplateR ) where import Import import Utils.Form import Handler.Utils import qualified Database.Esqueleto.Utils as E import Database.Esqueleto.Utils.TH import qualified Data.CaseInsensitive as CI import qualified Data.Map as Map import qualified Database.Esqueleto as E import Handler.Course.Register import System.FilePath (addExtension, pathSeparator) import qualified Data.Conduit.List as C getCShowR :: TermId -> SchoolId -> CourseShorthand -> Handler Html getCShowR tid ssh csh = do mbAid <- maybeAuthId (cid,course,schoolName,participants,registration,lecturers,assistants,correctors,tutors,mAllocation,hasApplicationTemplate,mApplication,news,events) <- runDB . maybeT notFound $ do [(E.Entity cid course, E.Value schoolName, E.Value participants, fmap entityVal -> registration)] <- lift . E.select . E.from $ \((school `E.InnerJoin` course) `E.LeftOuterJoin` participant) -> do E.on $ E.just (course E.^. CourseId) E.==. participant E.?. CourseParticipantCourse E.&&. E.val mbAid E.==. participant E.?. CourseParticipantUser E.on $ course E.^. CourseSchool E.==. school E.^. SchoolId E.where_ $ course E.^. CourseTerm E.==. E.val tid E.&&. course E.^. CourseSchool E.==. E.val ssh E.&&. course E.^. CourseShorthand E.==. E.val csh E.limit 1 -- we know that there is at most one match, but we tell the DB this info too let numParticipants = E.sub_select . E.from $ \part -> do E.where_ $ part E.^. CourseParticipantCourse E.==. course E.^. CourseId return ( E.countRows :: E.SqlExpr (E.Value Int)) return (course,school E.^. SchoolName, numParticipants, participant) staff <- lift . 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 E.orderBy [ E.asc $ user E.^. UserSurname, E.asc $ user E.^. UserDisplayName ] return ( lecturer E.^. LecturerType , user E.^. UserDisplayEmail, user E.^. UserDisplayName, user E.^. UserSurname) let partStaff :: (LecturerType, UserEmail, Text, Text) -> Either (UserEmail, Text, Text) (UserEmail, Text, Text) partStaff (CourseLecturer ,name,surn,mail) = Right (name,surn,mail) partStaff (_courseAssistant,name,surn,mail) = Left (name,surn,mail) (assistants,lecturers) = partitionWith partStaff $ map $(unValueN 4) staff correctors <- fmap (map $(unValueN 3)) . lift . E.select $ E.from $ \(sheet `E.InnerJoin` sheetCorrector `E.InnerJoin` user) -> E.distinctOnOrderBy [E.asc $ user E.^. UserSurname, E.asc $ user E.^. UserDisplayName, E.asc $ user E.^. UserEmail ] $ do E.on $ sheetCorrector E.^. SheetCorrectorUser E.==. user E.^. UserId E.on $ sheetCorrector E.^. SheetCorrectorSheet E.==. sheet E.^. SheetId E.where_ $ sheet E.^. SheetCourse E.==. E.val cid E.orderBy [ E.asc $ user E.^. UserSurname, E.asc $ user E.^. UserDisplayName ] return ( user E.^. UserEmail, user E.^. UserDisplayName, user E.^. UserSurname ) tutors <- fmap (map $(unValueN 3)) . lift . E.select $ E.from $ \(tutorial `E.InnerJoin` tutor `E.InnerJoin` user) -> E.distinctOnOrderBy [E.asc $ user E.^. UserSurname, E.asc $ user E.^. UserDisplayName, E.asc $ user E.^. UserEmail ] $ do E.on $ tutor E.^. TutorUser E.==. user E.^. UserId E.on $ tutor E.^. TutorTutorial E.==. tutorial E.^. TutorialId E.where_ $ tutorial E.^. TutorialCourse E.==. E.val cid E.orderBy [ E.asc $ user E.^. UserSurname, E.asc $ user E.^. UserDisplayName ] return ( user E.^. UserEmail, user E.^. UserDisplayName, user E.^. UserSurname ) mAllocation <- fmap (fmap entityVal . listToMaybe) . lift . E.select . E.from $ \(allocation `E.InnerJoin` allocationCourse) -> do E.on $ allocation E.^. AllocationId E.==. allocationCourse E.^. AllocationCourseAllocation E.where_ $ allocationCourse E.^. AllocationCourseCourse E.==. E.val cid E.limit 1 return allocation hasApplicationTemplate <- lift . E.selectExists . E.from $ \courseAppInstructionFile -> E.where_ $ courseAppInstructionFile E.^. CourseAppInstructionFileCourse E.==. E.val cid mApplication <- lift . fmap (listToMaybe =<<) . for mbAid $ \uid -> selectList [CourseApplicationCourse ==. cid, CourseApplicationUser ==. uid, CourseApplicationAllocation ==. Nothing] [] news' <- lift $ selectList [ CourseNewsCourse ==. cid ] [ Desc CourseNewsVisibleFrom, Desc CourseNewsTitle, Desc CourseNewsSummary, Desc CourseNewsContent ] cTime <- NTop . Just <$> liftIO getCurrentTime news <- forMaybeM news' $ \(Entity nId n@CourseNews{..}) -> do cID <- encrypt nId :: MaybeT (MaybeT DB) CryptoUUIDCourseNews guardM . hasReadAccessTo $ CNewsR tid ssh csh cID CNShowR let visible = cTime >= NTop courseNewsVisibleFrom files' <- lift . lift . E.select . E.from $ \(newsFile `E.InnerJoin` file) -> do E.on $ file E.^. FileId E.==. newsFile E.^. CourseNewsFileFile E.where_ $ newsFile E.^. CourseNewsFileNews E.==. E.val nId return (E.isNothing $ file E.^. FileContent, file E.^. FileTitle) let files = files' & over (mapped . _1) E.unValue & over (mapped . _2) E.unValue lastEditText <- formatTime SelFormatDateTime $ maybe id max (guardOn visible =<< courseNewsVisibleFrom) courseNewsLastEdit mayEdit <- hasWriteAccessTo $ CNewsR tid ssh csh cID CNEditR mayDelete <- hasWriteAccessTo $ CNewsR tid ssh csh cID CNDeleteR return (cID, n, visible, files, lastEditText, mayEdit, mayDelete) events' <- fmap (sortOn $ courseEventTime . entityVal) . lift $ selectList [ CourseEventCourse ==. cid ] [] events <- mapM (\(Entity evId ev) -> (, ev) <$> encrypt evId) events' return (cid,course,schoolName,participants,registration,lecturers,assistants,correctors,tutors,mAllocation,hasApplicationTemplate,mApplication,news,events) let mDereg' = maybe id min (allocationOverrideDeregister =<< mAllocation) <$> courseDeregisterUntil course mDereg <- traverse (formatTime SelFormatDateTime) mDereg' cID <- encrypt cid :: Handler CryptoUUIDCourse mAllocation' <- for mAllocation $ \alloc@Allocation{..} -> (,) <$> pure alloc <*> toTextUrl (AllocationR allocationTerm allocationSchool allocationShorthand AShowR :#: cID) regForm <- if | is _Just mbAid -> do (courseRegisterForm', regButton) <- courseRegisterForm (Entity cid course) (regWidget, regEnctype) <- generateFormPost $ renderAForm FormStandard courseRegisterForm' return $ wrapForm' regButton regWidget def { formAction = Just . SomeRoute $ CourseR tid ssh csh CRegisterR , formEncoding = regEnctype , formSubmit = FormSubmit } | otherwise -> return . modal $(widgetFile "course/login-to-register") . Left . SomeRoute $ AuthR LoginR registrationOpen <- hasWriteAccessTo $ CourseR tid ssh csh CRegisterR let tutorialDBTable = DBTable{..} where dbtSQLQuery tutorial = do E.where_ $ tutorial E.^. TutorialCourse E.==. E.val cid return tutorial dbtRowKey = (E.^. TutorialId) dbtProj = return dbtColonnade = dbColonnade $ mconcat [ sortable (Just "type") (i18nCell MsgTutorialType) $ \DBRow{ dbrOutput = Entity _ Tutorial{..} } -> textCell $ CI.original tutorialType , sortable (Just "name") (i18nCell MsgTutorialName) $ \DBRow{ dbrOutput = Entity _ Tutorial{..} } -> indicatorCell <> anchorCell (CTutorialR tid ssh csh tutorialName TUsersR) [whamlet|#{tutorialName}|] , sortable Nothing (i18nCell MsgTutorialTutors) $ \DBRow{ dbrOutput = Entity tutid _ } -> sqlCell $ do tutTutors <- fmap (map $(unValueN 3)) . E.select . E.from $ \(tutor `E.InnerJoin` user) -> do E.on $ tutor E.^. TutorUser E.==. user E.^. UserId E.where_ $ tutor E.^. TutorTutorial E.==. E.val tutid return (user E.^. UserEmail, user E.^. UserDisplayName, user E.^. UserSurname) return [whamlet| $newline never