Merge branch 'master' into feat/assign-correctors

This commit is contained in:
Gregor Kleen 2018-06-29 10:51:56 +02:00
commit 6e0558d094
96 changed files with 5811 additions and 1566 deletions

View File

@ -19,6 +19,7 @@ should-log-all: "_env:LOG_ALL:false"
# mutable-static: false
# skip-combining: false
auth-dummy-login: "_env:DUMMY_LOGIN:false"
allow-deprecated: "_env:ALLOW_DEPRECATED:false"
# NB: If you need a numeric value (e.g. 123) to parse as a String, wrap it in single quotes (e.g. "_env:PGPASS:'123'")
# See https://github.com/yesodweb/yesod/wiki/Configuration#parsing-numeric-values-as-strings

View File

@ -25,6 +25,7 @@ main = db $ do
, userEmail = "G.Kleen@campus.lmu.de"
, userDisplayName = "Gregor Kleen"
, userMaxFavourites = 6
, userTheme = AberdeenReds
}
fhamann <- insert User
{ userPlugin = "LDAP"
@ -33,6 +34,7 @@ main = db $ do
, userEmail = "felix.hamann@campus.lmu.de"
, userDisplayName = "Felix Hamann"
, userMaxFavourites = defaultFavourites
, userTheme = Default
}
jost <- insert User
{ userPlugin = "LDAP"
@ -41,6 +43,7 @@ main = db $ do
, userEmail = "jost@tcs.ifi.lmu.de"
, userDisplayName = "Steffen Jost"
, userMaxFavourites = 14
, userTheme = MintGreen
}
void . insert $ Term
{ termName = summer2017

View File

@ -1,3 +1,12 @@
BtnSubmit: Senden
BtnAbort: Abbrechen
BtnDelete: Löschen
BtnRegister: Anmelden
BtnDeregister: Abmelden
RegisterFrom: Anmeldungen von
RegisterTo: Anmeldungen bis
SummerTerm year@Integer: Sommersemester #{tshow year}
WinterTerm year@Integer: Wintersemester #{tshow year}/#{tshow $ succ year}
PSLimitNonPositive: “pagesize” muss größer als null sein
@ -5,13 +14,23 @@ Page n@Int64: #{tshow n}
TermEdited tid@TermIdentifier: Semester #{termToText tid} erfolgreich editiert.
TermNewTitle: Semester editiere/anlegen.
InvalidInput: Eingaben bitte korrigieren.
Term: Semester
TermPlaceholder: W/S + vierstellige Jahreszahl
TermEditHeading: Semester editieren/anlegen
Course: Kurs
CourseSecret: Zugangspasswort
CourseNewOk tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} wurde erfolgreich erstellt.
CourseEditOk tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} wurde erfolgreich geändert.
CourseNewDupShort tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} konnte nicht erstellt werden: Es gibt bereits einen anderen Kurs mit dem Kürzel #{courseShortHand} in diesem Semester.
CourseEditDupShort tid@TermIdentifier courseShortHand@Text: Kurs #{termToText tid}-#{courseShortHand} konnte nicht geändert werden: Es gibt bereits einen anderen Kurs mit dem Kürzel #{courseShortHand} in diesem Semester.
FFSheetName: Name
TermCourseListHeading tid@TermIdentifier: Kursübersicht #{termToText tid}
TermCourseListTitle tid@TermIdentifier: Kurse #{termToText tid}
CourseEditHeading: Kurs editieren/anlegen
CourseEditTitle: Kurs editieren/anlegen
Sheet: Blatt
SheetNewOk tid@TermIdentifier courseShortHand@Text sheetName@Text: Neues Übungsblatt #{sheetName} wurde im Kurs #{termToText tid}-#{courseShortHand} erfolgreich erstellt.
SheetTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand} #{sheetName}
SheetTitleNew tid@TermIdentifier courseShortHand@Text : #{termToText tid}-#{courseShortHand}: Neues Übungsblatt
@ -21,9 +40,12 @@ SheetDelTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: Übun
SheetDelText submissionNo@Int: Dies kann nicht mehr rückgängig gemacht werden! Alle Einreichungen gehen ebenfalls verloren! Es gibt #{show submissionNo} Abgaben.
SheetDelOk tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termToText tid}-#{courseShortHand}: Übungsblatt #{sheetName} gelöscht.
Deadline: Abgabe
Done: Eingereicht
Unauthorized: Sie haben hierfür keine explizite Berechtigung.
UnauthorizedAnd l@Text r@Text: "#{l}" und "#{r}"
UnauthorizedOr l@Text r@Text: "#{l}" oder "#{r}"
UnauthorizedAnd l@Text r@Text: #{l} UND #{r}
UnauthorizedOr l@Text r@Text: #{l} ODER #{r}
UnauthorizedSchoolAdmin: Sie sind nicht als Administrator für dieses Institut eingetragen.
UnauthorizedSchoolLecturer: Sie sind nicht als Veranstalter für dieses Institut eingetragen.
UnauthorizedLecturer: Sie sind nicht als Veranstalter für diese Veranstaltung eingetragen.
@ -31,12 +53,15 @@ UnauthorizedCorrector: Sie sind nicht als Korrektor für diese Veranstaltung ein
UnauthorizedSheetCorrector: Sie sind nicht als Korrektor für dieses Übungsblatt eingetragen.
UnauthorizedCorrectorAny: Sie sind nicht als Korrektor für eine Veranstaltung eingetragen.
UnauthorizedParticipant: Sie sind nicht als Teilnehmer für diese Veranstaltung registriert.
UnauthorizedCourseTime: Dieses Kurs erlaubt momentan keine Anmeldungen.
UnauthorizedSheetTime: Dieses Übungsblatt ist momentan nicht freigegeben.
UnauthorizedSubmissionOwner: Sie sind an dieser Abgabe nicht beteiligt.
UnauthorizedSubmissionCorrector: Sie sind nicht der Korrektor für diese Abgabe.
OnlyUploadOneFile: Bitte nur eine Datei hochladen.
DeprecatedRoute: Diese Ansicht ist obsolet und könnte in Zukunft entfallen.
UnfreeMaterials: Die Materialien für diese Veranstaltung sind nicht allgemein freigegeben.
UnauthorizedWrite: Sie haben hierfür keine Schreibberechtigung
SubmissionWrongSheet: Abgabenummer gehört nicht zum angegebenen Übungsblatt.
SubmissionAlreadyExists: Sie haben bereits eine Abgabe zu diesem Übungsblatt.
@ -44,8 +69,9 @@ SubmissionTitle tid@TermIdentifier courseShortHand@Text sheetName@Text: #{termTo
SubmissionMember g@Int: Mitabgebende(r) ##{tshow g}
SubmissionArchive: Zip-Archiv der Abgabedatei(en)
SubmissionFile: Datei zur Abgabe
SubmissionAlreadyExistsFor user@Text: #{user} hat bereits eine Abgabe zu diesem Übungsblatt.
SubmissionAlreadyExistsFor user@Text: #{user} hat bereits eine Abgabe zu diesem bÜbungsblatt.
EMail: E-Mail
EMailUnknown email@Text: E-Mail #{email} gehört zu keinem bekannten Benutzer.
NotAParticipant user@Text tid@TermIdentifier csh@Text: #{user} ist nicht im Kurs #{termToText tid}-#{csh} angemeldet.
@ -60,4 +86,29 @@ CorProportion: Anteil
DeleteRow: Zeile entfernen
ProportionNegative: Anteile dürfen nicht negativ sein
CorrectorsUpdated: Korrektoren erfolgreich aktualisiert
CorrectorsPlaceholder: Korrektoren...
CorrectorsPlaceholder: Korrektoren...
HomeHeading: Aktuelle Termine
ProfileHeading: Benutzerprofil und Einstellungen
ProfileDataHeading: Gespeicherte Benutzerdaten
TermsHeading: Semesterübersicht
NumCourses n@Int64: #{tshow n} Kurse
CloseAlert: Schliessen
Name: Name
MatrikelNr: Matrikelnummer
Theme: Oberflächen Design
Favoriten: Anzahl gespeicherter Favoriten
Plugin: Plugin
Ident: Identifizierung
Settings: Individuelle Benutzereinstellungen
SettingsUpdate: Einstellungen wurden gespeichert.
SheetExercise: Aufgabenstellung
SheetHint: Hinweise
SheetSolution: Lösung
SheetMarking: Korrekturhinweise
MultiFileUploadInfo: (Mehrere Dateien mit Shift oder Strg auswählen)
NatField xyz@Text: #{xyz} muss eine natürliche Zahl sein!

5
models
View File

@ -4,7 +4,8 @@ User
matrikelnummer Text Maybe
email Text
displayName Text
maxFavourites Int default=12
maxFavourites Int default=12
theme Theme default='default'
UniqueAuthentication plugin ident
UniqueEmail email
UserAdmin
@ -59,7 +60,7 @@ Course
term TermId
school SchoolId
capacity Int Maybe
hasRegistration Bool -- canRegisterNow = hasRegistration && maybe False (<= currentTime) registerFrom && maybe True (>= currentTime) registerTo
-- canRegisterNow = maybe False (<= currentTime) registerFrom && maybe True (>= currentTime) registerTo
registerFrom UTCTime Maybe
registerTo UTCTime Maybe
deregisterUntil UTCTime Maybe

41
routes
View File

