63 lines
2.1 KiB
Haskell
63 lines
2.1 KiB
Haskell
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
module Lisa.Views where
|
|
|
|
import Prelude hiding (div)
|
|
|
|
import Control.Monad (forM_)
|
|
import Data.List (intersperse)
|
|
import Data.Text (Text, isInfixOf)
|
|
import Network.Wai (Request)
|
|
import Text.Blaze.Html5 hiding (map)
|
|
import Text.Blaze.Html5.Attributes hiding (form)
|
|
|
|
import Lisa.Types (Session)
|
|
import Lisa.Squeak (Document(..), Lecture(..), SqueakError(..))
|
|
|
|
viewIndex :: Html
|
|
viewIndex = do
|
|
h1 "Lisa"
|
|
ul $ do
|
|
li $ a "Vorlesungen" ! href "/lectures"
|
|
li $ a "Debuginformation" ! href "/debug"
|
|
|
|
viewLectures :: Text -> [Lecture] -> Html
|
|
viewLectures query lectures = do
|
|
h1 $ text "Vorlesungen"
|
|
form ! action "/lectures" ! method "GET" $ do
|
|
input ! name "query" ! value (textValue query)
|
|
button ! type_ "submit" $ text "Filtern"
|
|
ul $ forM_ (filter matchQuery lectures) $ \(Lecture lid displayName aliases) -> do
|
|
li $ do
|
|
div $ a ! href (textValue $ "/lectures/" <> lid) $ text displayName
|
|
div $ text $ mconcat $ intersperse ", " aliases
|
|
where
|
|
matchQuery (Lecture _id displayName aliases) =
|
|
any (query `isInfixOf`) (displayName : aliases)
|
|
|
|
viewLecture :: Text -> [Document] -> Html
|
|
viewLecture lecture documents = do
|
|
h1 $ text ("Vorlesung " <> lecture)
|
|
table $ do
|
|
thead $ tr $ mapM_ th ["Art", "Vorlesungen", "Prüfer", "Datum", "Semester", "Seiten"]
|
|
tbody $ forM_ documents $ \document -> tr $ do
|
|
td $ text $ documentType document
|
|
td $ text $ mconcat $ intersperse ", " $ map lectureDisplayName $ documentLectures document
|
|
td $ text "TBD"
|
|
td $ string $ show $ documentDate document
|
|
td $ text $ documentSemester document
|
|
td $ string $ show $ documentNumPages document
|
|
|
|
viewDebug :: Request -> Session -> Html
|
|
viewDebug request session = do
|
|
h1 $ text "Debuginformation"
|
|
fieldset $ do
|
|
legend "Request"
|
|
pre $ string $ show request
|
|
fieldset $ do
|
|
legend "Session"
|
|
pre $ string $ show session
|
|
|
|
viewSqueakError :: SqueakError -> Html
|
|
viewSqueakError err = string $ show err
|