Introduce pageActions and use in favourites

This commit is contained in:
Gregor Kleen 2018-04-13 16:03:06 +02:00
parent 8433df99c7
commit ad6f1ab199
3 changed files with 29 additions and 28 deletions

View File

@ -9,6 +9,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternGuards #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE FlexibleInstances, UndecidableInstances #-}
module Foundation where
@ -353,6 +354,15 @@ instance YesodBreadcrumbs UniWorX where
breadcrumb ProfileR = return ("Profile", Just HomeR)
breadcrumb _ = return ("home", Nothing)
pageActions :: Route UniWorX -> [MenuTypes]
pageActions (CourseR tid csh CourseShowR) = [ PageActionPrime $ MenuItem
{ menuItemLabel = "Übungsblätter"
, menuItemIcon = Nothing
, menuItemRoute = CSheetR tid csh SheetListR
, menuItemAccessCallback' = return True
}
]
pageActions _ = []
defaultLinks :: [MenuTypes]
defaultLinks = -- Define the menu items of the header.
@ -422,7 +432,7 @@ defaultMenuLayout menu widget = do
menuTypes <- filterM (menuItemAccessCallback . menuItem) menu
-- Lookup Favourites if possible
favourites <- do
favourites' <- do
muid <- maybeAuthId
case muid of
Nothing -> return []
@ -432,6 +442,11 @@ defaultMenuLayout menu widget = do
E.orderBy [ E.asc $ course E.^. CourseShorthand ]
return course
favourites <- forM favourites' $ \(Entity _ c@Course{..})
-> let
courseRoute = CourseR courseTermId courseShorthand CourseShowR
in (c, courseRoute, ) <$> filterM (menuItemAccessCallback . menuItem) (pageActions courseRoute)
-- We break up the default layout into two components:
-- default-layout is the contents of the body tag, and
-- default-layout-wrapper is the entire page. Since the final

View File

@ -92,15 +92,7 @@ getCourseShowR tid csh = do
return $ (courseEnt,dependent)
let course = entityVal courseEnt
(regWidget, regEnctype) <- generateFormPost $ identifyForm "registerBtn" $ registerButton $ mbRegistered
let pageActions =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Übungsblätter"
, menuItemIcon = Nothing
, menuItemRoute = CSheetR tid csh SheetListR
, menuItemAccessCallback' = return True
}
]
defaultLinkLayout pageActions $ do
defaultLinkLayout [] $ do
setTitle $ [shamlet| #{toPathPiece tid} - #{csh}|]
$(widgetFile "course")

View File

@ -17,23 +17,17 @@ $newline never
<h3 .asidenav__box-title>
WiSe 17/18
<ul .asidenav__list>
$forall (Entity _ Course{..}) <- favourites
$with route <- CourseR courseTermId courseShorthand CourseShowR
<li .asidenav__list-item :Just route == mcurrentRoute:.asidenav__list-item--active>
<a .asidenav__link-wrapper href=@{route}>
<div .asidenav__link-shorthand>#{courseShorthand}
<div .asidenav__link-label>#{courseName}
<li .asidenav__list-item>
<a .asidenav__link-wrapper href="/course/S2018/ixd/show">
<div .asidenav__link-shorthand>EXAMPLE
<div .asidenav__link-label>Beispiel-Kurs
<ul .asidenav__nested-list>
<li .asidenav__list-item>
<a .asidenav__link-wrapper href="/course/S2018/ixd/ex">Übungsblätter
<li .asidenav__list-item>
<a .asidenav__link-wrapper href="/course/S2018/ixd/show">Klausuren
<li .asidenav__list-item>
<a .asidenav__link-wrapper href="/course/S2018/ixd/show">Übungsgruppen
$forall (Course{..}, courseRoute, pageActions) <- favourites
<li .asidenav__list-item>
<a .asidenav__link-wrapper href=@{courseRoute}>
<div .asidenav__link-shorthand>#{courseShorthand}
<div .asidenav__link-label>#{courseName}
<ul .asidenav__nested-list>
$forall action <- pageActions
$case action
$of PageActionPrime (MenuItem{..})
<li .asidenav__list-item>
<a .asidenav__link-wrapper href=@{menuItemRoute}>#{menuItemLabel}
$of _
<div .asidenav__toggler>