@ -18,8 +18,10 @@
--
-- !materials -- only if course allows all materials to be free (no meaning outside of courses)
-- !time -- access depends on time somehow
-- !isRead -- only if it is read-only access (i.e. GET but not POST)
-- !isWrite -- only if it is write access (i.e. POST only) why needed???
--
-- !deprecated -- like free, but logs and gives a warning
-- !deprecated -- like free, but logs and gives a warning; entirely disabled in production
--
/static StaticR Static appStatic !free
@ -28,38 +30,49 @@
/favicon.ico FaviconR GET !free
/robots.txt RobotsR GET !free
/ HomeR GET POST !free
/profile ProfileR GET !free
/users UsersR GET -- no tags, i.e. admins only
/ HomeR GET !free
/users UsersR GET -- no tags, i.e. admins only
/admin/test AdminTestR GET POST
/admin/user/#CryptoUUIDUser AdminUserR GET
/term TermShowR GET !free
/term/edit TermEditR GET POST
/term/#TermId/edit TermEditExistR GET
!/term/#TermId TermCourseListR GET !free
/profile ProfileR GET POST !free !free
/profile/data ProfileDataR GET !free !free
/terms TermShowR GET !free
/terms/current TermCurrentR GET !free
/terms/edit TermEditR GET POST
/terms/#TermId/edit TermEditExistR GET
!/terms/#TermId TermCourseListR GET !free
-- For Pattern Synonyms see Foundation
/course/ CourseListR GET !free
!/course/new CourseNewR GET POST !lecturer
/course/#TermId/#Text CourseR !lecturer:
/show CShowR GET POST !free
/show CShowR GET !free
/register CRegisterR POST !time
/edit CEditR GET POST
/ex SheetListR GET !registered !materials
!/ex/new SheetNewR GET POST
/ex/#Text SheetR:
/show SShowR GET !timeANDregistered !timeANDmaterials !corrector
/#SheetFileType/#FilePath SFileR GET !timeANDregistered !timeANDmaterials !corrector
!/#SheetFileType/*FilePath SFileR GET !timeANDregistered !timeANDmaterials !corrector
/edit SEditR GET POST
/delete SDelR GET POST
!/submission/#SubmissionMode SubmissionR GET POST !timeANDregistered !owner
!/sub/new SubmissionNewR GET POST !timeANDregistered
!/sub/own SubmissionOwnR GET !free
!/sub/#CryptoFileNameSubmission SubmissionR GET POST !owner !corrector
/correctors SCorrR GET POST
!/#UUID CryptoUUIDDispatchR GET !free -- just redirect
-- TODO below
!/#{ZIPArchiveName SubmissionId} SubmissionDownloadArchiveR GET !deprecated
!/#CryptoUUIDSubmission/#FilePath SubmissionDownloadSingleR GET !deprecated
!/#CryptoFileNameSubmission/*FilePath SubmissionDownloadSingleR GET !deprecated
/submission SubmissionListR GET !deprecated
/submission/#CryptoUUIDSubmission SubmissionDemoR GET POST !deprecated
/submissions.zip SubmissionDownloadMultiArchiveR POST !deprecated
-- TODO above
!/#UUID CryptoUUIDDispatchR GET !free -- just redirect
!/*{CI FilePath} CryptoFileNameDispatchR GET !free

View File

@ -43,6 +43,7 @@ import Handler.Common
import Handler.Home
import Handler.Profile
import Handler.Users
import Handler.Admin
import Handler.Term
import Handler.Course
import Handler.Sheet

View File

@ -24,6 +24,8 @@ import Data.CryptoID.Poly.ImplicitNamespace
import Data.UUID.Cryptographic.ImplicitNamespace
import System.FilePath.Cryptographic.ImplicitNamespace
import qualified Data.Text as Text
import Data.UUID.Types
import Web.PathPieces
@ -35,11 +37,21 @@ instance PathPiece UUID where
fromPathPiece = fromString . unpack
toPathPiece = pack . toString
instance (CI.FoldCase s, PathPiece s) => PathPiece (CI s) where
fromPathPiece = fmap CI.mk . fromPathPiece
toPathPiece = toPathPiece . CI.foldedCase
-- Generates CryptoUUID... Datatypes
instance {-# OVERLAPS #-} PathMultiPiece FilePath where
fromPathMultiPiece = Just . unpack . intercalate "/"
toPathMultiPiece = Text.splitOn "/" . pack
instance (CI.FoldCase s, PathMultiPiece s) => PathMultiPiece (CI s) where
fromPathMultiPiece = fmap CI.mk . fromPathMultiPiece
toPathMultiPiece = toPathMultiPiece . CI.foldedCase
-- Generates CryptoUUID... and CryptoFileName... Datatypes
decCryptoIDs [ ''SubmissionId
, ''CourseId
, ''SheetId
, ''FileId
, ''UserId
]
@ -47,12 +59,12 @@ decCryptoIDs [ ''SubmissionId
newtype SubmissionMode = SubmissionMode (Maybe CryptoUUIDSubmission)
newtype SubmissionMode = SubmissionMode (Maybe CryptoFileNameSubmission)
deriving (Show, Read, Eq)
pattern NewSubmission :: SubmissionMode
pattern NewSubmission = SubmissionMode Nothing
pattern ExistingSubmission :: CryptoUUIDSubmission -> SubmissionMode
pattern ExistingSubmission :: CryptoFileNameSubmission -> SubmissionMode
pattern ExistingSubmission cID = SubmissionMode (Just cID)
instance PathPiece SubmissionMode where
@ -62,6 +74,7 @@ instance PathPiece SubmissionMode where
toPathPiece (SubmissionMode Nothing) = "new"
toPathPiece (SubmissionMode (Just x)) = toPathPiece x
newtype ZIPArchiveName objID = ZIPArchiveName (CryptoID (CI FilePath) objID)
deriving (Show, Read, Eq)

View File

@ -1,7 +1,6 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
@ -49,6 +48,7 @@ import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import Data.List (foldr1)
import qualified Data.List as List
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Map (Map, (!?))
@ -68,9 +68,17 @@ import System.FilePath
import Handler.Utils.Templates
import Handler.Utils.StudyFeatures
import Handler.Utils.DateTime
import Control.Lens
import Utils.Lens
-- -- TODO: Move me to appropriate Place
instance DisplayAble TermId where
display = termToText . unTermKey
instance DisplayAble UTCTime where
display = pack . formatTimeGerDT2 -- default Time Format to be used: 00.00.00 00:00
-- infixl 9 :$:
-- pattern a :$: b = a b
@ -110,7 +118,6 @@ type MsgRenderer = MsgRendererS UniWorX -- see Utils
pattern CSheetR tid csh shn ptn
= CourseR tid csh (SheetR shn ptn)
-- Menus and Favourites
data MenuItem = MenuItem
{ menuItemLabel :: Text
@ -146,6 +153,13 @@ instance RenderMessage UniWorX TermIdentifier where
Winter -> renderMessage' $ MsgWinterTerm year
where renderMessage' = renderMessage foundation ls
instance RenderMessage UniWorX SheetFileType where
renderMessage foundation ls = \case
SheetExercise -> renderMessage' MsgSheetExercise
SheetHint -> renderMessage' MsgSheetHint
SheetSolution -> renderMessage' MsgSheetSolution
SheetMarking -> renderMessage' MsgSheetMarking
where renderMessage' = renderMessage foundation ls
-- Access Control
data AccessPredicate
@ -159,14 +173,12 @@ orAR _ _ Authorized = Authorized
orAR _ AuthenticationRequired _ = AuthenticationRequired
orAR _ _ AuthenticationRequired = AuthenticationRequired
orAR mr (Unauthorized x) (Unauthorized y) = Unauthorized . render mr $ MsgUnauthorizedOr x y
andAR _ Authorized Authorized = Authorized
andAR _ Authorized other = other
andAR _ other Authorized = other
andAR _ AuthenticationRequired other = other
andAR _ other AuthenticationRequired = other
-- and
andAR mr (Unauthorized x) (Unauthorized y) = Unauthorized . render mr $ MsgUnauthorizedAnd x y
andAR _ reason@(Unauthorized x) _ = reason
andAR _ _ reason@(Unauthorized x) = reason
andAR _ Authorized other = other
andAR _ AuthenticationRequired _ = AuthenticationRequired
orAP,andAP :: AccessPredicate -> AccessPredicate -> AccessPredicate
orAP = liftAR orAR (== Authorized)
@ -176,22 +188,23 @@ liftAR :: (MsgRenderer -> AuthResult -> AuthResult -> AuthResult)
-> (AuthResult -> Bool) -- ^ Predicate to Short-Circuit on first argument
-> AccessPredicate -> AccessPredicate -> AccessPredicate
-- Ensure to first evaluate Pure conditions, then Handler before DB
liftAR op sc (APPure f) (APPure g) = APPure $ \r -> shortCircuitM sc (f r) (g r) . op =<< ask
liftAR op sc (APHandler f) (APHandler g) = APHandler $ \r -> shortCircuitM sc (f r) (g r) . op =<< getMsgRenderer
liftAR op sc (APDB f) (APDB g) = APDB $ \r -> shortCircuitM sc (f r) (g r) . op =<< getMsgRenderer
liftAR op sc (APPure f) apg = liftAR op sc (APHandler $ \r -> runReader (f r) <$> getMsgRenderer) apg
liftAR op sc apf apg@(APPure _) = liftAR op sc apg apf
liftAR op sc (APHandler f) apdb = liftAR op sc (APDB $ lift . f) apdb
liftAR op sc apdb apg@(APHandler _) = liftAR op sc apg apdb
liftAR ops sc (APPure f) (APPure g) = APPure $ \r -> shortCircuitM sc (f r) (g r) . ops =<< ask
liftAR ops sc (APHandler f) (APHandler g) = APHandler $ \r -> shortCircuitM sc (f r) (g r) . ops =<< getMsgRenderer
liftAR ops sc (APDB f) (APDB g) = APDB $ \r -> shortCircuitM sc (f r) (g r) . ops =<< getMsgRenderer
liftAR ops sc (APPure f) apg = liftAR ops sc (APHandler $ \r -> runReader (f r) <$> getMsgRenderer) apg
liftAR ops sc apf apg@(APPure _) = liftAR ops sc apg apf
liftAR ops sc (APHandler f) apdb = liftAR ops sc (APDB $ lift . f) apdb
liftAR ops sc apdb apg@(APHandler _) = liftAR ops sc apg apdb
trueAP,falseAP :: AccessPredicate
trueAP = APPure . const $ return Authorized
falseAP = APPure . const $ Unauthorized . ($ MsgUnauthorized) . render <$> ask
-- TODO: I believe falseAP := adminAP
falseAP = APPure . const $ Unauthorized . ($ MsgUnauthorized) . render <$> ask -- always use adminAP instead
adminAP :: AccessPredicate
adminAP :: AccessPredicate -- access for admins (of appropriate school in case of course-routes)
adminAP = APDB $ \case
-- Courses: access only to school admins
CourseR tid csh _ -> exceptT return return $ do
authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId
[E.Value c] <- lift . E.select . E.from $ \(course `E.InnerJoin` userAdmin) -> do
@ -200,23 +213,24 @@ adminAP = APDB $ \case
E.&&. course E.^. CourseTerm E.==. E.val tid
E.&&. course E.^. CourseShorthand E.==. E.val csh
return (E.countRows :: E.SqlExpr (E.Value Int64))
guardMExceptT (unauthorizedI MsgUnauthorizedSchoolAdmin) (c > 0)
guardMExceptT (c > 0) (unauthorizedI MsgUnauthorizedSchoolAdmin)
return Authorized
-- other routes: access to any admin is granted here
_other -> exceptT return return $ do
authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId
adrights <- lift $ selectFirst [UserAdminUser ==. authId] []
case adrights of
(Just _) -> return Authorized
Nothing -> lift $ unauthorizedI $ MsgUnauthorized
guardMExceptT (isJust adrights) (unauthorizedI $ MsgUnauthorized)
return Authorized
knownTags :: Map (CI Text) AccessPredicate
knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId
knownTags = Map.fromList -- should not throw exceptions, i.e. no getBy404 or requireAuthId
[("free", trueAP)
,("deprecated", APHandler $ \r -> do
$logWarnS "AccessControl" ("deprecated route: " <> tshow r)
addMessageI "error" MsgDeprecatedRoute
return Authorized
allow <- appAllowDeprecated . appSettings <$> getYesod
return $ bool (Unauthorized "Deprecated Route") Authorized allow
)
,("lecturer", APDB $ \case
CourseR tid csh _ -> exceptT return return $ do
@ -227,7 +241,7 @@ knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId
E.&&. course E.^. CourseTerm E.==. E.val tid
E.&&. course E.^. CourseShorthand E.==. E.val csh
return (E.countRows :: E.SqlExpr (E.Value Int64))
guardMExceptT (unauthorizedI MsgUnauthorizedLecturer) (c > 0)
guardMExceptT (c>0) (unauthorizedI MsgUnauthorizedLecturer)
return Authorized
_ -> exceptT return return $ do
authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId
@ -245,7 +259,7 @@ knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId
resMap :: Map CourseId (Set SheetId)
resMap = Map.fromListWith Set.union [ (cid, Set.singleton sid) | (E.Value cid, E.Value sid) <- resList ]
case route of
CSheetR _ _ _ (SubmissionR (ExistingSubmission cID)) -> maybeT (unauthorizedI MsgUnauthorizedSubmissionCorrector) $ do
CSheetR _ _ _ (SubmissionR cID) -> maybeT (unauthorizedI MsgUnauthorizedSubmissionCorrector) $ do
sid <- catchIfMaybeT (const True :: CryptoIDError -> Bool) $ decrypt cID
Submission{..} <- MaybeT . lift $ get sid
guard $ maybe False (== authId) submissionRatingBy
@ -260,21 +274,32 @@ knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId
guard $ cid `Set.member` Map.keysSet resMap
return Authorized
_ -> do
guardMExceptT (unauthorizedI MsgUnauthorizedCorrectorAny) . not $ Map.null resMap
guardMExceptT (not $ Map.null resMap) (unauthorizedI MsgUnauthorizedCorrectorAny)
return Authorized
)
,("time", APDB $ \case
CSheetR tid csh shn subRoute -> maybeT (unauthorizedI MsgUnauthorizedSheetTime) $ do
Entity cid _ <- MaybeT . getBy $ CourseTermShort tid csh
Entity sid Sheet{..} <- MaybeT . getBy $ CourseSheet cid shn
cTime <- liftIO getCurrentTime
case subRoute of
SFileR SheetHint _ -> guard $ maybe False (<= cTime) sheetHintFrom
SFileR SheetSolution _ -> guard $ maybe False (<= cTime) sheetSolutionFrom
SubmissionR NewSubmission -> guard $ sheetActiveFrom <= cTime && cTime <= sheetActiveTo
_ -> guard $ maybe False (<= cTime) sheetVisibleFrom
return Authorized
r -> do
CSheetR tid csh shn subRoute -> maybeT (unauthorizedI MsgUnauthorizedSheetTime) $ do
Entity cid _ <- MaybeT . getBy $ CourseTermShort tid csh
Entity sid Sheet{..} <- MaybeT . getBy $ CourseSheet cid shn
cTime <- liftIO getCurrentTime
let started = sheetActiveFrom <= cTime || NTop sheetVisibleFrom <= (NTop $ Just cTime)
case subRoute of
SFileR SheetExercise _ -> guard started
SFileR SheetHint _ -> guard $ maybe False (<= cTime) sheetHintFrom
SFileR SheetSolution _ -> guard $ maybe False (<= cTime) sheetSolutionFrom
SFileR SheetMarking _ -> mzero -- only for correctors and lecturers
SubmissionNewR -> guard $ sheetActiveFrom <= cTime && cTime <= sheetActiveTo
_ -> guard started
return Authorized
CourseR tid csh CRegisterR -> maybeT (unauthorizedI MsgUnauthorizedCourseTime) $ do
Entity cid Course{..} <- MaybeT . getBy $ CourseTermShort tid csh
cTime <- (NTop . Just) <$> liftIO getCurrentTime
guard $ NTop courseRegisterFrom <= cTime
&& NTop courseRegisterTo >= cTime
return Authorized
r -> do
$logErrorS "AccessControl" $ "'!time' used on route that doesn't support it: " <> tshow r
unauthorizedI MsgUnauthorized
)
@ -287,7 +312,7 @@ knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId
E.&&. course E.^. CourseTerm E.==. E.val tid
E.&&. course E.^. CourseShorthand E.==. E.val csh
return (E.countRows :: E.SqlExpr (E.Value Int64))
guardMExceptT (unauthorizedI MsgUnauthorizedParticipant) (c > 0)
guardMExceptT (c > 0) (unauthorizedI MsgUnauthorizedParticipant)
return Authorized
r -> do
$logErrorS "AccessControl" $ "'!registered' used on route that doesn't support it: " <> tshow r
@ -303,16 +328,27 @@ knownTags = -- should not throw exceptions, i.e. no getBy404 or requireAuthId
unauthorizedI MsgUnauthorized
)
,("owner", APDB $ \case
CSheetR _ _ _ (SubmissionR (ExistingSubmission cID)) -> exceptT return return $ do
CSheetR _ _ _ (SubmissionR cID) -> exceptT return return $ do
sid <- catchIfMExceptT (const $ unauthorizedI MsgUnauthorizedSubmissionOwner) (const True :: CryptoIDError -> Bool) $ decrypt cID
authId <- maybeExceptT AuthenticationRequired $ lift maybeAuthId
void . maybeMExceptT (unauthorizedI MsgUnauthorizedSubmissionOwner) . getBy $ UniqueSubmissionUser authId sid
return Authorized
CSheetR _ _ _ (SubmissionR NewSubmission) -> unauthorizedI MsgUnauthorizedSubmissionOwner
CSheetR _ _ _ SubmissionNewR -> unauthorizedI MsgUnauthorizedSubmissionOwner
r -> do
$logErrorS "AccessControl" $ "'!owner' used on route that doesn't support it: " <> tshow r
unauthorizedI MsgUnauthorized
)
,("isRead", APHandler $ \route ->
bool <$> return Authorized
<*> unauthorizedI MsgUnauthorizedWrite
<*> isWriteRequest route
)
,("isWrite", APHandler $ \route -> do
write <- isWriteRequest route
if write
then return Authorized
else unauthorizedI MsgUnauthorized
)
]
@ -341,9 +377,6 @@ evalAccess r = case route2ap r of
(APHandler p) -> p r
(APDB p) -> runDB $ p r
-- TODO: isAuthorized = evalAccess'
-- Please see the documentation for the Yesod typeclass. There are a number
@ -370,9 +403,9 @@ instance Yesod UniWorX where
-- To add it, chain it together with the defaultMiddleware: yesodMiddleware = defaultYesodMiddleware . defaultCsrfMiddleware
-- For details, see the CSRF documentation in the Yesod.Core.Handler module of the yesod-core package.
yesodMiddleware handler = do
res <- defaultYesodMiddleware handler
void . runMaybeT $ do
route <- MaybeT getCurrentRoute
guardM . lift $ (== Authorized) <$> isAuthorized route False
case route of -- update Course Favourites here
CourseR tid csh _ -> do
uid <- MaybeT maybeAuthId
@ -392,52 +425,67 @@ instance Yesod UniWorX where
[ Desc CourseFavouriteTime
, OffsetBy $ userMaxFavourites user
]
lift $ mapM delete oldFavs
lift $ mapM_ delete oldFavs
_other -> return ()
return res
defaultYesodMiddleware handler -- handler is executed afterwards, so Favourites are updated immediately
defaultLayout widget = do
master <- getYesod
mmsgs <- getMessages
messageRender <- getMessageRender -- needed, since there is no i18n interpolation in Julius
mcurrentRoute <- getCurrentRoute
-- Get the breadcrumbs, as defined in the YesodBreadcrumbs instance.
(title, parents) <- breadcrumbs
-- let isParent :: Route UniWorX -> Bool
-- isParent r = r == (fst parents)
let
menu = defaultLinks ++ maybe [] pageActions mcurrentRoute
menuTypes <- filterM (menuItemAccessCallback . menuItem) menu
-- Lookup Favourites if possible
favourites' <- do
muid <- maybeAuthId
-- Lookup Favourites & Theme if possible -- TODO: cache this info in a cookie?!
(favourites',show -> currentTheme) <- do
muid <- maybeAuthPair
case muid of
Nothing -> return []
(Just uid) -> runDB . E.select . E.from $ \(course `E.InnerJoin` courseFavourite) -> do
E.on (course E.^. CourseId E.==. courseFavourite E.^. CourseFavouriteCourse)
E.where_ (courseFavourite E.^. CourseFavouriteUser E.==. E.val uid)
E.orderBy [ E.asc $ course E.^. CourseShorthand ]
return course
Nothing -> return ([],Default)
(Just (uid,user)) -> do
favs <- runDB $ E.select . E.from $ \(course `E.InnerJoin` courseFavourite) -> do
E.on (course E.^. CourseId E.==. courseFavourite E.^. CourseFavouriteCourse)
E.where_ (courseFavourite E.^. CourseFavouriteUser E.==. E.val uid)
E.orderBy [ E.asc $ course E.^. CourseShorthand ]
return course
return (favs, userTheme user)
favourites <- forM favourites' $ \(Entity _ c@Course{..})
-> let
courseRoute = CourseR courseTerm courseShorthand CShowR
in (c, courseRoute, ) <$> filterM (menuItemAccessCallback . menuItem) (pageActions courseRoute)
let highlight :: Route UniWorX -> Bool -- highlight last route in breadcrumbs, favorites taking priority
highlight = let crumbs = mcons mcurrentRoute $ fst <$> parents
actFav = List.intersect (snd3 <$> favourites) crumbs
highRs = if null actFav then crumbs else actFav
in \r -> r `elem` highRs
-- 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
-- value passed to hamletToRepHtml cannot be a widget, this allows
-- you to use normal widget features in default-layout.
let
navbar :: Widget
navbar = $(widgetFile "widgets/navbar")
asidenav :: Widget
asidenav = $(widgetFile "widgets/asidenav")
contentHeadline :: Maybe Widget
contentHeadline = pageHeading =<< mcurrentRoute
breadcrumbs :: Widget
breadcrumbs = $(widgetFile "widgets/breadcrumbs")
pageactionprime :: Widget
@ -450,21 +498,28 @@ instance Yesod UniWorX where
hasPageActions = any isPageActionPrime menuTypes
pc <- widgetToPageContent $ do
addStylesheetRemote "https://fonts.googleapis.com/css?family=Source+Sans+Pro:300,400,600,800,900"
addStylesheetRemote "https://fonts.googleapis.com/css?family=Source+Sans+Pro:300,400,600,800,900|Roboto:300,400,600"
addScript $ StaticR js_zepto_js
addScript $ StaticR js_fetchPolyfill_js
addScript $ StaticR js_urlPolyfill_js
addScript $ StaticR js_featureChecker_js
addScript $ StaticR js_flatpickr_js
addScript $ StaticR js_tabber_js
addStylesheet $ StaticR css_flatpickr_css
addStylesheet $ StaticR css_tabber_css
addStylesheet $ StaticR css_fonts_css
addStylesheet $ StaticR css_icons_css
addStylesheet $ StaticR css_fontawesome_css
$(widgetFile "default-layout")
$(widgetFile "standalone/modal")
$(widgetFile "standalone/showHide")
$(widgetFile "standalone/inputs")
$(widgetFile "standalone/tooltip")
$(widgetFile "standalone/tabber")
$(widgetFile "standalone/alerts")
$(widgetFile "standalone/datepicker")
withUrlRenderer $(hamletFile "templates/default-layout-wrapper.hamlet")
-- The page to be redirected to when authentication is required.
authRoute _ = Just $ AuthR LoginR
@ -510,97 +565,6 @@ instance Yesod UniWorX where
makeLogger = return . appLogger
{- ALL DEPRECATED and will be deleted, once knownTags is completed
isAuthorizedDB :: Route UniWorX -> Bool -> YesodDB UniWorX AuthResult
isAuthorizedDB route@(routeAttrs -> attrs) writeable
| "adminAny" `member` attrs = adminAccess Nothing
| "lecturerAny" `member` attrs = lecturerAccess Nothing
isAuthorizedDB UsersR _ = adminAccess Nothing
isAuthorizedDB (SubmissionDemoR cID) _ = return Authorized -- submissionAccess $ Right cID
isAuthorizedDB (SubmissionDownloadSingleR cID _) _ = submissionAccess $ Right cID
isAuthorizedDB (SubmissionDownloadArchiveR (ZIPArchiveName cID)) _ = submissionAccess $ Left cID
isAuthorizedDB TermEditR _ = adminAccess Nothing
isAuthorizedDB (TermEditExistR _) _ = adminAccess Nothing
isAuthorizedDB CourseNewR _ = lecturerAccess Nothing
isAuthorizedDB (CourseR t c CEditR) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c)
isAuthorizedDB (CourseR t c (SheetR SheetListR)) False = return Authorized --
isAuthorizedDB (CourseR t c (SheetR SheetListR)) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c)
isAuthorizedDB (CourseR t c (SheetR (SShowR s))) _ = return Authorized -- TODO: nur für angemeldete Kursteilnehmer falls sichtbar, sonst nur Lectrurer oder Korrektor
isAuthorizedDB (CourseR t c (SheetR (SheetFileR s _ _))) _ = return Authorized -- TODO: nur für angemeldete Kursteilnehmer falls sichtbar, sonst nur Lectrurer oder Korrektor
isAuthorizedDB (CourseR t c (SheetR SheetNewR)) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c)
isAuthorizedDB (CourseR t c (SheetR (SEditR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c)
isAuthorizedDB (CourseR t c (SheetR (SDelR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c)
isAuthorizedDB (CourseR t c (SheetR (SubmissionR s m))) _ = return Authorized -- TODO -- submissionAccess $ Right cID
isAuthorizedDB (CourseR t c (SheetR (SheetCorrectorsR s))) _ = courseLecturerAccess . entityKey =<< getBy404 (CourseTermShort t c)
isAuthorizedDB (CourseEditIDR cID) _ = do
courseId <- decrypt cID
courseLecturerAccess courseId
isAuthorizedDB _route _isWrite = return $ Unauthorized "No access to this route." -- Calling isAuthorized here creates infinite loop!
submissionAccess :: Either CryptoFileNameSubmission CryptoUUIDSubmission -> YesodDB UniWorX AuthResult
submissionAccess cID = do
authId <- lift requireAuthId
submissionId <- either decrypt decrypt cID
Submission{..} <- get404 submissionId
submissionUsers <- map (submissionUserUser . entityVal) <$> selectList [SubmissionUserSubmission ==. submissionId] []
let auth = authId `elem` submissionUsers || Just authId == submissionRatingBy
return $ case auth of
True -> Authorized
False -> Unauthorized "No access to this submission"
adminAccess :: Maybe SchoolId -- ^ If @Just@, matched exactly against 'userAdminSchool'
-> YesodDB UniWorX AuthResult
adminAccess school = do
authId <- lift requireAuthId
adrights <- selectList ((UserAdminUser ==. authId) : maybe [] (\s -> [UserAdminSchool ==. s]) school) []
return $ if (not $ null adrights)
then Authorized
else Unauthorized "No admin access" -- TODO internationalize
lecturerAccess :: Maybe SchoolId
-> YesodDB UniWorX AuthResult
lecturerAccess school = do
authId <- lift requireAuthId
lecrights <- selectList ((UserLecturerUser ==. authId) : maybe [] (\s -> [UserLecturerSchool ==. s]) school) []
return $ if (not $ null lecrights)
then Authorized
else Unauthorized "No lecturer access" -- TODO internationalize
lecturerAccess' :: SchoolId -> YesodDB UniWorX AuthResult
lecturerAccess' = authorizedFor UniqueSchoolLecturer MsgUnauthorizedSchoolLecturer
courseLecturerAccess :: CourseId -> YesodDB UniWorX AuthResult
courseLecturerAccess = authorizedFor UniqueLecturer MsgUnauthorizedLecturer
--courseCorrectorAccess :: CourseId -> YesodDB UniWorX AuthResult
--courseCorrectorAccess = authorizedFor UniqueCorrector MsgUnauthorizedCorrector
-- TODO: Correctors are no longer unit, could be ByTutorial and also by ByProportion
courseParticipantAccess :: CourseId -> YesodDB UniWorX AuthResult
courseParticipantAccess = authorizedFor UniqueParticipant MsgUnauthorizedParticipant
authorizedFor :: ( PersistEntityBackend record ~ BaseBackend backend
, PersistEntity record, PersistUniqueRead backend
, YesodAuth master, RenderMessage master msg
)
=> (AuthId master -> t -> Unique record) -> msg -> t -> ReaderT backend (HandlerT master IO) AuthResult
authorizedFor authType msg courseId = do
authId <- lift requireAuthId
access <- getBy $ authType authId courseId
case access of
(Just _) -> return Authorized
Nothing -> unauthorizedI msg
isAuthorizedDB' :: Route UniWorX -> Bool -> YesodDB UniWorX Bool
isAuthorizedDB' route isWrite = (== Authorized) <$> isAuthorizedDB route isWrite
isAuthorized' :: Route UniWorX -> Bool -> Handler Bool
isAuthorized' route isWrite = runDB $ isAuthorizedDB' route isWrite
-}
-- Define breadcrumbs.
instance YesodBreadcrumbs UniWorX where
breadcrumb TermShowR = return ("Semester", Just HomeR)
@ -611,7 +575,7 @@ instance YesodBreadcrumbs UniWorX where
breadcrumb (TermCourseListR term) = return (toPathPiece term, Just TermShowR)
breadcrumb (CourseR term course CShowR) = return (course, Just $ TermCourseListR term)
breadcrumb CourseNewR = return ("Neu", Just CourseListR)
breadcrumb (CourseR _ _ CEditR) = return ("Editieren", Just CourseListR)
breadcrumb (CourseR tid csh CEditR) = return ("Editieren", Just $ CourseR tid csh CShowR)
breadcrumb (CourseR tid csh SheetListR) = return ("Übungen",Just $ CourseR tid csh CShowR)
breadcrumb (CourseR tid csh SheetNewR ) = return ("Neu", Just $ CourseR tid csh SheetListR)
@ -624,29 +588,46 @@ instance YesodBreadcrumbs UniWorX where
breadcrumb SubmissionListR = return ("Abgaben", Just HomeR)
breadcrumb HomeR = return ("Uniworky", Nothing)
breadcrumb (AuthR _) = return ("Login", Just HomeR)
breadcrumb ProfileR = return ("Profile", Just HomeR)
breadcrumb HomeR = return ("UniWorkY", Nothing)
breadcrumb (AuthR _) = return ("Login", Just HomeR)
breadcrumb ProfileR = return ("Profile", Just HomeR)
breadcrumb ProfileDataR = return ("Data", Just ProfileR)
breadcrumb _ = return ("home", Nothing)
pageActions :: Route UniWorX -> [MenuTypes]
pageActions (CourseR tid csh CShowR) =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Übungsblätter"
, menuItemIcon = Nothing
, menuItemRoute = CourseR tid csh SheetListR
, menuItemAccessCallback' = return True
}
, PageActionPrime $ MenuItem
{ menuItemLabel = "Kurs Editieren"
, menuItemIcon = Nothing
, menuItemRoute = CourseR tid csh CEditR
, menuItemAccessCallback' = return True
}
, PageActionPrime $ MenuItem
{ menuItemLabel = "Übungsblätter"
, menuItemIcon = Nothing
, menuItemRoute = CourseR tid csh SheetListR
, menuItemAccessCallback' = do --TODO always show for lecturer
let sheetRouteAccess shn = (== Authorized) <$> (isAuthorized (CSheetR tid csh shn SShowR) False)
muid <- maybeAuthId
(sheets,lecturer) <- runDB $ do
cid <- getKeyBy404 $ CourseTermShort tid csh
sheets <- map (sheetName.entityVal) <$> selectList [SheetCourse ==. cid] [Desc SheetActiveFrom]
lecturer <- case muid of
Nothing -> return False
(Just uid) -> existsBy $ UniqueLecturer uid cid
return (sheets,lecturer)
or2M (return lecturer) $ anyM sheets sheetRouteAccess
}
, PageActionSecondary $ MenuItem
{ menuItemLabel = "Neues Übungsblatt anlegen"
, menuItemIcon = Nothing
, menuItemRoute = CourseR tid csh SheetNewR
, menuItemAccessCallback' = return True
}
]
pageActions (CourseR tid csh SheetListR) =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Neues Übungsblatt"
{ menuItemLabel = "Neues Übungsblatt anlegen"
, menuItemIcon = Nothing
, menuItemRoute = CourseR tid csh SheetNewR
, menuItemAccessCallback' = return True
@ -654,10 +635,16 @@ pageActions (CourseR tid csh SheetListR) =
]
pageActions (CSheetR tid csh shn SShowR) =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Abgabe"
{ menuItemLabel = "Abgabe anlegen"
, menuItemIcon = Nothing
, menuItemRoute = CSheetR tid csh shn (SubmissionR NewSubmission)
, menuItemAccessCallback' = return True
, menuItemRoute = CSheetR tid csh shn SubmissionNewR
, menuItemAccessCallback' = return True -- TODO: check that no submission already exists
}
, PageActionPrime $ MenuItem
{ menuItemLabel = "Abgabe ansehen"
, menuItemIcon = Nothing
, menuItemRoute = CSheetR tid csh shn SubmissionOwnR
, menuItemAccessCallback' = return True -- TODO: check that a submission already exists
}
, PageActionPrime $ MenuItem
{ menuItemLabel = "Korrektoren"
@ -668,7 +655,7 @@ pageActions (CSheetR tid csh shn SShowR) =
]
pageActions TermShowR =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Neues Semester"
{ menuItemLabel = "Neues Semester anlegen"
, menuItemIcon = Nothing
, menuItemRoute = TermEditR
, menuItemAccessCallback' = return True
@ -676,15 +663,67 @@ pageActions TermShowR =
]
pageActions (TermCourseListR _) =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Neuer Kurs"
{ menuItemLabel = "Neuen Kurs anlegen"
, menuItemIcon = Just "book"
, menuItemRoute = CourseNewR
, menuItemAccessCallback' = return True
}
]
pageActions (ProfileR) =
[ PageActionPrime $ MenuItem
{ menuItemLabel = "Gespeicherte Daten anzeigen"
, menuItemIcon = Just "book"
, menuItemRoute = ProfileDataR
, menuItemAccessCallback' = return True
}
]
pageActions (HomeR) =
[
-- NavbarAside $ MenuItem
-- { menuItemLabel = "Benutzer"
-- , menuItemIcon = Just "users"
-- , menuItemRoute = UsersR
-- , menuItemAccessCallback' = return True
-- }
-- ,
NavbarAside $ MenuItem
{ menuItemLabel = "AdminDemo"
, menuItemIcon = Nothing
, menuItemRoute = AdminTestR
, menuItemAccessCallback' = return True
}
]
pageActions _ = []
i18nHeading :: (MonadWidget m, RenderMessage site msg, HandlerSite m ~ site) => msg -> m ()
i18nHeading msg = liftWidgetT $ toWidget =<< getMessageRender <*> pure msg
pageHeading :: Route UniWorX -> Maybe Widget
pageHeading HomeR
= Just $ i18nHeading MsgHomeHeading
pageHeading (AdminTestR)
= Just $ [whamlet|Internal Code Demonstration Page|]
pageHeading ProfileR
= Just $ i18nHeading MsgProfileHeading
pageHeading ProfileDataR
= Just $ i18nHeading MsgProfileDataHeading
pageHeading TermShowR
= Just $ i18nHeading MsgTermsHeading
pageHeading TermEditR
= Just $ i18nHeading MsgTermEditHeading
pageHeading (TermCourseListR tid)
= Just . i18nHeading . MsgTermCourseListHeading $ unTermKey tid
pageHeading CourseNewR
= Just $ i18nHeading MsgCourseEditHeading
pageHeading (CourseR tid csh CShowR)
= Just $ do
Entity _ Course{..} <- handlerToWidget . runDB . getBy404 $ CourseTermShort tid csh
toWidget courseName
-- TODO: add headings for more single course- and single term-pages
pageHeading _
= Nothing
defaultLinks :: [MenuTypes]
defaultLinks = -- Define the menu items of the header.
[ NavbarRight $ MenuItem
@ -712,26 +751,20 @@ defaultLinks = -- Define the menu items of the header.
, menuItemAccessCallback' = isJust <$> maybeAuthPair
}
, NavbarAside $ MenuItem
{ menuItemLabel = "Aktuelle Veranstaltungen"
, menuItemIcon = Just "book"
{ menuItemLabel = "Kurse"
, menuItemIcon = Just "calendar-alt"
, menuItemRoute = CourseListR -- should be CourseListActiveR or similar in the future
, menuItemAccessCallback' = return True
}
, NavbarAside $ MenuItem
{ menuItemLabel = "Alte Veranstaltungen"
, menuItemIcon = Just "book"
, menuItemRoute = CourseListR -- should be CourseListInactiveR or similar in the future
, menuItemAccessCallback' = return True
}
, NavbarAside $ MenuItem
{ menuItemLabel = "Veranstaltungen"
, menuItemIcon = Just "book"
, menuItemRoute = CourseListR
{ menuItemLabel = "Semester"
, menuItemIcon = Just "graduation-cap"
, menuItemRoute = TermShowR
, menuItemAccessCallback' = return True
}
, NavbarAside $ MenuItem
{ menuItemLabel = "Benutzer"
, menuItemIcon = Just "user"
, menuItemIcon = Just "users"
, menuItemRoute = UsersR
, menuItemAccessCallback' = return True -- Creates a LOOP: (Authorized ==) <$> isAuthorized UsersR False
}
@ -779,6 +812,7 @@ instance YesodAuth UniWorX where
let
userMaxFavourites = 12 -- TODO: appDefaultFavourites appSettings
userTheme = Default -- TODO: appDefaultFavourites appSettings
newUser = User{..}
userUpdate = [ UserMatrikelnummer =. userMatrikelnummer
, UserDisplayName =. userDisplayName

71
src/Handler/Admin.hs Normal file
View File

@ -0,0 +1,71 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
module Handler.Admin where
import Import
import Handler.Utils
-- import Data.Time
-- import qualified Data.Text as T
-- import Data.Function ((&))
-- import Yesod.Form.Bootstrap3
import Web.PathPieces (showToPathPiece, readFromPathPiece)
-- import Colonnade hiding (fromMaybe)
-- import Yesod.Colonnade
-- import qualified Data.UUID.Cryptographic as UUID
-- BEGIN - Buttons needed only here
data CreateButton = CreateMath | CreateInf -- Dummy for Example
deriving (Enum, Eq, Ord, Bounded, Read, Show)
instance PathPiece CreateButton where -- for displaying the button only, not really for paths
toPathPiece = showToPathPiece
fromPathPiece = readFromPathPiece
instance Button CreateButton where
label CreateMath = [whamlet|Ma<i>thema</i>tik|]
label CreateInf = "Informatik"
cssClass CreateMath = BCInfo
cssClass CreateInf = BCPrimary
-- END Button needed here
getAdminTestR :: Handler Html -- Demo Page. Referenzimplementierungen sollte hier gezeigt werden!
getAdminTestR = do
(btnWdgt, btnEnctype) <- generateFormPost (buttonForm :: Form CreateButton)
defaultLayout $ do
-- setTitle "UniWorkY Admin Testpage"
$(widgetFile "adminTest")
postAdminTestR :: Handler Html
postAdminTestR = do
((btnResult,_), _) <- runFormPost $ buttonForm
case btnResult of
(FormSuccess CreateInf) -> setMessage "Informatik-Knopf gedrückt"
(FormSuccess CreateMath) -> addMessage "warning" "Knopf Mathematik erkannt"
_other -> return ()
getAdminTestR
getAdminUserR :: CryptoUUIDUser -> Handler Html
getAdminUserR uuid = do
uid <- decrypt uuid
User{..} <- runDB $ get404 uid
defaultLayout $
[whamlet|
<h1>TODO
<h2>Admin Page for User #{display userDisplayName}
|]

View File

@ -1,6 +1,7 @@
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
@ -15,9 +16,9 @@ import Handler.Utils
-- import Data.Time
import qualified Data.Text as T
import Data.Function ((&))
import Yesod.Form.Bootstrap3
-- import Yesod.Form.Bootstrap3
import Colonnade hiding (fromMaybe)
import Colonnade hiding (fromMaybe,bool)
import Yesod.Colonnade
import qualified Data.UUID.Cryptographic as UUID
@ -26,6 +27,13 @@ import qualified Data.UUID.Cryptographic as UUID
getCourseListR :: Handler TypedContent
getCourseListR = redirect TermShowR
getTermCurrentR :: Handler Html
getTermCurrentR = do
termIds <- runDB $ selectKeysList [TermActive ==. True] [] -- [Desc TermName] does not work, since database representation has wrong ordering
case fromNullable termIds of
Nothing -> notFound
(Just (maximum -> tid)) -> getTermCourseListR tid
getTermCourseListR :: TermId -> Handler Html
getTermCourseListR tidini = do
(term,courses) <- runDB $ (,)
@ -65,13 +73,13 @@ getTermCourseListR tidini = do
]
let coursesTable = encodeWidgetTable tableSortable colonnadeTerms courses
defaultLayout $ do
setTitle "Semesterkurse"
setTitleI . MsgTermCourseListTitle $ unTermKey tidini
$(widgetFile "courses")
getCShowR :: TermId -> Text -> Handler Html
getCShowR tid csh = do
mbAid <- maybeAuthId
(courseEnt,(schoolMB,participants,mbRegistered)) <- runDB $ do
(courseEnt,(schoolMB,participants,registered)) <- runDB $ do
courseEnt@(Entity cid course) <- getBy404 $ CourseTermShort tid csh
dependent <- (,,)
<$> get (courseSchool course) -- join
@ -83,60 +91,63 @@ getCShowR tid csh = do
return $ isJust regL)
return $ (courseEnt,dependent)
let course = entityVal courseEnt
(regWidget, regEnctype) <- generateFormPost $ identifyForm "registerBtn" $ registerButton $ mbRegistered
(regWidget, regEnctype) <- generateFormPost $ identifyForm "registerBtn" $ registerForm registered $ courseRegisterSecret course
registrationOpen <- (==Authorized) <$> isAuthorized (CourseR tid csh CRegisterR) True
defaultLayout $ do
setTitle $ [shamlet| #{toPathPiece tid} - #{csh}|]
$(widgetFile "course")
registerButton :: Bool -> Form ()
registerButton registered = renderAForm FormStandard $
pure () <* bootstrapSubmit regMsg
where
msg = if registered then "Abmelden" else "Anmelden"
regMsg = msg :: BootstrapSubmit Text
postCShowR :: TermId -> Text -> Handler Html
postCShowR tid csh = do
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 -> Text -> Handler Html
postCRegisterR tid csh = do
aid <- requireAuthId
(cid, registered) <- runDB $ do
(Entity cid _) <- getBy404 $ CourseTermShort tid csh
(cid, course, registered) <- runDB $ do
(Entity cid course) <- getBy404 $ CourseTermShort tid csh
registered <- isJust <$> (getBy $ UniqueParticipant aid cid)
return (cid, registered)
((regResult,_), _) <- runFormPost $ identifyForm "registerBtn" $ registerButton registered
return (cid, course, registered)
((regResult,_), _) <- runFormPost $ identifyForm "registerBtn" $ registerForm registered $ courseRegisterSecret course
case regResult of
(FormSuccess _)
(FormSuccess codeOk)
| registered -> do
runDB $ deleteBy $ UniqueParticipant aid cid
addMessage "info" "Sie wurden abgemeldet."
| otherwise -> do
| codeOk -> do
actTime <- liftIO $ getCurrentTime
regOk <- runDB $ insertUnique $ CourseParticipant cid aid actTime
when (isJust regOk) $ addMessage "success" "Erfolgreich angemeldet!"
| otherwise -> addMessage "danger" "Falsches Kennwort!"
(_other) -> return () -- TODO check this!
-- redirect or not?! I guess not, since we want GET now
getCShowR tid csh
redirect $ CourseR tid csh CShowR
getCourseNewR :: Handler Html
getCourseNewR = do
-- TODO: Defaults für Semester hier ermitteln und übergeben
courseEditHandler Nothing
courseEditHandler True Nothing
postCourseNewR :: Handler Html
postCourseNewR = courseEditHandler Nothing
postCourseNewR = courseEditHandler False Nothing
getCEditR :: TermId -> Text -> Handler Html
getCEditR tid csh = do
course <- runDB $ getBy $ CourseTermShort tid csh
courseEditHandler course
courseEditHandler True course
postCEditR :: TermId -> Text -> Handler Html
postCEditR = getCEditR
getCourseEditIDR :: CryptoUUIDCourse -> Handler Html
getCourseEditIDR cID = do
cIDKey <- getsYesod appCryptoIDKey
courseID <- UUID.decrypt cIDKey cID
courseEditHandler =<< runDB (getEntity courseID)
postCEditR tid csh = do
course <- runDB $ getBy $ CourseTermShort tid csh
courseEditHandler False course
courseDeleteHandler :: Handler Html -- not called anywhere yet
@ -150,8 +161,8 @@ courseDeleteHandler = undefined
redirect $ TermCourseListR $ cfTerm res
-}
courseEditHandler :: Maybe (Entity Course) -> Handler Html
courseEditHandler course = do
courseEditHandler :: Bool -> Maybe (Entity Course) -> Handler Html
courseEditHandler isGet course = do
aid <- requireAuthId -- TODO: Verify that Editor is owner of the Course to be Edited!!!
((result, formWidget), formEnctype) <- runFormPost $ newCourseForm $ courseToForm <$> course
case result of
@ -170,11 +181,10 @@ courseEditHandler course = do
, courseTerm = cfTerm res
, courseSchool = cfSchool res
, courseCapacity = cfCapacity res
, courseHasRegistration = cfHasReg res
, courseRegisterSecret = cfSecret res
, courseRegisterFrom = cfRegFrom res
, courseRegisterTo = cfRegTo res
, courseDeregisterUntil = Nothing -- TODO
, courseRegisterSecret = Nothing -- TODO
, courseMaterialFree = True -- TODO
}
case insertOkay of
@ -226,27 +236,26 @@ courseEditHandler course = do
, courseTerm = cfTerm res
, courseSchool = cfSchool res
, courseCapacity = cfCapacity res
, courseHasRegistration = cfHasReg res
, courseRegisterSecret = cfSecret res
, courseRegisterFrom = cfRegFrom res
, courseRegisterTo = cfRegTo res
, courseDeregisterUntil = Nothing -- TODO
, courseRegisterSecret = Nothing -- TODO
, courseMaterialFree = True -- TODO
}
)
insert_ $ CourseEdit aid now cid
-- if (isNothing updOkay)
-- then do
addMessageI "info" $ MsgCourseEditOk tident csh
addMessageI "success" $ MsgCourseEditOk tident csh
-- redirect $ TermCourseListR tid
-- else addMessageI "danger" $ MsgCourseEditDupShort tident csh
(FormFailure _) -> addMessageI "warning" MsgInvalidInput
(FormMissing) | isGet -> return ()
other -> addMessage "error" $ [shamlet| Error: #{show other}|]
let formTitle = "Kurs editieren/anlegen" :: Text
actionUrl <- fromMaybe CourseNewR <$> getCurrentRoute
defaultLayout $ do
setTitle [shamlet| #{formTitle} |]
setTitleI MsgCourseEditTitle
$(widgetFile "formPage")
@ -259,7 +268,7 @@ data CourseForm = CourseForm
, cfTerm :: TermId
, cfSchool :: SchoolId
, cfCapacity :: Maybe Int
, cfHasReg :: Bool
, cfSecret :: Maybe Text
, cfRegFrom :: Maybe UTCTime
, cfRegTo :: Maybe UTCTime
}
@ -278,7 +287,7 @@ courseToForm cEntity = CourseForm
, cfTerm = courseTerm course
, cfSchool = courseSchool course
, cfCapacity = courseCapacity course
, cfHasReg = courseHasRegistration course
, cfSecret = courseRegisterSecret course
, cfRegFrom = courseRegisterFrom course
, cfRegTo = courseRegisterTo course
}
@ -305,9 +314,15 @@ newCourseForm template = identForm FIDcourse $ \html -> do
<*> areq termActiveField (fsb "Semester") (cfTerm <$> template)
<*> areq schoolField (fsb "Institut") (cfSchool <$> template)
<*> aopt (natField "Kapazität") (fsb "Kapazität") (cfCapacity <$> template)
<*> areq checkBoxField (fsb "Anmeldung") (cfHasReg <$> template)
<*> aopt utcTimeField (fsb "Anmeldung von:") (cfRegFrom <$> template)
<*> aopt utcTimeField (fsb "Anmeldung bis:") (cfRegTo <$> template)
<*> aopt textField (fslpI MsgCourseSecret "beliebige Zeichenkette"
& setTooltip "Optional: Anmeldung zum Kurs benötigt ein Passwort")
(cfSecret <$> template)
<*> aopt utcTimeField (fslpI MsgRegisterFrom "(ohne Datum keine Anmeldung möglich)"
& setTooltip "Ohne Datum ist keine Anmeldung zu diesem Kurs möglich!")
(cfRegFrom <$> template)
<*> aopt utcTimeField (fslpI MsgRegisterTo "(ohne Datum unbegrenzte Anmeldung möglich)"
& setTooltip "Die Anmeldung darf ohne Begrenzung sein")
(cfRegTo <$> template)
<* submitButton
return $ case result of
FormSuccess courseResult
@ -316,10 +331,11 @@ newCourseForm template = identForm FIDcourse $ \html -> do
(FormFailure errorMsgs,
[whamlet|
<div class="alert alert-danger">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
<div class="alert__content">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
^{widget}
|]
)
@ -333,20 +349,12 @@ validateCourse :: CourseForm -> [Text]
validateCourse (CourseForm{..}) =
[ msg | (False, msg) <-
[
( cfRegFrom <= cfRegTo
( NTop cfRegFrom <= NTop cfRegTo
, "Ende des Anmeldezeitraums muss nach dem Anfang liegen"
)
,
-- No starting date is okay: effective immediately
-- ( cfHasReg <= (isNothing cfRegFrom)
-- , "Beginn der Anmeldung angeben oder Anmeldungen deaktivieren"
-- )
-- ,
( cfHasReg == (isJust cfRegTo)
, "Ende des Anmeldezeitraums angeben oder Anmeldungen deaktivieren"
)
,
( isJust cfRegFrom <= cfHasReg
, "Anmeldungen aktivieren oder Anmeldezeitraum löschen"
)
] ]

View File

@ -14,6 +14,7 @@
module Handler.CryptoIDDispatch
( getCryptoUUIDDispatchR
, getCryptoFileNameDispatchR
) where
import Import hiding (Proxy)
@ -26,6 +27,9 @@ import Yesod.Core.Types (HandlerContents(..), ErrorResponse(..))
import qualified Control.Monad.Catch as E (Handler(..))
import Data.CaseInsensitive (CI)
import qualified Data.CaseInsensitive as CI
class CryptoRoute ciphertext plaintext where
cryptoIDRoute :: p plaintext -> ciphertext -> Handler (Route UniWorX)
@ -33,13 +37,28 @@ class CryptoRoute ciphertext plaintext where
instance CryptoRoute UUID SubmissionId where
cryptoIDRoute _ (CryptoID -> cID) = do
(smid :: SubmissionId) <- decrypt cID
cID' <- encrypt smid
(tid,csh,shn) <- runDB $ do
shid <- submissionSheet <$> get404 smid
Sheet{..} <- get404 shid
Course{..} <- get404 sheetCourse
return (courseTerm, courseShorthand, sheetName)
return $ CSheetR tid csh shn $ SubmissionR $ SubmissionMode $ Just cID
return $ CSheetR tid csh shn $ SubmissionR cID'
instance CryptoRoute (CI FilePath) SubmissionId where
cryptoIDRoute _ (CryptoID -> cID) = do
(smid :: SubmissionId) <- decrypt cID
(tid,csh,shn) <- runDB $ do
shid <- submissionSheet <$> get404 smid
Sheet{..} <- get404 shid
Course{..} <- get404 sheetCourse
return (courseTerm, courseShorthand, sheetName)
return $ CSheetR tid csh shn $ SubmissionR cID
instance CryptoRoute UUID UserId where
cryptoIDRoute _ (CryptoID -> cID) = do
(_ :: UserId) <- decrypt cID
return $ AdminUserR cID
class Dispatch ciphertext (x :: [*]) where
dispatchID :: p x -> ciphertext -> Handler (Maybe (Route UniWorX))
@ -64,5 +83,12 @@ getCryptoUUIDDispatchR :: UUID -> Handler ()
getCryptoUUIDDispatchR uuid = dispatchID p uuid >>= maybe notFound (redirectWith found302)
where
p :: Proxy '[ SubmissionId
, UserId
]
p = Proxy
getCryptoFileNameDispatchR :: CI FilePath -> Handler ()
getCryptoFileNameDispatchR path = dispatchID p path >>= maybe notFound (redirectWith found302)
where
p :: Proxy '[ SubmissionId ]
p = Proxy

View File

@ -4,54 +4,171 @@
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE IncoherentInstances #-} -- why is this needed? Instance for "display deadline" ought to be clear
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PartialTypeSignatures #-}
module Handler.Home where
import Import
import Handler.Utils
-- import Data.Time
import qualified Data.Map as Map
import Data.Time
-- import qualified Data.Text as T
-- import Yesod.Form.Bootstrap3
import Web.PathPieces (showToPathPiece, readFromPathPiece)
-- import Web.PathPieces (showToPathPiece, readFromPathPiece)
-- import Colonnade
-- import Yesod.Colonnade
-- import Control.Lens
import Colonnade hiding (fromMaybe, singleton)
import Yesod.Colonnade
import qualified Database.Esqueleto as E
-- import qualified Data.UUID.Cryptographic as UUID
-- BEGIN - Buttons needed only here
data CreateButton = CreateMath | CreateInf -- Dummy for Example
deriving (Enum, Eq, Ord, Bounded, Read, Show)
instance PathPiece CreateButton where -- for displaying the button only, not really for paths
toPathPiece = showToPathPiece
fromPathPiece = readFromPathPiece
-- Some constants:
nrSheetDeadlines :: Int64
nrSheetDeadlines = 10
offSheetDeadlines :: NominalDiffTime
offSheetDeadlines = 15
--nrExamDeadlines = 10
--offExamDeadlines = 15
--nrCourseDeadlines = 10
--offCourseDeadlines = 15
instance Button CreateButton where
label CreateMath = [whamlet|Ma<i>thema</i>tik|]
label CreateInf = "Informatik"
cssClass CreateMath = BCInfo
cssClass CreateInf = BCPrimary
-- END Button needed here
getHomeR :: Handler Html
getHomeR = do
(btnWdgt, btnEnctype) <- generateFormPost (buttonForm :: Form CreateButton)
muid <- maybeAuthId
case muid of
Nothing -> homeAnonymous
Just uid -> homeUser uid
homeAnonymous :: Handler Html
homeAnonymous = do
cTime <- liftIO getCurrentTime
let fTime = addUTCTime (offSheetDeadlines * nominalDay) cTime
let tableData :: E.SqlExpr (Entity Course)
-> E.SqlQuery (E.SqlExpr (Entity Course))
tableData course = do
E.where_ $ (E.not_ $ E.isNothing $ course E.^. CourseRegisterFrom)
E.&&. (course E.^. CourseRegisterFrom E.<=. E.val (Just cTime))
E.&&. ((E.isNothing $ course E.^. CourseRegisterTo)
E.||. (course E.^. CourseRegisterTo E.>=. E.val (Just cTime)))
E.limit nrSheetDeadlines
E.orderBy [ E.asc $ course E.^. CourseRegisterTo
, E.desc $ course E.^. CourseShorthand
]
E.limit nrSheetDeadlines
return course
colonnade :: Colonnade Sortable (DBRow (Entity Course)) (Cell UniWorX)
colonnade = mconcat
[ -- dbRow
sortable (Just "course") (i18nCell MsgCourse) $ \DBRow{ dbrOutput=(Entity {entityVal = course}) } -> do
let tid = courseTerm course
csh = courseShorthand course
cell [whamlet|<a href=@{CourseR tid csh CShowR}>#{display csh}|]
, sortable (Just "deadline") (i18nCell MsgRegisterTo) $ \DBRow{ dbrOutput=(Entity {entityVal = course}) } ->
textCell $ display $ courseRegisterTo course
]
courseTable <- dbTable def $ DBTable
{ dbtSQLQuery = tableData
, dbtColonnade = colonnade
, dbtSorting = Map.fromList
[ ( "term"
, SortColumn $ \(course) -> course E.^. CourseTerm
)
, ( "course"
, SortColumn $ \(course) -> course E.^. CourseShorthand
)
-- TODO
]
, dbtFilter = mempty {- [ ( "term"
, FilterColumn $ \(course `E.InnerJoin` _ `E.InnerJoin` _ ) tids -> if
| Set.null tids -> E.val True :: E.SqlExpr (E.Value Bool)
| otherwise -> course E.^. CourseTerm `E.in_` E.valList (Set.toList tids)
)
] -}
, dbtAttrs = tableDefault
, dbtIdent = "upcomingdeadlines" :: Text
}
defaultLayout $ do
setTitle "Willkommen zum Uniworky Test!"
$(widgetFile "dsgvDisclaimer")
$(widgetFile "home")
homeUser :: Key User -> Handler Html
homeUser uid = do
cTime <- liftIO getCurrentTime
let fTime = addUTCTime (offSheetDeadlines * nominalDay) cTime
postHomeR :: Handler Html
postHomeR = do
((btnResult,_), _) <- runFormPost $ buttonForm
case btnResult of
(FormSuccess CreateInf) -> setMessage "Informatik-Knopf gedrückt"
(FormSuccess CreateMath) -> addMessage "warning" "Knopf Mathematik erkannt"
_other -> return ()
getHomeR
tableData :: E.InnerJoin (E.InnerJoin (E.SqlExpr (Entity CourseParticipant))
(E.SqlExpr (Entity Course )))
(E.SqlExpr (Entity Sheet ))
-> E.SqlQuery ( E.SqlExpr (E.Value (Key Term))
, E.SqlExpr (E.Value Text)
, E.SqlExpr (E.Value Text)
, E.SqlExpr (E.Value UTCTime))
tableData (participant `E.InnerJoin` course `E.InnerJoin` sheet) = do
E.on $ course E.^. CourseId E.==. sheet E.^. SheetCourse
E.on $ course E.^. CourseId E.==. participant E.^. CourseParticipantCourse
E.where_ $ participant E.^. CourseParticipantUser E.==. E.val uid
E.&&. sheet E.^. SheetActiveTo E.<=. E.val fTime
E.&&. sheet E.^. SheetActiveTo E.>=. E.val cTime
E.orderBy [ E.asc $ sheet E.^. SheetActiveTo
, E.desc $ sheet E.^. SheetName
, E.desc $ course E.^. CourseShorthand
]
E.limit nrSheetDeadlines
return
( course E.^. CourseTerm
, course E.^. CourseShorthand
, sheet E.^. SheetName
, sheet E.^. SheetActiveTo
)
colonnade :: Colonnade Sortable (DBRow (E.Value (Key Term), E.Value Text, E.Value Text, E.Value UTCTime)) (Cell UniWorX)
colonnade = mconcat
[ -- dbRow
sortable (Just "course") (i18nCell MsgCourse) $ \DBRow{ dbrOutput=(E.Value tid, E.Value csh, _, _) } ->
cell [whamlet|<a href=@{CourseR tid csh CShowR}>#{display csh}|]
, sortable (Just "sheet") (i18nCell MsgSheet) $ \DBRow{ dbrOutput=(E.Value tid, E.Value csh, E.Value shn, _) } ->
cell [whamlet|<a href=@{CSheetR tid csh shn SShowR}>#{display shn}|]
, sortable (Just "deadline") (i18nCell MsgDeadline) $ \DBRow{ dbrOutput=(_, _, _, E.Value deadline) } ->
textCell $ display deadline
, sortable (Just "done") (i18nCell MsgDone) $ \DBRow{ dbrOutput=(_, _, _, _) } ->
textCell $ "?"
]
sheetTable <- dbTable def $ DBTable
{ dbtSQLQuery = tableData
, dbtColonnade = colonnade
, dbtSorting = Map.fromList
[ ( "term"
, SortColumn $ \(_ `E.InnerJoin` course `E.InnerJoin` _ ) -> course E.^. CourseTerm
)
, ( "course"
, SortColumn $ \(_ `E.InnerJoin` course `E.InnerJoin` _ ) -> course E.^. CourseShorthand
)
-- TODO
]
, dbtFilter = mempty {- [ ( "term"
, FilterColumn $ \(course `E.InnerJoin` _ `E.InnerJoin` _ ) tids -> if
| Set.null tids -> E.val True :: E.SqlExpr (E.Value Bool)
| otherwise -> course E.^. CourseTerm `E.in_` E.valList (Set.toList tids)
)
] -}
, dbtAttrs = tableDefault
, dbtIdent = "upcomingdeadlines" :: Text
}
defaultLayout $ do
-- setTitle "Willkommen zum Uniworky Test!"
$(widgetFile "homeUser")
$(widgetFile "dsgvDisclaimer")

View File

@ -1,5 +1,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
@ -7,24 +9,121 @@ module Handler.Profile where
import Import
import Handler.Utils
-- import Colonnade hiding (fromMaybe, singleton)
-- import Yesod.Colonnade
import qualified Database.Esqueleto as E
import Database.Esqueleto ((^.))
data SettingsForm = SettingsForm
{ stgMaxFavourties :: Int
, stgTheme :: Theme
}
makeSettingForm :: Maybe SettingsForm -> Form SettingsForm
makeSettingForm template = identForm FIDsettings $ \html -> do
let themeList = [(display t,t) | t <- allThemes]
(result, widget) <- flip (renderAForm FormStandard) html $ SettingsForm
<$> areq (natFieldI $ MsgNatField "Favoriten") -- TODO: natFieldI not working here
(fslpI MsgFavoriten "Anzahl Favoriten") (stgMaxFavourties <$> template)
<*> areq (selectFieldList themeList)
(fslI MsgTheme ) (stgTheme <$> template)
<* submitButton
return (result, widget) -- no validation required here
getProfileR :: Handler Html
getProfileR = do
(uid, user) <- requireAuthPair
(admin_rights,lecturer_rights) <- runDB $ (,) <$>
(uid, User{..}) <- requireAuthPair
let settingsTemplate = Just $ SettingsForm
{ stgMaxFavourties = userMaxFavourites
, stgTheme = userTheme
}
((res,formWidget), formEnctype) <- runFormPost $ makeSettingForm settingsTemplate
case res of
(FormSuccess SettingsForm{..}) -> do
runDB $ do
update uid [ UserMaxFavourites =. stgMaxFavourties
, UserTheme =. stgTheme
]
when (stgMaxFavourties < userMaxFavourites) $ do
-- prune Favourites to user-defined size
oldFavs <- selectKeysList [ CourseFavouriteUser ==. uid]
[ Desc CourseFavouriteTime
, OffsetBy $ stgMaxFavourties
]
mapM_ delete oldFavs
addMessageI "info" $ MsgSettingsUpdate
redirect ProfileR -- TODO: them change does not happen without redirect
(FormFailure msgs) -> forM_ msgs $ (addMessage "warning") . toHtml
_ -> return ()
(admin_rights,lecturer_rights,lecture_owner,lecture_corrector,participant,studies) <- runDB $ (,,,,,) <$>
(E.select $ E.from $ \(adright `E.InnerJoin` school) -> do
E.where_ $ adright ^. UserAdminUser E.==. E.val uid
E.on $ adright ^. UserAdminSchool E.==. school ^. SchoolId
return (school ^. SchoolName)
return (school ^. SchoolShorthand)
)
<*>
<*>
(E.select $ E.from $ \(lecright `E.InnerJoin` school) -> do
E.where_ $ lecright ^. UserLecturerUser E.==. E.val uid
E.on $ lecright ^. UserLecturerSchool E.==. school ^. SchoolId
return (school ^. SchoolName)
)
defaultLayout $ do
setTitle . toHtml $ userIdent user <> "'s User page"
$(widgetFile "profile")
return (school ^. SchoolShorthand)
)
<*>
(E.select $ E.from $ \(lecturer `E.InnerJoin` course) -> do
E.where_ $ lecturer ^. LecturerUser E.==. E.val uid
E.on $ lecturer ^. LecturerCourse E.==. course ^. CourseId
return (course ^. CourseShorthand, course ^. CourseTerm)
)
<*>
(E.select $ E.from $ \(corrector `E.InnerJoin` course) -> do
E.where_ $ corrector ^. CorrectorUser E.==. E.val uid
E.on $ corrector ^. CorrectorCourse E.==. course ^. CourseId
return (course ^. CourseShorthand, course ^. CourseTerm)
)
<*>
(E.select $ E.from $ \(participant `E.InnerJoin` course) -> do
E.where_ $ participant ^. CourseParticipantUser E.==. E.val uid
E.on $ participant ^. CourseParticipantCourse E.==. course ^. CourseId
return (course ^. CourseShorthand, course ^. CourseTerm, participant ^. CourseParticipantRegistration)
)
<*>
(E.select $ E.from $ \(studydegree `E.InnerJoin` studyfeat `E.InnerJoin` studyterms) -> do
E.where_ $ studyfeat ^. StudyFeaturesUser E.==. E.val uid
E.on $ studyfeat ^. StudyFeaturesField E.==. studyterms ^. StudyTermsId
E.on $ studyfeat ^. StudyFeaturesDegree E.==. studydegree ^. StudyDegreeId
return (studydegree ^. StudyDegreeName
,studyterms ^. StudyTermsName
,studyfeat ^. StudyFeaturesType
,studyfeat ^. StudyFeaturesSemester)
)
let formText = Just MsgSettings
actionUrl = ProfileR
settingsForm = $(widgetFile "formPageI18n")
defaultLayout $ do
setTitle . toHtml $ userIdent <> "'s User page"
$(widgetFile "profile")
$(widgetFile "dsgvDisclaimer")
postProfileR :: Handler Html
postProfileR = do
-- TODO
getProfileR
getProfileDataR :: Handler Html
getProfileDataR = do
(uid, User{..}) <- requireAuthPair
-- mr <- getMessageRender
defaultLayout $ do
$(widgetFile "profileData")
$(widgetFile "dsgvDisclaimer")

View File

@ -10,10 +10,11 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeOperators #-}
module Handler.Sheet where
import Import
import Import
import System.FilePath (takeFileName)
import Handler.Utils
@ -22,7 +23,7 @@ import Handler.Utils.Zip
-- import Data.Time
import qualified Data.Text as T
-- import Data.Function ((&))
--
--
import Colonnade hiding (fromMaybe, singleton)
import Yesod.Colonnade
import Text.Blaze (text)
@ -44,6 +45,7 @@ import Network.Mime
import Data.Set (Set)
import qualified Data.Set as Set
import qualified Data.Map as Map
import Data.Map (Map, (!), (!?))
import qualified Data.Map as Map
@ -58,7 +60,7 @@ instance Eq (Unique Sheet) where
{-
* Implement Handlers
* Implement Breadcrumbs in Foundation
* Implement Breadcrumbs in Foundation
* Implement Access in Foundation
-}
@ -89,7 +91,7 @@ makeSheetForm msId template = identForm FIDsheet $ \html -> do
E.&&. sheetFile E.^. SheetFileType E.==. E.val fType
return (file E.^. FileId)
| otherwise = return Set.empty
(result, widget) <- flip (renderAForm FormStandard) html $ SheetForm
<$> areq textField (fsb "Name") (sfName <$> template)
<*> aopt htmlField (fsb "Hinweise für Teilnehmer") (sfDescription <$> template)
@ -104,6 +106,7 @@ makeSheetForm msId template = identForm FIDsheet $ \html -> do
<*> fileAFormOpt (fsb "Hinweis")
<*> aopt utcTimeField (fsb "Lösung ab") (sfSolutionFrom <$> template)
<*> fileAFormOpt (fsb "Lösung")
<*> formToAForm (correctorForm msId (maybe [] sfCorrectors template))
<* submitButton
return $ case result of
FormSuccess sheetResult
@ -112,10 +115,11 @@ makeSheetForm msId template = identForm FIDsheet $ \html -> do
(FormFailure errorMsgs,
[whamlet|
<div class="alert alert-danger">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
<div class="alert__content">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
^{widget}
|]
)
@ -157,16 +161,16 @@ getSheetList courseEnt = do
rated <- count $ (SubmissionRatingTime !=. Nothing):sheetsub
return (sid, sheet, (submissions, rated))
let colBase = mconcat
[ headed "Blatt" $ \(sid,sheet,_) -> linkButton (toWgt $ sheetName sheet) BCLink $ CSheetR tid csh (sheetName sheet) SShowR
[ headed "Blatt" $ \(sid,sheet,_) -> simpleLink (toWgt $ sheetName sheet) $ CSheetR tid csh (sheetName sheet) SShowR
, headed "Abgabe ab" $ toWgt . formatTimeGerWD . sheetActiveFrom . snd3
, headed "Abgabe bis" $ toWgt . formatTimeGerWD . sheetActiveTo . snd3
, headed "Bewertung" $ toWgt . show . sheetType . snd3
, headed "Abgabe lbis" $ toWgt . formatTimeGerWD . sheetActiveTo . snd3
, headed "Bewertung" $ toWgt . display . sheetType . snd3
]
let colAdmin = mconcat -- only show edit button for allowed course assistants
[ headed "Korrigiert" $ toWgt . snd . trd3
, headed "Eingereicht" $ toWgt . fst . trd3
, headed "" $ \s -> linkButton "Edit" BCLink $ CSheetR tid csh (sheetName $ snd3 s) SEditR
, headed "" $ \s -> linkButton "Delete" BCLink $ CSheetR tid csh (sheetName $ snd3 s) SDelR
, headed "" $ \s -> simpleLink "Edit" $ CSheetR tid csh (sheetName $ snd3 s) SEditR
, headed "" $ \s -> simpleLink "Delete" $ CSheetR tid csh (sheetName $ snd3 s) SDelR
]
showAdmin <- case sheets of
((_,firstSheet,_):_) -> do
@ -177,7 +181,7 @@ getSheetList courseEnt = do
then colBase `mappend` colAdmin
else colBase
defaultLayout $ do
setTitle $ toHtml $ T.append "Übungsblätter " csh
setTitle $ toHtml $ csh <> " Übungsblätter"
if null sheets
then [whamlet|Es wurden noch keine Übungsblätter angelegt.|]
else encodeWidgetTable tableDefault colSheets sheets
@ -212,16 +216,18 @@ getSShowR tid csh shn = do
-- return desired columns
return $ (file E.^. FileTitle, file E.^. FileModified, sheetFile E.^. SheetFileType)
let colonnadeFiles = mconcat
[ sortable (Just "type") "Typ" $ \(_,_, E.Value ftype) -> textCell $ toPathPiece ftype
[ sortable (Just "type") "Typ" $ \(_,_, E.Value ftype) -> cell $ [whamlet| _{ftype}|]
, sortable (Just "path") "Dateiname" $ anchorCell (\(E.Value fName,_,E.Value fType) -> CSheetR tid csh shn (SFileR fType fName))
(\(E.Value fName,_,_) -> str2widget fName)
, sortable (Just "time") "Modifikation" $ \(_,E.Value modified,_) -> stringCell $ formatTimeGerWDT modified
, sortable (Just "time") "Modifikation" $ \(_,E.Value modified,_) -> stringCell $ formatTimeGerWDT (modified :: UTCTime)
]
fileTable <- dbTable def $ DBTable
{ dbtSQLQuery = fileData
, dbtColonnade = colonnadeFiles
, dbtAttrs = tableDefault
, dbtFilter = Map.empty
, dbtIdent = "files" :: Text
-- TODO: Add column for and visibility date
, dbtSorting = [ ( "type"
, SortColumn $ \(sheet `E.InnerJoin` sheetFile `E.InnerJoin` file) -> sheetFile E.^. SheetFileType
)

View File

@ -61,7 +61,7 @@ makeSubmissionForm :: Maybe SubmissionId -> Bool -> SheetGroup -> [Text] -> Form
makeSubmissionForm msmid unpackZips grouping buddies = identForm FIDsubmission $ \html -> do
flip (renderAForm FormStandard) html $ (,)
<$> (bool (\f fs _ -> Just <$> areq f fs Nothing) aopt $ isJust msmid) (zipFileField unpackZips) (fsm $ bool MsgSubmissionFile MsgSubmissionArchive unpackZips) Nothing
<*> (catMaybes <$> sequenceA [bool aforced' aopt editableBuddies textField (fsm $ MsgSubmissionMember g) buddy
<*> (catMaybes <$> sequenceA [bool aforced' aopt editableBuddies textField (fslpI (MsgSubmissionMember g) "user@campus.lmu.de" ) buddy
| g <- [1..(max groupNr $ length buddies)] -- groupNr might have decreased meanwhile
| buddy <- map (Just . Just) buddies ++ repeat Nothing -- show current buddies
])
@ -74,10 +74,33 @@ makeSubmissionForm msmid unpackZips grouping buddies = identForm FIDsubmission $
aforced' f fs (Just (Just v)) = Just <$> aforced f fs v
aforced' _ _ _ = error "Cannot happen since groupNr==0 if grouping/=Arbitrary"
getSubmissionNewR, postSubmissionNewR :: TermId -> Text -> Text -> Handler Html
getSubmissionNewR = postSubmissionNewR
postSubmissionNewR tid csh shn = submissionHelper tid csh shn NewSubmission
getSubmissionR, postSubmissionR :: TermId -> Text -> Text -> SubmissionMode -> Handler Html
getSubmissionR, postSubmissionR :: TermId -> Text -> Text -> CryptoFileNameSubmission -> Handler Html
getSubmissionR = postSubmissionR
postSubmissionR tid csh shn (SubmissionMode mcid) = do
postSubmissionR tid csh shn cid = submissionHelper tid csh shn $ ExistingSubmission cid
getSubmissionOwnR :: TermId -> Text -> Text -> Handler Html
getSubmissionOwnR tid csh shn = do
authId <- requireAuthId
sid <- runDB $ do
shid <- fetchSheetId tid csh shn
submissions <- E.select . E.from $ \(submission `E.InnerJoin` submissionUser) -> do
E.on (submission E.^. SubmissionId E.==. submissionUser E.^. SubmissionUserSubmission)
E.where_ $ submissionUser E.^. SubmissionUserUser E.==. E.val authId
E.&&. submission E.^. SubmissionSheet E.==. E.val shid
return $ submission E.^. SubmissionId
case submissions of
((E.Value sid):_) -> return sid
[] -> notFound
cID <- encrypt sid
redirect . CourseR tid csh . SheetR shn $ SubmissionR cID
submissionHelper :: TermId -> Text -> Text -> SubmissionMode -> Handler Html
submissionHelper tid csh shn (SubmissionMode mcid) = do
uid <- requireAuthId
msmid <- traverse decrypt mcid
(Entity shid Sheet{..}, buddies, lastEdits) <- runDB $ do
@ -112,7 +135,7 @@ postSubmissionR tid csh shn (SubmissionMode mcid) = do
(E.Value smid:_) -> do
cID <- encrypt smid
addMessageI "info" $ MsgSubmissionAlreadyExists
redirect $ CSheetR tid csh shn $ SubmissionR $ SubmissionMode $ Just cID
redirect $ CSheetR tid csh shn $ SubmissionR cID
(Just smid) -> do
shid' <- submissionSheet <$> get404 smid
when (shid /= shid') $ invalidArgsI [MsgSubmissionWrongSheet]
@ -181,7 +204,7 @@ postSubmissionR tid csh shn (SubmissionMode mcid) = do
(Nothing, Just smid) -- no new files, existing submission partners updated
-> return smid
(Just files, _) -- new files
-> runConduit $ transPipe lift files .| Conduit.map Left .| sinkSubmission shid uid ((,False) <$> msmid)
-> runConduit $ transPipe lift files .| extractRatings .| sinkSubmission shid uid ((,False) <$> msmid)
_ -> error "Impossible, because of definition of `makeSubmissionForm`"
-- Determine members of pre-registered group
groupUids <- fmap (setFromList . map E.unValue) . E.select . E.from $ \(submissionGroupUser `E.InnerJoin` submissionGroup `E.InnerJoin` submissionGroupUser') -> do
@ -203,7 +226,7 @@ postSubmissionR tid csh shn (SubmissionMode mcid) = do
_other -> return Nothing
case mCID of
Just cID -> redirect $ CSheetR tid csh shn $ SubmissionR $ SubmissionMode $ Just cID
Just cID -> redirect $ CSheetR tid csh shn $ SubmissionR cID
Nothing -> return ()
mArCid <- fmap ZIPArchiveName <$> traverse encrypt msmid
@ -231,6 +254,7 @@ postSubmissionR tid csh shn (SubmissionMode mcid) = do
, SortColumn $ \(sf `E.InnerJoin` f) -> f E.^. FileModified
)
]
, dbtFilter = []
}
mFileTable <- traverse (dbTable def) . fmap smid2ArchiveTable $ (,) <$> msmid <*> mcid
@ -265,16 +289,15 @@ submissionFileQuery submissionID (sf `E.InnerJoin` f) = E.distinctOnOrderBy [E.a
E.orderBy [E.desc $ sf E.^. SubmissionFileIsUpdate] -- E.desc returns corrector updated data first
return f
getSubmissionDownloadSingleR :: CryptoUUIDSubmission -> FilePath -> Handler TypedContent
getSubmissionDownloadSingleR :: CryptoFileNameSubmission -> FilePath -> Handler TypedContent
getSubmissionDownloadSingleR cID path = do
submissionID <- decrypt cID
cID' <- encrypt submissionID
runDB $ do
isRating <- maybe False (== submissionID) <$> isRatingFile path
case isRating of
True -> do
file <- runMaybeT $ lift . ratingFile cID' =<< MaybeT (getRating submissionID)
file <- runMaybeT $ lift . ratingFile cID =<< MaybeT (getRating submissionID)
maybe notFound (return . toTypedContent . Text.decodeUtf8) $ fileContent =<< file
False -> do
results <- E.select . E.from $ \(sf `E.InnerJoin` f) -> E.distinctOnOrderBy [E.asc $ f E.^. FileTitle] $ do

View File

@ -31,10 +31,10 @@ getTermShowR = do
-- return term
--
let
termData :: E.SqlExpr (Entity Term) -> E.SqlQuery (E.SqlExpr (Entity Term), E.SqlExpr (E.Value Int64))
termData term = do
-- E.orderBy [E.desc $ term E.^. TermStart ]
let courseCount :: E.SqlExpr (E.Value Int)
courseCount = E.sub_select . E.from $ \course -> do
let courseCount = E.sub_select . E.from $ \course -> do
E.where_ $ term E.^. TermId E.==. course E.^. CourseTerm
return E.countRows
return (term, courseCount)
@ -58,11 +58,9 @@ getTermShowR = do
stringCell $ formatTimeGerWD termLectureEnd
, sortable Nothing "Aktiv" $ \(Entity _ Term{..},_) ->
textCell $ bool "" tickmark termActive
, sortable Nothing "Kursliste" $ \(Entity tid Term{..}, E.Value numCourses) ->
cell [whamlet|
<a href=@{TermCourseListR tid}>
#{show numCourses} Kurse
|]
, sortable Nothing "Kursliste" $ anchorCell
(\(Entity tid _, _) -> TermCourseListR tid)
(\(_, E.Value numCourses) -> [whamlet|_{MsgNumCourses numCourses}|])
, sortable (Just "start") "Semesteranfang" $ \(Entity _ Term{..},_) ->
stringCell $ formatTimeGerWD termStart
, sortable (Just "end") "Semesterende" $ \(Entity _ Term{..},_) ->
@ -86,6 +84,17 @@ getTermShowR = do
, SortColumn $ \term -> term E.^. TermLectureEnd
)
]
, dbtFilter = [ ( "active"
, FilterColumn $ \term -> (term E.^. TermActive :: E.SqlExpr (E.Value Bool))
)
, ( "course"
, FilterColumn $ \term csh -> case csh of -- FilterColumn-Lambdas are
[] -> E.val True :: E.SqlExpr (E.Value Bool)
cshs -> E.exists . E.from $ \course -> do
E.where_ $ course E.^. CourseTerm E.==. term E.^. TermId
E.&&. course E.^. CourseShorthand `E.in_` E.valList cshs
)
]
, dbtAttrs = tableDefault
, dbtIdent = "terms" :: Text
}
@ -123,21 +132,21 @@ termEditHandler term = do
redirect TermShowR
(FormMissing ) -> return ()
(FormFailure _) -> addMessageI "warning" MsgInvalidInput
let formTitle = "Semester editieren/anlegen" :: Text
let actionUrl = TermEditR
defaultLayout $ do
setTitle [shamlet| #{formTitle} |]
setTitleI MsgTermEditHeading
$(widgetFile "formPage")
newTermForm :: Maybe Term -> Form Term
newTermForm template html = do
renderMessage <- getMessageRender
(result, widget) <- flip (renderAForm FormStandard) html $ Term
<$> areq termNewField (bfs ("Semester" :: Text)) (termName <$> template)
<*> areq dayField (bfs ("Erster Tag" :: Text)) (termStart <$> template)
<*> areq dayField (bfs ("Letzer Tag" :: Text)) (termEnd <$> template)
<$> areq termNewField (fslpI MsgTerm (renderMessage MsgTermPlaceholder)) (termName <$> template)
<*> areq dayField (fsl ("Erster Tag" :: Text)) (termStart <$> template)
<*> areq dayField (fsl ("Letzer Tag" :: Text)) (termEnd <$> template)
<*> pure [] -- TODO: List of Day field required, must probably be done as its own form and then combined
<*> areq dayField (bfs ("Beginn Vorlesungen" :: Text)) (termLectureStart <$> template)
<*> areq dayField (bfs ("Ende Vorlesungen" :: Text)) (termLectureEnd <$> template)
<*> areq dayField (fsl "Beginn Vorlesungen") (termLectureStart <$> template)
<*> areq dayField (fsl ("Ende Vorlesungen" :: Text)) (termLectureEnd <$> template)
<*> areq checkBoxField (bfs ("Aktiv" :: Text)) (termActive <$> template)
<* submitButton
return $ case result of
@ -147,10 +156,11 @@ newTermForm template html = do
(FormFailure errorMsgs,
[whamlet|
<div class="alert alert-danger">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
<div class="alert__content">
<h4> Fehler:
<ul>
$forall errmsg <- errorMsgs
<li> #{errmsg}
^{widget}
|]
)

View File

@ -1,6 +1,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
@ -34,7 +35,10 @@ getUsersR = do
Nothing -> "???"
(Just school) -> schoolShorthand school
let colonnadeUsers = mconcat $
[ headed "User" $ text2widget.userDisplayName.entityVal.fst3
[ headed "User" $ \u -> do
cID <- encrypt $ entityKey $ fst3 u
let name = display $ userDisplayName $ entityVal $ fst3 u
[whamlet|<a href=@{AdminUserR cID}>#{name}|]
, headed "Admin for Schools" $ (\u -> text2widget $ intercalate ", " $ map (getSchoolname.userAdminSchool .entityVal) $ snd3 u)
, headed "Lecturer at Schools" $ (\u -> text2widget $ intercalate ", " $ map (getSchoolname.userLecturerSchool.entityVal) $ trd3 u)
]

View File

@ -43,8 +43,11 @@ formatTimeGerDTlong = formatTimeGer "%A, %e. %B %Y, %k:%M:%S"
formatTimeGerWDT :: FormatTime t => t -> String
formatTimeGerWDT = formatTimeGer $ dateTimeFmt germanTimeLocale
formatTimeGerDT :: FormatTime t => t -> String
formatTimeGerDT = formatTimeGer "%e.%m.%y %k:%M"
formatTimeGerDT :: FormatTime t => t -> String -- 0.00.00 0:00
formatTimeGerDT = formatTimeGer "%e.%m.%y %k:%M" -- leading spaces at start, otherwise 0 padding
formatTimeGerDT2 :: FormatTime t => t -> String -- 00.00.00 00:00
formatTimeGerDT2 = formatTimeGer "%d.%m.%y %H:%M" -- always padding with 0
formatTimeGerWD :: FormatTime t => t -> String
formatTimeGerWD = formatTimeGer "%a %e.%m.%y"

View File

@ -14,7 +14,7 @@
module Handler.Utils.Form where
import Handler.Utils.Form.Types
import Handler.Utils.Templates
import Handler.Utils.DateTime
@ -48,7 +48,7 @@ import Control.Monad.Writer.Class
-- Unique Form Identifiers to avoid accidents --
------------------------------------------------
data FormIdentifier = FIDcourse | FIDsheet | FIDsubmission | FIDcorrectors
data FormIdentifier = FIDcourse | FIDsheet | FIDsubmission | FIDsettings | FIDcorrectors
deriving (Enum, Eq, Ord, Bounded, Read, Show)
@ -100,8 +100,8 @@ instance PathPiece BtnDelete where -- for displaying the button only, not rea
fromPathPiece = readFromPathPiece
instance Button BtnDelete where
label BtnDelete = "Löschen"
label BtnAbort = "Abrechen"
label BtnDelete = [whamlet|_{MsgBtnDelete}|]
label BtnAbort = [whamlet|_{MsgBtnAbort}|]
cssClass BtnDelete = BCDanger
cssClass BtnAbort = BCDefault
@ -115,10 +115,26 @@ instance PathPiece SubmitButton where
fromPathPiece = readFromPathPiece
instance Button SubmitButton where
label BtnSubmit = "Submit"
label BtnSubmit = [whamlet|_{MsgBtnSubmit}|]
cssClass BtnSubmit = BCPrimary
data RegisterButton = BtnRegister | BtnDeregister
deriving (Enum, Eq, Ord, Bounded, Read, Show)
instance PathPiece RegisterButton where
toPathPiece = showToPathPiece
fromPathPiece = readFromPathPiece
instance Button RegisterButton where
label BtnRegister = [whamlet|_{MsgBtnRegister}|]
label BtnDeregister = [whamlet|_{MsgBtnDeregister}|]
cssClass BtnRegister = BCPrimary
cssClass BtnDeregister = BCDanger
-- -- Looks like a button, but is just a link (e.g. for create course, etc.)
-- data LinkButton = LinkButton (Route UniWorX)
-- deriving (Enum, Eq, Ord, Bounded, Read, Show)
@ -135,8 +151,10 @@ linkButton lbl cls url = [whamlet| <a href=@{url} .btn .#{bcc2txt cls} role=butt
-- |]
-- <input .btn .#{bcc2txt cls} type="submit" value=^{lbl}>
simpleLink :: Widget -> Route UniWorX -> Widget
simpleLink lbl url = [whamlet| <a href=@{url}>^{lbl} |]
buttonField :: Button a => a -> Field Handler a
buttonField :: Button a => a -> Field Handler a -- already validates that the correct button press was received (result only neccessary for combinedButtonField)
buttonField btn = Field {fieldParse, fieldView, fieldEnctype}
where
fieldEnctype = UrlEncoded
@ -224,6 +242,10 @@ buttonForm csrf = do
-- Fields --
------------
natFieldI :: (Monad m, Integral i, RenderMessage (HandlerSite m) msg, RenderMessage (HandlerSite m) FormMessage) => msg -> Field m i
natFieldI msg = checkBool (>= 0) msg intField
natField :: (Monad m, Integral i, RenderMessage (HandlerSite m) FormMessage) => Text -> Field m i
natField d = checkBool (>= 0) (T.append d " muss eine natürliche Zahl sein.") $ intField
@ -364,7 +386,7 @@ utcTimeField = Field
where
fieldTimeFormat :: String
--fieldTimeFormat = "%e.%m.%y %k:%M"
fieldTimeFormat = "%Y-%m-%eT%H:%M"
fieldTimeFormat = "%Y-%m-%dT%H:%M"
readTime :: Text -> Either FormMessage UTCTime
readTime t =
@ -376,12 +398,48 @@ utcTimeField = Field
showTime = fromString . (formatTime germanTimeLocale fieldTimeFormat)
fsm :: RenderMessage UniWorX msg => msg -> FieldSettings UniWorX
fsm :: RenderMessage UniWorX msg => msg -> FieldSettings UniWorX -- DEPRECATED
fsm = bfs -- TODO: get rid of Bootstrap
fsb :: Text -> FieldSettings site
fsb :: Text -> FieldSettings site -- DEPRECATED
fsb = bfs -- Just to avoid annoying Ambiguous Type Errors
fsl :: Text -> FieldSettings UniWorX
fsl lbl =
FieldSettings { fsLabel = (SomeMessage lbl)
, fsTooltip = Nothing
, fsId = Nothing
, fsName = Nothing
, fsAttrs = []
}
fslI :: RenderMessage UniWorX msg => msg -> FieldSettings UniWorX
fslI lbl =
FieldSettings { fsLabel = (SomeMessage lbl)
, fsTooltip = Nothing
, fsId = Nothing
, fsName = Nothing
, fsAttrs = []
}
fslp :: Text -> Text -> FieldSettings UniWorX
fslp lbl placeholder =
FieldSettings { fsLabel = (SomeMessage lbl)
, fsTooltip = Nothing
, fsId = Nothing
, fsName = Nothing
, fsAttrs = [("placeholder", placeholder)]
}
fslpI :: RenderMessage UniWorX msg => msg -> Text -> FieldSettings UniWorX
fslpI lbl placeholder =
FieldSettings { fsLabel = (SomeMessage lbl)
, fsTooltip = Nothing
, fsId = Nothing
, fsName = Nothing
, fsAttrs = [("placeholder", placeholder)]
}
addAttr :: Text -> Text -> FieldSettings site -> FieldSettings site
addAttr attr valu fs = fs { fsAttrs=newAttrs (fsAttrs fs) }
where
@ -425,7 +483,7 @@ setNameClass fs gName gClass = fs { fsName= Just gName, fsAttrs=("class",gClass)
setTooltip :: String -> FieldSettings site -> FieldSettings site
setTooltip tt fs
| null tt = fs { fsTooltip = Nothing }
| otherwise = fs { fsTooltip = Just $ fromString tt }
| otherwise = fs { fsTooltip = Just $ fromString tt, fsAttrs=("info",fromString tt):(fsAttrs fs) }
optionsPersistCryptoId :: forall site backend a msg.
( YesodPersist site

View File

@ -35,6 +35,9 @@ numberColonnade = headed "Nr" (fromString.show)
pairColonnade :: (Functor h) => Colonnade h a c -> Colonnade h b c -> Colonnade h (a,b) c
pairColonnade a b = mconcat [ lmap fst a, lmap snd b]
i18nCell :: RenderMessage site a => a -> Cell site
i18nCell msg = cell [whamlet|_{msg}|]
-- Table Modification
encodeHeadedWidgetTableNumbered :: Attribute -> Colonnade Headed a (WidgetT site IO ()) -> [a] -> WidgetT site IO ()

View File

@ -7,10 +7,15 @@
, LambdaCase
, ViewPatterns
, FlexibleContexts
, FlexibleInstances
, MultiParamTypeClasses
, TypeFamilies
#-}
module Handler.Utils.Table.Pagination
( SortColumn(..), SortDirection(..)
, FilterColumn(..), IsFilterColumn
, DBRow(..), DBOutput
, DBTable(..)
, PaginationSettings(..)
, PSValidator(..)
@ -22,7 +27,7 @@ import Handler.Utils.Table.Pagination.Types
import Import
import qualified Database.Esqueleto as E
import qualified Database.Esqueleto.Internal.Sql as E (SqlSelect)
import qualified Database.Esqueleto.Internal.Sql as E (SqlSelect,unsafeSqlValue)
import qualified Database.Esqueleto.Internal.Language as E (From)
import Text.Blaze (Attribute)
import qualified Text.Blaze.Html5.Attributes as Html5
@ -36,11 +41,14 @@ import qualified Network.Wai as Wai
import Data.CaseInsensitive (CI)
import qualified Data.CaseInsensitive as CI
import Control.Monad.RWS hiding ((<>), Foldable(..), mapM_)
import Control.Monad.RWS hiding ((<>), Foldable(..), mapM_, forM_)
import Data.Map (Map, (!))
import qualified Data.Map as Map
import Colonnade hiding (bool, fromMaybe)
import Data.Profunctor (lmap)
import Colonnade hiding (bool, fromMaybe, singleton)
import Colonnade.Encode
import Yesod.Colonnade
@ -64,22 +72,65 @@ instance PathPiece SortDirection where
sqlSortDirection :: t -> (SortColumn t, SortDirection) -> E.SqlExpr E.OrderBy
sqlSortDirection t (SortColumn e, SortAsc ) = E.asc $ e t
sqlSortDirection t (SortColumn e, SortDesc) = E.desc $ e t
data DBTable = forall a r h i t.
( ToSortable h
, E.SqlSelect a r
data FilterColumn t = forall a. IsFilterColumn t a => FilterColumn a
filterColumn :: FilterColumn t -> [Text] -> t -> E.SqlExpr (E.Value Bool)
filterColumn (FilterColumn f) = filterColumn' f
class IsFilterColumn t a where
filterColumn' :: a -> [Text] -> t -> E.SqlExpr (E.Value Bool)
instance IsFilterColumn t (E.SqlExpr (E.Value Bool)) where
filterColumn' fin _ _ = fin
instance IsFilterColumn t cont => IsFilterColumn t (t -> cont) where
filterColumn' cont is t = filterColumn' (cont t) is t
instance {-# OVERLAPPABLE #-} (PathPiece (Element l), IsFilterColumn t cont, MonoPointed l, Monoid l) => IsFilterColumn t (l -> cont) where
filterColumn' cont is t = filterColumn' (cont input) is' t
where
(input, ($ []) -> is') = go (mempty, id) is
go acc [] = acc
go (acc, is') (i:is)
| Just i' <- fromPathPiece i = go (acc `mappend` singleton i', is') is
| otherwise = go (acc, is' . (i:)) is
data DBRow r = DBRow
{ dbrIndex, dbrCount :: Int64
, dbrOutput :: r
}
class DBOutput r r' where
dbProj :: r -> r'
instance DBOutput r r where
dbProj = id
instance DBOutput (DBRow r) r where
dbProj = dbrOutput
instance DBOutput (DBRow r) (Int64, r) where
dbProj = (,) <$> dbrIndex <*> dbrOutput
data DBTable = forall a r r' h i t.
( ToSortable h, Functor h
, E.SqlSelect a r, DBOutput (DBRow r) r'
, PathPiece i
, E.From E.SqlQuery E.SqlExpr E.SqlBackend t
) => DBTable
{ dbtSQLQuery :: t -> E.SqlQuery a
, dbtColonnade :: Colonnade h r (Cell UniWorX)
, dbtColonnade :: Colonnade h r' (Cell UniWorX)
, dbtSorting :: Map Text (SortColumn t)
, dbtFilter :: Map Text (FilterColumn t)
, dbtAttrs :: Attribute
, dbtIdent :: i
}
data PaginationSettings = PaginationSettings
{ psSorting :: [(Text, SortDirection)]
, psFilter :: Map Text [Text]
, psLimit :: Int64
, psPage :: Int64
, psShortcircuit :: Bool
@ -88,15 +139,16 @@ data PaginationSettings = PaginationSettings
instance Default PaginationSettings where
def = PaginationSettings
{ psSorting = []
, psFilter = Map.empty
, psLimit = 50
, psPage = 0
, psShortcircuit = False
}
newtype PSValidator = PSValidator { runPSValidator :: Maybe PaginationSettings -> ([SomeMessage UniWorX], PaginationSettings) }
newtype PSValidator = PSValidator { runPSValidator :: DBTable -> Maybe PaginationSettings -> ([SomeMessage UniWorX], PaginationSettings) }
instance Default PSValidator where
def = PSValidator $ \case
def = PSValidator $ \DBTable{..} -> \case
Nothing -> def
Just ps -> swap . (\act -> execRWS act () ps) $ do
l <- gets psLimit
@ -106,7 +158,7 @@ instance Default PSValidator where
dbTable :: PSValidator -> DBTable -> Handler Widget
dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do
dbTable PSValidator{..} dbtable@(DBTable{ dbtIdent = (toPathPiece -> dbtIdent), dbtColonnade = (lmap dbProj -> dbtColonnade), .. }) = do
let
sortingOptions = mkOptionList
[ Option t' (t, d) t'
@ -114,39 +166,53 @@ dbTable PSValidator{..} DBTable{ dbtIdent = (toPathPiece -> dbtIdent), .. } = do
, d <- [SortAsc, SortDesc]
, let t' = t <> "-" <> toPathPiece d
]
(_, defPS) = runPSValidator Nothing
(_, defPS) = runPSValidator dbtable Nothing
wIdent n
| not $ null dbtIdent = dbtIdent <> "-" <> n
| otherwise = n
dbtAttrs'
| not $ null dbtIdent = Html5.id (fromString $ unpack dbtIdent) <> dbtAttrs
| otherwise = dbtAttrs
multiTextField = Field
{ fieldParse = \ts _ -> return . Right $ Just ts
, fieldView = undefined
, fieldEnctype = UrlEncoded
}
psResult <- runInputGetResult $ PaginationSettings
<$> (fromMaybe [] <$> iopt (multiSelectField $ return sortingOptions) (wIdent "sorting"))
<*> (Map.mapMaybe ((\args -> args <$ guard (not $ null args)) =<<) <$> Map.traverseWithKey (\k _ -> iopt multiTextField $ wIdent k) dbtFilter)
<*> (fromMaybe (psLimit defPS) <$> iopt intField (wIdent "pagesize"))
<*> (fromMaybe (psPage defPS) <$> iopt intField (wIdent "page"))
<*> ireq checkBoxField (wIdent "table-only")
$(logDebug) . tshow $ (,,,) <$> (length . psSorting <$> psResult)
<*> (psLimit <$> psResult)
<*> (psPage <$> psResult)
<*> (psShortcircuit <$> psResult)
$(logDebug) . tshow $ (,,,,) <$> (length . psSorting <$> psResult)
<*> (Map.keys . psFilter <$> psResult)
<*> (psLimit <$> psResult)
<*> (psPage <$> psResult)
<*> (psShortcircuit <$> psResult)
let
(errs, PaginationSettings{..}) = case psResult of
FormSuccess ps -> runPSValidator $ Just ps
FormFailure errs -> first (map SomeMessage errs <>) $ runPSValidator Nothing
FormMissing -> runPSValidator Nothing
FormSuccess ps -> runPSValidator dbtable $ Just ps
FormFailure errs -> first (map SomeMessage errs <>) $ runPSValidator dbtable Nothing
FormMissing -> runPSValidator dbtable Nothing
psSorting' = map (first (dbtSorting !)) psSorting
sqlQuery' = E.from $ \t -> dbtSQLQuery t
<* E.orderBy (map (sqlSortDirection t) psSorting')
<* E.limit psLimit
<* E.offset (psPage * psLimit)
<* Map.foldrWithKey (\key args expr -> E.where_ (filterColumn (dbtFilter ! key) args t) >> expr) (return ()) psFilter
mapM_ (addMessageI "warning") errs
(rows, [E.Value rowCount]) <- runDB $ (,) <$> E.select sqlQuery' <*> E.select (E.countRows <$ E.from dbtSQLQuery :: E.SqlQuery (E.SqlExpr (E.Value Int64)))
rows' <- runDB . E.select $ (,) <$> pure (E.unsafeSqlValue "row_number() OVER ()" :: E.SqlExpr (E.Value Int64), E.unsafeSqlValue "count(*) OVER ()" :: E.SqlExpr (E.Value Int64)) <*> sqlQuery'
let
rowCount
| ((_, E.Value n), _):_ <- rows' = n
| otherwise = 0
rows = map (\((E.Value i, E.Value n), r) -> DBRow i n r) rows'
bool return (sendResponse <=< tblLayout) psShortcircuit $ do
getParams <- handlerToWidget $ queryToQueryText . Wai.queryString . reqWaiRequest <$> getRequest

View File

@ -12,7 +12,7 @@ import Colonnade
import Colonnade.Encode
data Sortable a = Sortable
{ sortableKey :: (Maybe Text)
{ sortableKey :: Maybe Text
, sortableContent :: a
}
@ -23,6 +23,9 @@ instance Headedness Sortable where
headednessPure = Sortable Nothing
headednessExtract = Just $ \(Sortable _ x) -> x
headednessExtractForall = Just $ ExtractForall (\(Sortable _ x) -> x)
instance Functor Sortable where
fmap f Sortable{..} = Sortable { sortableContent = f sortableContent, .. }
newtype SortableP s = SortableP { toSortable :: forall a. s a -> Sortable a}

View File

@ -12,6 +12,8 @@ module Model.Types where
import ClassyPrelude
import Utils
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Fixed
import Database.Persist.TH
@ -23,7 +25,7 @@ import Web.HttpApiData
import Data.Text (Text)
import qualified Data.Text as Text
import Text.Read (readMaybe)
import Text.Read (readMaybe,readsPrec)
-- import Data.CaseInsensitive (CI)
import qualified Data.CaseInsensitive as CI
@ -41,6 +43,9 @@ type Points = Centi
toPoints :: Integral a => a -> Points
toPoints = MkFixed . fromIntegral
pToI :: Points -> Integer
pToI = fromPoints -- TODO: do we want to multiply?
fromPoints :: Integral a => Points -> a
fromPoints (MkFixed c) = fromInteger c
@ -50,6 +55,13 @@ data SheetType
| Pass { maxPoints, passingPoints :: Points }
| NotGraded
deriving (Show, Read, Eq)
instance DisplayAble SheetType where
display (Bonus {..}) = tshow (pToI maxPoints) <> " Bonuspunkte"
display (Normal{..}) = tshow (pToI maxPoints) <> " Punkte"
display (Pass {..}) = "Bestanden ab " <> tshow (pToI passingPoints) <> " von " <> tshow (pToI maxPoints)
display (NotGraded) = "Unbewertet"
deriveJSON defaultOptions ''SheetType
derivePersistFieldJSON "SheetType"
@ -73,6 +85,13 @@ instance PathPiece SheetFileType where
fromPathPiece t =
lookup (CI.mk t) [(CI.mk $ toPathPiece ty,ty) | ty <- [minBound..maxBound]]
-- $(deriveSimpleWith ''DisplayAble 'display (drop 17) ''SheetFileType)
instance DisplayAble SheetFileType where -- deprecated, see RenderMessage instance in Foundation
display SheetExercise = "Aufgabenstellung"
display SheetHint = "Hinweise"
display SheetSolution = "Musterlösung"
display SheetMarking = "Korrekturhinweise"
data ExamStatus = Attended | NoShow | Voided
deriving (Show, Read, Eq, Ord, Enum, Bounded)
derivePersistField "ExamStatus"
@ -128,6 +147,9 @@ data TermIdentifier = TermIdentifier
-- from_TermId_to_TermIdentifier = unTermKey
-- from_TermIdentifier_to_TermId = TermKey
instance DisplayAble TermIdentifier where
display = termToText
--TODO: Enforce the number of digits within year, with parsing filling in the current leading digits? Goal: short urls
termToText :: TermIdentifier -> Text
termToText TermIdentifier{..} = Text.pack $ seasonToChar season : show year
@ -183,4 +205,29 @@ data StudyFieldType = FieldPrimary | FieldSecondary
derivePersistField "StudyFieldType"
-- Skins / Themes
data Theme --Simply add Themes to this type only. CamelCase will be converted to "-lower"
= Default
| NeutralBlue
| AberdeenReds
| MintGreen
| SkyLove
deriving (Eq,Ord,Bounded,Enum)
$(deriveShowWith uncamel ''Theme) -- show for internal use in css/js
$(deriveSimpleWith ''DisplayAble 'display camelSpace ''Theme) -- display to display at user
allThemes :: [Theme]
allThemes = [minBound..maxBound]
readTheme :: Map String Theme
readTheme = Map.fromList [ (show t,t) | t <- allThemes ]
instance Read Theme where -- generic Read-Instance for Show/Bounded
readsPrec _ s
| (Just t) <- (Map.lookup s readTheme) = [(t,"")]
| otherwise = [(Default,"")] -- read shall always succeed
derivePersistField "Theme"

View File

@ -71,6 +71,8 @@ data AppSettings = AppSettings
, appAuthDummyLogin :: Bool
-- ^ Indicate if auth dummy login should be enabled.
, appAllowDeprecated :: Bool
-- ^ Indicate if deprecated routes are accessible for everyone
}
instance FromJSON AppSettings where
@ -104,6 +106,7 @@ instance FromJSON AppSettings where
appCryptoIDKeyFile <- o .: "cryptoid-keyfile"
appAuthDummyLogin <- o .:? "auth-dummy-login" .!= defaultDev
appAllowDeprecated <- o .:? "allow-deprecated" .!= defaultDev
return AppSettings {..}

View File

@ -2,6 +2,7 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeSynonymInstances, FlexibleInstances, UndecidableInstances #-}
{-# LANGUAGE TypeFamilies, FlexibleContexts, ConstraintKinds #-}
{-# LANGUAGE QuasiQuotes #-}
@ -11,6 +12,10 @@ module Utils
import ClassyPrelude.Yesod
import Data.List (foldl)
import Data.Foldable as Fold
import qualified Data.Char as Char
import Utils.DB as Utils
import Utils.Common as Utils
@ -25,6 +30,8 @@ import Control.Monad.Trans.Maybe (MaybeT(..))
import Control.Monad.Catch
import qualified Database.Esqueleto as E (Value, unValue)
-----------
-- Yesod --
-----------
@ -65,10 +72,70 @@ withFragment :: ( Monad m
withFragment form html = (flip fmap) form $ \(x, widget) -> (x, toWidget html >> widget)
uncamel :: String -> String -- "Model.Theme.CamelCaseThing" -> "camel-case-thing"
uncamel = ("theme-" ++) . reverse . foldl helper []
where
helper _ '.' = []
helper acc c
| Char.isSpace c = acc
| Char.isUpper c = Char.toLower c : '-' : acc
| otherwise = c : acc
camelSpace :: String -> String -- "Model.Theme.CamelCaseThing" -> "Camel Case Thing"
camelSpace = reverse . foldl helper []
where
helper _ '.' = []
helper acc c
| Char.isSpace c = acc
| Char.isUpper c = c : ' ' : acc
| otherwise = c : acc
-- Convert anything to Text, and I don't care how
class DisplayAble a where
display :: a -> Text
instance DisplayAble Text where
display = id
instance DisplayAble String where
display = pack
instance DisplayAble a => DisplayAble (Maybe a) where
display Nothing = ""
display (Just x) = display x
instance DisplayAble a => DisplayAble (E.Value a) where
display = display . E.unValue
-- The easy way out of UndecidableInstances (TypeFamilies would have been proper, but are much more complicated)
instance {-# OVERLAPPABLE #-} Show a => DisplayAble a where
display = pack . show
------------
-- Tuples --
------------
fst3 :: (a,b,c) -> a
fst3 (x,_,_) = x
snd3 :: (a,b,c) -> b
snd3 (_,y,_) = y
trd3 :: (a,b,c) -> c
trd3 (_,_,z) = z
-- Further projections are available via TemplateHaskell, defined in Utils.Common:
-- $(projN n m) :: (t1,..,tn) -> tm (for m<=n)
-- snd3 = $(projNI 3 2)
-----------
-- Lists --
-----------
-- notNull = not . null
----------
-- Maps --
----------
@ -85,7 +152,22 @@ maybeT :: Monad m => m a -> MaybeT m a -> m a
maybeT x m = runMaybeT m >>= maybe x return
catchIfMaybeT :: (MonadCatch m, Exception e) => (e -> Bool) -> m a -> MaybeT m a
catchIfMaybeT pred act = catchIf pred (lift act) (const mzero)
catchIfMaybeT p act = catchIf p (lift act) (const mzero)
mcons :: Maybe a -> [a] -> [a]
mcons Nothing xs = xs
mcons (Just x) xs = x:xs
newtype NTop a = NTop a -- treat Nothing as Top for Ord (Maybe a); default implementation treats Nothing as bottom
instance Eq a => Eq (NTop (Maybe a)) where
(NTop x) == (NTop y) = x == y
instance Ord a => Ord (NTop (Maybe a)) where
compare (NTop Nothing) (NTop Nothing) = EQ
compare (NTop Nothing) _ = GT
compare _ (NTop Nothing) = LT
compare (NTop (Just x)) (NTop (Just y)) = compare x y
---------------
-- Exception --
@ -97,17 +179,23 @@ maybeExceptT err act = lift act >>= maybe (throwE err) return
maybeMExceptT :: Monad m => (m e) -> m (Maybe b) -> ExceptT e m b
maybeMExceptT err act = lift act >>= maybe (lift err >>= throwE) return
guardExceptT :: Monad m => e -> Bool -> ExceptT e m ()
guardExceptT err b = unless b $ throwE err
whenExceptT :: Monad m => Bool -> e -> ExceptT e m ()
whenExceptT b err = when b $ throwE err
guardMExceptT :: Monad m => (m e) -> Bool -> ExceptT e m ()
guardMExceptT err b = unless b $ lift err >>= throwE
whenMExceptT :: Monad m => Bool -> (m e) -> ExceptT e m ()
whenMExceptT b err = when b $ lift err >>= throwE
guardExceptT :: Monad m => Bool -> e -> ExceptT e m ()
guardExceptT b err = unless b $ throwE err
guardMExceptT :: Monad m => Bool -> (m e) -> ExceptT e m ()
guardMExceptT b err = unless b $ lift err >>= throwE
exceptT :: Monad m => (e -> m b) -> (a -> m b) -> ExceptT e m a -> m b
exceptT f g = either f g <=< runExceptT
catchIfMExceptT :: (MonadCatch m, Exception e) => (e -> m e') -> (e -> Bool) -> m a -> ExceptT e' m a
catchIfMExceptT err pred act = catchIf pred (lift act) (throwE <=< lift . err)
catchIfMExceptT err p act = catchIf p (lift act) (throwE <=< lift . err)
------------
@ -120,3 +208,38 @@ shortCircuitM sc mx my op = do
case sc x of
True -> return x
False -> op <$> pure x <*> my
guardM :: MonadPlus m => m Bool -> m ()
guardM f = guard =<< f
-- Some Utility Functions from Agda.Utils.Monad
-- | Monadic if-then-else.
ifM :: Monad m => m Bool -> m a -> m a -> m a
ifM c m m' =
do b <- c
if b then m else m'
-- | @ifNotM mc = ifM (not <$> mc)@
ifNotM :: Monad m => m Bool -> m a -> m a -> m a
ifNotM c = flip $ ifM c
-- | Lazy monadic conjunction.
and2M :: Monad m => m Bool -> m Bool -> m Bool
and2M ma mb = ifM ma mb (return False)
andM :: (Foldable f, Monad m) => f (m Bool) -> m Bool
andM = Fold.foldr and2M (return True)
allM :: (Functor f, Foldable f, Monad m) => f a -> (a -> m Bool) -> m Bool
allM xs f = andM $ fmap f xs
-- | Lazy monadic disjunction.
or2M :: Monad m => m Bool -> m Bool -> m Bool
or2M ma mb = ifM ma (return True) mb
orM :: (Foldable f, Monad m) => f (m Bool) -> m Bool
orM = Fold.foldr or2M (return False)
anyM :: (Functor f, Foldable f, Monad m) => f a -> (a -> m Bool) -> m Bool
anyM xs f = orM $ fmap f xs

View File

@ -2,24 +2,20 @@
{-# LANGUAGE QuasiQuotes #-}
module Utils.Common where
-- Common Utility Functions
-- Common Utility Functions that require TemplateHaskell
-- import Data.Char
import Language.Haskell.TH
import Control.Monad
import Control.Monad.Trans.Class
import Control.Monad.Trans.Maybe
import Control.Monad.Trans.Except
-- import Control.Monad
-- import Control.Monad.Trans.Class
-- import Control.Monad.Trans.Maybe
-- import Control.Monad.Trans.Except
------------
-- Tuples --
------------
fst3 :: (a,b,c) -> a
fst3 (x,_,_) = x
snd3 :: (a,b,c) -> b
snd3 (_,y,_) = y
trd3 :: (a,b,c) -> c
trd3 (_,_,z) = z
projNI :: Int -> Int -> ExpQ -- generic projection gives I-th element of N-tuple, i.e. snd3 = $(projNI 3 2) --ghci -fth
-- $(projN n m) :: (t1,..,tn) -> tm (for m<=n)
@ -54,3 +50,30 @@ altFun perm = lamE pat rhs
fn = mkName "fn"
-- Special Show-Instances for Themes
deriveShowWith :: (String -> String) -> Name -> Q [Dec]
deriveShowWith = deriveSimpleWith ''Show 'show
-- deriveDisplayWith :: (String -> String) -> Name -> Q [Dec]
-- deriveDisplayWith = deriveSimpleWith ''DisplayAble 'display
deriveSimpleWith :: Name -> Name -> (String -> String) -> Name -> Q [Dec]
deriveSimpleWith cls fun strOp ty = do
(TyConI tyCon) <- reify ty
(tyConName, cs) <- case tyCon of
DataD [] nm [] _ cs _ -> return (nm, cs)
_ -> fail "deriveShowTheme: tyCon must be a plain datatype enumeration"
let instanceT = conT cls `appT` conT tyConName
return <$> instanceD (return []) instanceT [genDecs cs]
where
genDecs :: [Con] -> Q Dec
genDecs cs = funD fun (map genClause cs)
genClause :: Con -> Q Clause
genClause (NormalC name []) =
let pats = [ConP name []]
body = NormalB $ LitE $ StringL $ strOp $ show $ name
in return $ Clause pats body []
genClause _ = fail "deriveShowTheme: constructors not allowed to have arguments"

View File

@ -11,10 +11,8 @@ import qualified Data.List as List
import Data.Map (Map)
import qualified Data.Map as Map
import Database.Persist
-- import Database.Persist -- currently not needed here
-- getKeyBy :: PersistEntity val => Unique val -> ReaderT backend0 m0 (Maybe (Entity val))
-- getKeyBy :: Unique a -> YesodDB site (Key a)
entities2map :: PersistEntity record => [Entity record] -> Map (Key record) record
entities2map = foldl' (\m entity -> Map.insert (entityKey entity) (entityVal entity) m) Map.empty
@ -27,6 +25,10 @@ getKeyBy404 :: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity
=> Unique record -> ReaderT backend m (Key record)
getKeyBy404 = (fmap entityKey) . getBy404 -- TODO optimize this, so that DB does not deliver entire record!
existsBy :: (PersistEntityBackend record ~ BaseBackend backend, PersistEntity record, PersistUniqueRead backend, MonadIO m)
=> Unique record -> ReaderT backend m Bool
existsBy = fmap isJust . getBy
myReplaceUnique
:: (MonadIO m

View File

@ -4,5 +4,6 @@ unset HOST
export DETAILED_LOGGING=true
export LOG_ALL=true
export DUMMY_LOGIN=true
export ALLOW_DEPRECATED=true
exec -- stack exec -- yesod devel

740
static/css/flatpickr.css Normal file
View File

@ -0,0 +1,740 @@
.flatpickr-calendar {
background: transparent;
opacity: 0;
display: none;
text-align: center;
visibility: hidden;
padding: 0;
-webkit-animation: none;
animation: none;
direction: ltr;
border: 0;
font-size: 14px;
line-height: 24px;
border-radius: 5px;
position: absolute;
width: 307.875px;
-webkit-box-sizing: border-box;
box-sizing: border-box;
-ms-touch-action: manipulation;
touch-action: manipulation;
background: #fff;
-webkit-box-shadow: 1px 0 0 #e6e6e6, -1px 0 0 #e6e6e6, 0 1px 0 #e6e6e6, 0 -1px 0 #e6e6e6, 0 3px 13px rgba(0,0,0,0.08);
box-shadow: 1px 0 0 #e6e6e6, -1px 0 0 #e6e6e6, 0 1px 0 #e6e6e6, 0 -1px 0 #e6e6e6, 0 3px 13px rgba(0,0,0,0.08);
}
.flatpickr-calendar.open,
.flatpickr-calendar.inline {
opacity: 1;
max-height: 640px;
visibility: visible;
}
.flatpickr-calendar.open {
display: inline-block;
z-index: 99999;
}
.flatpickr-calendar.animate.open {
-webkit-animation: fpFadeInDown 300ms cubic-bezier(0.23, 1, 0.32, 1);
animation: fpFadeInDown 300ms cubic-bezier(0.23, 1, 0.32, 1);
}
.flatpickr-calendar.inline {
display: block;
position: relative;
top: 2px;
}
.flatpickr-calendar.static {
position: absolute;
top: calc(100% + 2px);
}
.flatpickr-calendar.static.open {
z-index: 999;
display: block;
}
.flatpickr-calendar.multiMonth .flatpickr-days .dayContainer:nth-child(n+1) .flatpickr-day.inRange:nth-child(7n+7) {
-webkit-box-shadow: none !important;
box-shadow: none !important;
}
.flatpickr-calendar.multiMonth .flatpickr-days .dayContainer:nth-child(n+2) .flatpickr-day.inRange:nth-child(7n+1) {
-webkit-box-shadow: -2px 0 0 #e6e6e6, 5px 0 0 #e6e6e6;
box-shadow: -2px 0 0 #e6e6e6, 5px 0 0 #e6e6e6;
}
.flatpickr-calendar .hasWeeks .dayContainer,
.flatpickr-calendar .hasTime .dayContainer {
border-bottom: 0;
border-bottom-right-radius: 0;
border-bottom-left-radius: 0;
}
.flatpickr-calendar .hasWeeks .dayContainer {
border-left: 0;
}
.flatpickr-calendar.showTimeInput.hasTime .flatpickr-time {
height: 40px;
border-top: 1px solid #e6e6e6;
}
.flatpickr-calendar.noCalendar.hasTime .flatpickr-time {
height: auto;
}
.flatpickr-calendar:before,
.flatpickr-calendar:after {
position: absolute;
display: block;
pointer-events: none;
border: solid transparent;
content: '';
height: 0;
width: 0;
left: 22px;
}
.flatpickr-calendar.rightMost:before,
.flatpickr-calendar.rightMost:after {
left: auto;
right: 22px;
}
.flatpickr-calendar:before {
border-width: 5px;
margin: 0 -5px;
}
.flatpickr-calendar:after {
border-width: 4px;
margin: 0 -4px;
}
.flatpickr-calendar.arrowTop:before,
.flatpickr-calendar.arrowTop:after {
bottom: 100%;
}
.flatpickr-calendar.arrowTop:before {
border-bottom-color: #e6e6e6;
}
.flatpickr-calendar.arrowTop:after {
border-bottom-color: #fff;
}
.flatpickr-calendar.arrowBottom:before,
.flatpickr-calendar.arrowBottom:after {
top: 100%;
}
.flatpickr-calendar.arrowBottom:before {
border-top-color: #e6e6e6;
}
.flatpickr-calendar.arrowBottom:after {
border-top-color: #fff;
}
.flatpickr-calendar:focus {
outline: 0;
}
.flatpickr-wrapper {
position: relative;
display: inline-block;
}
.flatpickr-months {
display: -webkit-box;
display: -webkit-flex;
display: -ms-flexbox;
display: flex;
}
.flatpickr-months .flatpickr-month {
background: transparent;
color: rgba(0,0,0,0.9);
fill: rgba(0,0,0,0.9);
height: 28px;
line-height: 1;
text-align: center;
position: relative;
-webkit-user-select: none;
-moz-user-select: none;
-ms-user-select: none;
user-select: none;
overflow: hidden;
-webkit-box-flex: 1;
-webkit-flex: 1;
-ms-flex: 1;
flex: 1;
}
.flatpickr-months .flatpickr-prev-month,
.flatpickr-months .flatpickr-next-month {
text-decoration: none;
cursor: pointer;
position: absolute;
top: 0px;
line-height: 16px;
height: 28px;
padding: 10px;
z-index: 3;
}
.flatpickr-months .flatpickr-prev-month.disabled,
.flatpickr-months .flatpickr-next-month.disabled {
display: none;
}
.flatpickr-months .flatpickr-prev-month i,
.flatpickr-months .flatpickr-next-month i {
position: relative;
}
.flatpickr-months .flatpickr-prev-month.flatpickr-prev-month,
.flatpickr-months .flatpickr-next-month.flatpickr-prev-month {
/*
/*rtl:begin:ignore*/
/*
*/
left: 0;
/*
/*rtl:end:ignore*/
/*
*/
}
/*
/*rtl:begin:ignore*/
/*
/*rtl:end:ignore*/
.flatpickr-months .flatpickr-prev-month.flatpickr-next-month,
.flatpickr-months .flatpickr-next-month.flatpickr-next-month {
/*
/*rtl:begin:ignore*/
/*
*/
right: 0;
/*
/*rtl:end:ignore*/
/*
*/
}
/*
/*rtl:begin:ignore*/
/*
/*rtl:end:ignore*/
.flatpickr-months .flatpickr-prev-month:hover,
.flatpickr-months .flatpickr-next-month:hover {
color: #959ea9;
}
.flatpickr-months .flatpickr-prev-month:hover svg,
.flatpickr-months .flatpickr-next-month:hover svg {
fill: #f64747;
}
.flatpickr-months .flatpickr-prev-month svg,
.flatpickr-months .flatpickr-next-month svg {
width: 14px;
height: 14px;
}
.flatpickr-months .flatpickr-prev-month svg path,
.flatpickr-months .flatpickr-next-month svg path {
-webkit-transition: fill 0.1s;
transition: fill 0.1s;
fill: inherit;
}
.numInputWrapper {
position: relative;
height: auto;
}
.numInputWrapper input,
.numInputWrapper span {
display: inline-block;
}
.numInputWrapper input {
width: 100%;
min-width: auto !important;
}
.numInputWrapper input::-ms-clear {
display: none;
}
.numInputWrapper span {
position: absolute;
right: 0;
width: 14px;
padding: 0 4px 0 2px;
height: 50%;
line-height: 50%;
opacity: 0;
cursor: pointer;
border: 1px solid rgba(57,57,57,0.15);
-webkit-box-sizing: border-box;
box-sizing: border-box;
}
.numInputWrapper span:hover {
background: rgba(0,0,0,0.1);
}
.numInputWrapper span:active {
background: rgba(0,0,0,0.2);
}
.numInputWrapper span:after {
display: block;
content: "";
position: absolute;
}
.numInputWrapper span.arrowUp {
top: 0;
border-bottom: 0;
}
.numInputWrapper span.arrowUp:after {
border-left: 4px solid transparent;
border-right: 4px solid transparent;
border-bottom: 4px solid rgba(57,57,57,0.6);
top: 26%;
}
.numInputWrapper span.arrowDown {
top: 50%;
}
.numInputWrapper span.arrowDown:after {
border-left: 4px solid transparent;
border-right: 4px solid transparent;
border-top: 4px solid rgba(57,57,57,0.6);
top: 40%;
}
.numInputWrapper span svg {
width: inherit;
height: auto;
}
.numInputWrapper span svg path {
fill: rgba(0,0,0,0.5);
}
.numInputWrapper:hover {
background: rgba(0,0,0,0.05);
}
.numInputWrapper:hover span {
opacity: 1;
}
.flatpickr-current-month {
font-size: 135%;
line-height: inherit;
font-weight: 300;
color: inherit;
position: absolute;
width: 75%;
left: 12.5%;
padding: 6.16px 0 0 0;
line-height: 1;
height: 28px;
display: inline-block;
text-align: center;
-webkit-transform: translate3d(0px, 0px, 0px);
transform: translate3d(0px, 0px, 0px);
}
.flatpickr-current-month span.cur-month {
font-family: inherit;
font-weight: 700;
color: inherit;
display: inline-block;
margin-left: 0.5ch;
padding: 0;
}
.flatpickr-current-month span.cur-month:hover {
background: rgba(0,0,0,0.05);
}
.flatpickr-current-month .numInputWrapper {
width: 6ch;
width: 7ch\0;
display: inline-block;
}
.flatpickr-current-month .numInputWrapper span.arrowUp:after {
border-bottom-color: rgba(0,0,0,0.9);
}
.flatpickr-current-month .numInputWrapper span.arrowDown:after {
border-top-color: rgba(0,0,0,0.9);
}
.flatpickr-current-month input.cur-year {
background: transparent;
-webkit-box-sizing: border-box;
box-sizing: border-box;
color: inherit;
cursor: text;
padding: 0 0 0 0.5ch;
margin: 0;
display: inline-block;
font-size: inherit;
font-family: inherit;
font-weight: 300;
line-height: inherit;
height: auto;
border: 0;
border-radius: 0;
vertical-align: initial;
}
.flatpickr-current-month input.cur-year:focus {
outline: 0;
}
.flatpickr-current-month input.cur-year[disabled],
.flatpickr-current-month input.cur-year[disabled]:hover {
font-size: 100%;
color: rgba(0,0,0,0.5);
background: transparent;
pointer-events: none;
}
.flatpickr-weekdays {
background: transparent;
text-align: center;
overflow: hidden;
width: 100%;
display: -webkit-box;
display: -webkit-flex;
display: -ms-flexbox;
display: flex;
-webkit-box-align: center;
-webkit-align-items: center;
-ms-flex-align: center;
align-items: center;
height: 28px;
}
.flatpickr-weekdays .flatpickr-weekdaycontainer {
display: -webkit-box;
display: -webkit-flex;
display: -ms-flexbox;
display: flex;
-webkit-box-flex: 1;
-webkit-flex: 1;
-ms-flex: 1;
flex: 1;
}
span.flatpickr-weekday {
cursor: default;
font-size: 90%;
background: transparent;
color: rgba(0,0,0,0.54);
line-height: 1;
margin: 0;
text-align: center;
display: block;
-webkit-box-flex: 1;
-webkit-flex: 1;
-ms-flex: 1;
flex: 1;
font-weight: bolder;
}
.dayContainer,
.flatpickr-weeks {
padding: 1px 0 0 0;
}
.flatpickr-days {
position: relative;
overflow: hidden;
display: -webkit-box;
display: -webkit-flex;
display: -ms-flexbox;
display: flex;
-webkit-box-align: start;
-webkit-align-items: flex-start;
-ms-flex-align: start;
align-items: flex-start;
width: 307.875px;
}
.flatpickr-days:focus {
outline: 0;
}
.dayContainer {
padding: 0;
outline: 0;
text-align: left;
width: 307.875px;
min-width: 307.875px;
max-width: 307.875px;
-webkit-box-sizing: border-box;
box-sizing: border-box;
display: inline-block;
display: -ms-flexbox;
display: -webkit-box;
display: -webkit-flex;
display: flex;
-webkit-flex-wrap: wrap;
flex-wrap: wrap;
-ms-flex-wrap: wrap;
-ms-flex-pack: justify;
-webkit-justify-content: space-around;
justify-content: space-around;
-webkit-transform: translate3d(0px, 0px, 0px);
transform: translate3d(0px, 0px, 0px);
opacity: 1;
}
.dayContainer + .dayContainer {
-webkit-box-shadow: -1px 0 0 #e6e6e6;
box-shadow: -1px 0 0 #e6e6e6;
}
.flatpickr-day {
background: none;
border: 1px solid transparent;
border-radius: 150px;
-webkit-box-sizing: border-box;
box-sizing: border-box;
color: #393939;
cursor: pointer;
font-weight: 400;
width: 14.2857143%;
-webkit-flex-basis: 14.2857143%;
-ms-flex-preferred-size: 14.2857143%;
flex-basis: 14.2857143%;
max-width: 39px;
height: 39px;
line-height: 39px;
margin: 0;
display: inline-block;
position: relative;
-webkit-box-pack: center;
-webkit-justify-content: center;
-ms-flex-pack: center;
justify-content: center;
text-align: center;
}
.flatpickr-day.inRange,
.flatpickr-day.prevMonthDay.inRange,
.flatpickr-day.nextMonthDay.inRange,
.flatpickr-day.today.inRange,
.flatpickr-day.prevMonthDay.today.inRange,
.flatpickr-day.nextMonthDay.today.inRange,
.flatpickr-day:hover,
.flatpickr-day.prevMonthDay:hover,
.flatpickr-day.nextMonthDay:hover,
.flatpickr-day:focus,
.flatpickr-day.prevMonthDay:focus,
.flatpickr-day.nextMonthDay:focus {
cursor: pointer;
outline: 0;
background: #e6e6e6;
border-color: #e6e6e6;
}
.flatpickr-day.today {
border-color: #959ea9;
}
.flatpickr-day.today:hover,
.flatpickr-day.today:focus {
border-color: #959ea9;
background: #959ea9;
color: #fff;
}
.flatpickr-day.selected,
.flatpickr-day.startRange,
.flatpickr-day.endRange,
.flatpickr-day.selected.inRange,
.flatpickr-day.startRange.inRange,
.flatpickr-day.endRange.inRange,
.flatpickr-day.selected:focus,
.flatpickr-day.startRange:focus,
.flatpickr-day.endRange:focus,
.flatpickr-day.selected:hover,
.flatpickr-day.startRange:hover,
.flatpickr-day.endRange:hover,
.flatpickr-day.selected.prevMonthDay,
.flatpickr-day.startRange.prevMonthDay,
.flatpickr-day.endRange.prevMonthDay,
.flatpickr-day.selected.nextMonthDay,
.flatpickr-day.startRange.nextMonthDay,
.flatpickr-day.endRange.nextMonthDay {
background: #569ff7;
-webkit-box-shadow: none;
box-shadow: none;
color: #fff;
border-color: #569ff7;
}
.flatpickr-day.selected.startRange,
.flatpickr-day.startRange.startRange,
.flatpickr-day.endRange.startRange {
border-radius: 50px 0 0 50px;
}
.flatpickr-day.selected.endRange,
.flatpickr-day.startRange.endRange,
.flatpickr-day.endRange.endRange {
border-radius: 0 50px 50px 0;
}
.flatpickr-day.selected.startRange + .endRange,
.flatpickr-day.startRange.startRange + .endRange,
.flatpickr-day.endRange.startRange + .endRange {
-webkit-box-shadow: -10px 0 0 #569ff7;
box-shadow: -10px 0 0 #569ff7;
}
.flatpickr-day.selected.startRange.endRange,
.flatpickr-day.startRange.startRange.endRange,
.flatpickr-day.endRange.startRange.endRange {
border-radius: 50px;
}
.flatpickr-day.inRange {
border-radius: 0;
-webkit-box-shadow: -5px 0 0 #e6e6e6, 5px 0 0 #e6e6e6;
box-shadow: -5px 0 0 #e6e6e6, 5px 0 0 #e6e6e6;
}
.flatpickr-day.disabled,
.flatpickr-day.disabled:hover,
.flatpickr-day.prevMonthDay,
.flatpickr-day.nextMonthDay,
.flatpickr-day.notAllowed,
.flatpickr-day.notAllowed.prevMonthDay,
.flatpickr-day.notAllowed.nextMonthDay {
color: rgba(57,57,57,0.3);
background: transparent;
border-color: transparent;
cursor: default;
}
.flatpickr-day.disabled,
.flatpickr-day.disabled:hover {
cursor: not-allowed;
color: rgba(57,57,57,0.1);
}
.flatpickr-day.week.selected {
border-radius: 0;
-webkit-box-shadow: -5px 0 0 #569ff7, 5px 0 0 #569ff7;
box-shadow: -5px 0 0 #569ff7, 5px 0 0 #569ff7;
}
.flatpickr-day.hidden {
visibility: hidden;
}
.rangeMode .flatpickr-day {
margin-top: 1px;
}
.flatpickr-weekwrapper {
display: inline-block;
float: left;
}
.flatpickr-weekwrapper .flatpickr-weeks {
padding: 0 12px;
-webkit-box-shadow: 1px 0 0 #e6e6e6;
box-shadow: 1px 0 0 #e6e6e6;
}
.flatpickr-weekwrapper .flatpickr-weekday {
float: none;
width: 100%;
line-height: 28px;
}
.flatpickr-weekwrapper span.flatpickr-day,
.flatpickr-weekwrapper span.flatpickr-day:hover {
display: block;
width: 100%;
max-width: none;
color: rgba(57,57,57,0.3);
background: transparent;
cursor: default;
border: none;
}
.flatpickr-innerContainer {
display: block;
display: -webkit-box;
display: -webkit-flex;
display: -ms-flexbox;
display: flex;
-webkit-box-sizing: border-box;
box-sizing: border-box;
overflow: hidden;
}
.flatpickr-rContainer {
display: inline-block;
padding: 0;
-webkit-box-sizing: border-box;
box-sizing: border-box;
}
.flatpickr-time {
text-align: center;
outline: 0;
display: block;
height: 0;
line-height: 40px;
max-height: 40px;
-webkit-box-sizing: border-box;
box-sizing: border-box;
overflow: hidden;
display: -webkit-box;
display: -webkit-flex;
display: -ms-flexbox;
display: flex;
}
.flatpickr-time:after {
content: "";
display: table;
clear: both;
}
.flatpickr-time .numInputWrapper {
-webkit-box-flex: 1;
-webkit-flex: 1;
-ms-flex: 1;
flex: 1;
width: 40%;
height: 40px;
float: left;
}
.flatpickr-time .numInputWrapper span.arrowUp:after {
border-bottom-color: #393939;
}
.flatpickr-time .numInputWrapper span.arrowDown:after {
border-top-color: #393939;
}
.flatpickr-time.hasSeconds .numInputWrapper {
width: 26%;
}
.flatpickr-time.time24hr .numInputWrapper {
width: 49%;
}
.flatpickr-time input {
background: transparent;
-webkit-box-shadow: none;
box-shadow: none;
border: 0;
border-radius: 0;
text-align: center;
margin: 0;
padding: 0;
height: inherit;
line-height: inherit;
cursor: pointer;
color: #393939;
font-size: 14px;
position: relative;
-webkit-box-sizing: border-box;
box-sizing: border-box;
}
.flatpickr-time input.flatpickr-hour {
font-weight: bold;
}
.flatpickr-time input.flatpickr-minute,
.flatpickr-time input.flatpickr-second {
font-weight: 400;
}
.flatpickr-time input:focus {
outline: 0;
border: 0;
}
.flatpickr-time .flatpickr-time-separator,
.flatpickr-time .flatpickr-am-pm {
height: inherit;
display: inline-block;
float: left;
line-height: inherit;
color: #393939;
font-weight: bold;
width: 2%;
-webkit-user-select: none;
-moz-user-select: none;
-ms-user-select: none;
user-select: none;
-webkit-align-self: center;
-ms-flex-item-align: center;
align-self: center;
}
.flatpickr-time .flatpickr-am-pm {
outline: 0;
width: 18%;
cursor: pointer;
text-align: center;
font-weight: 400;
}
.flatpickr-time .flatpickr-am-pm:hover,
.flatpickr-time .flatpickr-am-pm:focus {
background: #f0f0f0;
}
.flatpickr-input[readonly] {
cursor: pointer;
min-width: auto;
}
@-webkit-keyframes fpFadeInDown {
from {
opacity: 0;
-webkit-transform: translate3d(0, -20px, 0);
transform: translate3d(0, -20px, 0);
}
to {
opacity: 1;
-webkit-transform: translate3d(0, 0, 0);
transform: translate3d(0, 0, 0);
}
}
@keyframes fpFadeInDown {
from {
opacity: 0;
-webkit-transform: translate3d(0, -20px, 0);
transform: translate3d(0, -20px, 0);
}
to {
opacity: 1;
-webkit-transform: translate3d(0, 0, 0);
transform: translate3d(0, 0, 0);
}
}

