diff --git a/messages/de.msg b/messages/de.msg index 568eaf109..c97852f20 100644 --- a/messages/de.msg +++ b/messages/de.msg @@ -190,4 +190,8 @@ CourseMembersCount num@Int64: #{display num} CourseMembersCountLimited num@Int64 max@Int64: #{display num}/#{display max} NoTableContent: Kein Tabelleninhalt -NoUpcomingSheetDeadlines: Keine anstehenden Übungsblätter \ No newline at end of file +NoUpcomingSheetDeadlines: Keine anstehenden Übungsblätter + +AdminFor: Administrator +LecturerFor: Dozent +UserListTitle: Komprehensive Benutzerliste \ No newline at end of file diff --git a/src/Handler/Users.hs b/src/Handler/Users.hs index 17aadafb9..31faf23af 100644 --- a/src/Handler/Users.hs +++ b/src/Handler/Users.hs @@ -4,6 +4,7 @@ {-# LANGUAGE QuasiQuotes #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE RecordWildCards #-} module Handler.Users where @@ -11,39 +12,64 @@ import Import -- import Data.Text import Handler.Utils -import Colonnade hiding (fromMaybe) -import Yesod.Colonnade +import qualified Data.Map as Map --- import qualified Database.Esqueleto as E --- import Database.Esqueleto ((^.)) +import Colonnade hiding (fromMaybe) + +import qualified Database.Esqueleto as E getUsersR :: Handler Html getUsersR = do - -- TODO: Esqueleto, combine the two queries into one - (users,schools) <- runDB $ (,) - <$> (selectList [] [Asc UserDisplayName] - >>= mapM (\usr -> (,,) - <$> pure usr - <*> selectList [UserAdminUser ==. entityKey usr] [Asc UserAdminSchool] - <*> selectList [UserLecturerUser ==. entityKey usr] [Asc UserLecturerSchool] - )) - <*> selectList [] [Asc SchoolShorthand] - let schoolnames = entities2map schools - let getSchoolname = \sid -> - case lookup sid schoolnames of - Nothing -> "???" - (Just school) -> schoolShorthand school - let colonnadeUsers = mconcat $ - [ headed "User" $ \u -> do - cID <- encrypt $ entityKey $ fst3 u - let name = display $ userDisplayName $ entityVal $ fst3 u - [whamlet|#{name}|] - , headed "Admin" $ (\u -> text2widget $ intercalate ", " $ map (getSchoolname.userAdminSchool .entityVal) $ snd3 u) - , headed "Lecturer" $ (\u -> text2widget $ intercalate ", " $ map (getSchoolname.userLecturerSchool.entityVal) $ trd3 u) + let + colonnadeUsers = dbColonnade . mconcat $ + [ dbRow + , sortable (Just "display-name") (i18nCell MsgName) $ \DBRow{ dbrOutput = Entity uid User{..} } -> anchorCellM + (AdminUserR <$> encrypt uid) + (toWidget . display $ userDisplayName) + , sortable Nothing (i18nCell MsgAdminFor) $ \DBRow{ dbrOutput = Entity uid _ } -> mempty + { dbCellContents = do + schools <- E.select . E.from $ \(school `E.InnerJoin` userAdmin) -> do + E.on $ school E.^. SchoolId E.==. userAdmin E.^. UserAdminSchool + E.where_ $ userAdmin E.^. UserAdminUser E.==. E.val uid + E.orderBy [E.asc $ school E.^. SchoolShorthand] + return $ school E.^. SchoolShorthand + return [whamlet| +