5
static/css/fontawesome.css vendored Normal file

File diff suppressed because one or more lines are too long

View File

@ -1,9 +1,29 @@
@font-face {
font-family: 'Glyphicons Halflings';
src: url('../fonts/glyphicons-halflings-regular.eot');
src: url('../fonts/glyphicons-halflings-regular.eot?#iefix') format('embedded-opentype'),
url('../fonts/glyphicons-halflings-regular.woff2') format('woff2'),
url('../fonts/glyphicons-halflings-regular.woff') format('woff'),
url('../fonts/glyphicons-halflings-regular.ttf') format('truetype'),
url('../fonts/glyphicons-halflings-regular.svg#glyphicons_halflingsregular') format('svg');
src: url('../fonts/glyphicons/glyphicons-halflings-regular.eot');
src: url('../fonts/glyphicons/glyphicons-halflings-regular.eot?#iefix') format('embedded-opentype'),
url('../fonts/glyphicons/glyphicons-halflings-regular.woff2') format('woff2'),
url('../fonts/glyphicons/glyphicons-halflings-regular.woff') format('woff'),
url('../fonts/glyphicons/glyphicons-halflings-regular.ttf') format('truetype'),
url('../fonts/glyphicons/glyphicons-halflings-regular.svg#glyphicons_halflingsregular') format('svg');
}
/*!
* Font Awesome Free 5.1.0 by @fontawesome - https://fontawesome.com
* License - https://fontawesome.com/license (Icons: CC BY 4.0, Fonts: SIL OFL 1.1, Code: MIT License)
*/
@font-face{
font-family:"Font Awesome 5 Free";
font-style:normal;
font-weight:900;
src:url(../fonts/fontawesome/fa-solid-900.eot);
src:url(../fonts/fontawesome/fa-solid-900.eot?#iefix) format("embedded-opentype"),
url(../fonts/fontawesome/fa-solid-900.woff2) format("woff2"),
url(../fonts/fontawesome/fa-solid-900.woff) format("woff"),
url(../fonts/fontawesome/fa-solid-900.ttf) format("truetype"),
url(../fonts/fontawesome/fa-solid-900.svg#fontawesome) format("svg");
}
.fa,.fas{
font-family:"Font Awesome 5 Free";
font-weight:900;
}

View File

@ -26,9 +26,19 @@
.glyphicon--user::before {
content: '\e008';
}
.glyphicon--group::before {
/* TODO: get updated glyphicons for group-icon */
content: '\e284';
}
.glyphicon--education::before {
content: '\e233';
}
.glyphicon--login::before {
content: '\e161';
}
.glyphicon--logout::before {
content: '\e163';
}
.glyphicon--none::before {
content: '';
}

View File

@ -1,8 +1,6 @@
.tab-group {
/* box-shadow: 0 0 0 18px white, 0 0 0 20px #b3b7c1; */
border-top: 2px solid #dcdcdc;
padding-top: 30px;
margin-top: 40px;
}
.tab-group-openers {

Binary file not shown.

File diff suppressed because it is too large Load Diff

After

Width:  |  Height:  |  Size: 579 KiB

Binary file not shown.

Binary file not shown.

Binary file not shown.

View File

Before

Width:  |  Height:  |  Size: 62 KiB

After

Width:  |  Height:  |  Size: 62 KiB

2
static/js/flatpickr.js Normal file

File diff suppressed because one or more lines are too long

View File

@ -80,9 +80,11 @@
};
// apply plugin to all available tab-groups
$('.tab-group').each(function(i, t) {
$(t).tabgroup();
})
// apply plugin to all available tab-groups if on wide screen
if (window.innerWidth > 768) {
$('.tab-group').each(function(i, t) {
$(t).tabgroup();
});
}
});
})($);

View File

@ -0,0 +1,44 @@
<div .container>
<h1>Uniworky - Admin Demopage
<p>
Diese interne Seite dient lediglich zum Testen diverser Funktionalitäten
und zur Demonstration der verschiedenen Hilfsfunktionen/Module.
Der Handler sollte jeweils aktuelle Beispiele für alle möglichen Funktionalitäten enthalten, so dass man immer weiß, wo man nachschlagen kann.
<div .container>
<h2 .js-show-hide__toggle>Teilweise funktionierende Abschnitte
<ul>
<li .list-group-item>
<a href=@{UsersR}>Benutzer Verwaltung
<li .list-group-item>
<a href=@{TermShowR}>Semester Verwaltung
<a href=@{TermEditR}>Neues Semester anlegen
<li .list-group-item>
<a href=@{CourseNewR}>Kurse anlegen
<li .list-group-item>
<a href=@{SubmissionListR}>Dateien hochladen und abrufen
<hr>
<div .container>
<h2>Funktionen zum Testen
<ul>
<li>
Knopf-Test:
<form .form-inline method=post action=@{AdminTestR} enctype=#{btnEnctype}>
^{btnWdgt}
<li><br>
Modals:
^{modal ".toggler1" Nothing}
<a href="/" .btn.toggler1>Klick mich für Ajax-Test
<noscript>(Für Modals bitte JS aktivieren)</noscript>
^{modal ".toggler2" (Just "Test Inhalt für Modal")}
<div .btn.toggler2>Klick mich für Content-Test
<noscript>(Für Modals bitte JS aktivieren)</noscript>

View File

@ -1,102 +1,53 @@
<div .container>
<h2>#{courseName course}
<table>
$maybe school <- schoolMB
<tr>
<th #school>Fakultät/Institut
<div .scrolltable>
<table .table.table--striped.table--hover.table--vertical>
$maybe school <- schoolMB
<tr .table__row>
<th #school>Fakultät/Institut
<td>
#{schoolName school}
$maybe descr <- courseDescription course
<tr .table__row>
<th #description>Beschreibung
<td>
#{descr}
$maybe link <- courseLinkExternal course
<tr .table__row>
<th #website>Website
<td>
<a href=#{link} target="_blank" rel="noopener" title="Website des Kurses">#{link}
<tr .table__row>
<th #participants>Teilnehmer
<td>
#{schoolName school}
$maybe descr <- courseDescription course
<tr>
<th #description>Beschreibung
#{participants}
$maybe capacity <- courseCapacity course
\ von #{capacity}
<tr .table__row>
<th #registration>Anmeldezeitraum
<td>
<p>#{descr}
$maybe link <- courseLinkExternal course
<tr>
<th #website>Website
$maybe regFrom <- courseRegisterFrom course
#{formatTimeGerWD regFrom}
$maybe regTo <- courseRegisterTo course
\ bis #{formatTimeGerWD regTo}
<tr .table__row>
<th>
<td>
<a href=#{link}>#{link}
<tr>
<th #participants>Teilnehmer
<td>
#{participants}
$maybe capacity <- courseCapacity course
\ von #{capacity}
<tr>
<th #registration>Anmeldezeitraum
<td>
$maybe regFrom <- courseRegisterFrom course
#{formatTimeGerWD regFrom}
$maybe regTo <- courseRegisterTo course
\ bis #{formatTimeGerWD regTo}
$if registrationOpen
<div .course__registration.container>
<form method=post action=@{CourseR tid csh CRegisterR} enctype=#{regEnctype}>
$# regWidget is defined through templates/widgets/registerForm
^{regWidget}
$# if allowed to register
<div .course__registration>
<a href="#">Anmelden
$# <form method=post action=@{CourseR tid csh CShow} enctype=#{regEnctype}>
$# ^{regWidget}
<div .container>
<div .tab-group>
<div .tab data-tab-name="Übungsblätter">
^{modal "#modal-toggler__new-sheet" Nothing}
<h3 .tab-title>Übungsblätter
<table .table.table-striped.table-hover>
<thead>
<tr>
<th>Blatt
<th>Abgabe ab
<th>Abgabe bis
<th>Bewertung</th>
<tbody>
<tr>
<td>
<a href="http://localhost:3000/course/S2018/ffp/ex/Blatt%201/show" role="button">Blatt 1
<td>Do 08.04.18
<td>Do 11.04.18
<td>NotGraded
<tr>
<td>
<a href="http://localhost:3000/course/S2018/ffp/ex/Blatt%201/show" role="button">Blatt 2
<td>Do 15.04.18
<td>Do 18.04.18
<td>NotGraded
<tr .no-hover.no-stripe>
<td>&nbsp;
<td>&nbsp;
<td>&nbsp;
<td>&nbsp;
<td>
<a href="/course/S2018/ffp/ex/new" #modal-toggler__new-sheet>Neues Übungsblatt anlegen
<div .tab data-tab-name="Übungsgruppen">
<h3 .tab-title>Übungsgruppen
<table .table.table-striped.table-hover>
<thead>
<tr>
<th>Name
<th>Termin
<th>Raum
<th>Studenten
<th>Tutor
<th>Anmeldung bis
<tbody>
<tr>
<td>
<a href="#">Gruppe 1
<td>Montag 10:00 - 12:00
<td>N/A
<td>2/10
<td>Tutor1 Tutoren
<td>Do 21.02.2019, 19:00
<tr>
<td>
<a href="#">Gruppe 2
<td>Montag 12:00 - 14:00
<td>N/A
<td>0/10
<td>Assistant1 Assistant
<td>Di 21.02.2017, 19:00
<div .tab data-tab-name="Klausuren">
<h3 .tab-title>Klausuren
<div>...
$# <div .container>
$# <div .tab-group>
$# <div .tab data-tab-name="Übungsblätter">
$# ^{modal "#modal-toggler__new-sheet" Nothing}
$# <h3 .tab-title>Übungsblätter
$# <h1>TODO: Sortierbare Tabelle der bisherigen Übungsblätter
$# <div .tab data-tab-name="Übungsgruppen">
$# <h3 .tab-title>Übungsgruppen
$# <h1>TODO: Sortierbare Tabelle der Übungsgruppen
$# <div .tab data-tab-name="Klausuren">
$# <h3 .tab-title>Klausuren
$# <div>...

View File

@ -0,0 +1,8 @@
th {
vertical-align: top;
text-align: left;
}
th, td {
padding-bottom: 7px;
}

View File

@ -1,4 +1,3 @@
<div .container>
<h1>Kursübersicht für Semester #{termToText $ unTermKey tidini}
<div .scrolltable>
^{coursesTable}

View File

@ -39,7 +39,7 @@ $newline never
}
<body .no-js>
<body .no-js .#{currentTheme}>
<!-- removes no-js class from body if client supports javascript -->
<script>
document.body.classList.remove('no-js');

View File

@ -8,13 +8,28 @@
<div .main__content>
<!-- alerts -->
$forall (status, msg) <- mmsgs
$with status2 <- bool status "info" (status == "")
<div class="alert alert-#{status2}">#{msg}
<!-- breadcrumbs -->
$if not $ Just HomeR == mcurrentRoute
^{breadcrumbs}
<!-- prime page actions -->
^{pageactionprime}
<div .main__content-body>
<!-- actual content -->
^{widget}
<h1>
$maybe headline <- contentHeadline
^{headline}
$nothing
HEADLINE MISSING!
<!-- prime page actions -->
^{pageactionprime}
<!-- alerts -->
$forall (status, msg) <- mmsgs
$with status2 <- bool status "info" (status == "")
<div class="alert alert-#{status2}">
<div .alert__content>
#{msg}
<!-- actual content -->
^{widget}

View File

@ -1,47 +1,19 @@
:root {
/* THEME 1 */
--base00: #72a85b;
--base-bg-color: #1d1c1d;
--base-font-color: #fff;
--sec-font-color: #fff;
--box-bg-color: #3c3c3c;
/* THEME 2 */
--base00: #38428a;
--base-bg-color: #ffffff;
--base-font-color: rgb(53, 53, 53);
--sec-font-color: #eaf2ff;
--box-bg-color: #dddddd;
/* THEME 3 */
--darkbase: #364B60;
--lightbase: #2490E8;
--lighterbase: #60C2FF;
--whitebase: #FCFFFA;
--greybase: #B1B5C0;
--fontbase: #34303a;
--fontsec: #5b5861;
/* THEME 4 */
--darkerbase: #274a65;
--darkbase: #425d79;
--lightbase: #598EB5;
--lighterbase: #5F98C2;
--whitebase: #FCFFFA;
--greybase: #B1B5C0;
--lightgreybase: #D9DEDB;
--blackbase: #1A2A36;
--fontbase: #34303a;
--fontsec: #5b5861;
--primarybase: #4C7A9C;
/* THEME INDEPENDENT COLORS */
--errorbase: red;
--warningbase: #fe7700;
--validbase: #2dcc35;
--infobase: var(--darkbase);
--color-error: #ff3860;
--color-warning: #ffdd57;
--color-success: #23d160;
--color-info: #c4c4c4;
--color-lightblack: #1A2A36;
--color-lightwhite: #FCFFFA;
--color-grey: #B1B5C0;
--color-font: #34303a;
--color-fontsec: #5b5861;
/* FONTS */
--fontfamilybase: "Source Sans Pro", Helvetica, sans-serif;
--font-base: "Source Sans Pro", Helvetica, sans-serif;
--font-logo: "Roboto", var(--font-base);
/* DIMENSIONS */
--header-height: 80px;
@ -56,13 +28,63 @@
body {
background-color: white;
color: var(--fontbase);
font-family: var(--fontfamilybase);
color: var(--color-font);
font-family: var(--font-base);
font-weight: 400;
font-size: 16px;
overflow-y: scroll;
}
/* THEMES */
body {
/* DEFAULT THEME */
--color-primary: #4C7A9C;
--color-light: #598EB5;
--color-lighter: #5F98C2;
--color-dark: #425d79;
--color-darker: #274a65;
--color-link: var(--color-dark);
--color-link-hover: var(--color-darker);
&.theme--neutral-blue {
--color-primary: #3E606F;
--color-light: rgb(189, 201, 219);
--color-lighter: rgb(145, 159, 170);
--color-dark: rgb(42, 74, 88);
--color-darker: #193441;
}
&.theme--aberdeen-reds {
--color-primary: #820333;
--color-light: #C9283E;
--color-lighter: #F0433A;
--color-dark: #540032;
--color-darker: #2E112D;
}
&.theme--mint-green {
--color-primary: #5C996B;
--color-light: #7ACC8F;
--color-lighter: #99FFB2;
--color-dark: #3D6647;
--color-darker: #1F3324;
}
&.theme--sky-love {
--color-primary: #87ABE5;
--color-light: #A0C6F2;
--color-lighter: #BAE2FF;
--color-dark: #7A95DE;
--color-darker: #6B7BC9;
--color-link: var(--color-lightblack);
--color-link-hover: var(--color-darker);
}
}
/* END THEMES */
a,
a:visited {
text-decoration: none;
@ -70,6 +92,15 @@ a:visited {
transition: color .2s ease, background-color .2s ease;
}
a {
color: var(--color-link);
}
a:hover {
color: var(--color-link-hover);
}
ul {
list-style-type: none;
}
@ -87,68 +118,47 @@ h1 {
}
h2 {
font-size: 24px;
margin: 10px 0 5px;
margin: 10px 0;
}
h3 {
font-size: 20px;
margin: 5px 0;
margin: 10px 0;
}
h4 {
font-size: 16px;
margin: 0;
}
table {
margin: 21px 0;
}
.scrolltable {
width: 100%;
overflow: auto;
}
@media (max-width: 768px) {
.table-striped {
h1 {
font-size: 24px;
}
tbody {
tr:not(.no-stripe):nth-child(even) {
background-color: #e8e8e8;
}
h2 {
font-size: 20px;
}
h3 {
font-size: 16px;
}
}
.table-hover {
tbody {
tr:not(.no-hover):hover {
background-color: #d8d8d8;
}
}
}
th, td {
text-align: left;
padding: 0 13px 0 7px;
vertical-align: baseline;
}
th:first-child,
td:first-child {
padding-left: 0;
border-left: 0;
}
th {
border-left: 2px solid var(--greybase);
}
/* LAYOUT */
.main {
display: flex;
min-height: calc(100vh - var(--header-height));
overflow: hidden;
}
@media (max-width: 768px) {
.main {
min-height: calc(100vh - var(--header-height-collapsed));
}
}
.main__content {
position: relative;
background-color: white;
padding: 0 40px;
flex: 1;
z-index: 0;
overflow: hidden;
@ -159,18 +169,21 @@ th {
p {
margin: 10px 0;
}
}
a {
color: var(--darkbase);
}
.main__content-body {
padding: 0 40px 60px;
}
a:hover {
color: var(--lightbase);
@media (max-width: 768px) {
.main__content-body {
padding: 10px 20px 60px;
}
}
.pseudo-focus {
outline: 5px auto var(--lightbase);
outline: 5px auto var(--color-light);
outline: 5px auto -webkit-focus-ring-color;
}
@ -182,28 +195,22 @@ button,
outline: 0;
border: 0;
box-shadow: 0;
background-color: var(--lightbase);
background-color: var(--color-dark);
color: white;
padding: 10px 17px;
min-width: 100px;
transition: all .1s;
font-size: 16px;
cursor: pointer;
border-radius: 4px;
display: inline-block;
}
input.btn-primary,
button.btn-primary,
a.btn.btn-primary,
.btn.btn-primary {
background-color: var(--primarybase);
}
input.btn-info,
button.btn-info,
a.btn.btn-info,
.btn.btn-info {
background-color: var(--infobase)
a {
color: white;
}
a:hover {
color: white;
}
}
input[type="submit"][disabled],
@ -212,7 +219,7 @@ button[disabled],
a.btn[disabled],
.btn[disabled] {
opacity: 0.3;
background-color: var(--greybase);
background-color: var(--color-grey);
cursor: default;
}
@ -221,20 +228,127 @@ input[type="button"]:not([disabled]):hover,
button:not([disabled]):hover,
a.btn:not([disabled]):hover,
.btn:not([disabled]):hover {
background-color: var(--lighterbase);
background-color: var(--color-light);
text-decoration: underline;
color: white;
}
input.btn-primary,
button.btn-primary,
a.btn.btn-primary,
.btn.btn-primary {
background-color: var(--color-primary);
}
input.btn-info,
button.btn-info,
a.btn.btn-info,
.btn.btn-info {
background-color: var(--color-info)
}
input[type="submit"].btn-info:hover,
input[type="button"].btn-info:hover,
button.btn-info:hover,
a.btn.btn-info:hover,
.btn.btn-info:hover {
background-color: var(--greybase)
background-color: var(--color-grey)
}
.alert-debug {
background-color: rgb(240, 30, 240);
/* GENERAL TABLE STYLES */
.table {
margin: 21px 0;
width: 100%;
}
.table--striped {
.table__row:not(.no-stripe):nth-child(even) {
background-color: rgba(0, 0, 0, 0.03);
}
}
.table--hover {
.table__row:not(.no-hover):not(.table__row--head):hover {
background-color: rgba(0, 0, 0, 0.07);
}
}
/* SCROLLTABLE */
.scrolltable {
overflow: auto;
}
/* TABLE DESIGN */
.table__row {
/* TODO: move outside of table__row as soon as tds and ths get their own class */
/* .table__td, .table__th { */
td, th {
padding-top: 14px;
padding-bottom: 10px;
padding-left: 10px;
padding-right: 10px;
max-width: 300px;
}
/* .table__td { */
td {
font-size: 16px;
color: #808080;
line-height: 1.4;
vertical-align: top;
}
/* .table__th { */
th {
background-color: var(--color-dark);
position: relative;
font-size: 16px;
color: #fff;
line-height: 1.4;
padding-top: 10px;
padding-bottom: 10px;
font-weight: bold;
text-align: left;
}
}
@media (max-width: 1200px) {
.table th {
padding: 4px 6px;
}
}
.table__td-content {
max-height: 100px;
overflow-y: auto;
}
.table__th-link {
color: white;
font-weight: bold;
&:hover {
color: inherit;
}
}
.table--vertical {
th {
background-color: transparent;
color: var(--color-font);
width: 170px;
text-align: right;
padding-right: 15px;
font-weight: 400;
}
td {
font-weight: 600;
color: var(--color-font);
}
}

View File

@ -0,0 +1,15 @@
<div .notification .notification-danger>
<div .notification__content>
<h1>
Hinweis zum Datenschutz
<p>
Dieses experimentelle Programm wurde noch nicht
hinsichtlich des Datenschutzes überprüft.
<em>
Die Benutzung erfolgt derzeit freiwillig und auf eigene Gefahr!
Wir sind natürlich bemüht, alle Datenschutzrechtlichen Vorgaben
zu erfüllen, doch eine Überprüfung kann erst stattfinden,
sobald die Software weitestgehend fertiggestellt wurde und
sich nicht mehr verändert. Um dies zu Erreichen sind jedoch Test
unter realen Bedingungen erforderlich. Wir bitten um Ihr Verständnis.

View File

@ -0,0 +1,50 @@
.notification {
position: relative;
border-radius: 3px;
padding: 10px 20px 20px;
margin: 40px 0;
color: var(--color-lighter);
box-shadow: 0 0 4px 2px inset currentColor;
padding-left: 20%;
color: #318dc5 ;
&::before {
content: 'i';
position: absolute;
display: flex;
left: 0;
top: 0;
height: 100%;
width: 20%;
font-size: 100px;
align-items: center;
justify-content: center;
}
}
@media (max-width: 768px) {
.notification {
padding-left: 40px;
&::before {
height: auto;
width: 45px;
font-size: 40px;
top: 15px;
}
}
}
.notification-danger {
color: #c51919 ;
&::before {
content: '!';
}
}
.notification__content {
color: var(--color-font);
}

View File

@ -1,12 +1,2 @@
<div .container>
<div .bs-docs-section>
<div .row>
<div .col-lg-12>
<div .page-header>
<h1 #forms>
#{formTitle}
<div .row>
<div .col-md-10 .col-lg-9>
<div .bs-callout bs-callout-info well>
<form .form-horizontal method=post action=@{actionUrl}#forms enctype=#{formEnctype}>
^{formWidget}
<form .form-horizontal method=post action=@{actionUrl}#forms enctype=#{formEnctype}>
^{formWidget}

View File

@ -1,15 +1,5 @@
<div .container>
<div .bs-docs-section>
<div .row>
<div .col-lg-12>
<div .page-header>
<h1 #forms>
_{formTitle}
$maybe text <- formText
_{text}
<div .row>
<div .col-md-10 .col-lg-9>
<div .bs-callout bs-callout-info well>
<form .form-horizontal method=post action=@{actionUrl}#forms enctype=#{formEnctype}>
^{formWidget}
$maybe text <- formText
<h3>
_{text}
<form .form-horizontal method=post action=@{actionUrl}#forms enctype=#{formEnctype}>
^{formWidget}

View File

@ -1,63 +1,14 @@
<div .container>
<h1>Uniworky - Demo
<h3>
Testumgebung für die Re-Implementierung von <a href="https://uniworx.ifi.lmu.de/">UniWorX</a>
<p>
Die Reimplementierung von
UniWorX ist noch nicht abgeschlossen.
Re-Implementierung von <a href="https://uniworx.ifi.lmu.de/">UniWorX</a>
<p .alert .alert-danger>Das System ist noch nicht produktiv einsetzbar
<div .alert .alert-danger>
<div .alert__content>
Vorabversion!
Die Implementierung von
UniWorkY ist noch nicht abgeschlossen.
<hr>
<div .container>
<h2 .js-show-hide__toggle>Teilweise funktionierende Abschnitte
<h1>Kurse mit offener Registrierung
<div .container>
^{courseTable}
<ul>
<li .list-group-item>
<a href=@{UsersR}>Benutzer Verwaltung
<li .list-group-item>
<a href=@{TermShowR}>Semester Verwaltung
<a href=@{TermEditR}>Neues Semester anlegen
<li .list-group-item>
<a href=@{CourseNewR}>Kurse anlegen
<li .list-group-item>
<a href=@{SubmissionListR}>Dateien hochladen und abrufen
<hr>
<div .container>
<h2>Funktionen zum Testen
<ul>
<li>
Knopf-Test:
<form .form-inline method=post action=@{HomeR} enctype=#{btnEnctype}>
^{btnWdgt}
<li><br>
Modals:
^{modal ".toggler1" Nothing}
<a href="/" .btn.toggler1>Klick mich für Ajax-Test
<noscript>(Für Modals bitte JS aktivieren)</noscript>
^{modal ".toggler2" (Just "Test Inhalt für Modal")}
<div .btn.toggler2>Klick mich für Content-Test
<noscript>(Für Modals bitte JS aktivieren)</noscript>
<li><br>
Multi-File-Input für bereits hochgeladene Dateien:
<form>
<div .form-group>
<label .form-group__label>Datei(en)
$# file 1
<div .file-checkbox__container>
<label .file-checkbox__label.reactive-label.btn for="f2-1">Datenschutz.txt
<div .checkbox>
<input .file-checkbox id="f2-1" name="f2" value="Datenschutz.txt" type="checkbox">
<label for="f2-1">
$# file 2
<div .file-checkbox__container>
<label .file-checkbox__label.reactive-label.btn for="f2-2">fill-db.hs
<div .checkbox>
<input .file-checkbox id="f2-2" name="f2" value="fill-db.hs" type="checkbox">
<label for="f2-2">

View File

23
templates/homeUser.hamlet Normal file
View File

@ -0,0 +1,23 @@
<div .container>
<h3>
Re-Implementierung von <a href="https://uniworx.ifi.lmu.de/">UniWorX</a>
<div .alert .alert-danger>
<div .alert__content>
Vorabversion!
Die Implementierung von
UniWorkY ist noch nicht abgeschlossen.
<h1>Anstehende Übungsblätter
<div .container>
^{sheetTable}
<h1>
Anstehende Klausuren
TODO
<h1>
Anstehende Kursanmeldungen
TODO

View File

@ -6,16 +6,15 @@ $forall FileUploadInfo{..} <- fileInfos
<input .file-checkbox.js-file-checkbox id=#{fuiHtmlId} name=#{fieldName} :fuiChecked:checked value=#{toPathPiece fuiId} type="checkbox">
<label for=#{fuiHtmlId}>
<div .file-checkbox__container.file-checkbox__container--checked>
<label .file-checkbox__label.reactive-label.btn for=fi1>file1.txt
<div .checkbox>
<input .file-checkbox.js-file-checkbox id=fi1 name=file checked value="file1.txt" type="checkbox">
<label for=fi1>
$# new files
<input type="file" name=#{fieldName} multiple>
<input type="file" name=#{fieldName} id=#{fieldId} multiple :req:required="required">
<div .file-input__multi-info>
_{MsgMultiFileUploadInfo}
<div .file-input__unpack>
<label for=#{fieldId}_zip>ZIPs entpacken
<input type=checkbox id=#{fieldId}_zip name=#{fieldName} value=#{unpackZips} :req:required>
<label for=#{fieldId}_zip>ZIPs automatisch entpacken
<input type=checkbox id=#{fieldId}_zip name=#{fieldName} value=#{unpackZips}>
<div class="js-tooltip">
<div class="tooltip__handle">?
<div class="tooltip__content hidden">Entpackt hochgeladene Zip-Dateien (*.zip) automatisch und fügt den Inhalt dem Stamm-Verzeichnis der Abgabe hinzu.

View File

@ -0,0 +1,24 @@
.file-input__unpack {
font-size: .9rem;
display: flex;
align-items: center;
margin-top: 10px;
.checkbox {
display: inline-block;
margin-left: 5px;
}
}
.file-input__multi-info {
font-size: .9rem;
font-style: italic;
margin-top: 10px;
color: var(--color-fontsec);
}
.file-input__list {
margin-left: 15px;
margin-top: 10px;
font-weight: 600;
}

View File

@ -1,23 +1,77 @@
<div .ui.container>
<div .profile>
<h1>
Access granted!
<div .scrolltable>
<table .table.table--striped.table--hover.table--vertical>
<tr.table__row>
<th> _{MsgName}
<td> #{display userDisplayName}
<tr.table__row>
<th> _{MsgMatrikelNr}
<td> #{display userMatrikelnummer}
<tr.table__row>
<th> _{MsgEMail}
<td> #{display userEmail}
<tr.table__row>
<th> _{MsgIdent}
<td> #{display userIdent}
<tr.table__row>
<th> _{MsgPlugin}
<td> #{display userPlugin}
$if not $ null admin_rights
<tr.table__row>
<th> Administrator
<td>
<ul>
$forall institute <- admin_rights
<li>#{display institute}
$if not $ null lecturer_rights
<tr.table__row>
<th> Lehrberechtigt
<td>
<ul>
$forall institute <- lecturer_rights
<li>#{display institute}
$if not $ null lecture_owner
<tr.table__row>
<th> Eigene Kurse
<td>
<ul>
$forall (E.Value csh, E.Value tid) <- lecture_owner
<li>
<a href=@{CourseR tid csh CShowR}>#{display tid} - #{csh}
$if not $ null lecture_corrector
<tr.table__row>
<th> Korrektor
<td>
<ul>
$forall (E.Value csh, E.Value tid) <- lecture_corrector
<li>
<a href=@{CourseR tid csh CShowR}>#{display tid} - #{csh}
$if not $ null studies
<tr.table__row>
<th> Studiengänge
<td>
<table .table .table-striped .table-hover>
<tr.table__row>
<th> Abschluss
<th> Studiengang
<th> Studienart
<th> Semester
<p>
This page is protected and access is allowed only for authenticated users.
$forall (degree,field,fieldtype,semester) <- studies
<tr.table__row>
<td> #{display degree}
<td> #{display field}
<td> #{display fieldtype}
<td> #{display semester}
$if not $ null participant
<tr.table__row>
<th> Teilnehmer
<td>
<ul>
$forall (E.Value csh, E.Value tid, regSince) <- participant
<li>
<a href=@{CourseR tid csh CShowR}>#{display tid} - #{csh}
seit #{display regSince}
<p>
Your data is protected with us <strong><span class="username">#{userIdent user}</span></strong>!
$if not $ null admin_rights
<h1>
Administrator für die Institute
<ul>
$forall institute <- admin_rights
<li>#{show institute}
$if not $ null lecturer_rights
<h1>
Lehrberechtigung für die Institute
<ul>
$forall institute <- lecturer_rights
<li>#{show institute}
^{settingsForm}

View File

@ -0,0 +1,24 @@
<div .container>
<div .alert .alert-danger>
<div .alert__content>
TODO: Alle Benutzerbezogenen Daten sollen hier angezeigt
und verlinkt werden
(alle Abgaben, Klausurnoten, etc.)
<em> TODO: Hier mehr Daten in Tabellen anzeigen!
<h2>
<em> TODO: Knopf zum Löschen aller Daten erstellen
<p>
<h4>Hinweise:
<ul>
<li>
Nicht aufgeführt sind Zeitstempel mit Benutzerinformationen, z.B. bei der Editierung und Korrekturen von Übungen, Übungsgruppenleiterschaft, Raumbuchungen, etc.
<li>
Benutzerdaten bleiben so lange gespeichert, bis ein Institutsadministrator über die Exmatrikulation informiert wurde. Dann wird der Account gelöscht.
Abgaben/Bonuspunkte werden unwiderruflich gelöscht.
Klausurnoten verbleiben aus statistischen Gründen anonymisiert im System.
<li>
Bei gemeinsamen Gruppenabgaben wird nur die Zuordnung zu diesem Benutzer gelöscht.
Die Abgabe selbst wird erst gelöscht, wenn alle Benutzer einer Abgabe deren Löschung veranlasst haben.

View File

@ -13,7 +13,7 @@
<h2 #description>Hinweise
<p> #{descr}
<h3>Bewertung
<p> #{show $ sheetType sheet}
<p> #{display $ sheetType sheet}
$maybe marking <- sheetMarkingText sheet
<p> #{marking}
<br>

View File

@ -0,0 +1 @@
<!-- only here to be able to include alerts using `toWidget` -->

View File

@ -0,0 +1,24 @@
(function() {
'use strict';
window.utils = window.utils || {};
window.utils.alert = function(alertEl) {
var closeEl = document.createElement('DIV');
closeEl.classList.add('alert__close');
closeEl.innerText = #{String (messageRender MsgCloseAlert)};
closeEl.addEventListener('click', function(event) {
alertEl.classList.add('alert--invisible');
});
alertEl.appendChild(closeEl);
}
})();
document.addEventListener('DOMContentLoaded', function() {
// setup alerts
Array.from(document.querySelectorAll('.alert')).forEach(function(alertEl) {
window.utils.alert(alertEl);
});
});

View File

@ -0,0 +1,72 @@
/* ALERTS */
.alert {
position: relative;
display: flex;
justify-content: space-between;
background-color: #f5f5f5;
font-size: 1rem;
border-color: #dbdbdb;
border-radius: 4px;
border-style: solid;
border-width: 0 0 0 4px;
color: #4a4a4a;
z-index: 0;
max-height: 200px;
transition: all .2s ease-in-out;
transform-origin: top;
}
.alert__content {
padding: 1.25em 1.5em;
}
.alert__close {
cursor: pointer;
text-align: right;
display: flex;
align-items: center;
justify-content: center;
padding: 0 10px;
background-color: var(--color-light);
color: var(--color-lightwhite);
transition: all .2s ease;
&:hover {
background-color: var(--color-primary);
transform: scale(1.05, 1.05);
}
}
.alert-success {
background-color: #f6fef9;
border-color: var(--color-success);
.alert__close {
background-color: var(--color-success);
}
}
.alert-warning {
background-color: #fffdf5;
border-color: var(--color-warning);
.alert__close {
background-color: var(--color-warning);
color: var(--color-dark);
}
}
.alert-danger,
.alert-error {
border-color: var(--color-error);
background-color: #fff5f7;
.alert__close {
background-color: var(--color-error);
}
}
.alert--invisible {
max-height: 0;
transform: scaleY(0);
}

View File

@ -0,0 +1 @@
<!-- only here to be able to include datepicker using `toWidget` -->

View File

@ -0,0 +1,36 @@
document.addEventListener('DOMContentLoaded', function() {
"use strict";
var config = {
dtLocal: {
enableTime: true,
altInput: true,
altFormat: "j. F Y, H:i",
dateFormat: "Y-m-dTH:i",
time_24hr: true
},
d: {
altFormat: "j. F Y",
dateFormat: "Y-m-d",
altInput: true
},
t: {
enableTime: true,
noCalendar: true,
altFormat: "H:i",
dateFormat: "H:i",
altInput: true,
time_24hr: true
}
};
Array.from(document.querySelectorAll('input[type="date"]')).forEach(function(el) {
flatpickr(el, config.d);
});
Array.from(document.querySelectorAll('input[type="time"]')).forEach(function(el) {
flatpickr(el, config.t);
});
Array.from(document.querySelectorAll('input[type="datetime-local"]')).forEach(function(el) {
flatpickr(el, config.dtLocal);
});
});

View File

@ -3,153 +3,68 @@
window.utils = window.utils || {};
// makes <label> smaller if <input> is focussed
window.utils.reactiveInputLabel = function(input, label) {
// updates to dom
if (input.value.length > 0) {
label.classList.add('reactive-label--small');
}
// add event listeners
input.addEventListener('focus', function() {
label.classList.add('reactive-label--small');
});
label.addEventListener('click', function() {
label.classList.add('reactive-label--small');
input.focus();
});
input.addEventListener('blur', function() {
if (input.value.length < 1) {
label.classList.remove('reactive-label--small');
}
});
};
// allows for multiple file uploads with separate inputs
window.utils.reactiveFileUpload = function(input, formGroup) {
var currValidInputCount = 0;
var addMore = false;
var inputName = input.getAttribute('name');
var isMulti = input.hasAttribute('multiple') ? true : false;
var wrapper = formGroup;
// FileInput PseudoClass
function FileInput(container, input, label, remover) {
this.container = container;
this.input = input;
this.label = label;
this.remover = remover;
addListener(this);
window.utils.initializeFileUpload = function(input) {
var isMulti = input.hasAttribute('multiple');
var fileList = isMulti ? addFileList() : null;
var label = addFileLabel();
this.addTo = function(parentElement) {
parentElement.appendChild(this.container);
}
this.remove = function() {
this.container.remove();
}
this.wasValid = function() {
return this.container.classList.contains('file-input__container--valid');
}
function renderFileList(files) {
fileList.innerHTML = '';
Array.from(files).forEach(function(file, index) {
var fileDisplayEl = document.createElement('li');
fileDisplayEl.innerHTML = file.name;
fileList.appendChild(fileDisplayEl);
});
}
function addNextInput() {
var inputs = wrapper.querySelectorAll('.file-input__container');
if (inputs[inputs.length - 1].classList.contains('file-input__container--valid')) {
makeInput(inputName).addTo(wrapper);
}
}
// updates submitbutton and form-group-stripe
function updateForm() {
var submitBtn = formGroup.parentElement.querySelector('[type=submit]');
formGroup.classList.remove('form-group--has-error');
if (currValidInputCount > 0) {
if (formGroup.classList.contains('form-group')) {
formGroup.classList.add('form-group--valid')
}
function updateLabel(files) {
if (files.length) {
if (isMulti) {
addNextInput();
label.innerText = files.length + ' Dateien ausgwählt';
} else {
label.innerHTML = files[0].name;
}
} else {
if (formGroup.classList.contains('form-group')) {
formGroup.classList.remove('form-group--valid')
}
resetFileLabel();
}
}
// addseventlistener destInput
function addListener(fileInput) {
fileInput.input.addEventListener('change', function(event) {
if (fileInput.input.value.length > 0) {
// update label
var filePath = fileInput.input.value.replace(/\\/g, '/').split('/');
var fileName = filePath[filePath.length - 1];
fileInput.label.innerHTML = fileName;
// increase count if this field was empty previously
if (!fileInput.wasValid()) {
currValidInputCount++;
}
fileInput.container.classList.add('file-input__container--valid')
// show next input
} else {
if (isMulti) {
currValidInputCount--;
}
clearInput(fileInput);
}
updateForm();
});
fileInput.input.addEventListener('focus', function() {
fileInput.container.classList.add('pseudo-focus');
});
fileInput.input.addEventListener('blur', function() {
fileInput.container.classList.remove('pseudo-focus');
});
fileInput.remover.addEventListener('click', function() {
if (fileInput.wasValid()) {
currValidInputCount--;
}
clearInput(fileInput);
});
}
// clears or removes fileinput based on multi-file or not
function clearInput(fileInput) {
if (isMulti) {
fileInput.remove();
function addFileList() {
var list = document.createElement('ol');
list.classList.add('file-input__list');
var unpackEl = input.parentElement.querySelector('.file-input__unpack');
if (unpackEl) {
input.parentElement.insertBefore(list, unpackEl);
} else {
fileInput.container.classList.remove('file-input__container--valid')
fileInput.label.innerHTML = '';
input.parentElement.appendChild(list);
}
updateForm();
return list;
}
// create new wrapped input element with name name
function makeInput(name) {
var cont = document.createElement('div');
var desc = document.createElement('label');
var nextInput = document.createElement('input');
var remover = document.createElement('div');
cont.classList.add('file-input__container');
desc.classList.add('file-input__label', 'btn');
nextInput.classList.add('js-file-input');
desc.setAttribute('for', name + '-' + currValidInputCount);
remover.classList.add('file-input__remover');
nextInput.setAttribute('id', name + '-' + currValidInputCount);
nextInput.setAttribute('name', name);
nextInput.setAttribute('type', 'file');
cont.appendChild(nextInput);
cont.appendChild(desc);
cont.appendChild(remover);
return new FileInput(cont, nextInput, desc, remover);
function addFileLabel() {
var label = document.createElement('label');
label.classList.add('file-input__label');
label.setAttribute('for', input.id);
input.parentElement.insertBefore(label, input);
return label;
}
function resetFileLabel() {
// interpolate translated String here
label.innerText = 'Datei' + (isMulti ? 'en' : '') + ' auswählen';
}
// initial setup
function setup() {
var newInput = makeInput(inputName);
resetFileLabel();
input.classList.add('file-input__input--hidden');
input.addEventListener('change', function() {
if (isMulti) {
wrapper = document.createElement('div');
wrapper.classList.add('file-input__wrapper');
formGroup.insertBefore(wrapper, input);
renderFileList(input.files);
}
input.remove();
newInput.addTo(wrapper);
updateForm();
}
setup();
updateLabel(input.files);
});
}
// to remove previously uploaded files
@ -182,63 +97,47 @@
setup();
}
window.utils.reactiveFormGroup = function(formGroup, input) {
// updates to dom
if (input.value.length > 0) {
formGroup.classList.add('form-group--valid');
} else {
formGroup.classList.remove('form-group--valid');
}
input.addEventListener('input', function() {
formGroup.classList.remove('form-group--has-error');
if (input.value.length > 0) {
formGroup.classList.add('form-group--valid');
window.utils.initializeCheckboxRadio = function(input, type) {
if (!input.parentElement.classList.contains(type)) {
var parentEl = input.parentElement;
var siblingEl = input.nextElementSibling;
var wrapperEl = document.createElement('div');
var labelEl = document.createElement('label');
wrapperEl.classList.add(type);
labelEl.setAttribute('for', input.id);
wrapperEl.appendChild(input);
wrapperEl.appendChild(labelEl);
if (siblingEl) {
parentEl.insertBefore(wrapperEl, siblingEl);
} else {
formGroup.classList.remove('form-group--valid');
parentEl.appendChild(wrapperEl);
}
});
};
}
}
})();
document.addEventListener('DOMContentLoaded', function() {
// setup reactive labels
Array.from(document.querySelectorAll('.reactive-label')).forEach(function(label) {
var input = document.querySelector('#' + label.getAttribute('for'));
if (!input) {
console.error('No input found for ReactiveLabel! Targeted input: \'#%s\'', label.getAttribute('for'));
label.classList.remove('reactive-label');
return false;
}
// initialize checkboxes
Array.from(document.querySelectorAll('input[type="checkbox"]')).forEach(function(inp) {
window.utils.initializeCheckboxRadio(inp, 'checkbox');
});
var parent = label.parentElement;
var type = input.getAttribute('type');
var isListening = !RegExp(['date', 'checkbox', 'radio', 'hidden', 'file'].join('|')).test(type);
var isInFormGroup = parent.classList.contains('form-group') && parent.classList.contains('form-group--required');
if (isInFormGroup) {
window.utils.reactiveFormGroup(parent, input);
}
if (isListening) {
window.utils.reactiveInputLabel(input, label);
} else {
label.classList.remove('reactive-label');
}
// initialize radios
Array.from(document.querySelectorAll('input[type="radio"]')).forEach(function(inp) {
window.utils.initializeCheckboxRadio(inp, 'radio');
});
// initialize file-upload-fields
Array.from(document.querySelectorAll('input[type="file"]')).map(function(inp) {
var formGroup = inp.parentNode;
while (!formGroup.classList.contains('form-group') && formGroup !== document.body) {
formGroup = formGroup.parentNode;
}
window.utils.reactiveFileUpload(inp, formGroup);
Array.from(document.querySelectorAll('input[type="file"]')).forEach(function(inp) {
window.utils.initializeFileUpload(inp);
});
// initialize file-checkbox-fields
Array.from(document.querySelectorAll('.js-file-checkbox')).map(function(inp) {
Array.from(document.querySelectorAll('.js-file-checkbox')).forEach(function(inp) {
window.utils.reactiveFileCheckbox(inp);
});
});

View File

@ -1,40 +1,49 @@
/* GENERAL STYLES FOR FORMS */
form {
margin: 20px 0;
}
/* FORM GROUPS */
.form-group {
position: relative;
display: flex;
display: grid;
grid-template-columns: 25% max-content;
grid-auto-columns: 25%;
grid-template-columns: 1fr 3fr;
grid-gap: 5px;
justify-content: flex-start;
align-items: center;
margin: 10px 0;
padding-left: 10px;
align-items: flex-start;
padding: 4px 0;
border-left: 2px solid transparent;
+ .form-group {
margin-top: 13px;
}
}
.form-group__label {
width: 25%;
white-space: nowrap;
font-weight: 600;
padding-top: 6px;
}
@media (max-width: 999px) {
.form-group--required {
.form-group__label::after {
content: ' *';
color: var(--color-error);
}
}
.form-group--has-error {
background-color: rgba(255, 0, 0, 0.1);
input, textarea {
border-color: var(--color-error) !important;
}
}
@media (max-width: 768px) {
.form-group {
grid-template-columns: 1fr;
grid-template-rows: 30px;
align-items: baseline;
margin-top: 17px;
flex-direction: column;
> * {
width: 100%;
}
}
}
@ -43,38 +52,36 @@ input[type="text"],
input[type="password"],
input[type="url"],
input[type="number"],
input[type="email"] {
background-color: rgba(0, 0, 0, 0.05);
padding: 7px 3px 7px;
outline: 0;
border: 0;
border-bottom: 2px solid var(--darkbase);
box-shadow: 0 2px 13px rgba(0, 0, 0, 0.05);
color: var(--fontbase);
transition: all .1s;
font-size: 16px;
min-width: 400px;
input[type="email"],
input[type*="date"],
input[type*="time"] {
/* from bulma.css */
color: #363636;
border-color: #dbdbdb;
background-color: #f3f3f3;
box-shadow: inset 0 1px 2px 1px rgba(50,50,50,.05);
width: 100%;
max-width: 600px;
-webkit-appearance: none;
align-items: center;
border: 1px solid transparent;
border-radius: 4px;
font-size: 1rem;
line-height: 1.5;
padding: 4px 13px;
}
.form-group--required {
input, textarea {
border-bottom-color: var(--lighterbase);
}
input[type="number"] {
width: 100px;
text-align: right;
}
.form-group--valid {
input, textarea {
border-bottom-color: var(--validbase);
}
}
.form-group--has-error {
input, textarea {
border-bottom-color: var(--errorbase);
}
input[type*="date"],
input[type*="time"],
.flatpickr-input[type="text"] {
width: 50%;
width: 250px;
}
input[type="text"]:focus,
@ -82,32 +89,53 @@ input[type="password"]:focus,
input[type="url"]:focus,
input[type="number"]:focus,
input[type="email"]:focus {
border-bottom-color: var(--lightbase);
/* border-bottom-color: var(--color-light);
background-color: transparent;
box-shadow: 0 0 13px var(--lighterbase);
box-shadow: 0 0 13px var(--color-lighter); */
border-color: #3273dc;
box-shadow: 0 0 0 0.125em rgba(50,115,220,.25);
outline: 0;
}
/* BUTTON STYLE SEE default-layout.lucius */
/* TEXTAREAS */
textarea {
outline: 0;
border: 0;
padding: 7px 4px;
min-width: 400px;
min-height: 100px;
font-family: var(--fontfamilybase);
font-size: 16px;
color: var(--fontbase);
background-color: rgba(0, 0, 0, 0.05);
box-shadow: 0 2px 13px rgba(0, 0, 0, 0.05);
border-bottom: 2px solid var(--darkbase);
width: 100%;
height: 170px;
max-width: 600px;
font-size: 1rem;
line-height: 1.5;
color: #363636;
background-color: #f3f3f3;
padding: 4px 13px;
-webkit-appearance: none;
appearance: none;
border: 1px solid #dbdbdb;
border-radius: 2px;
box-shadow: inset 0 1px 2px 1px rgba(50,50,50,.05);
vertical-align: top;
}
textarea:focus {
background-color: transparent;
border-bottom-color: var(--lightbase);
box-shadow: 0 0 13px var(--lighterbase);
border-color: #3273dc;
box-shadow: 0 0 0 0.125em rgba(50,115,220,.25);
outline: 0;
}
/* OPTIONS */
select,
option {
font-size: 1rem;
line-height: 1.5;
padding: 4px 13px;
border: 1px solid #dbdbdb;
border-radius: 2px;
outline: 0;
color: #363636;
min-width: 200px;
background-color: #f3f3f3;
box-shadow: inset 0 1px 2px 1px rgba(50,50,50,.05);
}
/* CUSTOM LEGACY CHECKBOX AND RADIO BOXES */
@ -116,6 +144,7 @@ input[type="checkbox"] {
height: 20px;
width: 20px;
-webkit-appearance: none;
appearance: none;
cursor: pointer;
}
input[type="checkbox"]::before {
@ -123,14 +152,14 @@ input[type="checkbox"]::before {
position: absolute;
width: 20px;
height: 20px;
background-color: var(--lighterbase);
background-color: var(--color-lighter);
display: flex;
align-items: center;
justify-content: center;
border-radius: 2px;
}
input[type="checkbox"]:checked::before {
background-color: var(--lightbase);
background-color: var(--color-light);
}
input[type="checkbox"]:checked::after {
content: '✓';
@ -150,80 +179,56 @@ input[type="checkbox"]:checked::after {
.radio {
position: relative;
> [type="checkbox"],
> [type="radio"] {
[type="checkbox"],
[type="radio"] {
display: none;
}
> label {
label {
display: block;
height: 30px;
width: 30px;
background-color: var(--greybase);
height: 24px;
width: 24px;
background-color: #f3f3f3;
box-shadow: inset 0 1px 2px 1px rgba(50,50,50,.05);
border-radius: 4px;
color: white;
cursor: pointer;
}
> label::before,
> label::after {
label::before,
label::after {
content: '';
position: absolute;
top: 14px;
left: 5px;
top: 11px;
left: 3px;
display: block;
width: 20px;
height: 20px;
background-color: white;
width: 18px;
height: 2px;
background-color: var(--color-font);
transition: all .2s;
transform: scale(0.5, 0.1);
}
> label::before {
width: 20px;
height: 2px;
transform: scale(0.1, 0.1);
}
> label::after {
width: 20px;
height: 2px;
transform: scale(0.1, 0.1);
}
> :checked + label {
background-color: var(--lightbase);
:checked + label {
background-color: var(--color-primary);
text-decoration: underline;
}
&:hover > label {
background-color: var(--lighterbase);
}
&:hover > label::before {
transform: scale(0.8, 0.4);
}
> :checked + label::before {
:checked + label::before {
background-color: white;
transform: scale(1, 1) rotate(45deg);
}
> :checked + label:hover::after,
> :checked + label:hover::before {
transform: scale(1, 1) rotate(0deg);
}
&:hover > label::after {
transform: scale(0.8, 0.4);
}
> :checked + label::after {
:checked + label::after {
background-color: white;
transform: scale(1, 1) rotate(-45deg);
}
}
.radio > label::before {
.radio label::before {
transform: scale(0.01, 0.01) rotate(45deg);
}
.radio > label::after {
.radio label::after {
transform: scale(0.01, 0.01) rotate(-45deg);
}
@ -239,140 +244,16 @@ input[type="checkbox"]:checked::after {
z-index: -1;
}
/* REACTIVE LABELS */
.reactive-label {
cursor: text;
color: var(--fontsec);
transform: translate(0, 0);
transition: all .1s;
}
.reactive-label--small {
cursor: default;
color: var(--fontbase);
}
@media (max-width: 999px) {
.reactive-label {
position: relative;
transform: translate(2px, 30px);
}
.reactive-label--small {
transform: translate(2px, 0px);
color: var(--fontsec);
/*font-size: 14px;*/
}
}
/* CUSTOM FILE INPUT */
input[type="file"].js-file-input {
color: white;
width: 0.1px;
height: 0.1px;
opacity: 0;
overflow: hidden;
position: absolute;
z-index: -1;
outline: 0;
border: 0;
}
.file-input__wrapper {
grid-column-start: 2;
}
.file-input__container,
.file-checkbox__container,
.file-input__unpack {
grid-column-start: 2;
display: flex;
justify-content: space-between;
margin: 4px 0;
}
.file-input__label,
.file-input__remover,
.file-checkbox__label,
.file-checkbox__remover {
display: block;
border-radius: 2px;
padding: 5px 13px;
color: var(--whitebase);
.file-input__label {
cursor: pointer;
}
.file-input__label,
.file-checkbox__label {
text-align: left;
position: relative;
height: 30px;
}
.file-checkbox__label {
background-color: var(--greybase);
text-decoration: line-through;
}
.file-input__label.btn,
.file-checkbox__label.btn {
padding: 5px 13px;
}
.file-input__label::after,
.file-input__label::before {
position: absolute;
content: '';
background-color: white;
width: 16px;
height: 2px;
top: 14px;
top: 50%;
left: 12px;
left: 50%;
display: inline-block;
background-color: var(--color-primary);
color: white;
padding: 10px 17px;
border-radius: 3px;
}
.file-input__label::after {
transform: translate(-50%, -50%) rotate(90deg);
}
.file-input__label::before {
transform: translate(-50%, -50%);
}
.file-checkbox__checkbox {
margin-left: 10px;
}
.file-input__remover {
.file-input__input--hidden {
display: none;
width: 40px;
height: 30px;
text-align: center;
background-color: var(--warningbase);
position: relative;
margin-left: 10px;
}
.file-input__remover::before {
position: absolute;
content: '';
width: 16px;
height: 2px;
top: 14px;
left: 12px;
background-color: white;
}
.file-input__container--valid > .file-input__label {
background-color: var(--lightbase);
}
.file-checkbox__container--checked > .file-checkbox__label {
text-decoration: none;
background-color: var(--lighterbase);
&.btn:hover {
background-color: var(--lighterbase);
text-decoration: line-through;
}
}
.file-input__container--valid > .file-input__label::before,
.file-input__container--valid > .file-input__label::after {
content: none;
}
.file-input__container--valid > .file-input__remover {
display: block;
}
@media (max-width: 999px) {
.file-input__wrapper,
.file-input__container,
.file-checkbox__container,
.file-input__unpack {
grid-column-start: 1;
}
}

View File

@ -10,7 +10,7 @@
max-height: calc(100vh - 30px);
border-radius: 7px;
z-index: -1;
color: var(--fontbase);
color: var(--color-font);
padding: 20px;
overflow: auto;
opacity: 0;
@ -23,17 +23,17 @@
}
}
@media (max-width: 999px) {
@media (max-width: 1024px) {
.modal {
min-width: 80vw;
}
}
@media (max-width: 666px) {
@media (max-width: 768px) {
.modal {
min-width: 90vw;
}
}
@media (max-width: 444px) {
@media (max-width: 425px) {
.modal {
min-width: calc(100vw - 20px);
}
@ -70,7 +70,7 @@
justify-content: center;
width: 30px;
height: 30px;
background-color: var(--darkerbase);
background-color: var(--color-darker);
border-radius: 2px;
cursor: pointer;
z-index: 20;

View File

@ -24,12 +24,12 @@
left: -28px;
top: 10px;
border-left: 8px solid transparent;
border-top: 8px solid var(--lightbase);
border-top: 8px solid var(--color-light);
}
.js-show-hide__toggle:hover::before,
.js-show-hide--collapsed .js-show-hide__toggle::before {
border-left: 8px solid var(--lightbase);
border-left: 8px solid var(--color-light);
border-top: 8px solid transparent;
top: 5px;
left: -22px;

View File

@ -0,0 +1 @@
<!-- only here to be able to include tabber using `toWidget` -->

View File

@ -0,0 +1,7 @@
.tab-opener {
background-color: var(--color-dark);
&.tab-visible {
border-bottom-color: var(--color-primary);
}
}

View File

@ -0,0 +1 @@
<!-- only here to be able to include tooltips using `toWidget` -->

View File

@ -0,0 +1,37 @@
(function() {;
'use strict';
window.utils = window.utils || {};
// allows for multiple file uploads with separate inputs
window.utils.tooltip = function(tt) {
var handle = tt.querySelector('.tooltip__handle');
var content = tt.querySelector('.tooltip__content');
var left = false;
handle.addEventListener('mouseenter', function() {
left = false;
content.classList.toggle('to-left', handle.getBoundingClientRect().left + 300 > window.innerWidth);
content.classList.remove('hidden');
});
handle.addEventListener('mouseleave', function() {
left = true;
window.setTimeout(function() {
if (left) {
content.classList.add('hidden');
}
}, 250);
});
}
})();
document.addEventListener('DOMContentLoaded', function() {
// initialize tooltips
Array.from(document.querySelectorAll('.js-tooltip')).forEach(function(tt) {
window.utils.tooltip(tt);
});
});

View File

@ -0,0 +1,58 @@
.js-tooltip {
position: relative;
.tooltip__handle {
background-color: var(--color-dark);
border-radius: 50%;
height: 1.5rem;
width: 1.5rem;
line-height: 1.5rem;
font-size: 1.2rem;
color: white;
display: inline-block;
text-align: center;
cursor: default;
margin: 0 10px;
}
.tooltip__content {
position: absolute;
top: -10px;
transform: translateY(-100%);
left: 3px;
width: 275px;
z-index: 10;
background-color: #fafafa;
border-radius: 4px;
padding: 13px 17px;
box-shadow: 0 0 20px 4px rgba(0, 0, 0, 0.1);
// display: none;
&.to-left {
left: auto;
right: 3px;
&::after {
left: auto;
right: 10px;
}
}
&::after {
content: '';
width: 16px;
height: 16px;
background-color: #fafafa;
transform: rotate(45deg);
position: absolute;
left: 10px;
// box-shadow: 0 0 4px black;
// outline: 1px solid red;
bottom: -8px;
}
}
.hidden {
display: none;
}
}

View File

@ -46,7 +46,7 @@
#{fileTitle file}&nbsp;
<span .label .label-warning>Gelöscht
$else
<a href=@{SubmissionDownloadSingleR cID $ fileTitle file} download .list-group-item>
<a href=@{SubmissionDownloadSingleR cID' $ fileTitle file} download .list-group-item>
#{fileTitle file}
$if submissionFileIsUpdate sFile
&nbsp;

View File

@ -1,12 +1,18 @@
<table id="#{dbtIdent}">
$newline never
<table id="#{dbtIdent}" .table.table--striped.table--hover>
$maybe sortableP <- pSortable
$with toSortable <- toSortable sortableP
<thead>
$forall OneColonnade{..} <- getColonnade dbtColonnade
^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead}
<tr .table__row>
$forall OneColonnade{..} <- getColonnade dbtColonnade
<!-- TODO: give ths a class 'table__th' -->
<!-- TODO: wrap content of th in 'div.table__th-content' -->
^{widgetFromCell th $ withSortLinks $ toSortable oneColonnadeHead}
$nothing
<tbody>
$forall row <- rows
<tr>
<tr .table__row>
$forall OneColonnade{..} <- getColonnade dbtColonnade
<!-- TODO: give tds a class 'table__td' -->
<!-- TODO: wrap content of td in 'div.table__td-content' -->
^{widgetFromCell td $ oneColonnadeEncode row}

View File

@ -1,45 +1,44 @@
table th {
position: relative;
padding-right: 20px;
/* SORTABLE TABLE */
.table {
&.sortable {
/* TODO: move outside of table as soon as tds and ths get their own class */
th.sortable {
position: relative;
padding-right: 24px;
cursor: pointer;
}
a {
font-weight: 800;
th.sortable::after,
th.sortable::before {
content: '';
position: absolute;
top: 50%;
right: 4px;
width: 0;
height: 0;
border-left: 8px solid transparent;
border-right: 8px solid transparent;
border-bottom: 8px solid rgba(255, 255, 255, 0.4);
}
th.sortable::before {
/* magic numbers to move arrow back in the right position after flipping it.
this allows us to use the same border for the up and the down arrow */
transform: translateY(150%) scale(1, -1);
transform-origin: top;
}
th.sortable::after {
transform: translateY(-150%);
}
th.sortable:hover::before,
th.sortable:hover::after {
border-bottom-color: rgba(255, 255, 255, 0.7);
}
th.sorted-asc::before,
th.sorted-desc::after {
border-bottom-color: white !important;
}
}
table th.sorted-asc,
table th.sorted-desc {
color: var(--lightbase);
}
table th.sortable::after,
table th.sortable::before {
content: '';
position: absolute;
right: 0;
width: 0;
height: 0;
transform: translateY(-100%);
border-left: 8px solid transparent;
border-right: 8px solid transparent;
}
table th.sortable::before {
top: 21px;
border-top: 8px solid rgba(0, 0, 0, 0.1);
}
table th.sortable::after {
top: 9px;
border-bottom: 8px solid rgba(0, 0, 0, 0.1);
}
table th.sorted-asc::before {
border-top: 8px solid var(--lightbase);
}
table th.sorted-desc::after {
border-bottom: 8px solid var(--lightbase);
}

View File

@ -1,3 +1,4 @@
/* PAGINATION */
.pagination {
margin-top: 20px;
text-align: center;
@ -5,25 +6,25 @@
.pagination-link {
margin: 0 7px;
display: inline-block;
background-color: var(--greybase);
background-color: var(--color-grey);
a {
color: var(--whitebase);
color: var(--color-lightwhite);
padding: 7px 13px;
display: inline-block;
}
&:not(.current):hover {
background-color: var(--lighterbase);
background-color: var(--color-lighter);
a {
color: var(--whitebase);
color: var(--color-lightwhite);
}
}
&.current {
pointer-events: none;
background-color: var(--lightbase);
background-color: var(--color-light);
a {
text-decoration: underline;

View File

@ -1,10 +1,10 @@
$maybe flag <- sortableKey
$case directions
$of [SortAsc]
<a href=#{tblLink $ setParam (wIdent "sorting") (Just $ flag <> "-desc")}>
<a .table__th-link href=#{tblLink $ setParam (wIdent "sorting") (Just $ flag <> "-desc")}>
^{cellContents}
$of _
<a href=#{tblLink $ setParam (wIdent "sorting") (Just $ flag <> "-asc")}>
<a .table__th-link href=#{tblLink $ setParam (wIdent "sorting") (Just $ flag <> "-asc")}>
^{cellContents}
$nothing
^{cellContents}

View File

@ -1,4 +1,2 @@
<div .container>
<h1>Semesterübersicht
^{table}

View File

@ -1,24 +1,13 @@
$newline never
<aside .main__aside>
<div .asidenav>
<div .asidenav__box>
<ul .asidenav__list>
$forall menuType <- menuTypes
$case menuType
$of NavbarAside (MenuItem label mIcon route _)
<li .asidenav__list-item :Just route == mcurrentRoute:.asidenav__list-item--active>
<a .asidenav__link-wrapper href=@{route}>
$if isJust mIcon
<div .glyphicon.glyphicon--#{fromMaybe "" mIcon}>
<div .asidenav__link-label>#{label}
$of _
<div .asidenav__box>
<h3 .asidenav__box-title>
$# TODO: this has to come from favourites somehow. Show favourites from older terms?
WiSe 17/18
<ul .asidenav__list>
$forall (Course{..}, courseRoute, pageActions) <- favourites
<li .asidenav__list-item>
<li .asidenav__list-item :highlight courseRoute:.asidenav__list-item--active>
<a .asidenav__link-wrapper href=@{courseRoute}>
<div .asidenav__link-shorthand>#{courseShorthand}
<div .asidenav__link-label>#{courseName}
@ -26,7 +15,7 @@ $newline never
$forall action <- pageActions
$case action
$of PageActionPrime (MenuItem{..})
<li .asidenav__list-item>
<li .asidenav__nested-list-item>
<a .asidenav__link-wrapper href=@{menuItemRoute}>#{menuItemLabel}
$of _

View File

@ -4,7 +4,7 @@
window.utils = window.utils || {};
// Defines a function to turn an element into an interactive aside-navigation.
// If the small is smaller than 999px the navigation is automatically
// If the screen is smaller than 999px the navigation is automatically
// collapsed - even when dynamically resized (e.g. switching from portatit
// to landscape).
// The can user may also manually collapse and expand the navigation by
@ -16,7 +16,7 @@
// (potentially happening) initial collapse of the asidenav
// goes unnoticed by the user.
var animClass = 'main__aside--transitioning';
var aboveCollapsedNav = false;
var hoveringAboveCollapsedNav = false;
init();
function init() {
@ -62,17 +62,21 @@
if (!hasCollapsedClass()) {
return false;
}
aboveCollapsedNav = true;
hoveringAboveCollapsedNav = true;
window.setTimeout(function() {
if (aboveCollapsedNav && !document.body.classList.contains('touch-supported')) {
if (hoveringAboveCollapsedNav && !document.body.classList.contains('touch-supported')) {
asideEl.classList.add('pseudo-hover');
}
}, 800);
}, 200);
}, false);
asideEl.addEventListener('mouseleave', function(event) {
aboveCollapsedNav = false;
asideEl.classList.remove('pseudo-hover');
hoveringAboveCollapsedNav = false;
window.setTimeout(function() {
if (!hoveringAboveCollapsedNav) {
asideEl.classList.remove('pseudo-hover');
}
}, 200);
}, false);
}
};
@ -80,6 +84,18 @@
document.addEventListener('DOMContentLoaded', function() {
utils.aside(document.querySelector('.main__aside'));
var asidenavEl = document.querySelector('.main__aside');
var mainEl = document.querySelector('.main__content');
asidenavEl.style.height = `${mainEl.clientHeight + 75}px`;
window.addEventListener('resize', function() {
window.requestAnimationFrame(function() {
asidenavEl.style.height = `${mainEl.clientHeight + 75}px`;
});
});
// TODO: make it swipeable on mobile and narrower
// utils.aside(asidenavEl);
});

View File

@ -1,40 +1,185 @@
.main__aside {
position: relative;
background-color: #425d79;
position: absolute;
background-color: var(--color-dark);
box-shadow: 0 0 10px rgba(0, 0, 0, 0.3);
z-index: 1;
flex: 0 0 300px;
min-height: calc(100% - 80px);
transition: all .2s ease-out;
width: 24%;
~ .main__content {
padding-left: 24%;
transition: padding-left .2s ease-out;
}
}
.main__aside--transitioning {
transition: flex-basis .2s ease;
/* maximum width of 300px for wide screens */
@media (min-width: 1200px) {
.main__aside {
width: 300px;
~ .main__content {
padding-left: 300px;
}
}
}
.main__aside--transitioning .asidenav__box{
.asidenav {
color: white;
}
.asidenav__box {
transition: opacity .2s ease;
}
.main__aside--collapsed.pseudo-hover {
overflow: visible;
.asidenav__box-title {
padding: 7px 13px;
margin-top: 30px;
background-color: transparent;
transition: all .2s ease;
}
.main__aside--collapsed {
width: 50px;
flex-basis: 50px;
overflow: hidden;
.asidenav__box-title {
width: 50px;
padding: 1px;
font-size: 18px;
text-align: center;
margin-bottom: 0;
background-color: var(--fontsec);
.asidenav__list-item {
position: relative;
color: var(--color-lightwhite);
&:hover {
color: var(--color-link);
background-color: var(--color-lightwhite);
.asidenav__link-shorthand {
transform: scale(1.05, 1.0);
transform-origin: right;
text-shadow: none;
}
> .asidenav__link-wrapper {
color: var(--color-link);
}
.asidenav__nested-list {
transform: translateX(100%);
opacity: 1;
width: 200px;
}
}
+ .asidenav__list-item {
margin-top: 4px;
}
}
/* small list-item-padding for medium to large screens */
@media (min-width: 1024px) {
.asidenav__list-item {
padding-left: 10px;
}
}
.asidenav__list-item--active {
background-color: var(--color-lightwhite);
.asidenav__link-wrapper {
color: var(--color-link);
}
.asidenav__link-shorthand {
transform: scale(1.05, 1.0);
transform-origin: right;
text-shadow: none;
}
}
.asidenav__link-wrapper {
position: relative;
display: flex;
align-items: center;
padding: 7px 10px;
justify-content: flex-start;
color: var(--color-lightwhite);
z-index: 1;
.glyphicon {
width: 50px;
}
.glyphicon + .asidenav__link-label {
padding-left: 0;
}
}
.asidenav__link-shorthand {
display: none;
}
.asidenav__link-label {
line-height: 1;
}
/* hover sub-menus */
.asidenav__nested-list {
position: absolute;
top: 0;
right: 0;
color: var(--color-font);
transform: translateX(0);
opacity: 0;
transition: all .2s ease-out;
width: 0;
overflow: hidden;
z-index: -1;
}
.asidenav__nested-list-item {
position: relative;
color: var(--color-lightwhite);
background-color: var(--color-dark);
&:hover {
color: var(--color-link);
background-color: var(--color-lightwhite);
.asidenav__link-wrapper {
background-color: white;
color: var(--color-link);
}
}
.asidenav__link-wrapper {
padding-left: 13px;
padding-right: 13px;
border-left: 20px solid white;
transition: all .2s ease;
color: var(--color-lightwhite);
}
}
/* STATE COLLAPSED */
@media (max-width: 768px) {
.main__aside {
width: 50px;
flex-basis: 50px;
overflow: hidden;
min-height: calc(100% - 50px);
~ .main__content {
padding-left: 50px;
}
.asidenav__box-title {
width: 50px;
padding: 1px;
font-size: 18px;
text-align: center;
margin-bottom: 0;
}
.asidenav__link-shorthand {
display: flex;
position: static;
background-color: var(--darkbase);
color: var(--whitebase);
height: 50px;
width: 50px;
text-align: center;
@ -50,186 +195,32 @@
align-items: center;
justify-content: center;
}
.asidenav__link-label {
.asidenav__list-item {
padding-left: 0;
}
}
}
.asidenav {
width: 300px;
margin-top: 20px;
color: white;
.js-show-hide__target {
overflow: visible;
}
.js-show-hide__toggle::before {
top: 14px;
right: 12px;
left: auto !important;
}
.js-show-hide__toggle:hover::before,
.js-show-hide--collapsed .js-show-hide__toggle::before {
top: 10px !important;
right: 8px !important;
}
.js-show-hide--collapsed .js-show-hide__toggle:hover::before {
top: 14px !important;
right: 12px !important;
}
}
.asidenav__box-title {
padding: 7px 13px;
margin-top: 13px;
background-color: transparent;
transition: all .2s ease;
a {
color: white;
}
}
/* hover sub-menus */
.asidenav__nested-list {
position: absolute;
top: 0;
right: 0;
color: var(--fontbase);
transform: translateX(0);
opacity: 0;
transition: all .2s ease-out;
width: 0;
overflow: hidden;
z-index: -1;
.asidenav__list-item {
background-color: var(--darkbase);
color: white;
&:first-child {
margin-top: 0;
}
}
.asidenav__link-wrapper {
padding-left: 13px;
padding-right: 13px;
border-left: 20px solid white;
transition: all .2s ease;
&:hover {
background-color: white;
color: var(--darkbase) !important;
border-left: 20px solid var(--darkbase);
}
}
}
.asidenav__list-item {
position: relative;
background-color: white;
color: var(--darkbase);
margin: 4px 0;
&:not(.asidenav__list-item--active):hover {
color: white;
background-color: var(--darkbase);
.asidenav__nested-list {
transform: translateX(100%);
opacity: 1;
width: 200px;
+ .asidenav__list-item {
margin: 0;
}
}
.asidenav__link-wrapper,
.asidenav__link-wrapper {
color: var(--color-lightwhite);
padding: 0;
}
.asidenav__nested-list,
.asidenav__link-label {
color: white;
display: none;
}
.asidenav__link-shorthand {
transform: scale(1.05, 1.0);
transform-origin: right;
.asidenav__list-item--active {
.asidenav__link-wrapper {
background-color: var(--color-lightwhite);
color: var(--color-dark);
}
}
}
}
.asidenav__list-item--active {
background-color: var(--darkbase);
color: white;
.asidenav__link-wrapper {
pointer-events: none;
color: white;
}
.asidenav__link-shorthand {
transform: scale(1.05, 1.0);
transform-origin: right;
}
}
.asidenav__link-wrapper {
position: relative;
display: flex;
height: 50px;
align-items: center;
justify-content: flex-start;
color: var(--darkbase);
z-index: 1;
.glyphicon {
width: 50px;
}
.asidenav__link-shorthand {
display: block;
position: absolute;
color: var(--greybase);
line-height: 50px;
opacity: 0.3;
right: 10px;
top: 0;
font-size: 40px;
text-transform: uppercase;
transition: transform .2s ease;
}
.asidenav__link-label {
padding-left: 13px;
}
.glyphicon + .asidenav__link-label {
padding-left: 0;
}
}
.asidenav__toggler {
position: absolute;
bottom: 20px;
height: 50px;
width: 100%;
display: flex;
align-items: center;
justify-content: center;
transition: background-color .2s ease;
border-top: 1px solid var(--whitebase);
border-bottom: 1px solid var(--whitebase);
cursor: pointer;
&::before {
content: '\e079';
display: block;
font-family: 'Glyphicons Halflings';
color: var(--whitebase);
}
&:hover {
background-color: var(--lightbase);
}
}
.main__aside--collapsed .asidenav__toggler::before {
content: '\e080';
}

View File

@ -1,7 +1,7 @@
$newline never
<div .breadcrumbs__container>
<ul .breadcrumbs__list.list--inline>
$forall bc <- parents
<li .breadcrumbs__item>
<a .breadcrumbs__link href="@{fst bc}">#{snd bc}
&gt;
<li .breadcrumbs__item--active>#{title}
<li .breadcrumbs__item>#{title}

View File

@ -1,14 +1,60 @@
.breadcrumbs__container {
position: relative;
color: white;
z-index: 10;
align-self: flex-end;
margin-bottom: 20px;
transition: margin-bottom .2s ease;
color: var(--color-font);
margin-left: 40px;
margin-top: 25px;
}
.breadcrumbs__container--animated {
transition: left .2s ease;
@media (max-width: 768px) {
.breadcrumbs__container {
margin-left: 20px;
}
}
.breadcrumbs__container .breadcrumbs__link {
color: white;
.breadcrumbs__link {
&:hover {
color: var(--color-fontsec);
}
}
.breadcrumbs__item {
padding-right: 14px;
position: relative;
line-height: 28px;
opacity: 0.8;
z-index: 1;
margin-right: 10px;
&:last-child {
margin-right: 0;
font-weight: 800;
color: var(--color-dark);
top: 1px;
&::after {
content: none;
}
}
--color-separator: var(--color-primary);
&:hover {
opacity: 1;
}
&::after {
content: '';
position: absolute;
top: 11px;
right: 0;
width: 7px;
height: 7px;
border-bottom: 1px solid var(--color-separator);
border-right: 1px solid var(--color-separator);
transform: rotate(-45deg);
z-index: 10;
}
}

View File

@ -5,5 +5,7 @@ $case formLayout
$forall view <- views
<div .form-group :fvRequired view:.form-group--required :not $ fvRequired view:.form-group--optional :isJust $ fvErrors view:.form-group--has-error>
$if not (Blaze.null $ fvLabel view)
<label .form-group__label .reactive-label for=#{fvId view}>#{fvLabel view}
^{fvInput view}
<label .form-group__label for=#{fvId view}>#{fvLabel view}
<div .form-group__input>
$# FIXME: file-input does not have `required` attribute, although set on form-group
^{fvInput view}

View File

@ -3,23 +3,25 @@
window.utils = window.utils || {};
// registers input-listener for each element in <elements> (array) and
// enables <button> if <validation> for these elements returns true
window.utils.reactiveButton = function(elements, button, validation) {
if (elements.length == 0) {
// registers input-listener for each element in <inputs> (array) and
// enables <button> if <validation> for these inputs returns true
window.utils.reactiveButton = function(form, button, validation) {
var requireds = Array.from(form.querySelectorAll('[required]'));
if (requireds.length == 0) {
return false;
}
var checkboxes = elements[0].getAttribute('type') === 'checkbox';
var eventType = checkboxes ? 'change' : 'input';
updateButtonState();
elements.forEach(function(el) {
requireds.forEach(function(el) {
var checkbox = el.getAttribute('type') === 'checkbox';
var eventType = checkbox ? 'change' : 'input';
el.addEventListener(eventType, function() {
updateButtonState();
});
});
function updateButtonState() {
if (validation.call(null, elements) === true) {
if (validation.call(null, requireds) === true) {
button.removeAttribute('disabled');
} else {
button.setAttribute('disabled', 'true');
@ -33,19 +35,21 @@ document.addEventListener('DOMContentLoaded', function() {
// auto reactiveButton submit-buttons with required fields
var forms = document.querySelectorAll('form');
Array.from(forms).forEach(function(form) {
var requireds = form.querySelectorAll('[required]');
var submitBtn = form.querySelector('[type=submit]');
if (submitBtn && requireds) {
window.utils.reactiveButton(Array.from(requireds), submitBtn, function validateForm(inputs) {
var done = true;
inputs.forEach(function(inp) {
var len = inp.value.trim().length;
if (done && len === 0) {
done = false;
}
});
return done;
});
if (submitBtn) {
window.utils.reactiveButton(form, submitBtn, validateForm);
}
});
function validateForm(inputs) {
var done = true;
inputs.forEach(function(inp) {
var len = inp.value.trim().length;
if (done && len === 0) {
done = false;
}
});
return done;
}
});

View File

@ -2,9 +2,17 @@ $newline never
<div .navbar-container>
<nav .navbar.js-sticky-navbar>
<!-- breadcrumbs -->
$if not $ Just HomeR == mcurrentRoute
^{breadcrumbs}
<a href="/" .navbar__logo>
<ul .navbar__list.list--inline>
$forall menuType <- menuTypes
$case menuType
$of NavbarAside (MenuItem label mIcon route _)
<li .navbar__list-item :highlight route:.navbar__list-item--active>
<a .navbar__link-wrapper href=@{route}>
<i .fas.fa-#{fromMaybe "none" mIcon}>
<div .navbar__link-label>#{label}
$of _
<ul .navbar__list.list--inline>
$forall menuType <- menuTypes

View File

@ -1,48 +1,31 @@
(function() {
'use strict';
(function () {
'use strict';
window.utils = window.utils || {};
window.utils = window.utils || {};
window.utils.stickynav = function(nav) {
var ticking = false;
init();
function init() {
nav.style.paddingLeft = document.body.getBoundingClientRect().width < 999 ? '90px' : '';
window.setTimeout(function() {
nav.classList.add('navbar--animated');
}, 200);
checkScroll();
addListener();
}
// checks scroll direction and shows/hides navbar accordingly
function checkScroll() {
var sticky = window.scrollY > 0;
nav.classList.toggle('navbar--sticky', sticky);
ticking = false;
}
function addListener() {
window.addEventListener('scroll', function(e) {
if (!ticking) {
window.requestAnimationFrame(checkScroll);
ticking = true;
}
}, false);
}
window.addEventListener('resize', function() {
nav.style.paddingLeft = document.body.getBoundingClientRect().width < 999 ? '90px' : '';
}, false);
}
window.utils.stickynav = function (nav) {
var ticking = false;
init();
function init() {
window.addEventListener('scroll', function (e) {
if (!ticking) {
window.requestAnimationFrame(update);
ticking = true;
}
}, false);
update();
}
function update() {
var sticky = window.scrollY > 30;
nav.classList.toggle('navbar--sticky', sticky);
ticking = false;
}
}
})();
document.addEventListener('DOMContentLoaded', function() {
utils.stickynav(document.querySelector('.js-sticky-navbar'));
document.addEventListener('DOMContentLoaded', function () {
// utils.stickynav(document.querySelector('.js-sticky-navbar'));
});

View File

@ -6,121 +6,221 @@
justify-content: space-between;
width: 100%;
height: var(--header-height);
padding-right: 5vw;
padding-left: 90px;
background: var(--darkerbase); /* Old browsers */
background: -moz-linear-gradient(bottom, var(--darkerbase) 0%, #425d79 100%); /* FF3.6-15 */
background: -webkit-linear-gradient(bottom, var(--darkerbase) 0%,#425d79 100%); /* Chrome10-25,Safari5.1-6 */
background: linear-gradient(to top, var(--darkerbase) 0%,#425d79 100%); /* W3C, IE10+, FF16+, Chrome26+, Opera12+, Safari7+ */
padding-right: 2vw;
padding-left: calc(24% + 40px);
background: var(--color-darker); /* Old browsers */
background: -moz-linear-gradient(bottom, var(--color-dark) 0%, var(--color-darker) 100%); /* FF3.6-15 */
background: -webkit-linear-gradient(bottom, var(--color-dark) 0%,var(--color-darker) 100%); /* Chrome10-25,Safari5.1-6 */
background: linear-gradient(to top, var(--color-dark) 0%,var(--color-darker) 100%); /* W3C, IE10+, FF16+, Chrome26+, Opera12+, Safari7+ */
color: white;
box-shadow: 0 1px 10px rgba(0, 0, 0, 0.1);
z-index: 10;
top: 0;
left: 0;
overflow: hidden;
transition: height 0.2s ease;
box-shadow: 0 0 4px rgba(0, 0, 0, 0.2);
transition: all .2s cubic-bezier(0.03, 0.43, 0.58, 1);
}
@media (min-width: 1200px) {
.navbar {
padding-left: 340px;
}
}
@media (max-width: 768px) {
.navbar {
padding: 0px;
}
}
.navbar__logo {
position: absolute;
top: 15px;
left: 20px;
transition: all .2s ease;
transform-origin: left;
width: 0px;
color: var(--color-lightwhite);
&:hover {
color: var(--color-lightwhite);
}
&::before {
content: 'UniWorkY';
font-family: var(--font-logo);
font-size: 42px;
font-weight: bold;
letter-spacing: 2px;
}
}
@media (max-width: 1024px) {
.navbar__logo {
transform: scale(0.7);
}
}
@media (max-width: 768px) {
.navbar__logo {
display: none;
}
}
/* links */
.navbar__link-wrapper {
display: flex;
flex-direction: column;
justify-content: center;
align-items: center;
height: var(--header-height);
color: var(--color-lightwhite);
transition: height .2s cubic-bezier(0.03, 0.43, 0.58, 1);
}
.navbar__link-label {
transition: opacity .2s ease;
padding: 0 13px;
text-transform: uppercase;
}
@media (max-width: 768px) {
.navbar__link-label {
padding: 0 7px;
}
}
@media (max-width: 500px) {
.navbar__link-label {
display: none;
}
}
/* navbar list */
.navbar__list {
align-self: flex-end;
white-space: nowrap;
}
/* list item */
.navbar__list-item {
position: relative;
transition: background-color .1s ease;
.glyphicon {
position: relative;
width: 100%;
width: 20px;
height: 20px;
}
.glyphicon::before {
height: 20px;
}
}
.navbar :last-child {
margin-left: auto;
.fas {
height: 20px;
}
}
.navbar .navbar__link-wrapper {
display: flex;
flex-direction: column;
justify-content: center;
align-items: center;
height: 80px;
color: var(--whitebase);
transition: height .2s ease;
}
@media (max-width: 500px) {
.navbar__link-label {
transition: opacity .2s ease;
padding: 0 13px;
color: white;
text-transform: uppercase;
.navbar__list-item {
width: 50px;
}
}
.navbar__list-item--secondary {
margin-left: 20px;
color: var(--greybase);
color: var(--color-grey);
}
@media (max-width: 768px) {
.navbar__list-item--secondary {
margin-left: 0;
}
}
.navbar__list-item--secondary + .navbar__list-item--secondary {
margin-left: 0;
border-left: 0;
}
.navbar__list-item--active {
background-color: white;
color: var(--darkbase);
background-color: var(--color-lightwhite);
color: var(--color-dark);
.navbar__link-wrapper {
color: var(--darkbase);
color: var(--color-dark);
}
}
.navbar__list-item--active .navbar__link-wrapper {
pointer-events: none;
}
.navbar__list-item--active .navbar__link-label {
color: var(--darkbase);
color: var(--color-dark);
}
.navbar .navbar__list-item:not(.navbar__list-item--active):hover {
background-color: var(--darkerbase);
}
.navbar .navbar__list-item:not(.navbar__list-item--active):hover .navbar__link-wrapper {
color: var(--whitebase);
}
.navbar .navbar__list-item:not(.navbar__list-item--active):hover .navbar__link-label {
color: var(--whitebase);
}
.navbar__list-item--secondary .navbar__link-wrapper,
.navbar__list-item--secondary .navbar__link-label {
color: var(--greybase);
background-color: var(--color-darker);
color: var(--color-lightwhite);
}
.navbar__list-item--secondary .navbar__link-wrapper {
color: var(--color-grey);
}
/* sticky state */
.navbar--sticky {
height: var(--header-height-collapsed);
z-index: 100;
.navbar__link-wrapper {
height: 50px;
height: var(--header-height-collapsed);
}
.breadcrumbs__container {
margin-bottom: 7px;
.navbar__logo {
top: 5px;
}
}
}
.navbar--animated {
transition: all .2s ease;
}
.navbar__pushdown {
/*display: none;*/
height: var(--header-height);
transition: height .2s ease;
transition: height .2s cubic-bezier(0.03, 0.43, 0.58, 1);
}
.navbar--sticky + .navbar__pushdown {
display: block;
height: var(--header-height-collapsed);
}
@media (max-width: 768px) {
.navbar,
.navbar__pushdown {
height: var(--header-height-collapsed);
}
.navbar__link-wrapper {
height: var(--header-height-collapsed);
}
}
@media (max-height: 768px) {
.navbar,
.navbar__pushdown {
height: var(--header-height-collapsed);
}
.navbar__link-wrapper {
height: var(--header-height-collapsed);
}
.navbar__logo {
top: 5px;
}
}

View File

@ -1,13 +1,17 @@
.page-nav-prime {
background-color: var(--lightgreybase);
padding: 13px;
margin: 13px 0;
}
.page-nav-prime .pagenav__list {
margin: 7px 0 0;
.pagenav__list {
display: block;
}
.page-nav-prime .pagenav__list-item {
.pagenav__list-item {
display: inline-block;
margin-right: 7px;
&:not(:last-child) {
margin-right: 7px;
padding-right: 7px;
border-right: 1px solid var(--color-primary);
}
}

View File

@ -0,0 +1,8 @@
$# extra protects us against CSRF
#{extra}
$# Maybe display textField for passcode
$maybe secretView <- msecretView
^{fvInput secretView}
$# Always display register/deregister button
^{fvInput btnView}