From f7bab3befc4c42cde430699681f8caf8a959ab39 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Wed, 16 Sep 2020 16:25:08 +0200 Subject: [PATCH 1/5] feat(exams): exam design & school exam rules --- frontend/src/app.sass | 5 + messages/uniworx/de-de-formal.msg | 43 ++++++ messages/uniworx/en-eu.msg | 43 ++++++ models/exams.model | 1 + models/schools.model | 4 + package.yaml | 1 + src/Data/Universe/TH.hs | 40 ++++-- src/Foundation/I18n.hs | 4 + src/Handler/Exam/Edit.hs | 3 +- src/Handler/Exam/Form.hs | 55 +++++++- src/Handler/Exam/New.hs | 3 +- src/Handler/Exam/Show.hs | 2 + src/Handler/School.hs | 24 +++- src/Handler/Utils/Exam.hs | 16 +++ src/Handler/Utils/Form.hs | 96 +++++++++++++ src/Model/Migration.hs | 11 ++ src/Model/Types/Exam.hs | 128 ++++++++++++++++++ src/Model/Types/Security.hs | 3 + src/Utils/Icon.hs | 2 + src/Utils/PathPiece.hs | 18 ++- templates/exam-show.hamlet | 37 +++++ templates/i18n/changelog/de-de-formal.hamlet | 7 + templates/i18n/changelog/en-eu.hamlet | 7 + .../i18n/exam-mode/aids/de-de-formal.hamlet | 9 ++ templates/i18n/exam-mode/aids/en-eu.hamlet | 9 ++ .../i18n/exam-mode/online/de-de-formal.hamlet | 7 + templates/i18n/exam-mode/online/en-eu.hamlet | 7 + .../requiredEquipment/de-de-formal.hamlet | 40 ++++++ .../exam-mode/requiredEquipment/en-eu.hamlet | 40 ++++++ .../synchronicity/de-de-formal.hamlet | 11 ++ .../i18n/exam-mode/synchronicity/en-eu.hamlet | 11 ++ test/Database/Fill.hs | 10 +- 32 files changed, 674 insertions(+), 23 deletions(-) create mode 100644 templates/i18n/exam-mode/aids/de-de-formal.hamlet create mode 100644 templates/i18n/exam-mode/aids/en-eu.hamlet create mode 100644 templates/i18n/exam-mode/online/de-de-formal.hamlet create mode 100644 templates/i18n/exam-mode/online/en-eu.hamlet create mode 100644 templates/i18n/exam-mode/requiredEquipment/de-de-formal.hamlet create mode 100644 templates/i18n/exam-mode/requiredEquipment/en-eu.hamlet create mode 100644 templates/i18n/exam-mode/synchronicity/de-de-formal.hamlet create mode 100644 templates/i18n/exam-mode/synchronicity/en-eu.hamlet diff --git a/frontend/src/app.sass b/frontend/src/app.sass index 56f4d7028..86bb47969 100644 --- a/frontend/src/app.sass +++ b/frontend/src/app.sass @@ -628,6 +628,11 @@ section &.notification--broad max-width: none + &:first-child + margin-top: 0 + &:last-child + margin-bottom: 0 + .form-section-notification display: grid grid-template-columns: 1fr 3fr diff --git a/messages/uniworx/de-de-formal.msg b/messages/uniworx/de-de-formal.msg index ff7a2f644..b6003ac68 100644 --- a/messages/uniworx/de-de-formal.msg +++ b/messages/uniworx/de-de-formal.msg @@ -1829,6 +1829,39 @@ ExamFormOccurrences: Prüfungstermine/Räume ExamFormAutomaticFunctions: Automatische Funktionen ExamFormCorrection: Korrektur ExamFormParts: Teile +ExamFormMode: Ausgestaltung der Prüfung + +ExamModeFormNone: Keine Angabe +ExamModeFormCustom: Benutzerdefiniert +ExamModeFormAids: Erlaubte Hilfsmittel +ExamModeFormOnline: Online/Offline +ExamModeFormSynchronicity: Synchron/Asynchron +ExamModeFormRequiredEquipment: Erforderliche Hilfsmittel +ExamModeFormRequiredEquipmentIdentificationTip: Es wird stets ein Hinweis angezeigt, dass Teilnehmer sich ausweisen können müssen. + +ExamShowAids: Erlaubte Hilfsmittel +ExamShowOnline: Online/Offline +ExamShowSynchronicity: Synchron/Asynchron +ExamShowRequiredEquipment: Erforderliche Hilfsmittel +ExamShowRequiredEquipmentNoneSet: Keine Angabe durch die Kursverwalter +ExamShowIdentificationRequired: Prüfungsteilnehmer müssen sich ausweisen können. Halten Sie dafür einen amtlichen Lichtbildausweis (Personalausweis, Reisepass, Aufenthaltstitel) und Ihren Studierendenausweis bereit. + +ExamOpenBook: Open Book +ExamClosedBook: Closed Book + +ExamOnline: Online +ExamOffline: Offline + +ExamSynchronous: Synchron +ExamAsynchronous: Asynchron + +ExamRequiredEquipmentNone: Nichts +ExamRequiredEquipmentPen: Stift +ExamRequiredEquipmentPaperPen: Stift & Papier +ExamRequiredEquipmentCalculatorPen: Stift & Taschenrechner +ExamRequiredEquipmentCalculatorPaperPen: Stift, Papier & Taschenrechner +ExamRequiredEquipmentWebcamMicrophoneInternet: Webcam & Mikrophon +ExamRequiredEquipmentMicrophoneInternet: Mikrophon ExamCorrectors: Korrektoren ExamCorrectorsTip: Hier eingetragene Korrektoren können zwischen Beginn der Prüfung und "Bewertung abgeschlossen ab" Ergebnisse für alle Teilprüfungen und alle Teilnehmer im System hinterlegen. @@ -1881,6 +1914,9 @@ ExamFinishedMustBeAfterStart: "Ergebnisse sichtbar ab" muss nach Beginn liegen ExamClosedMustBeAfterFinished: "Noten stehen fest ab" muss nach "Ergebnisse sichtbar ab" liegen ExamClosedMustBeAfterStart: "Noten stehen fest ab" muss nach Beginn liegen ExamClosedMustBeAfterEnd: "Noten stehen fest ab" muss nach Ende liegen +ExamRegistrationMustFollowSchoolSeparationFromStart dayCount@Int: Nach Regeln des Instituts #{pluralDE dayCount "muss" "müssen"} zwischen "Anmeldung ab" und "Beginn" mindestens #{dayCount} #{pluralDE dayCount "Tag" "Tage"} liegen. +ExamRegistrationMustFollowSchoolDuration dayCount@Int: Nach Regeln des Instituts #{pluralDE dayCount "muss" "müssen"} zwischen "Anmeldung ab" und "Anmeldung bis" mindestens #{dayCount} #{pluralDE dayCount "Tag" "Tage"} liegen. +ExamModeRequiredForRegistration: Nach Regeln des Institus muss die "Ausgestaltung der Prüfung" vollständig angegeben sein, bevor "Anmeldung ab" festgelegt werden kann. ExamOccurrenceEndMustBeAfterStart eoName@ExamOccurrenceName: Beginn des Termins #{eoName} muss vor seinem Ende liegen ExamOccurrenceStartMustBeAfterExamStart eoName@ExamOccurrenceName: Beginn des Termins #{eoName} muss nach Beginn der Prüfung liegen @@ -2230,6 +2266,13 @@ SchoolName: Name SchoolLdapOrganisations: Assoziierte LDAP-Fragmente SchoolLdapOrganisationsTip: Beim Login via LDAP werden dem Nutzer alle Institute zugeordnet deren assoziierte LDAP-Fragmente im Eintrag des Nutzer gefunden werden SchoolLdapOrganisationMissing: LDAP-Fragment wird benötigt +SchoolExamMinimumRegisterBeforeStart: Minimale Tage zwischen Anmeldebeginn und Termin für Prüfungen +SchoolExamMinimumRegisterBeforeStartTip: Wenn angegeben werden Dozenten gezwungen Anmeldezeitraum und Prüfungstermin stets zusammen einzustellen. +SchoolExamMinimumRegisterDuration: Minimale Anmeldedauer für Prüfungen +SchoolExamMinimumRegisterDurationTip: Wenn angegeben werden Dozenten daran gehindert Anmeldefristen von weniger als der minimalen Dauer für ihre Prüfungen einzustellen. +SchoolExamRequireModeForRegistration: Prüfungsmodus erforderlich für Anmeldung +SchoolExamRequireModeForRegistrationTip: Sollen Dozenten gezwungen werden Prüfungsmodus und Anmeldefrist stets zusammen einzustellen? +SchoolExamDiscouragedModes: Prüfungsmodi mit Warnung SchoolUpdated ssh@SchoolId: #{ssh} erfolgreich angepasst SchoolTitle ssh@SchoolId: Institut „#{ssh}“ diff --git a/messages/uniworx/en-eu.msg b/messages/uniworx/en-eu.msg index 5a28dab5c..2fa32d5c1 100644 --- a/messages/uniworx/en-eu.msg +++ b/messages/uniworx/en-eu.msg @@ -1828,6 +1828,39 @@ ExamFormOccurrences: Occurrences/rooms ExamFormAutomaticFunctions: Automatic functions ExamFormCorrection: Correction ExamFormParts: Exam parts +ExamFormMode: Exam design + +ExamModeFormNone: Not specified +ExamModeFormCustom: Custom +ExamModeFormAids: Permitted exam aids +ExamModeFormOnline: Online/Offline +ExamModeFormSynchronicity: Synchronous/Asynchronous +ExamModeFormRequiredEquipment: Required equipment +ExamModeFormRequiredEquipmentIdentificationTip: There will always be a note informing participants that they will need photo identification. + +ExamShowAids: Permitted exam aids +ExamShowOnline: Online/Offline +ExamShowSynchronicity: Synchronous/Asynchronous +ExamShowRequiredEquipment: Required equipment +ExamShowRequiredEquipmentNoneSet: Not specified +ExamShowIdentificationRequired: Exam participants need to be able to identify themselves. Therefor please ensure that you have official photo identification („Personalausweis“, passport, residence permit) and your student identification at hand during the exam. + +ExamOpenBook: Open book +ExamClosedBook: Closed book + +ExamOnline: Online +ExamOffline: Offline + +ExamSynchronous: Synchronous +ExamAsynchronous: Asynchronous + +ExamRequiredEquipmentNone: Nothing +ExamRequiredEquipmentPen: Pen +ExamRequiredEquipmentPaperPen: Pen & paper +ExamRequiredEquipmentCalculatorPen: Pen & calculator +ExamRequiredEquipmentCalculatorPaperPen: Pen, paper & calculator +ExamRequiredEquipmentWebcamMicrophoneInternet: Webcam & microphone +ExamRequiredEquipmentMicrophoneInternet: Microphone ExamCorrectors: Correctors ExamCorrectorsTip: Correctors configured here may, after the start of the exam and until "Results visible from", enter exam part results for all exam parts and participants. @@ -1880,6 +1913,9 @@ ExamFinishedMustBeAfterStart: "Results visible from" must be after "start" ExamClosedMustBeAfterFinished: "Exam achievements registered" must be after "results visible from" ExamClosedMustBeAfterStart: "Exam achievements registered" must be after "start" ExamClosedMustBeAfterEnd: "Exam achievements registered" must be after "end" +ExamRegistrationMustFollowSchoolSeparationFromStart dayCount: As per school rules there #{pluralEN dayCount "needs" "need"} to be at least #{dayCount} #{pluralEN dayCount "day" "days"} between "Register from" and "Start". +ExamRegistrationMustFollowSchoolDuration dayCount: As per school rules there #{pluralEN dayCount "needs" "need"} to be at least #{dayCount} #{pluralEN dayCount "day" "days"} between "Register from" and "Register to". +ExamModeRequiredForRegistration: As per school rules "Exam design" needs to be fully specified before "Register from" may be set. ExamOccurrenceEndMustBeAfterStart eoName: End of the occurrence #{eoName} must be after it's start ExamOccurrenceStartMustBeAfterExamStart eoName: Start of the occurrence #{eoName} must be after the exam start @@ -2230,6 +2266,13 @@ SchoolName: Name SchoolLdapOrganisations: Associated LDAP fragments SchoolLdapOrganisationsTip: When logging in users are associated with any departments whose associated LDAP fragments are found in the users LDAP entry SchoolLdapOrganisationMissing: LDAP-fragment is required +SchoolExamMinimumRegisterBeforeStart: Minimum number of days between start of registration period and start of exams +SchoolExamMinimumRegisterBeforeStartTip: If specified course administrators will be forced to specify the start of the registration period and the start of the exam at the same time. +SchoolExamMinimumRegisterDuration: Minimum duration of registration period for exams +SchoolExamMinimumRegisterDurationTip: If specified course administrators will be prevented from setting a registration period of less than the specified number of days. +SchoolExamRequireModeForRegistration: Exam design required for registration +SchoolExamRequireModeForRegistrationTip: Should course administrators be forced to fully specify their exam design when setting a registration period? +SchoolExamDiscouragedModes: Exam designs to warn against SchoolUpdated ssh: Successfully edited #{ssh} SchoolTitle ssh: Department „#{ssh}“ diff --git a/models/exams.model b/models/exams.model index d89914768..95a5a50ab 100644 --- a/models/exams.model +++ b/models/exams.model @@ -17,6 +17,7 @@ Exam publicStatistics Bool gradingMode ExamGradingMode description Html Maybe + examMode ExamMode UniqueExam course name ExamPart exam ExamId diff --git a/models/schools.model b/models/schools.model index c5bd3d6ac..950b1c624 100644 --- a/models/schools.model +++ b/models/schools.model @@ -3,6 +3,10 @@ School json name (CI Text) shorthand (CI Text) -- SchoolKey :: SchoolShorthand -> SchoolId + examMinimumRegisterBeforeStart NominalDiffTime Maybe + examMinimumRegisterDuration NominalDiffTime Maybe + examRequireModeForRegistration Bool default=false + examDiscouragedModes ExamModeDNF UniqueSchool name UniqueSchoolShorthand shorthand -- required for Normalisation of CI Text Primary shorthand -- newtype Key School = SchoolKey { unSchoolKey :: SchoolShorthand } diff --git a/package.yaml b/package.yaml index cdc6fdba0..7b2b0fe71 100644 --- a/package.yaml +++ b/package.yaml @@ -158,6 +158,7 @@ other-extensions: - IncoherentInstances - OverloadedLists - UndecidableInstances + - ApplicativeDo default-extensions: - OverloadedStrings diff --git a/src/Data/Universe/TH.hs b/src/Data/Universe/TH.hs index 03250be58..7ebc86ea7 100644 --- a/src/Data/Universe/TH.hs +++ b/src/Data/Universe/TH.hs @@ -14,7 +14,10 @@ import Data.Universe.Helpers (interleave) import Control.Monad (unless) -import Data.List (elemIndex) +import Data.List (elemIndex, nub) + +import Control.Lens hiding (universe) +import Data.Generics.Product.Types -- | Get type var bind name @@ -52,26 +55,37 @@ finiteEnum tName = do |] deriveUniverse, deriveFinite :: Name -> DecsQ -deriveUniverse = deriveUniverse' [e|interleave|] [e|universe|] -deriveFinite tName = fmap concat . sequence $ - [ deriveUniverse' [e|concat|] [e|universeF|] tName - , do - DatatypeInfo{..} <- reifyDatatype tName - [d|instance Finite $(foldl appT (conT datatypeName) $ map (varT . getTVBName) datatypeVars)|] - ] +deriveUniverse tName = view _1 <$> deriveUniverse' [e|interleave|] [e|universe|] ([t|Universe|] `appT`) tName +deriveFinite tName = do + (decs, iCxt) <- deriveUniverse' [e|concat|] [e|universeF|] ([t|Finite|] `appT`) tName + fmap concat . sequence $ + [ pure decs + , do + DatatypeInfo{..} <- reifyDatatype tName + pure <$> instanceD (pure iCxt) (appT [t|Finite|] . foldl appT (conT datatypeName) $ map (varT . getTVBName) datatypeVars) [] + ] -deriveUniverse' :: ExpQ -> ExpQ -> Name -> DecsQ -deriveUniverse' interleaveExp universeExp tName = do +deriveUniverse' :: ExpQ -> ExpQ -> (TypeQ -> TypeQ) -> Name -> Q ([Dec], Cxt) +deriveUniverse' interleaveExp universeExp mkCxt tName = do DatatypeInfo{..} <- reifyDatatype tName - let datatype = foldl appT (conT datatypeName) $ map (varT . getTVBName) datatypeVars - consUniverse ConstructorInfo{..} = do + let consUniverse ConstructorInfo{..} = do unless (null constructorVars) $ fail "Constructors with variables no supported" foldl (\f t -> [e|ap|] `appE` f `appE` sigE universeExp (listT `appT` t)) [e|pure $(conE constructorName)|] $ map pure constructorFields - pure <$> instanceD (cxt []) [t|Universe $(datatype)|] + typ = foldl (\t bndr -> t `appT` varT (getTVBName bndr)) (conT tName) datatypeVars + iCxt = map (mkCxt . pure) $ filter (\t -> any (flip (elemOf types) t) usedTVars) fieldTypes + where usedTVars = filter (\n -> any (`usesVar` n) datatypeCons) $ map getTVBName datatypeVars + usesVar ConstructorInfo{..} n + | n `elem` map getTVBName constructorVars = False + | otherwise = any (elemOf types n) constructorFields + fieldTypes = nub $ concatMap constructorFields datatypeCons + + iCxt' <- cxt iCxt + + (, iCxt') . pure <$> instanceD (pure iCxt') [t|Universe $(typ)|] [ funD 'universe [ clause [] (normalB . appE interleaveExp . listE $ map consUniverse datatypeCons) [] ] diff --git a/src/Foundation/I18n.hs b/src/Foundation/I18n.hs index 71543f2d9..e14b7e802 100644 --- a/src/Foundation/I18n.hs +++ b/src/Foundation/I18n.hs @@ -225,6 +225,10 @@ embedRenderMessage ''UniWorX ''Quoting ("Csv" <>) embedRenderMessage ''UniWorX ''FavouriteReason id embedRenderMessage ''UniWorX ''Sex id embedRenderMessage ''UniWorX ''ExamGradingMode id +embedRenderMessage ''UniWorX ''ExamAidsPreset id +embedRenderMessage ''UniWorX ''ExamOnlinePreset id +embedRenderMessage ''UniWorX ''ExamSynchronicityPreset id +embedRenderMessage ''UniWorX ''ExamRequiredEquipmentPreset id embedRenderMessage ''UniWorX ''AuthenticationMode id diff --git a/src/Handler/Exam/Edit.hs b/src/Handler/Exam/Edit.hs index e284edc76..16fcc6357 100644 --- a/src/Handler/Exam/Edit.hs +++ b/src/Handler/Exam/Edit.hs @@ -25,7 +25,7 @@ postEEditR tid ssh csh examn = do return (cid, exam, template) - ((editExamResult, editExamWidget), editExamEnctype) <- runFormPost . validateForm validateExam . examForm $ Just template + ((editExamResult, editExamWidget), editExamEnctype) <- runFormPost . validateForm (validateExam cid $ Just oldExam) . examForm $ Just template formResult editExamResult $ \ExamForm{..} -> do insertRes <- runDBJobs $ do @@ -48,6 +48,7 @@ postEEditR tid ssh csh examn = do , examPublicStatistics = efPublicStatistics , examGradingMode = efGradingMode , examDescription = efDescription + , examExamMode = efExamMode } when (is _Nothing insertRes) $ do diff --git a/src/Handler/Exam/Form.hs b/src/Handler/Exam/Form.hs index 7674d6ef3..9f3d155b4 100644 --- a/src/Handler/Exam/Form.hs +++ b/src/Handler/Exam/Form.hs @@ -18,6 +18,7 @@ import qualified Data.Map as Map import qualified Data.Set as Set import qualified Database.Esqueleto as E +import qualified Database.Esqueleto.Utils as E import qualified Control.Monad.State.Class as State import Text.Blaze.Html.Renderer.String (renderHtml) @@ -40,6 +41,7 @@ data ExamForm = ExamForm , efGradingRule :: Maybe ExamGradingRule , efBonusRule :: Maybe ExamBonusRule , efOccurrenceRule :: ExamOccurrenceRule + , efExamMode :: ExamMode , efCorrectors :: Set (Either UserEmail UserId) , efExamParts :: Set ExamPartForm } @@ -117,6 +119,8 @@ examForm template html = do <*> optionalActionA (examGradingRuleForm $ efGradingRule =<< template) (fslI MsgExamAutomaticGrading & setTooltip MsgExamAutomaticGradingTip) (is _Just . efGradingRule <$> template) <*> optionalActionA (examBonusRuleForm $ efBonusRule =<< template) (fslI MsgExamBonus) (is _Just . efBonusRule <$> template) <*> examOccurrenceRuleForm (efOccurrenceRule <$> template) + <* aformSection MsgExamFormMode + <*> examModeForm (efExamMode <$> template) <* aformSection MsgExamFormCorrection <*> examCorrectorsForm (efCorrectors <$> template) <* aformSection MsgExamFormParts @@ -302,6 +306,7 @@ examFormTemplate (Entity eId Exam{..}) = do Entity _ ExamCorrector{..} <- correctors return examCorrectorUser ] + , efExamMode = examExamMode } examTemplate :: CourseId -> DB (Maybe ExamForm) @@ -347,11 +352,12 @@ examTemplate cid = runMaybeT $ do , efOccurrences = Set.empty , efExamParts = Set.empty , efCorrectors = Set.empty + , efExamMode = examExamMode oldExam } -validateExam :: (MonadHandler m, HandlerSite m ~ UniWorX) => FormValidator ExamForm m () -validateExam = do +validateExam :: (MonadHandler m, HandlerSite m ~ UniWorX) => CourseId -> Maybe Exam -> FormValidator ExamForm m () +validateExam cId oldExam = do ExamForm{..} <- State.get guardValidation MsgExamRegisterToMustBeAfterRegisterFrom $ NTop efRegisterTo >= NTop efRegisterFrom @@ -377,3 +383,48 @@ validateExam = do ] guardValidation (MsgExamOccurrenceDuplicateName $ eofName a) $ ((/=) `on` eofName) a b + + mSchool <- liftHandler . runDB . E.selectMaybe . E.from $ \(course `E.InnerJoin` school) -> do + E.on $ course E.^. CourseSchool E.==. school E.^. SchoolId + E.where_ $ course E.^. CourseId E.==. E.val cId + return school + + whenIsJust mSchool $ \(Entity _ School{..}) -> do + whenIsJust schoolExamMinimumRegisterBeforeStart $ \minSep -> do + let doValidation + | Just Exam{..} <- oldExam + , not . fromMaybe True $ (>=) <$> examStart <*> (addUTCTime minSep <$> examRegisterFrom) + = warnValidation + | otherwise + = guardValidation + doValidation (MsgExamRegistrationMustFollowSchoolSeparationFromStart . ceiling $ minSep / nominalDay) + . fromMaybe True $ (>=) <$> efStart <*> (addUTCTime minSep <$> efRegisterFrom) + whenIsJust schoolExamMinimumRegisterDuration $ \minDur -> do + let doValidation + | Just Exam{..} <- oldExam + , not . fromMaybe True $ (>=) <$> examRegisterTo <*> (addUTCTime minDur <$> examRegisterFrom) + = warnValidation + | otherwise + = guardValidation + doValidation (MsgExamRegistrationMustFollowSchoolDuration . ceiling $ minDur / nominalDay) + . fromMaybe True $ (>=) <$> efRegisterTo <*> (addUTCTime minDur <$> efRegisterFrom) + when schoolExamRequireModeForRegistration $ do + let doValidation + | Just Exam{ examExamMode = ExamMode{..}, .. } <- oldExam + , or [ is _Nothing examAids + , is _Nothing examOnline + , is _Nothing examSynchronicity + , is _Nothing examRequiredEquipment + ] + , is _Just examRegisterFrom + = warnValidation + | otherwise + = guardValidation + let ExamMode{..} = efExamMode + doValidation MsgExamModeRequiredForRegistration + $ is _Nothing efRegisterFrom + || and [ is _Just examAids + , is _Just examOnline + , is _Just examSynchronicity + , is _Just examRequiredEquipment + ] diff --git a/src/Handler/Exam/New.hs b/src/Handler/Exam/New.hs index ebc1fcde8..7b04df98a 100644 --- a/src/Handler/Exam/New.hs +++ b/src/Handler/Exam/New.hs @@ -24,7 +24,7 @@ postCExamNewR tid ssh csh = do template <- examTemplate cid return (cid, template) - ((newExamResult, newExamWidget), newExamEnctype) <- runFormPost . validateForm validateExam $ examForm template + ((newExamResult, newExamWidget), newExamEnctype) <- runFormPost . validateForm (validateExam cid Nothing) $ examForm template formResult newExamResult $ \ExamForm{..} -> do insertRes <- runDBJobs $ do @@ -49,6 +49,7 @@ postCExamNewR tid ssh csh = do , examGradingMode = efGradingMode , examPublicStatistics = efPublicStatistics , examDescription = efDescription + , examExamMode = efExamMode } whenIsJust insertRes $ \examid -> do insertMany_ diff --git a/src/Handler/Exam/Show.hs b/src/Handler/Exam/Show.hs index e206bc17b..2f206e05a 100644 --- a/src/Handler/Exam/Show.hs +++ b/src/Handler/Exam/Show.hs @@ -190,4 +190,6 @@ getEShowR tid ssh csh examn = do occurrenceMapping :: ExamOccurrenceName -> Maybe Widget occurrenceMapping occName = examOccurrenceMappingDescriptionWidget <$> fmap examOccurrenceMappingRule examExamOccurrenceMapping <*> (examExamOccurrenceMapping >>= Map.lookup occName . examOccurrenceMappingMapping) + + notificationPersonalIdentification = notification NotificationBroad =<< messageIconI Info IconPersonalIdentification MsgExamShowIdentificationRequired $(widgetFile "exam-show") diff --git a/src/Handler/School.hs b/src/Handler/School.hs index 4c72381bf..6b7193073 100644 --- a/src/Handler/School.hs +++ b/src/Handler/School.hs @@ -62,6 +62,10 @@ data SchoolForm = SchoolForm { sfShorthand :: CI Text , sfName :: CI Text , sfOrgUnits :: Set (CI Text) + , sfExamMinimumRegisterBeforeStart + , sfExamMinimumRegisterDuration :: Maybe NominalDiffTime + , sfExamRequireModeForRegistration :: Bool + , sfExamDiscouragedModes :: ExamModeDNF } mkSchoolForm :: Maybe SchoolId -> Maybe SchoolForm -> Form SchoolForm @@ -69,6 +73,10 @@ mkSchoolForm mSsh template = renderAForm FormStandard $ SchoolForm <$> maybe (\f fs -> areq f fs (sfShorthand <$> template)) (\ssh f fs -> aforced f fs (unSchoolKey ssh)) mSsh (textField & cfStrip & cfCI) (fslI MsgSchoolShort) <*> areq (textField & cfStrip & cfCI) (fslI MsgSchoolName) (sfName <$> template) <*> (Set.fromList . mapMaybe (fmap CI.mk . assertM' (not . Text.null) . Text.strip . CI.original) <$> massInputListA (ciField & addDatalist ldapOrgs) (const "") MsgSchoolLdapOrganisationMissing (const Nothing) ("ldap-organisations" :: Text) (fslI MsgSchoolLdapOrganisations & setTooltip MsgSchoolLdapOrganisationsTip) False (Set.toList . sfOrgUnits <$> template)) + <*> aopt daysField (fslI MsgSchoolExamMinimumRegisterBeforeStart & setTooltip MsgSchoolExamMinimumRegisterBeforeStartTip) (sfExamMinimumRegisterBeforeStart <$> template) + <*> aopt daysField (fslI MsgSchoolExamMinimumRegisterDuration & setTooltip MsgSchoolExamMinimumRegisterDurationTip) (sfExamMinimumRegisterDuration <$> template) + <*> apopt checkBoxField (fslI MsgSchoolExamRequireModeForRegistration & setTooltip MsgSchoolExamRequireModeForRegistration) (sfExamRequireModeForRegistration <$> template) + <*> areq (jsonField False) (fslI MsgSchoolExamDiscouragedModes) (sfExamDiscouragedModes <$> template <|> pure (ExamModeDNF predDNFFalse)) where ldapOrgs :: HandlerFor UniWorX (OptionList (CI Text)) ldapOrgs = fmap (mkOptionList . map (\t -> Option (CI.original t) t (CI.original t)) . Set.toAscList) . runDB $ @@ -82,6 +90,10 @@ schoolToForm ssh = do { sfShorthand = schoolShorthand , sfName = schoolName , sfOrgUnits = setOf (folded . _entityVal . _schoolLdapOrgUnit) ldapFrags + , sfExamMinimumRegisterBeforeStart = schoolExamMinimumRegisterBeforeStart + , sfExamMinimumRegisterDuration = schoolExamMinimumRegisterDuration + , sfExamRequireModeForRegistration = schoolExamRequireModeForRegistration + , sfExamDiscouragedModes = schoolExamDiscouragedModes } @@ -94,7 +106,13 @@ postSchoolEditR ssh = do formResult sfResult $ \SchoolForm{..} -> do runDB $ do - update ssh [ SchoolName =. sfName ] + update ssh + [ SchoolName =. sfName + , SchoolExamMinimumRegisterBeforeStart =. sfExamMinimumRegisterBeforeStart + , SchoolExamMinimumRegisterDuration =. sfExamMinimumRegisterDuration + , SchoolExamRequireModeForRegistration =. sfExamRequireModeForRegistration + , SchoolExamDiscouragedModes =. sfExamDiscouragedModes + ] forM_ sfOrgUnits $ \schoolLdapOrgUnit -> void $ upsert SchoolLdap { schoolLdapSchool = Just ssh @@ -131,6 +149,10 @@ postSchoolNewR = do didInsert <- is _Just <$> insertUnique School { schoolShorthand = sfShorthand , schoolName = sfName + , schoolExamMinimumRegisterBeforeStart = sfExamMinimumRegisterBeforeStart + , schoolExamMinimumRegisterDuration = sfExamMinimumRegisterDuration + , schoolExamRequireModeForRegistration = sfExamRequireModeForRegistration + , schoolExamDiscouragedModes = sfExamDiscouragedModes } when didInsert $ do insert_ UserFunction diff --git a/src/Handler/Utils/Exam.hs b/src/Handler/Utils/Exam.hs index 54632cde6..5d2b3c0b9 100644 --- a/src/Handler/Utils/Exam.hs +++ b/src/Handler/Utils/Exam.hs @@ -11,6 +11,7 @@ module Handler.Utils.Exam , _eaocMinimizeRooms, _eaocFinenessCost, _eaocNudge, _eaocNudgeSize , examAutoOccurrence , deregisterExamUsersCount, deregisterExamUsers + , examAidsPresetWidget, examOnlinePresetWidget, examSynchronicityPresetWidget, examRequiredEquipmentPresetWidget ) where import Import @@ -50,6 +51,8 @@ import qualified Data.Char as Char import qualified Data.RFC5051 as RFC5051 +import Handler.Utils.I18n + fetchExamAux :: ( SqlBackendCanRead backend , E.SqlSelect b a @@ -641,3 +644,16 @@ deregisterExamUsersCount eId uids = do deregisterExamUsers :: (MonadIO m, HandlerSite m ~ UniWorX, MonadHandler m, MonadCatch m) => ExamId -> [UserId] -> SqlPersistT m () deregisterExamUsers eId uids = void $ deregisterExamUsersCount eId uids + + +examAidsPresetWidget :: ExamAidsPreset -> Widget +examAidsPresetWidget preset = $(i18nWidgetFile "exam-mode/aids") + +examOnlinePresetWidget :: ExamOnlinePreset -> Widget +examOnlinePresetWidget preset = $(i18nWidgetFile "exam-mode/online") + +examSynchronicityPresetWidget :: ExamSynchronicityPreset -> Widget +examSynchronicityPresetWidget preset = $(i18nWidgetFile "exam-mode/synchronicity") + +examRequiredEquipmentPresetWidget :: ExamRequiredEquipmentPreset -> Widget +examRequiredEquipmentPresetWidget preset = $(i18nWidgetFile "exam-mode/requiredEquipment") diff --git a/src/Handler/Utils/Form.hs b/src/Handler/Utils/Form.hs index 4be16133b..83a7f2f57 100644 --- a/src/Handler/Utils/Form.hs +++ b/src/Handler/Utils/Form.hs @@ -19,6 +19,8 @@ import Handler.Utils.I18n import Handler.Utils.Files +import Handler.Utils.Exam + import Import import Data.Char ( chr, ord, isDigit ) import qualified Data.Char as Char @@ -1944,3 +1946,97 @@ courseParticipantStateIsActiveField optMsg = hoistField liftHandler . isoField ( userOptionsE :: E.SqlQuery (E.SqlExpr (Entity User)) -> Handler (OptionList UserId) userOptionsE = fmap (fmap entityKey) . flip optionsCryptoIdE userDisplayName + + +data CustomPresetFormOption p + = CPFONone + | CPFOPreset p + | CPFOCustom + deriving (Eq, Ord, Read, Show, Generic, Typeable) +deriveFinite ''CustomPresetFormOption +derivePathPiece ''CustomPresetFormOption (camelToPathPiece' 1) "--" + +customPresetForm :: forall a custom preset msg. + ( Finite preset, Ord preset, PathPiece preset + , RenderMessage UniWorX msg + ) + => Iso' a (Either custom preset) + -> Maybe (SomeMessage UniWorX, Maybe Widget) -- ^ Label for none option + -> Maybe (SomeMessage UniWorX, Maybe Widget) -- ^ Label for custom option + -> (preset -> (msg, Maybe Widget)) + -> (Maybe custom -> AForm Handler custom) + -> FieldSettings UniWorX + -> Maybe (Maybe a) + -> AForm Handler (Maybe a) +customPresetForm cpL noneOption customOption toOption customForm fs mPrev + = explainedMultiActionA actionMap options fs mPrev' + where + mPrev' = flip fmap mPrev $ preview (_Just . cpL) >>> \case + Nothing -> CPFONone + Just (Left _) -> CPFOCustom + Just (Right p) -> CPFOPreset p + + options = explainOptionList options' $ hoistMaybe . optionToWidget + where options' = do + MsgRenderer mr <- getMsgRenderer + let olReadExternal t = do + opt <- fromPathPiece t + case opt of + CPFONone -> opt <$ hoistMaybe noneOption + CPFOCustom -> opt <$ hoistMaybe customOption + CPFOPreset _ -> pure opt + olOptions = do + optionInternalValue <- universeF + optionDisplay <- case optionInternalValue of + CPFONone -> views _1 mr <$> hoistMaybe noneOption + CPFOCustom -> views _1 mr <$> hoistMaybe customOption + CPFOPreset p -> return . views _1 mr $ toOption p + let optionExternalValue = toPathPiece optionInternalValue + return Option{..} + return OptionList{..} + optionToWidget = \case + CPFONone -> noneOption ^? _Just . _2 . _Just + CPFOCustom -> customOption ^? _Just . _2 . _Just + CPFOPreset p -> toOption p ^. _2 + + actionMap :: Map (CustomPresetFormOption preset) (AForm Handler (Maybe a)) + actionMap = Map.fromList $ do + opt <- universeF + return . (opt, ) $ case opt of + CPFONone -> pure Nothing + CPFOPreset p -> pure . Just $ cpL # Right p + CPFOCustom -> reviews cpL Just . Left <$> customForm (mPrev ^? _Just . _Just . cpL . _Left) + +examModeForm :: Maybe ExamMode -> AForm Handler ExamMode +examModeForm mPrev = examMode + <$> customPresetForm examSynchronicityEither (Just (SomeMessage MsgExamModeFormNone, Nothing)) (Just (SomeMessage MsgExamModeFormCustom, Nothing)) (id &&& Just . examSynchronicityPresetWidget) (apreq htmlField (fslI MsgExamModeFormSynchronicity)) (fslI MsgExamModeFormSynchronicity) (examSynchronicity <$> mPrev) + <*> customPresetForm examOnlineEither (Just (SomeMessage MsgExamModeFormNone, Nothing)) (Just (SomeMessage MsgExamModeFormCustom, Nothing)) (id &&& Just . examOnlinePresetWidget) (apreq htmlField (fslI MsgExamModeFormOnline)) (fslI MsgExamModeFormOnline) (examOnline <$> mPrev) + <*> customPresetForm examAidsEither (Just (SomeMessage MsgExamModeFormNone, Nothing)) (Just (SomeMessage MsgExamModeFormCustom, Nothing)) (id &&& Just . examAidsPresetWidget) (apreq htmlField (fslI MsgExamModeFormAids)) (fslI MsgExamModeFormAids) (examAids <$> mPrev) + <*> customPresetForm examRequiredEquipmentEither (Just (SomeMessage MsgExamModeFormNone, Nothing)) (Just (SomeMessage MsgExamModeFormCustom, Nothing)) (id &&& Just . examRequiredEquipmentPresetWidget) (apreq htmlField (fslI MsgExamModeFormRequiredEquipment)) (fslI MsgExamModeFormRequiredEquipment & setTooltip MsgExamModeFormRequiredEquipmentIdentificationTip) (examRequiredEquipment <$> mPrev) + where + examMode examSynchronicity examOnline examAids examRequiredEquipment = ExamMode{..} + + examAidsEither :: Iso' ExamAids (Either Html ExamAidsPreset) + examAidsEither = iso examAidsToEither examAidsFromEither + where examAidsToEither (ExamAidsPreset p) = Right p + examAidsToEither (ExamAidsCustom c) = Left c + examAidsFromEither (Right p) = ExamAidsPreset p + examAidsFromEither (Left c) = ExamAidsCustom c + examOnlineEither :: Iso' ExamOnline (Either Html ExamOnlinePreset) + examOnlineEither = iso examOnlineToEither examOnlineFromEither + where examOnlineToEither (ExamOnlinePreset p) = Right p + examOnlineToEither (ExamOnlineCustom c) = Left c + examOnlineFromEither (Right p) = ExamOnlinePreset p + examOnlineFromEither (Left c) = ExamOnlineCustom c + examSynchronicityEither :: Iso' ExamSynchronicity (Either Html ExamSynchronicityPreset) + examSynchronicityEither = iso examSynchronicityToEither examSynchronicityFromEither + where examSynchronicityToEither (ExamSynchronicityPreset p) = Right p + examSynchronicityToEither (ExamSynchronicityCustom c) = Left c + examSynchronicityFromEither (Right p) = ExamSynchronicityPreset p + examSynchronicityFromEither (Left c) = ExamSynchronicityCustom c + examRequiredEquipmentEither :: Iso' ExamRequiredEquipment (Either Html ExamRequiredEquipmentPreset) + examRequiredEquipmentEither = iso examRequiredEquipmentToEither examRequiredEquipmentFromEither + where examRequiredEquipmentToEither (ExamRequiredEquipmentPreset p) = Right p + examRequiredEquipmentToEither (ExamRequiredEquipmentCustom c) = Left c + examRequiredEquipmentFromEither (Right p) = ExamRequiredEquipmentPreset p + examRequiredEquipmentFromEither (Left c) = ExamRequiredEquipmentCustom c diff --git a/src/Model/Migration.hs b/src/Model/Migration.hs index f82b909e2..79b42f8ec 100644 --- a/src/Model/Migration.hs +++ b/src/Model/Migration.hs @@ -950,6 +950,17 @@ customMigrations = Map.fromListWith (>>) INSERT INTO file_content_entry (hash, chunk_hash, ix) (SELECT hash, hash as chunk_hash, 0 as ix FROM file_content_chunk); |] ) + , ( AppliedMigrationKey [migrationVersion|41.0.0|] [version|42.0.0|] + , do + whenM (tableExists "exam") $ + [executeQQ| + ALTER TABLE exam ADD COLUMN "exam_mode" jsonb NOT NULL DEFAULT #{ExamMode Nothing Nothing Nothing Nothing}; + |] + whenM (tableExists "school") $ + [executeQQ| + ALTER TABLE school ADD COLUMN "exam_discouraged_modes" jsonb NOT NULL DEFAULT #{ExamModeDNF predDNFFalse}; + |] + ) ] diff --git a/src/Model/Types/Exam.hs b/src/Model/Types/Exam.hs index 6dbc7122e..ca4f3da94 100644 --- a/src/Model/Types/Exam.hs +++ b/src/Model/Types/Exam.hs @@ -32,6 +32,12 @@ module Model.Types.Exam , hasExamGradingPass, hasExamGradingGrades , ExamPartNumber , _ExamPartNumber, _ExamPartNumber' + , ExamAids(..), ExamAidsPreset(..) + , ExamOnline(..), ExamOnlinePreset(..) + , ExamSynchronicity(..), ExamSynchronicityPreset(..) + , ExamRequiredEquipment(..), ExamRequiredEquipmentPreset(..) + , ExamMode(..) + , ExamModePredicate(..), ExamModeDNF(..) ) where import Import.NoModel @@ -59,6 +65,8 @@ import qualified Data.Foldable import Data.Aeson (genericToJSON, genericParseJSON) +import Model.Types.Security + {-# ANN module ("HLint: ignore Use newtype instead of data" :: String) #-} @@ -427,3 +435,123 @@ pathPieceJSONKey ''ExamPartNumber instance Enum ExamPartNumber where toEnum = review _ExamPartNumber' . toEnum fromEnum = maybe (error "Converting non-numeric ExamPartNumber to Int") fromEnum . preview _ExamPartNumber' + + +data ExamAids + = ExamAidsPreset { examAidsPreset :: ExamAidsPreset } + | ExamAidsCustom { examAidsCustom :: Html } + deriving (Eq, Ord, Read, Show, Generic, Typeable) + +data ExamAidsPreset + = ExamOpenBook + | ExamClosedBook + deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable) + deriving anyclass (Universe, Finite) + +deriveJSON defaultOptions + { constructorTagModifier = camelToPathPiece' 2 + , fieldLabelModifier = camelToPathPiece' 2 + , sumEncoding = TaggedObject "mode" "data" + } ''ExamAids +derivePersistFieldJSON ''ExamAids + +nullaryPathPiece' ''ExamAidsPreset $ nameToPathPiece' 1 +pathPieceJSON ''ExamAidsPreset + +data ExamOnline + = ExamOnlinePreset { examOnlinePreset :: ExamOnlinePreset } + | ExamOnlineCustom { examOnlineCustom :: Html } + deriving (Eq, Ord, Read, Show, Generic, Typeable) + +data ExamOnlinePreset + = ExamOnline + | ExamOffline + deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable) + deriving anyclass (Universe, Finite) + +deriveJSON defaultOptions + { constructorTagModifier = camelToPathPiece' 2 + , fieldLabelModifier = camelToPathPiece' 2 + , sumEncoding = TaggedObject "mode" "data" + } ''ExamOnline +derivePersistFieldJSON ''ExamOnline + +nullaryPathPiece' ''ExamOnlinePreset $ nameToPathPiece' 1 +pathPieceJSON ''ExamOnlinePreset + +data ExamSynchronicity + = ExamSynchronicityPreset { examSynchronicityPreset :: ExamSynchronicityPreset } + | ExamSynchronicityCustom { examSynchronicityCustom :: Html } + deriving (Eq, Ord, Read, Show, Generic, Typeable) + +data ExamSynchronicityPreset + = ExamSynchronous + | ExamAsynchronous + deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable) + deriving anyclass (Universe, Finite) + +deriveJSON defaultOptions + { constructorTagModifier = camelToPathPiece' 2 + , fieldLabelModifier = camelToPathPiece' 2 + , sumEncoding = TaggedObject "mode" "data" + } ''ExamSynchronicity +derivePersistFieldJSON ''ExamSynchronicity + +nullaryPathPiece' ''ExamSynchronicityPreset $ nameToPathPiece' 1 +pathPieceJSON ''ExamSynchronicityPreset + +data ExamRequiredEquipment + = ExamRequiredEquipmentPreset { examRequiredEquipmentPreset :: ExamRequiredEquipmentPreset } + | ExamRequiredEquipmentCustom { examRequiredEquipmentCustom :: Html } + deriving (Eq, Ord, Read, Show, Generic, Typeable) + +data ExamRequiredEquipmentPreset + = ExamRequiredEquipmentNone + | ExamRequiredEquipmentPen + | ExamRequiredEquipmentPaperPen + | ExamRequiredEquipmentCalculatorPen + | ExamRequiredEquipmentCalculatorPaperPen + | ExamRequiredEquipmentWebcamMicrophoneInternet + | ExamRequiredEquipmentMicrophoneInternet + deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable) + deriving anyclass (Universe, Finite) + +deriveJSON defaultOptions + { constructorTagModifier = camelToPathPiece' 2 + , fieldLabelModifier = camelToPathPiece' 2 + , sumEncoding = TaggedObject "mode" "data" + } ''ExamRequiredEquipment +derivePersistFieldJSON ''ExamRequiredEquipment + +nullaryPathPiece' ''ExamRequiredEquipmentPreset $ nameToPathPiece' 3 +pathPieceJSON ''ExamRequiredEquipmentPreset + + +data ExamMode = ExamMode + { examAids :: Maybe ExamAids + , examOnline :: Maybe ExamOnline + , examSynchronicity :: Maybe ExamSynchronicity + , examRequiredEquipment :: Maybe ExamRequiredEquipment + } +deriveJSON defaultOptions + { fieldLabelModifier = camelToPathPiece' 1 + , sumEncoding = UntaggedValue + } ''ExamMode +derivePersistFieldJSON ''ExamMode + +data ExamModePredicate + = ExamModePredAids ExamAidsPreset + | ExamModePredOnline ExamOnlinePreset + | ExamModePredSynchronicity ExamSynchronicityPreset + | ExamModePredRequiredEquipment ExamRequiredEquipmentPreset + deriving (Eq, Ord, Read, Show, Generic, Typeable) +deriveJSON defaultOptions + { constructorTagModifier = camelToPathPiece' 3 + , sumEncoding = TaggedObject "setting" "preset" + } ''ExamModePredicate + +newtype ExamModeDNF = ExamModeDNF { examModeDNF :: PredDNF ExamModePredicate } + deriving (Eq, Ord, Read, Show, Generic, Typeable) + deriving newtype (Semigroup, Monoid, ToJSON, FromJSON) + +derivePersistFieldJSON ''ExamModeDNF diff --git a/src/Model/Types/Security.hs b/src/Model/Types/Security.hs index 9df7be8ab..bd2e27c02 100644 --- a/src/Model/Types/Security.hs +++ b/src/Model/Types/Security.hs @@ -184,6 +184,9 @@ dnfAssumeValue var val disagrees PLNegated{..} = plVar == var && val disagrees PLVariable{..} = plVar == var && not val +predDNFFalse :: PredDNF a +predDNFFalse = PredDNF $ Set.empty + data UserGroupName = UserGroupMetrics diff --git a/src/Utils/Icon.hs b/src/Utils/Icon.hs index e401f2db7..bbe18b4ba 100644 --- a/src/Utils/Icon.hs +++ b/src/Utils/Icon.hs @@ -86,6 +86,7 @@ data Icon | IconFileUploadSession | IconStandaloneFieldError | IconFileUser + | IconPersonalIdentification deriving (Eq, Ord, Enum, Bounded, Show, Read, Generic, Typeable) iconText :: Icon -> Text @@ -150,6 +151,7 @@ iconText = \case IconFileUploadSession -> "file-upload" IconStandaloneFieldError -> "exclamation" IconFileUser -> "file-user" + IconPersonalIdentification -> "id-card" instance Universe Icon instance Finite Icon diff --git a/src/Utils/PathPiece.hs b/src/Utils/PathPiece.hs index 11be9154b..939f47058 100644 --- a/src/Utils/PathPiece.hs +++ b/src/Utils/PathPiece.hs @@ -27,7 +27,7 @@ import qualified Data.HashMap.Strict as HashMap import Numeric.Natural -import Data.List (foldl) +import Data.List (nub, foldl) import Data.Aeson.Types import qualified Data.Aeson.Types as Aeson @@ -37,6 +37,9 @@ import Control.Monad.Fail import Data.Binary (Binary) import qualified Data.Binary as Binary +import Control.Lens +import Data.Generics.Product.Types + mkFiniteFromPathPiece :: Name -> Q ([Dec], Exp) mkFiniteFromPathPiece finiteType = do @@ -105,7 +108,7 @@ derivePathPiece adt mangle joinPP = do [] finDecs = [ pragInlD mapName NoInline FunLike AllPhases - , sigD mapName [t|HashMap Text ([Text] -> Maybe $(conT adt))|] + , sigD mapName $ forallT [] (cxt iCxt) [t|HashMap Text ([Text] -> Maybe $(typ))|] , funD mapName [ clause [] (normalB finClause) [] ] ] @@ -123,8 +126,17 @@ derivePathPiece adt mangle joinPP = do , match wildP (normalB [e|Nothing|]) [] ] ] + typ = foldl (\t bndr -> t `appT` varT (tvarName bndr)) (conT adt) datatypeVars + iCxt = map (appT [t|PathPiece|] . pure) $ filter (\t -> any (flip (elemOf types) t) usedTVars) fieldTypes + where usedTVars = filter (\n -> any (`usesVar` n) datatypeCons) $ map tvarName datatypeVars + usesVar ConstructorInfo{..} n + | n `elem` map tvarName constructorVars = False + | otherwise = any (elemOf types n) constructorFields + fieldTypes = nub $ concatMap constructorFields datatypeCons + tvarName (PlainTV n) = n + tvarName (KindedTV n _) = n sequence . (finDecs ++ ) . pure $ - instanceD (cxt []) [t|PathPiece $(conT adt)|] + instanceD (cxt iCxt) [t|PathPiece $(typ)|] [ funD 'toPathPiece (map toClause datatypeCons) , funD 'fromPathPiece diff --git a/templates/exam-show.hamlet b/templates/exam-show.hamlet index 176cf01fd..a28c0ed51 100644 --- a/templates/exam-show.hamlet +++ b/templates/exam-show.hamlet @@ -41,6 +41,41 @@ $maybe desc <- examDescription $maybe publishAssignments <- examPublishOccurrenceAssignments
_{MsgExamPublishOccurrenceAssignmentsParticipant}
^{formatTimeW SelFormatDateTime publishAssignments} + $maybe online <- examOnline examExamMode +
_{MsgExamShowOnline} +
+ $case online + $of ExamOnlinePreset p + ^{examOnlinePresetWidget p} + $of ExamOnlineCustom c + #{c} + $maybe synchronicity <- examSynchronicity examExamMode +
_{MsgExamShowSynchronicity} +
+ $case synchronicity + $of ExamSynchronicityPreset p + ^{examSynchronicityPresetWidget p} + $of ExamSynchronicityCustom c + #{c} + $maybe aids <- examAids examExamMode +
_{MsgExamShowAids} +
+ $case aids + $of ExamAidsPreset p + ^{examAidsPresetWidget p} + $of ExamAidsCustom c + #{c} + $maybe requiredEquipment <- examRequiredEquipment examExamMode +
_{MsgExamShowRequiredEquipment} +
+

+ $case requiredEquipment + $of ExamRequiredEquipmentPreset p + ^{examRequiredEquipmentPresetWidget p} + $of ExamRequiredEquipmentCustom c + #{c} + + ^{notificationPersonalIdentification} $maybe room <- examRoom

_{MsgExamRoom}
#{room} @@ -89,6 +124,8 @@ $maybe desc <- examDescription _{MsgExamRegistration}
^{registerWdgt} + $if is _Nothing (examRequiredEquipment examExamMode) + ^{notificationPersonalIdentification} $if showCloseWidget && is _Nothing examClosed
diff --git a/templates/i18n/changelog/de-de-formal.hamlet b/templates/i18n/changelog/de-de-formal.hamlet index e0e41fb22..76f81b8af 100644 --- a/templates/i18n/changelog/de-de-formal.hamlet +++ b/templates/i18n/changelog/de-de-formal.hamlet @@ -1,5 +1,12 @@ $newline never
+
+ ^{formatGregorianW 2020 09 16} +
+
    +
  • + Es kann nun die Ausgestaltung von Prüfungen angegeben werden. +
    ^{formatGregorianW 2020 08 28}
    diff --git a/templates/i18n/changelog/en-eu.hamlet b/templates/i18n/changelog/en-eu.hamlet index ef3f6e194..5c9da9a2c 100644 --- a/templates/i18n/changelog/en-eu.hamlet +++ b/templates/i18n/changelog/en-eu.hamlet @@ -1,5 +1,12 @@ $newline never
    +
    + ^{formatGregorianW 2020 09 16} +
    +
      +
    • + Exam design can now be specified. +
      ^{formatGregorianW 2020 08 28}
      diff --git a/templates/i18n/exam-mode/aids/de-de-formal.hamlet b/templates/i18n/exam-mode/aids/de-de-formal.hamlet new file mode 100644 index 000000000..10d51fbc0 --- /dev/null +++ b/templates/i18n/exam-mode/aids/de-de-formal.hamlet @@ -0,0 +1,9 @@ +$newline never + +$case preset + $of ExamOpenBook + Alle Offline-Hilfsmittel (z.B. Bücher, Notizen) sind zugelassen (“open book”). +
      + Online-Hilfsmittel (z.B. Internet-Browser, Kommunikationsmedien jeder Form) sind nicht gestattet. + $of ExamClosedBook + Es sind keine Hilsfmittel erlaubt, die über jene, die zur Teilnahme an der Prüfung erforderlich sind (siehe unten), hinausgehen (“closed book”) diff --git a/templates/i18n/exam-mode/aids/en-eu.hamlet b/templates/i18n/exam-mode/aids/en-eu.hamlet new file mode 100644 index 000000000..5401fa769 --- /dev/null +++ b/templates/i18n/exam-mode/aids/en-eu.hamlet @@ -0,0 +1,9 @@ +$newline never + +$case preset + $of ExamOpenBook + All offline aids (e.g. books, notes) are allowed (“open book”). +
      + Online aids (e.g. internet browser, communication media of any kind) are not permitted. + $of ExamClosedBook + No exam aids, beyond the required equipment (see below), are permitted (“closed book”). diff --git a/templates/i18n/exam-mode/online/de-de-formal.hamlet b/templates/i18n/exam-mode/online/de-de-formal.hamlet new file mode 100644 index 000000000..fcba8bf8e --- /dev/null +++ b/templates/i18n/exam-mode/online/de-de-formal.hamlet @@ -0,0 +1,7 @@ +$newline never + +$case preset + $of ExamOnline + Die Prüfung findet aussschließlich online statt oder hat Teile, die ausschließlich online stattfinden + $of ExamOffline + Die Prüfung findet offline in Person statt diff --git a/templates/i18n/exam-mode/online/en-eu.hamlet b/templates/i18n/exam-mode/online/en-eu.hamlet new file mode 100644 index 000000000..bc4030972 --- /dev/null +++ b/templates/i18n/exam-mode/online/en-eu.hamlet @@ -0,0 +1,7 @@ +$newline never + +$case preset + $of ExamOnline + The exam is held entirely online or has parts that are held entirely online + $of ExamOffline + The exam is held offline in person diff --git a/templates/i18n/exam-mode/requiredEquipment/de-de-formal.hamlet b/templates/i18n/exam-mode/requiredEquipment/de-de-formal.hamlet new file mode 100644 index 000000000..df2ef3eab --- /dev/null +++ b/templates/i18n/exam-mode/requiredEquipment/de-de-formal.hamlet @@ -0,0 +1,40 @@ +$newline never + +$case preset + $of ExamRequiredEquipmentNone + Es sind keinerlei eigene Hilfsmittel erforderlich; etwaige benötigte Werkzeuge werden von den Veranstaltern gestellt. + $of ExamRequiredEquipmentPen +
        +
      • Dokumentenechter Stift; nicht rot oder grün + $of ExamRequiredEquipmentPaperPen +
          +
        • Dokumentenechter Stift; nicht rot oder grün +
        • Ausreichend viel unbeschriebenes weißes Paper (A4) + $of ExamRequiredEquipmentCalculatorPen +
            +
          • Dokumentenechter Stift; nicht rot oder grün +
          • Nicht-programmierbarer Taschenrechner + $of ExamRequiredEquipmentCalculatorPaperPen +
              +
            • Dokumentenechter Stift; nicht rot oder grün +
            • Ausreichend viel unbeschriebenes weißes Paper (A4) +
            • Nicht-programmierbarer Taschenrechner + $of ExamRequiredEquipmentWebcamMicrophoneInternet +
                +
              • Webcam mit hinreichender Bildqualität um z.B. Ausweisdokumente lesen zu können +
              • +

                + Mikrophon +

                + Es ist Sorge zu tragen, dass die Prüfung nicht von elektronischen oder anderweitigen Störgeräuschen (Lärm, Mitbewohner, Elektronisches Feedback, etc.) gestört wird +

              • + Für die Dauer der Prüfung hinreichend zuverlässige und performante Anbindung ans Internet (idealerweise Kabelgebunden) + $of ExamRequiredEquipmentMicrophoneInternet +
                  +
                • +

                  + Mikrophon +

                  + Es ist Sorge zu tragen, dass die Prüfung nicht von elektronischen oder anderweitigen Störgeräuschen (Lärm, Mitbewohner, Elektronisches Feedback, etc.) gestört wird +

                • + Für die Dauer der Prüfung hinreichend zuverlässige und performante Anbindung ans Internet (idealerweise Kabelgebunden) diff --git a/templates/i18n/exam-mode/requiredEquipment/en-eu.hamlet b/templates/i18n/exam-mode/requiredEquipment/en-eu.hamlet new file mode 100644 index 000000000..210bb54df --- /dev/null +++ b/templates/i18n/exam-mode/requiredEquipment/en-eu.hamlet @@ -0,0 +1,40 @@ +$newline never + +$case preset + $of ExamRequiredEquipmentNone + No equipment is required; all tools necessary for participating in the exam are provided by the course administrators. + $of ExamRequiredEquipmentPen +
                    +
                  • Pen writing in indelible ink; not red or green + $of ExamRequiredEquipmentPaperPen +
                      +
                    • Pen writing in indelible ink; not red or green +
                    • Sufficient unmarked white paper (A4) + $of ExamRequiredEquipmentCalculatorPen +
                        +
                      • Pen writing in indelible ink; not red or green +
                      • Non-programmable calculator + $of ExamRequiredEquipmentCalculatorPaperPen +
                          +
                        • Pen writing in indelible ink; not red or green +
                        • Sufficient unmarked white paper (A4) +
                        • Non-programmable calculator + $of ExamRequiredEquipmentWebcamMicrophoneInternet +
                            +
                          • Webcam with sufficient image quality to be able to verify photo identification +
                          • +

                            + Microphone +

                            + The participant is required to ensure that the exam is not disturbed by electrical or other kinds of noise (housemates, electronic feedback, etc.) +

                          • + Connection to the internet of sufficient performance and reliability for the duration of the exam (ideally wired) + $of ExamRequiredEquipmentMicrophoneInternet +
                              +
                            • +

                              + Microphone +

                              + The participant is required to ensure that the exam is not disturbed by electrical or other kinds of noise (housemates, electronic feedback, etc.) +

                            • + Connection to the internet of sufficient performance and reliability for the duration of the exam (ideally wired) diff --git a/templates/i18n/exam-mode/synchronicity/de-de-formal.hamlet b/templates/i18n/exam-mode/synchronicity/de-de-formal.hamlet new file mode 100644 index 000000000..a5dd1f44d --- /dev/null +++ b/templates/i18n/exam-mode/synchronicity/de-de-formal.hamlet @@ -0,0 +1,11 @@ +$newline never + +$case preset + $of ExamSynchronous + Die Teilnehmer der Prüfung erhalten zu einem festen, kurzen Zeitintervall die Möglichkeit, an ihrer Prüfungsleistung zu arbeiten. +
                              + Beispiele für synchrone Prüfungsformen sind Klausuren, mündliche Prüfungen und Praktikumsabnahmen. + $of ExamAsynchronous + Die Teilnehmer der Prüfung können bis zum Abgabezeitpunkt über einen längeren Zeitraum prinzipiell asynchron an ihrer Prüfungsleistung arbeiten. +
                              + Beispiele für asynchrone Prüfungsformen sind Hausarbeiten und Seminararbeiten. diff --git a/templates/i18n/exam-mode/synchronicity/en-eu.hamlet b/templates/i18n/exam-mode/synchronicity/en-eu.hamlet new file mode 100644 index 000000000..4efc766e8 --- /dev/null +++ b/templates/i18n/exam-mode/synchronicity/en-eu.hamlet @@ -0,0 +1,11 @@ +$newline never + +$case preset + $of ExamSynchronous + The participants are given a fixed, short interval of time during which they are given the opportunity to work on their exam performance. +
                              + Examples of synchronous exams are written exams, oral examinations. + $of ExamAsynchronous + The participants can work on their exam performance over a longer period of time in an asynchronous fashion. +
                              + Examples of asynchronous exams are term papers and seminar papers. diff --git a/test/Database/Fill.hs b/test/Database/Fill.hs index 0292308da..4c4b0581c 100644 --- a/test/Database/Fill.hs +++ b/test/Database/Fill.hs @@ -365,8 +365,8 @@ fillDb = do , termLectureEnd , termActive = term >= currentTerm } - ifi <- insert' $ School "Institut für Informatik" "IfI" - mi <- insert' $ School "Institut für Mathematik" "MI" + ifi <- insert' $ School "Institut für Informatik" "IfI" (Just $ 14 * nominalDay) (Just $ 10 * nominalDay) True (ExamModeDNF predDNFFalse) + mi <- insert' $ School "Institut für Mathematik" "MI" Nothing Nothing False (ExamModeDNF predDNFFalse) void . insert' $ UserFunction gkleen ifi SchoolAdmin void . insert' $ UserFunction gkleen mi SchoolAdmin void . insert' $ UserFunction fhamann ifi SchoolAdmin @@ -665,6 +665,12 @@ fillDb = do , examPublicStatistics = True , examGradingMode = ExamGradingGrades , examDescription = Nothing + , examExamMode = ExamMode + { examAids = Just $ ExamAidsPreset ExamClosedBook + , examOnline = Just $ ExamOnlinePreset ExamOffline + , examSynchronicity = Just $ ExamSynchronicityPreset ExamSynchronous + , examRequiredEquipment = Just $ ExamRequiredEquipmentPreset ExamRequiredEquipmentNone + } } void . insertMany $ map (\u -> ExamRegistration examFFP u Nothing now) [ fhamann From f9c50c80f22770f5376396923b8921eaac3e7216 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Thu, 17 Sep 2020 13:05:01 +0200 Subject: [PATCH 2/5] feat(exams): check exam_discouraged_modes --- messages/uniworx/de-de-formal.msg | 1 + messages/uniworx/en-eu.msg | 1 + src/Handler/Exam/Form.hs | 3 +++ src/Handler/Exam/Show.hs | 10 ++++++++-- src/Handler/School.hs | 2 +- src/Handler/Utils/Exam.hs | 23 +++++++++++++++++++++++ src/Model/Types/Exam.hs | 4 +++- templates/exam-show.hamlet | 3 +++ 8 files changed, 43 insertions(+), 4 deletions(-) diff --git a/messages/uniworx/de-de-formal.msg b/messages/uniworx/de-de-formal.msg index b6003ac68..b46939abf 100644 --- a/messages/uniworx/de-de-formal.msg +++ b/messages/uniworx/de-de-formal.msg @@ -1917,6 +1917,7 @@ ExamClosedMustBeAfterEnd: "Noten stehen fest ab" muss nach Ende liegen ExamRegistrationMustFollowSchoolSeparationFromStart dayCount@Int: Nach Regeln des Instituts #{pluralDE dayCount "muss" "müssen"} zwischen "Anmeldung ab" und "Beginn" mindestens #{dayCount} #{pluralDE dayCount "Tag" "Tage"} liegen. ExamRegistrationMustFollowSchoolDuration dayCount@Int: Nach Regeln des Instituts #{pluralDE dayCount "muss" "müssen"} zwischen "Anmeldung ab" und "Anmeldung bis" mindestens #{dayCount} #{pluralDE dayCount "Tag" "Tage"} liegen. ExamModeRequiredForRegistration: Nach Regeln des Institus muss die "Ausgestaltung der Prüfung" vollständig angegeben sein, bevor "Anmeldung ab" festgelegt werden kann. +ExamModeSchoolDiscouraged: Nach Regeln des Instituts wird von der angegebenen "Ausgestaltung der Prüfung" abgeraten ExamOccurrenceEndMustBeAfterStart eoName@ExamOccurrenceName: Beginn des Termins #{eoName} muss vor seinem Ende liegen ExamOccurrenceStartMustBeAfterExamStart eoName@ExamOccurrenceName: Beginn des Termins #{eoName} muss nach Beginn der Prüfung liegen diff --git a/messages/uniworx/en-eu.msg b/messages/uniworx/en-eu.msg index 2fa32d5c1..79456dd64 100644 --- a/messages/uniworx/en-eu.msg +++ b/messages/uniworx/en-eu.msg @@ -1916,6 +1916,7 @@ ExamClosedMustBeAfterEnd: "Exam achievements registered" must be after "end" ExamRegistrationMustFollowSchoolSeparationFromStart dayCount: As per school rules there #{pluralEN dayCount "needs" "need"} to be at least #{dayCount} #{pluralEN dayCount "day" "days"} between "Register from" and "Start". ExamRegistrationMustFollowSchoolDuration dayCount: As per school rules there #{pluralEN dayCount "needs" "need"} to be at least #{dayCount} #{pluralEN dayCount "day" "days"} between "Register from" and "Register to". ExamModeRequiredForRegistration: As per school rules "Exam design" needs to be fully specified before "Register from" may be set. +ExamModeSchoolDiscouraged: As per school rules the specified "Exam design" is discouraged ExamOccurrenceEndMustBeAfterStart eoName: End of the occurrence #{eoName} must be after it's start ExamOccurrenceStartMustBeAfterExamStart eoName: Start of the occurrence #{eoName} must be after the exam start diff --git a/src/Handler/Exam/Form.hs b/src/Handler/Exam/Form.hs index 9f3d155b4..666b5af2e 100644 --- a/src/Handler/Exam/Form.hs +++ b/src/Handler/Exam/Form.hs @@ -12,6 +12,7 @@ import Handler.Exam.CorrectorInvite () import Handler.Utils import Handler.Utils.Invitations +import Handler.Utils.Exam (evalExamModeDNF) import Data.Map ((!)) import qualified Data.Map as Map @@ -428,3 +429,5 @@ validateExam cId oldExam = do , is _Just examSynchronicity , is _Just examRequiredEquipment ] + + warnValidation MsgExamModeSchoolDiscouraged . not $ evalExamModeDNF schoolExamDiscouragedModes efExamMode diff --git a/src/Handler/Exam/Show.hs b/src/Handler/Exam/Show.hs index 2f206e05a..b90bde092 100644 --- a/src/Handler/Exam/Show.hs +++ b/src/Handler/Exam/Show.hs @@ -26,8 +26,9 @@ getEShowR tid ssh csh examn = do cTime <- liftIO getCurrentTime mUid <- maybeAuthId - (Entity eId Exam{..}, examParts, examVisible, (gradingVisible, gradingShown), (occurrenceAssignmentsVisible, occurrenceAssignmentsShown), results, result, bonus, occurrences, (registered, mayRegister), registeredCount, lecturerInfoShown) <- runDB $ do + (Entity eId Exam{..}, School{..}, examParts, examVisible, (gradingVisible, gradingShown), (occurrenceAssignmentsVisible, occurrenceAssignmentsShown), results, result, bonus, occurrences, (registered, mayRegister), registeredCount, lecturerInfoShown) <- runDB $ do exam@(Entity eId Exam{..}) <- fetchExam tid ssh csh examn + school <- getJust examCourse >>= belongsToJust courseSchool let examVisible = NTop (Just cTime) >= NTop examVisibleFrom @@ -82,7 +83,7 @@ getEShowR tid ssh csh examn = do lecturerInfoShown <- hasReadAccessTo $ CExamR tid ssh csh examn EEditR - return (exam, examParts, examVisible, (gradingVisible, gradingShown), (occurrenceAssignmentsVisible, occurrenceAssignmentsShown), results, result, bonus, occurrences, (registered, mayRegister), registeredCount, lecturerInfoShown) + return (exam, school, examParts, examVisible, (gradingVisible, gradingShown), (occurrenceAssignmentsVisible, occurrenceAssignmentsShown), results, result, bonus, occurrences, (registered, mayRegister), registeredCount, lecturerInfoShown) let occurrenceNamesShown = lecturerInfoShown partNumbersShown = lecturerInfoShown @@ -174,6 +175,11 @@ getEShowR tid ssh csh examn = do let heading = prependCourseTitle tid ssh csh $ CI.original examName + notificationDiscouragedExamMode <- runMaybeT $ do + guard $ evalExamModeDNF schoolExamDiscouragedModes examExamMode + guardM . hasWriteAccessTo $ CExamR tid ssh csh examn EEditR + return $ notification NotificationBroad =<< messageI Warning MsgExamModeSchoolDiscouraged + siteLayoutMsg heading $ do setTitleI heading let diff --git a/src/Handler/School.hs b/src/Handler/School.hs index 6b7193073..2ba5695e4 100644 --- a/src/Handler/School.hs +++ b/src/Handler/School.hs @@ -76,7 +76,7 @@ mkSchoolForm mSsh template = renderAForm FormStandard $ SchoolForm <*> aopt daysField (fslI MsgSchoolExamMinimumRegisterBeforeStart & setTooltip MsgSchoolExamMinimumRegisterBeforeStartTip) (sfExamMinimumRegisterBeforeStart <$> template) <*> aopt daysField (fslI MsgSchoolExamMinimumRegisterDuration & setTooltip MsgSchoolExamMinimumRegisterDurationTip) (sfExamMinimumRegisterDuration <$> template) <*> apopt checkBoxField (fslI MsgSchoolExamRequireModeForRegistration & setTooltip MsgSchoolExamRequireModeForRegistration) (sfExamRequireModeForRegistration <$> template) - <*> areq (jsonField False) (fslI MsgSchoolExamDiscouragedModes) (sfExamDiscouragedModes <$> template <|> pure (ExamModeDNF predDNFFalse)) + <*> areq pathPieceField (fslI MsgSchoolExamDiscouragedModes) (sfExamDiscouragedModes <$> template <|> pure (ExamModeDNF predDNFFalse)) where ldapOrgs :: HandlerFor UniWorX (OptionList (CI Text)) ldapOrgs = fmap (mkOptionList . map (\t -> Option (CI.original t) t (CI.original t)) . Set.toAscList) . runDB $ diff --git a/src/Handler/Utils/Exam.hs b/src/Handler/Utils/Exam.hs index 5d2b3c0b9..1071cc435 100644 --- a/src/Handler/Utils/Exam.hs +++ b/src/Handler/Utils/Exam.hs @@ -12,6 +12,7 @@ module Handler.Utils.Exam , examAutoOccurrence , deregisterExamUsersCount, deregisterExamUsers , examAidsPresetWidget, examOnlinePresetWidget, examSynchronicityPresetWidget, examRequiredEquipmentPresetWidget + , evalExamModeDNF ) where import Import @@ -657,3 +658,25 @@ examSynchronicityPresetWidget preset = $(i18nWidgetFile "exam-mode/synchronicity examRequiredEquipmentPresetWidget :: ExamRequiredEquipmentPreset -> Widget examRequiredEquipmentPresetWidget preset = $(i18nWidgetFile "exam-mode/requiredEquipment") + + +evalExamModeDNF :: ExamModeDNF -> ExamMode -> Bool +evalExamModeDNF (ExamModeDNF PredDNF{..}) ExamMode{..} + = dnfTerms + & map (Set.toList . toNullable) . Set.toList + & map ( maybe True (ofoldr1 (&&)) + . fromNullable + . map (\pl -> bool id not (is _PLNegated pl) . evalPred $ plVar pl) + ) + & maybe False (ofoldr1 (||)) . fromNullable + where + evalPred :: ExamModePredicate -> Bool + evalPred = \case + ExamModePredAids p + -> examAids == Just (ExamAidsPreset p) + ExamModePredOnline p + -> examOnline == Just (ExamOnlinePreset p) + ExamModePredSynchronicity p + -> examSynchronicity == Just (ExamSynchronicityPreset p) + ExamModePredRequiredEquipment p + -> examRequiredEquipment == Just (ExamRequiredEquipmentPreset p) diff --git a/src/Model/Types/Exam.hs b/src/Model/Types/Exam.hs index ca4f3da94..6938ef227 100644 --- a/src/Model/Types/Exam.hs +++ b/src/Model/Types/Exam.hs @@ -549,9 +549,11 @@ deriveJSON defaultOptions { constructorTagModifier = camelToPathPiece' 3 , sumEncoding = TaggedObject "setting" "preset" } ''ExamModePredicate +derivePathPiece ''ExamModePredicate (camelToPathPiece' 3) "--" +deriveFinite ''ExamModePredicate newtype ExamModeDNF = ExamModeDNF { examModeDNF :: PredDNF ExamModePredicate } deriving (Eq, Ord, Read, Show, Generic, Typeable) - deriving newtype (Semigroup, Monoid, ToJSON, FromJSON) + deriving newtype (Semigroup, Monoid, ToJSON, FromJSON, PathPiece) derivePersistFieldJSON ''ExamModeDNF diff --git a/templates/exam-show.hamlet b/templates/exam-show.hamlet index a28c0ed51..040b3554a 100644 --- a/templates/exam-show.hamlet +++ b/templates/exam-show.hamlet @@ -20,6 +20,9 @@ $maybe desc <- examDescription #{desc}
                              + $maybe warn <- notificationDiscouragedExamMode + ^{warn} +
                              $if not examVisible
                              _{MsgExamVisibleFrom} From 65e06882d2491da5e30b1401db6ecc81efcac58b Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Thu, 17 Sep 2020 13:31:41 +0200 Subject: [PATCH 3/5] fix: tests --- .hlint.yaml | 1 + src/Model/Migration.hs | 4 ++-- src/Model/Types/Security.hs | 2 +- test/ModelSpec.hs | 18 ++++++++++++++++++ 4 files changed, 22 insertions(+), 3 deletions(-) diff --git a/.hlint.yaml b/.hlint.yaml index f12dfd72c..5414d2724 100644 --- a/.hlint.yaml +++ b/.hlint.yaml @@ -12,6 +12,7 @@ - ignore: { name: "Use ***" } - ignore: { name: "Redundant void" } - ignore: { name: "Too strict maybe" } + - ignore: { name: "Use Just" } - arguments: - -XQuasiQuotes diff --git a/src/Model/Migration.hs b/src/Model/Migration.hs index 79b42f8ec..55d1ee4ca 100644 --- a/src/Model/Migration.hs +++ b/src/Model/Migration.hs @@ -952,11 +952,11 @@ customMigrations = Map.fromListWith (>>) ) , ( AppliedMigrationKey [migrationVersion|41.0.0|] [version|42.0.0|] , do - whenM (tableExists "exam") $ + whenM (tableExists "exam") [executeQQ| ALTER TABLE exam ADD COLUMN "exam_mode" jsonb NOT NULL DEFAULT #{ExamMode Nothing Nothing Nothing Nothing}; |] - whenM (tableExists "school") $ + whenM (tableExists "school") [executeQQ| ALTER TABLE school ADD COLUMN "exam_discouraged_modes" jsonb NOT NULL DEFAULT #{ExamModeDNF predDNFFalse}; |] diff --git a/src/Model/Types/Security.hs b/src/Model/Types/Security.hs index bd2e27c02..f984a38d9 100644 --- a/src/Model/Types/Security.hs +++ b/src/Model/Types/Security.hs @@ -185,7 +185,7 @@ dnfAssumeValue var val disagrees PLVariable{..} = plVar == var && not val predDNFFalse :: PredDNF a -predDNFFalse = PredDNF $ Set.empty +predDNFFalse = PredDNF Set.empty data UserGroupName diff --git a/test/ModelSpec.hs b/test/ModelSpec.hs index 043786e83..cb7708b2f 100644 --- a/test/ModelSpec.hs +++ b/test/ModelSpec.hs @@ -39,6 +39,8 @@ import qualified Data.Conduit.Combinators as C import Data.Ratio ((%)) +import Data.Universe + instance Arbitrary EmailAddress where arbitrary = do @@ -167,6 +169,18 @@ instance Monad m => Arbitrary (File m) where | otherwise = False +instance Arbitrary ExamModePredicate where + arbitrary = elements universeF + +instance Arbitrary p => Arbitrary (PredLiteral p) where + arbitrary = elements [PLVariable, PLNegated] <*> arbitrary + +instance (Arbitrary p, Ord p) => Arbitrary (PredDNF p) where + arbitrary = PredDNF . Set.fromList . mapMaybe (fromNullable . Set.fromList) <$> arbitrary + shrink = fmap (PredDNF . Set.fromList . mapMaybe (fromNullable . Set.fromList)) . shrink . map otoList . otoList . dnfTerms + +deriving newtype instance Arbitrary ExamModeDNF + instance Arbitrary School where arbitrary = do names <- listOf1 $ pack . getPrintableString <$> arbitrary @@ -174,6 +188,10 @@ instance Arbitrary School where name = Text.toTitle $ unwords names schoolShorthand = CI.mk $ Text.filter Char.isUpper name schoolName = CI.mk name + schoolExamMinimumRegisterBeforeStart <- arbitrary + schoolExamMinimumRegisterDuration <- arbitrary + schoolExamRequireModeForRegistration <- arbitrary + schoolExamDiscouragedModes <- arbitrary return School{..} instance Arbitrary Term where From 0e1035ddb084064212ddba037889cf1e9affd154 Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Mon, 28 Sep 2020 12:23:38 +0200 Subject: [PATCH 4/5] refactor: generalize mkFaqItems --- src/Foundation/I18n.hs | 4 -- src/Foundation/SiteLayout.hs | 2 +- src/Foundation/Yesod/Middleware.hs | 1 - src/Handler/Info.hs | 2 +- src/Handler/Info/TH.hs | 50 ------------------------ src/Handler/News.hs | 2 +- src/Handler/SystemMessage.hs | 4 +- src/Handler/Utils/I18n.hs | 24 ++---------- src/Settings.hs | 9 +---- src/Settings/Locale.hs | 21 ++++++++++ src/Utils.hs | 12 +----- src/Utils/DateTime.hs | 2 + src/Utils/I18n.hs | 44 +++++++++++++++++++++ src/Utils/NTop.hs | 17 ++++++++ src/Utils/SystemMessage.hs | 5 +-- src/Utils/TH.hs | 63 ++++++++++++++++++++++++++++++ 16 files changed, 162 insertions(+), 100 deletions(-) create mode 100644 src/Settings/Locale.hs create mode 100644 src/Utils/I18n.hs create mode 100644 src/Utils/NTop.hs diff --git a/src/Foundation/I18n.hs b/src/Foundation/I18n.hs index 71543f2d9..90bcc6232 100644 --- a/src/Foundation/I18n.hs +++ b/src/Foundation/I18n.hs @@ -47,10 +47,6 @@ import Data.Text.Lens (packed) import Data.List ((!!)) -appLanguages :: NonEmpty Lang -appLanguages = "de-de-formal" :| ["en-eu"] - - pluralDE :: (Eq a, Num a) => a -- ^ Count -> Text -- ^ Singular diff --git a/src/Foundation/SiteLayout.hs b/src/Foundation/SiteLayout.hs index 765c1b70f..8ca6c3b29 100644 --- a/src/Foundation/SiteLayout.hs +++ b/src/Foundation/SiteLayout.hs @@ -446,7 +446,7 @@ applySystemMessages = liftHandler . maybeT_ . catchMPlus (Proxy @CryptoIDError) guard $ userSystemMessageShown <= Just systemMessageLastChanged guard $ userSystemMessageHidden <= Just systemMessageLastUnhide - (_, smTrans) <- MaybeT $ getSystemMessage appLanguages smId + (_, smTrans) <- MaybeT $ getSystemMessage smId let (summary, content) = case smTrans of Nothing -> (systemMessageSummary, systemMessageContent) diff --git a/src/Foundation/Yesod/Middleware.hs b/src/Foundation/Yesod/Middleware.hs index 6ba2b61ca..1a7183602 100644 --- a/src/Foundation/Yesod/Middleware.hs +++ b/src/Foundation/Yesod/Middleware.hs @@ -7,7 +7,6 @@ import Import.NoFoundation hiding (yesodMiddleware) import Foundation.Type import Foundation.Routes -import Foundation.I18n import Foundation.Authorization import Utils.Metrics diff --git a/src/Handler/Info.hs b/src/Handler/Info.hs index f62a9db0e..7f4749bb6 100644 --- a/src/Handler/Info.hs +++ b/src/Handler/Info.hs @@ -90,7 +90,7 @@ getGlossaryR = msgMap = $(glossaryTerms "glossary") -mkFaqItems "faq" +mkI18nWidgetEnum "FAQ" "faq" mkMessageFor "UniWorX" "FAQItem" "messages/faq" "de-de-formal" faqsWidget :: ( MonadHandler m, HandlerSite m ~ UniWorX diff --git a/src/Handler/Info/TH.hs b/src/Handler/Info/TH.hs index a36694c5c..25c55bdb6 100644 --- a/src/Handler/Info/TH.hs +++ b/src/Handler/Info/TH.hs @@ -1,6 +1,5 @@ module Handler.Info.TH ( glossaryTerms - , mkFaqItems ) where import Import @@ -22,52 +21,3 @@ glossaryTerms basename = do where unPathPiece :: Text -> String unPathPiece = repack . mconcat . map (over _head Char.toUpper) . Text.splitOn "-" - -mkFaqItems :: FilePath -> DecsQ -mkFaqItems basename = do - itemsAvailable <- i18nWidgetFilesAvailable' basename - let items = Map.mapWithKey (\k _ -> "FAQ" <> unPathPiece k) itemsAvailable - sequence - [ dataD (cxt []) dataName [] Nothing - [ normalC (mkName conName) [] - | (_, conName) <- Map.toAscList items - ] - [ derivClause (Just StockStrategy) - [ conT ''Eq - , conT ''Ord - , conT ''Read - , conT ''Show - , conT ''Enum - , conT ''Bounded - , conT ''Generic - , conT ''Typeable - ] - , derivClause (Just AnyclassStrategy) - [ conT ''Universe - , conT ''Finite - ] - ] - , instanceD (cxt []) (conT ''PathPiece `appT` conT dataName) - [ funD 'toPathPiece - [ clause [conP (mkName con) []] (normalB . litE . stringL $ repack int) [] - | (int, con) <- Map.toList items - ] - , funD 'fromPathPiece - [ clause [varP $ mkName "t"] - ( guardedB - [ (,) <$> normalG [e|$(varE $ mkName "t") == int|] <*> [e|Just $(conE $ mkName con)|] - | (int, con) <- Map.toList items - ]) [] - , clause [wildP] (normalB [e|Nothing|]) [] - ] - ] - , sigD (mkName "faqItemMap") [t|Map Text $(conT dataName)|] - , funD (mkName "faqItemMap") - [ clause [] (normalB [e| Map.fromList $(listE . map (\(int, con) -> tupE [litE . stringL $ repack int, conE $ mkName con]) $ Map.toList items) |]) [] - ] - ] - where - unPathPiece :: Text -> String - unPathPiece = repack . mconcat . map (over _head Char.toUpper) . Text.splitOn "-" - - dataName = mkName "FAQItem" diff --git a/src/Handler/News.hs b/src/Handler/News.hs index 04ee47d74..f21875ab3 100644 --- a/src/Handler/News.hs +++ b/src/Handler/News.hs @@ -69,7 +69,7 @@ newsSystemMessages = do (messages', Any anyHidden) <- liftHandler . runDB . runConduit . C.runWriterLC $ transPipe lift (selectKeys [] []) .| C.filterM (hasReadAccessTo . MessageR <=< encrypt) - .| transPipe lift (C.mapMaybeM $ \smId -> fmap (\args@(sm, _) -> (smId, sm, systemMessageToTranslation smId args)) <$> getSystemMessage appLanguages smId) + .| transPipe lift (C.mapMaybeM $ \smId -> fmap (\args@(sm, _) -> (smId, sm, systemMessageToTranslation smId args)) <$> getSystemMessage smId) .| C.filter (\(_, SystemMessage{..}, _) -> NTop systemMessageFrom <= NTop (Just now) && NTop (Just now) < NTop systemMessageTo) .| C.mapMaybeM checkHidden .| C.iterM (\(smId, _, _, _) -> tellShown smId) diff --git a/src/Handler/SystemMessage.hs b/src/Handler/SystemMessage.hs index 79ee42ae6..83d6aa46b 100644 --- a/src/Handler/SystemMessage.hs +++ b/src/Handler/SystemMessage.hs @@ -25,7 +25,7 @@ getMessageR, postMessageR :: CryptoUUIDSystemMessage -> Handler Html getMessageR = postMessageR postMessageR cID = do smId <- decrypt cID - (SystemMessage{..}, translation) <- runDB $ maybe notFound return =<< getSystemMessage appLanguages smId + (SystemMessage{..}, translation) <- runDB $ maybe notFound return =<< getSystemMessage smId let (summary, content) = case translation of Nothing -> (systemMessageSummary, systemMessageContent) Just SystemMessageTranslation{..} -> (systemMessageTranslationSummary, systemMessageTranslationContent) @@ -185,7 +185,7 @@ postMessageListR = do in cell . toWidget $ fromMaybe content summary ] dbtProj DBRow{ dbrOutput = smE@(Entity smId _), .. } = do - smT <- (>>= view _2) <$> getSystemMessage appLanguages smId + smT <- (>>= view _2) <$> getSystemMessage smId return DBRow { dbrOutput = (smE, smT) , .. diff --git a/src/Handler/Utils/I18n.hs b/src/Handler/Utils/I18n.hs index aaf7132f4..7a8ca8c0f 100644 --- a/src/Handler/Utils/I18n.hs +++ b/src/Handler/Utils/I18n.hs @@ -1,24 +1,22 @@ module Handler.Utils.I18n ( i18nWidgetFile - , i18nWidgetFilesAvailable, i18nWidgetFilesAvailable', i18nWidgetFiles + , i18nWidgetFiles + , module Utils.I18n ) where import Import.NoFoundation import Foundation.Type -import Foundation.I18n + +import Utils.I18n import Language.Haskell.TH import Language.Haskell.TH.Syntax (qRunIO) -import qualified Language.Haskell.TH.Syntax as TH import qualified Data.List as List import qualified Data.List.NonEmpty as NonEmpty -import qualified Data.Set as Set import qualified Data.Map as Map -import qualified Data.Text as Text - import System.Directory (listDirectory) @@ -51,20 +49,6 @@ i18nWidgetFile basename = do ] ++ [ clause [wildP] (normalB [e| error "selectLanguage returned an invalid translation" |]) [] ] -- Fallback mostly there so compiler does not complain about non-exhaustive pattern match ] [e|selectLanguage availableTranslations' >>= $(varE ws)|] -i18nWidgetFilesAvailable' :: FilePath -> Q (Map Text (NonEmpty Text)) -i18nWidgetFilesAvailable' basename = do - let i18nDirectory = "templates" "i18n" basename - availableFiles <- qRunIO $ listDirectory i18nDirectory - let fileKinds' = fmap (pack . dropExtension . takeBaseName &&& toTranslation . pack . takeBaseName) availableFiles - fileKinds :: Map Text [Text] - fileKinds = sortWith (NTop . flip List.elemIndex (NonEmpty.toList appLanguages)) . Set.toList <$> Map.fromListWith Set.union [ (kind, Set.singleton l) | (kind, Just l) <- fileKinds' ] - toTranslation fName = (listToMaybe . sortOn length) (mapMaybe ((flip Text.stripPrefix fName . (<>".")) . fst) fileKinds') - - iforM fileKinds $ \kind -> maybe (fail $ "‘" <> i18nDirectory <> "’ has no translations for ‘" <> unpack kind <> "’") return . NonEmpty.nonEmpty - -i18nWidgetFilesAvailable :: FilePath -> Q Exp -i18nWidgetFilesAvailable = TH.lift <=< i18nWidgetFilesAvailable' - i18nWidgetFiles :: FilePath -> Q Exp i18nWidgetFiles basename = do availableTranslations' <- i18nWidgetFilesAvailable' basename diff --git a/src/Settings.hs b/src/Settings.hs index b1b37557b..4e40ba9a4 100644 --- a/src/Settings.hs +++ b/src/Settings.hs @@ -12,6 +12,7 @@ module Settings , module Settings.Mime , module Settings.Cookies , module Settings.Log + , module Settings.Locale ) where import Import.NoModel @@ -55,6 +56,7 @@ import Settings.Cluster import Settings.Mime import Settings.Cookies import Settings.Log +import Settings.Locale import qualified System.FilePath as FilePath @@ -605,10 +607,3 @@ compileTimeAppSettings = case fromJSON $ applyEnvValue False mempty configSettingsYmlValue of Aeson.Error e -> error e Aeson.Success settings -> settings - - -getTimeLocale' :: [Lang] -> TimeLocale -getTimeLocale' = $(timeLocaleMap [("de-de", "de_DE.utf8"), ("en-GB", "en_GB.utf8")]) - -appTZ :: TZ -appTZ = $(includeSystemTZ "Europe/Berlin") diff --git a/src/Settings/Locale.hs b/src/Settings/Locale.hs new file mode 100644 index 000000000..f3d0f7a40 --- /dev/null +++ b/src/Settings/Locale.hs @@ -0,0 +1,21 @@ +module Settings.Locale + ( getTimeLocale' + , appTZ + , appLanguages + ) where + +import Utils.DateTime + +import Data.List.NonEmpty + +import Text.Shakespeare.I18N (Lang) + + +getTimeLocale' :: [Lang] -> TimeLocale +getTimeLocale' = $(timeLocaleMap [("de-de", "de_DE.utf8"), ("en-GB", "en_GB.utf8")]) + +appTZ :: TZ +appTZ = $(includeSystemTZ "Europe/Berlin") + +appLanguages :: NonEmpty Lang +appLanguages = "de-de-formal" :| ["en-eu"] diff --git a/src/Utils.hs b/src/Utils.hs index 4e0a169a5..f4aacc548 100644 --- a/src/Utils.hs +++ b/src/Utils.hs @@ -31,6 +31,7 @@ import Utils.Cookies as Utils import Utils.Cookies.Registered as Utils import Utils.Session as Utils import Utils.Csv as Utils +import Utils.NTop as Utils import Text.Blaze (Markup, ToMarkup) @@ -654,16 +655,7 @@ ignoreNothing _ Nothing y = y ignoreNothing _ x Nothing = x ignoreNothing f (Just x) (Just y) = Just $ f x y -newtype NTop a = NTop { nBot :: 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 +-- `NTop` moved to `Utils.NTop` exceptTMaybe :: Monad m => ExceptT e m a -> MaybeT m a exceptTMaybe = MaybeT . fmap (either (const Nothing) Just) . runExceptT diff --git a/src/Utils/DateTime.hs b/src/Utils/DateTime.hs index 27b30c9bf..dc2ce4677 100644 --- a/src/Utils/DateTime.hs +++ b/src/Utils/DateTime.hs @@ -45,6 +45,8 @@ import Algebra.Lattice.Ordered import Control.Monad.Fail +import Utils.Lang (selectLanguage') + -- $(timeLocaleMap _) :: [Lang] -> TimeLocale timeLocaleMap :: [(Lang, String)] -- ^ Languages and matching locales, first is taken as default diff --git a/src/Utils/I18n.hs b/src/Utils/I18n.hs new file mode 100644 index 000000000..2645230e2 --- /dev/null +++ b/src/Utils/I18n.hs @@ -0,0 +1,44 @@ +module Utils.I18n + ( i18nWidgetFilesAvailable, i18nWidgetFilesAvailable' + ) where + +import ClassyPrelude +import Settings.Locale (appLanguages) + +import Language.Haskell.TH +import Language.Haskell.TH.Syntax (qRunIO) +import qualified Language.Haskell.TH.Syntax as TH + +import qualified Data.List as List +import Data.List.NonEmpty (NonEmpty) +import qualified Data.List.NonEmpty as NonEmpty + +import qualified Data.Set as Set +import qualified Data.Map as Map + +import qualified Data.Text as Text + +import System.FilePath +import System.Directory (listDirectory) + +import Utils.NTop + +import Control.Lens (iforM) +import Control.Monad.Fail (fail) + + + +i18nWidgetFilesAvailable' :: FilePath -> Q (Map Text (NonEmpty Text)) +i18nWidgetFilesAvailable' basename = do + let i18nDirectory = "templates" "i18n" basename + availableFiles <- qRunIO $ listDirectory i18nDirectory + let fileKinds' = fmap (pack . dropExtension . takeBaseName &&& toTranslation . pack . takeBaseName) availableFiles + fileKinds :: Map Text [Text] + fileKinds = sortWith (NTop . flip List.elemIndex (NonEmpty.toList appLanguages)) . Set.toList <$> Map.fromListWith Set.union [ (kind, Set.singleton l) | (kind, Just l) <- fileKinds' ] + toTranslation fName = (listToMaybe . sortOn length) (mapMaybe ((flip Text.stripPrefix fName . (<>".")) . fst) fileKinds') + + iforM fileKinds $ \kind -> maybe (fail $ "‘" <> i18nDirectory <> "’ has no translations for ‘" <> unpack kind <> "’") return . NonEmpty.nonEmpty + +i18nWidgetFilesAvailable :: FilePath -> Q Exp +i18nWidgetFilesAvailable = TH.lift <=< i18nWidgetFilesAvailable' + diff --git a/src/Utils/NTop.hs b/src/Utils/NTop.hs new file mode 100644 index 000000000..1199f26c3 --- /dev/null +++ b/src/Utils/NTop.hs @@ -0,0 +1,17 @@ +module Utils.NTop + ( NTop(..) + ) where + +import ClassyPrelude + +-- | treat Nothing as Top for Ord (Maybe a); default implementation treats Nothing as bottom +newtype NTop a = NTop { nBot :: a } + deriving (Read, Show, Generic, Typeable) + deriving newtype (Eq) + +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 + diff --git a/src/Utils/SystemMessage.hs b/src/Utils/SystemMessage.hs index 214cf5b65..9d78b2690 100644 --- a/src/Utils/SystemMessage.hs +++ b/src/Utils/SystemMessage.hs @@ -7,10 +7,9 @@ import Data.List (findIndex) getSystemMessage :: (MonadHandler m, BackendCompatible SqlReadBackend backend) - => NonEmpty Lang -- ^ `appLanguages` - -> SystemMessageId + => SystemMessageId -> ReaderT backend m (Maybe (SystemMessage, Maybe SystemMessageTranslation)) -getSystemMessage appLanguages smId = withReaderT (projectBackend @SqlReadBackend) . runMaybeT $ do +getSystemMessage smId = withReaderT (projectBackend @SqlReadBackend) . runMaybeT $ do SystemMessage{..} <- MaybeT $ get smId translations <- lift $ selectList [SystemMessageTranslationMessage ==. smId] [] let diff --git a/src/Utils/TH.hs b/src/Utils/TH.hs index b233aaa73..b218011d1 100644 --- a/src/Utils/TH.hs +++ b/src/Utils/TH.hs @@ -13,8 +13,18 @@ import Language.Haskell.TH.Datatype import Data.List ((!!), foldl) +import Control.Lens import Control.Monad.Fail +import Utils.I18n + +import qualified Data.Char as Char +import Data.Universe (Universe, Finite) +import qualified Data.Map as Map +import qualified Data.Text as Text + +import Utils.PathPiece + ------------ -- Tuples -- ------------ @@ -188,3 +198,56 @@ dispatchTH dType = do let fName = mkName $ "dispatch" <> nameBase constructorName match (conP constructorName $ map varP pats) (normalB $ foldl (\e pat -> e `appE` varE pat) (varE fName) pats) [] lamCaseE matches + + +mkI18nWidgetEnum :: String -> FilePath -> DecsQ +mkI18nWidgetEnum (splitCamel -> namebase) basename = do + itemsAvailable <- i18nWidgetFilesAvailable' basename + let items = Map.mapWithKey (\k _ -> typPrefix <> unPathPiece k) itemsAvailable + sequence + [ dataD (cxt []) dataName [] Nothing + [ normalC (mkName conName) [] + | (_, conName) <- Map.toAscList items + ] + [ derivClause (Just StockStrategy) + [ conT ''Eq + , conT ''Ord + , conT ''Read + , conT ''Show + , conT ''Enum + , conT ''Bounded + , conT ''Generic + , conT ''Typeable + ] + , derivClause (Just AnyclassStrategy) + [ conT ''Universe + , conT ''Finite + ] + ] + , instanceD (cxt []) (conT ''PathPiece `appT` conT dataName) + [ funD 'toPathPiece + [ clause [conP (mkName con) []] (normalB . litE . stringL $ repack int) [] + | (int, con) <- Map.toList items + ] + , funD 'fromPathPiece + [ clause [varP $ mkName "t"] + ( guardedB + [ (,) <$> normalG [e|$(varE $ mkName "t") == int|] <*> [e|Just $(conE $ mkName con)|] + | (int, con) <- Map.toList items + ]) [] + , clause [wildP] (normalB [e|Nothing|]) [] + ] + ] + , sigD (mkName $ valPrefix <> "ItemMap") [t|Map Text $(conT dataName)|] + , funD (mkName $ valPrefix <> "ItemMap") + [ clause [] (normalB [e| Map.fromList $(listE . map (\(int, con) -> tupE [litE . stringL $ repack int, conE $ mkName con]) $ Map.toList items) |]) [] + ] + ] + where + unPathPiece :: Text -> String + unPathPiece = repack . mconcat . map (over _head Char.toUpper) . Text.splitOn "-" + + dataName = mkName $ typPrefix <> "Item" + + typPrefix = concat $ over (takingWhile Char.isLower $ _head . traverse) Char.toUpper namebase + valPrefix = concat $ over (takingWhile Char.isUpper $ _head . traverse) Char.toLower namebase From d9d353fcb7652c46a15016b5d2f400162c8271ef Mon Sep 17 00:00:00 2001 From: Gregor Kleen Date: Mon, 28 Sep 2020 19:47:32 +0200 Subject: [PATCH 5/5] feat(changelog): implement changelog like faq --- frontend/src/app.sass | 5 +- messages/uniworx/de-de-formal.msg | 5 +- messages/uniworx/en-eu.msg | 3 + models/changelog.model | 4 + src/Data/Time/Calendar/Instances.hs | 8 +- src/Foundation/I18n.hs | 1 + src/Handler/Info.hs | 19 +- src/Handler/Utils/DateTime.hs | 6 +- src/Model/Migration.hs | 26 + src/Model/Types.hs | 1 + src/Model/Types/Changelog.hs | 145 ++++++ src/Utils/DateTime.hs | 15 + src/Utils/PathPiece.hs | 11 + templates/changelog.hamlet | 14 + ...ociated-study-features.de-de-formal.hamlet | 4 + ...rse-associated-study-features.en-eu.hamlet | 4 + ...eletion-during-testing.de-de-formal.hamlet | 2 + ...count-deletion-during-testing.en-eu.hamlet | 2 + ...ional-datetime-formats.de-de-formal.hamlet | 2 + .../additional-datetime-formats.en-eu.hamlet | 2 + ...al-sheet-notifications.de-de-formal.hamlet | 2 + ...dditional-sheet-notifications.en-eu.hamlet | 2 + ...llocation-applications.de-de-formal.hamlet | 2 + .../allocation-applications.en-eu.hamlet | 2 + ...on-course-registration.de-de-formal.hamlet | 2 + ...llocation-course-registration.en-eu.hamlet | 2 + ...ocations-notifications.de-de-formal.hamlet | 2 + .../allocations-notifications.en-eu.hamlet | 2 + .../changelog/asidenav.de-de-formal.hamlet | 2 + .../i18n/changelog/asidenav.en-eu.hamlet | 2 + ...ed-corrections-filters.de-de-formal.hamlet | 2 + .../assigned-corrections-filters.en-eu.hamlet | 2 + ...pt-course-applications.de-de-formal.hamlet | 2 + ...ly-accept-course-applications.en-eu.hamlet | 2 + ...ommunication-tutorials.de-de-formal.hamlet | 2 + ...ourse-communication-tutorials.en-eu.hamlet | 2 + ...articipant-detail-page.de-de-formal.hamlet | 2 + ...ourse-participant-detail-page.en-eu.hamlet | 2 + .../better-csv-import.de-de-formal.hamlet | 2 + .../changelog/better-csv-import.en-eu.hamlet | 2 + .../better-file-uploads.de-de-formal.hamlet | 2 + .../better-file-uploads.en-eu.hamlet | 2 + ...ble-cell-colour-coding.de-de-formal.hamlet | 2 + ...tter-table-cell-colour-coding.en-eu.hamlet | 2 + ...ork-without-javascript.de-de-formal.hamlet | 2 + ...ttons-work-without-javascript.en-eu.hamlet | 2 + ...urable-datetime-format.de-de-formal.hamlet | 2 + .../configurable-datetime-format.en-eu.hamlet | 2 + ...gurable-display-emails.de-de-formal.hamlet | 2 + .../configurable-display-emails.en-eu.hamlet | 2 + ...igurable-display-names.de-de-formal.hamlet | 2 + .../configurable-display-names.en-eu.hamlet | 2 + ...s-display-improvements.de-de-formal.hamlet | 2 + ...rections-display-improvements.en-eu.hamlet | 2 + ...rectors-on-course-show.de-de-formal.hamlet | 2 + .../correctors-on-course-show.en-eu.hamlet | 2 + ...inistrator-invitations.de-de-formal.hamlet | 2 + ...rse-administrator-invitations.en-eu.hamlet | 2 + ...se-administrator-roles.de-de-formal.hamlet | 2 + .../course-administrator-roles.en-eu.hamlet | 2 + ...associated-study-field.de-de-formal.hamlet | 2 + ...course-associated-study-field.en-eu.hamlet | 2 + ...urse-convenience-links.de-de-formal.hamlet | 2 + .../course-convenience-links.en-eu.hamlet | 2 + ...se-list-over-all-terms.de-de-formal.hamlet | 2 + .../course-list-over-all-terms.en-eu.hamlet | 2 + .../course-materials.de-de-formal.hamlet | 2 + .../changelog/course-materials.en-eu.hamlet | 2 + .../course-messages.de-de-formal.hamlet | 2 + .../changelog/course-messages.en-eu.hamlet | 2 + .../changelog/course-news.de-de-formal.hamlet | 2 + .../i18n/changelog/course-news.en-eu.hamlet | 2 + .../course-occurences.de-de-formal.hamlet | 2 + .../changelog/course-occurences.en-eu.hamlet | 2 + ...ourse-occurrence-notes.de-de-formal.hamlet | 2 + .../course-occurrence-notes.en-eu.hamlet | 2 + ...ipants-list-add-sheets.de-de-formal.hamlet | 2 + ...-participants-list-add-sheets.en-eu.hamlet | 2 + ...ourse-participants-sex.de-de-formal.hamlet | 2 + .../course-participants-sex.en-eu.hamlet | 2 + ...urse-register-by-admin.de-de-formal.hamlet | 2 + .../course-register-by-admin.en-eu.hamlet | 2 + ...rthands-within-schools.de-de-formal.hamlet | 2 + ...rse-shorthands-within-schools.en-eu.hamlet | 2 + .../course-visibility.de-de-formal.hamlet | 2 + .../changelog/course-visibility.en-eu.hamlet | 2 + ...sv-course-applications.de-de-formal.hamlet | 2 + .../csv-course-applications.en-eu.hamlet | 2 + .../csv-exam-participants.de-de-formal.hamlet | 2 + .../csv-exam-participants.en-eu.hamlet | 2 + ...-participants-features.de-de-formal.hamlet | 2 + ...-course-participants-features.en-eu.hamlet | 2 + ...s-registered-tutorials.de-de-formal.hamlet | 2 + ...icipants-registered-tutorials.en-eu.hamlet | 2 + ...rt-course-participants.de-de-formal.hamlet | 2 + ...sv-export-course-participants.en-eu.hamlet | 2 + ...v-option-character-set.de-de-formal.hamlet | 2 + .../csv-option-character-set.en-eu.hamlet | 2 + .../csv-option-timestamp.de-de-formal.hamlet | 2 + .../csv-option-timestamp.en-eu.hamlet | 2 + templates/i18n/changelog/de-de-formal.hamlet | 463 ------------------ ...ll-sheet-files-by-type.de-de-formal.hamlet | 2 + ...nload-all-sheet-files-by-type.en-eu.hamlet | 2 + ...wnload-all-sheet-files.de-de-formal.hamlet | 2 + .../download-all-sheet-files.en-eu.hamlet | 2 + .../email-notifications.de-de-formal.hamlet | 2 + .../email-notifications.en-eu.hamlet | 2 + templates/i18n/changelog/en-eu.hamlet | 460 ----------------- .../changelog/english.de-de-formal.hamlet | 2 + templates/i18n/changelog/english.en-eu.hamlet | 2 + ...-for-table-item-vanish.de-de-formal.hamlet | 2 + ...essages-for-table-item-vanish.en-eu.hamlet | 2 + ...ocated-course-capacity.de-de-formal.hamlet | 2 + ...ate-allocated-course-capacity.en-eu.hamlet | 2 + ...articipant-duplication.de-de-formal.hamlet | 2 + ...ement-participant-duplication.en-eu.hamlet | 2 + .../exam-automatic-boni.de-de-formal.hamlet | 2 + .../exam-automatic-boni.en-eu.hamlet | 2 + ...exam-automatic-results.de-de-formal.hamlet | 2 + .../exam-automatic-results.en-eu.hamlet | 2 + ...n-better-rules-display.de-de-formal.hamlet | 3 + ...ribution-better-rules-display.en-eu.hamlet | 3 + ...atic-room-distribution.de-de-formal.hamlet | 3 + ...m-automatic-room-distribution.en-eu.hamlet | 3 + .../exam-closure.de-de-formal.hamlet | 2 + .../i18n/changelog/exam-closure.en-eu.hamlet | 2 + .../exam-correct.de-de-formal.hamlet | 2 + .../i18n/changelog/exam-correct.en-eu.hamlet | 2 + .../changelog/exam-design.de-de-formal.hamlet | 2 + .../i18n/changelog/exam-design.en-eu.hamlet | 2 + .../exam-grading-mode.de-de-formal.hamlet | 4 + .../changelog/exam-grading-mode.en-eu.hamlet | 3 + ...fice-exam-notification.de-de-formal.hamlet | 2 + ...exam-office-exam-notification.en-eu.hamlet | 2 + .../exam-offices.de-de-formal.hamlet | 2 + .../i18n/changelog/exam-offices.en-eu.hamlet | 2 + .../i18n/changelog/exams.de-de-formal.hamlet | 2 + templates/i18n/changelog/exams.en-eu.hamlet | 2 + ...rt-course-participants.de-de-formal.hamlet | 3 + .../export-course-participants.en-eu.hamlet | 2 + .../external-exams.de-de-formal.hamlet | 3 + .../changelog/external-exams.en-eu.hamlet | 3 + .../i18n/changelog/faq.de-de-formal.hamlet | 2 + templates/i18n/changelog/faq.en-eu.hamlet | 2 + .../file-download-option.de-de-formal.hamlet | 2 + .../file-download-option.en-eu.hamlet | 2 + ...er-course-participants.de-de-formal.hamlet | 2 + .../former-course-participants.en-eu.hamlet | 2 + .../forms-times-reset.de-de-formal.hamlet | 2 + .../changelog/forms-times-reset.en-eu.hamlet | 2 + .../haskell-campus-login.de-de-formal.hamlet | 3 + .../haskell-campus-login.en-eu.hamlet | 4 + .../hide-system-messages.de-de-formal.hamlet | 2 + .../hide-system-messages.en-eu.hamlet | 2 + .../i18n/changelog/i18n.de-de-formal.hamlet | 2 + templates/i18n/changelog/i18n.en-eu.hamlet | 2 + .../improved-submittor-ui.de-de-formal.hamlet | 2 + .../improved-submittor-ui.en-eu.hamlet | 2 + ...vements-for-correctors.de-de-formal.hamlet | 2 + .../improvements-for-correctors.en-eu.hamlet | 2 + .../lmu-internal-fields.de-de-formal.hamlet | 2 + .../lmu-internal-fields.en-eu.hamlet | 2 + .../markdown-emails.de-de-formal.hamlet | 3 + .../changelog/markdown-emails.en-eu.hamlet | 2 + .../markdown-html-input.de-de-formal.hamlet | 2 + .../markdown-html-input.en-eu.hamlet | 2 + ...-anonymised-correction.de-de-formal.hamlet | 2 + .../non-anonymised-correction.en-eu.hamlet | 2 + ...-participant-via-admin.de-de-formal.hamlet | 2 + ...-course-participant-via-admin.en-eu.hamlet | 2 + ...tion-exam-registration.de-de-formal.hamlet | 2 + ...otification-exam-registration.en-eu.hamlet | 2 + ...ion-submission-changed.de-de-formal.hamlet | 2 + ...tification-submission-changed.en-eu.hamlet | 2 + ...assing-by-points-works.de-de-formal.hamlet | 2 + .../passing-by-points-works.en-eu.hamlet | 2 + .../personal-information.de-de-formal.hamlet | 2 + .../personal-information.en-eu.hamlet | 2 + ...rsonalised-sheet-files.de-de-formal.hamlet | 2 + .../personalised-sheet-files.en-eu.hamlet | 2 + ...ered-submission-groups.de-de-formal.hamlet | 2 + .../registered-submission-groups.en-eu.hamlet | 2 + ...orrection-distribution.de-de-formal.hamlet | 2 + ...matic-correction-distribution.en-eu.hamlet | 2 + .../reworked-navigation.de-de-formal.hamlet | 2 + .../reworked-navigation.en-eu.hamlet | 2 + .../server-side-sessions.de-de-formal.hamlet | 2 + .../server-side-sessions.en-eu.hamlet | 2 + .../sheet-pass-always.de-de-formal.hamlet | 2 + .../changelog/sheet-pass-always.en-eu.hamlet | 2 + .../sheet-specific-files.de-de-formal.hamlet | 2 + .../sheet-specific-files.en-eu.hamlet | 2 + ...ission-and-zip-control.de-de-formal.hamlet | 2 + ...no-submission-and-zip-control.en-eu.hamlet | 2 + ...orrection-distribution.de-de-formal.hamlet | 2 + ...smart-correction-distribution.en-eu.hamlet | 2 + .../study-features.de-de-formal.hamlet | 2 + .../changelog/study-features.en-eu.hamlet | 2 + ...n-only-exam-registered.de-de-formal.hamlet | 2 + ...bmission-only-exam-registered.en-eu.hamlet | 2 + .../support-widget.de-de-formal.hamlet | 2 + .../changelog/support-widget.en-eu.hamlet | 2 + ...-forms-work-after-ajax.de-de-formal.hamlet | 2 + .../table-forms-work-after-ajax.en-eu.hamlet | 2 + .../table-summaries.de-de-formal.hamlet | 2 + .../changelog/table-summaries.en-eu.hamlet | 2 + ...ips-without-javascript.de-de-formal.hamlet | 2 + .../tooltips-without-javascript.en-eu.hamlet | 2 + ...-via-participant-table.de-de-formal.hamlet | 2 + ...tration-via-participant-table.en-eu.hamlet | 2 + ...tutorial-tutor-control.de-de-formal.hamlet | 2 + .../tutorial-tutor-control.en-eu.hamlet | 2 + .../changelog/tutorials.de-de-formal.hamlet | 2 + .../i18n/changelog/tutorials.en-eu.hamlet | 2 + ...ing-multiple-semesters.de-de-formal.hamlet | 3 + .../warning-multiple-semesters.en-eu.hamlet | 3 + ...-allocation-allocation.de-de-formal.hamlet | 2 + ...terface-allocation-allocation.en-eu.hamlet | 2 + .../yaml-ratings.de-de-formal.hamlet | 2 + .../i18n/changelog/yaml-ratings.en-eu.hamlet | 2 + templates/versionHistory.hamlet | 3 +- test/Database/Fill.hs | 4 +- 222 files changed, 681 insertions(+), 940 deletions(-) create mode 100644 models/changelog.model create mode 100644 src/Model/Types/Changelog.hs create mode 100644 templates/changelog.hamlet create mode 100644 templates/i18n/changelog/abolish-course-associated-study-features.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/abolish-course-associated-study-features.en-eu.hamlet create mode 100644 templates/i18n/changelog/account-deletion-during-testing.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/account-deletion-during-testing.en-eu.hamlet create mode 100644 templates/i18n/changelog/additional-datetime-formats.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/additional-datetime-formats.en-eu.hamlet create mode 100644 templates/i18n/changelog/additional-sheet-notifications.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/additional-sheet-notifications.en-eu.hamlet create mode 100644 templates/i18n/changelog/allocation-applications.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/allocation-applications.en-eu.hamlet create mode 100644 templates/i18n/changelog/allocation-course-registration.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/allocation-course-registration.en-eu.hamlet create mode 100644 templates/i18n/changelog/allocations-notifications.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/allocations-notifications.en-eu.hamlet create mode 100644 templates/i18n/changelog/asidenav.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/asidenav.en-eu.hamlet create mode 100644 templates/i18n/changelog/assigned-corrections-filters.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/assigned-corrections-filters.en-eu.hamlet create mode 100644 templates/i18n/changelog/automatically-accept-course-applications.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/automatically-accept-course-applications.en-eu.hamlet create mode 100644 templates/i18n/changelog/better-course-communication-tutorials.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/better-course-communication-tutorials.en-eu.hamlet create mode 100644 templates/i18n/changelog/better-course-participant-detail-page.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/better-course-participant-detail-page.en-eu.hamlet create mode 100644 templates/i18n/changelog/better-csv-import.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/better-csv-import.en-eu.hamlet create mode 100644 templates/i18n/changelog/better-file-uploads.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/better-file-uploads.en-eu.hamlet create mode 100644 templates/i18n/changelog/better-table-cell-colour-coding.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/better-table-cell-colour-coding.en-eu.hamlet create mode 100644 templates/i18n/changelog/buttons-work-without-javascript.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/buttons-work-without-javascript.en-eu.hamlet create mode 100644 templates/i18n/changelog/configurable-datetime-format.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/configurable-datetime-format.en-eu.hamlet create mode 100644 templates/i18n/changelog/configurable-display-emails.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/configurable-display-emails.en-eu.hamlet create mode 100644 templates/i18n/changelog/configurable-display-names.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/configurable-display-names.en-eu.hamlet create mode 100644 templates/i18n/changelog/corrections-display-improvements.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/corrections-display-improvements.en-eu.hamlet create mode 100644 templates/i18n/changelog/correctors-on-course-show.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/correctors-on-course-show.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-administrator-invitations.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-administrator-invitations.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-administrator-roles.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-administrator-roles.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-associated-study-field.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-associated-study-field.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-convenience-links.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-convenience-links.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-list-over-all-terms.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-list-over-all-terms.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-materials.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-materials.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-messages.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-messages.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-news.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-news.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-occurences.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-occurences.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-occurrence-notes.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-occurrence-notes.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-participants-list-add-sheets.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-participants-list-add-sheets.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-participants-sex.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-participants-sex.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-register-by-admin.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-register-by-admin.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-shorthands-within-schools.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-shorthands-within-schools.en-eu.hamlet create mode 100644 templates/i18n/changelog/course-visibility.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/course-visibility.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-course-applications.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-course-applications.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-exam-participants.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-exam-participants.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-export-course-participants-features.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-export-course-participants-features.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-export-course-participants-registered-tutorials.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-export-course-participants-registered-tutorials.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-export-course-participants.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-export-course-participants.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-option-character-set.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-option-character-set.en-eu.hamlet create mode 100644 templates/i18n/changelog/csv-option-timestamp.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/csv-option-timestamp.en-eu.hamlet delete mode 100644 templates/i18n/changelog/de-de-formal.hamlet create mode 100644 templates/i18n/changelog/download-all-sheet-files-by-type.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/download-all-sheet-files-by-type.en-eu.hamlet create mode 100644 templates/i18n/changelog/download-all-sheet-files.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/download-all-sheet-files.en-eu.hamlet create mode 100644 templates/i18n/changelog/email-notifications.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/email-notifications.en-eu.hamlet delete mode 100644 templates/i18n/changelog/en-eu.hamlet create mode 100644 templates/i18n/changelog/english.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/english.en-eu.hamlet create mode 100644 templates/i18n/changelog/error-messages-for-table-item-vanish.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/error-messages-for-table-item-vanish.en-eu.hamlet create mode 100644 templates/i18n/changelog/estimate-allocated-course-capacity.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/estimate-allocated-course-capacity.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-achievement-participant-duplication.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-achievement-participant-duplication.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-boni.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-boni.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-results.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-results.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-room-distribution.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-automatic-room-distribution.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-closure.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-closure.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-correct.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-correct.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-design.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-design.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-grading-mode.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-grading-mode.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-office-exam-notification.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-office-exam-notification.en-eu.hamlet create mode 100644 templates/i18n/changelog/exam-offices.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exam-offices.en-eu.hamlet create mode 100644 templates/i18n/changelog/exams.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/exams.en-eu.hamlet create mode 100644 templates/i18n/changelog/export-course-participants.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/export-course-participants.en-eu.hamlet create mode 100644 templates/i18n/changelog/external-exams.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/external-exams.en-eu.hamlet create mode 100644 templates/i18n/changelog/faq.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/faq.en-eu.hamlet create mode 100644 templates/i18n/changelog/file-download-option.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/file-download-option.en-eu.hamlet create mode 100644 templates/i18n/changelog/former-course-participants.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/former-course-participants.en-eu.hamlet create mode 100644 templates/i18n/changelog/forms-times-reset.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/forms-times-reset.en-eu.hamlet create mode 100644 templates/i18n/changelog/haskell-campus-login.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/haskell-campus-login.en-eu.hamlet create mode 100644 templates/i18n/changelog/hide-system-messages.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/hide-system-messages.en-eu.hamlet create mode 100644 templates/i18n/changelog/i18n.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/i18n.en-eu.hamlet create mode 100644 templates/i18n/changelog/improved-submittor-ui.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/improved-submittor-ui.en-eu.hamlet create mode 100644 templates/i18n/changelog/improvements-for-correctors.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/improvements-for-correctors.en-eu.hamlet create mode 100644 templates/i18n/changelog/lmu-internal-fields.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/lmu-internal-fields.en-eu.hamlet create mode 100644 templates/i18n/changelog/markdown-emails.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/markdown-emails.en-eu.hamlet create mode 100644 templates/i18n/changelog/markdown-html-input.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/markdown-html-input.en-eu.hamlet create mode 100644 templates/i18n/changelog/non-anonymised-correction.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/non-anonymised-correction.en-eu.hamlet create mode 100644 templates/i18n/changelog/notification-course-participant-via-admin.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/notification-course-participant-via-admin.en-eu.hamlet create mode 100644 templates/i18n/changelog/notification-exam-registration.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/notification-exam-registration.en-eu.hamlet create mode 100644 templates/i18n/changelog/notification-submission-changed.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/notification-submission-changed.en-eu.hamlet create mode 100644 templates/i18n/changelog/passing-by-points-works.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/passing-by-points-works.en-eu.hamlet create mode 100644 templates/i18n/changelog/personal-information.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/personal-information.en-eu.hamlet create mode 100644 templates/i18n/changelog/personalised-sheet-files.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/personalised-sheet-files.en-eu.hamlet create mode 100644 templates/i18n/changelog/registered-submission-groups.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/registered-submission-groups.en-eu.hamlet create mode 100644 templates/i18n/changelog/reworked-automatic-correction-distribution.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/reworked-automatic-correction-distribution.en-eu.hamlet create mode 100644 templates/i18n/changelog/reworked-navigation.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/reworked-navigation.en-eu.hamlet create mode 100644 templates/i18n/changelog/server-side-sessions.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/server-side-sessions.en-eu.hamlet create mode 100644 templates/i18n/changelog/sheet-pass-always.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/sheet-pass-always.en-eu.hamlet create mode 100644 templates/i18n/changelog/sheet-specific-files.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/sheet-specific-files.en-eu.hamlet create mode 100644 templates/i18n/changelog/sheets-no-submission-and-zip-control.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/sheets-no-submission-and-zip-control.en-eu.hamlet create mode 100644 templates/i18n/changelog/smart-correction-distribution.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/smart-correction-distribution.en-eu.hamlet create mode 100644 templates/i18n/changelog/study-features.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/study-features.en-eu.hamlet create mode 100644 templates/i18n/changelog/submission-only-exam-registered.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/submission-only-exam-registered.en-eu.hamlet create mode 100644 templates/i18n/changelog/support-widget.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/support-widget.en-eu.hamlet create mode 100644 templates/i18n/changelog/table-forms-work-after-ajax.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/table-forms-work-after-ajax.en-eu.hamlet create mode 100644 templates/i18n/changelog/table-summaries.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/table-summaries.en-eu.hamlet create mode 100644 templates/i18n/changelog/tooltips-without-javascript.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/tooltips-without-javascript.en-eu.hamlet create mode 100644 templates/i18n/changelog/tutorial-registration-via-participant-table.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/tutorial-registration-via-participant-table.en-eu.hamlet create mode 100644 templates/i18n/changelog/tutorial-tutor-control.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/tutorial-tutor-control.en-eu.hamlet create mode 100644 templates/i18n/changelog/tutorials.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/tutorials.en-eu.hamlet create mode 100644 templates/i18n/changelog/warning-multiple-semesters.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/warning-multiple-semesters.en-eu.hamlet create mode 100644 templates/i18n/changelog/webinterface-allocation-allocation.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/webinterface-allocation-allocation.en-eu.hamlet create mode 100644 templates/i18n/changelog/yaml-ratings.de-de-formal.hamlet create mode 100644 templates/i18n/changelog/yaml-ratings.en-eu.hamlet diff --git a/frontend/src/app.sass b/frontend/src/app.sass index 86bb47969..6df8a8afa 100644 --- a/frontend/src/app.sass +++ b/frontend/src/app.sass @@ -1105,9 +1105,8 @@ th, td pointer-events: none #changelog - font-size: 14px - white-space: pre-wrap - font-family: var(--font-monospace) + max-height: 75vh + overflow: auto #gitrev font-size: 12px diff --git a/messages/uniworx/de-de-formal.msg b/messages/uniworx/de-de-formal.msg index b46939abf..a1ea08cbf 100644 --- a/messages/uniworx/de-de-formal.msg +++ b/messages/uniworx/de-de-formal.msg @@ -2809,4 +2809,7 @@ CronMatchAsap: ASAP CronMatchNone: Nie SystemExamOffice: Prüfungsverwaltung -SystemFaculty: Fakultätsmitglied \ No newline at end of file +SystemFaculty: Fakultätsmitglied + +ChangelogItemFeature: Feature +ChangelogItemBugfix: Bugfix \ No newline at end of file diff --git a/messages/uniworx/en-eu.msg b/messages/uniworx/en-eu.msg index 79456dd64..fb29b90ad 100644 --- a/messages/uniworx/en-eu.msg +++ b/messages/uniworx/en-eu.msg @@ -2811,3 +2811,6 @@ CronMatchNone: Never SystemExamOffice: Exam office SystemFaculty: Faculty member + +ChangelogItemFeature: Feature +ChangelogItemBugfix: Bugfix \ No newline at end of file diff --git a/models/changelog.model b/models/changelog.model new file mode 100644 index 000000000..4cc42cb12 --- /dev/null +++ b/models/changelog.model @@ -0,0 +1,4 @@ +ChangelogItemFirstSeen + item ChangelogItem + firstSeen Day + Primary item diff --git a/src/Data/Time/Calendar/Instances.hs b/src/Data/Time/Calendar/Instances.hs index 15c77e94b..87e74ad1c 100644 --- a/src/Data/Time/Calendar/Instances.hs +++ b/src/Data/Time/Calendar/Instances.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module Data.Time.Calendar.Instances @@ -11,8 +10,13 @@ import Data.Time.Calendar import Data.Universe +import Language.Haskell.TH.Syntax (Lift) +import Type.Reflection -deriving newtype instance Hashable Day + +deriving instance Lift Day +instance Hashable Day where + hashWithSalt s (ModifiedJulianDay jDay) = s `hashWithSalt` hash (typeRep @Day) `hashWithSalt` jDay deriving instance Ord DayOfWeek instance Universe DayOfWeek where diff --git a/src/Foundation/I18n.hs b/src/Foundation/I18n.hs index 399ed3793..1d5ac1248 100644 --- a/src/Foundation/I18n.hs +++ b/src/Foundation/I18n.hs @@ -225,6 +225,7 @@ embedRenderMessage ''UniWorX ''ExamAidsPreset id embedRenderMessage ''UniWorX ''ExamOnlinePreset id embedRenderMessage ''UniWorX ''ExamSynchronicityPreset id embedRenderMessage ''UniWorX ''ExamRequiredEquipmentPreset id +embedRenderMessage ''UniWorX ''ChangelogItemKind id embedRenderMessage ''UniWorX ''AuthenticationMode id diff --git a/src/Handler/Info.hs b/src/Handler/Info.hs index 7f4749bb6..c45c5c9d6 100644 --- a/src/Handler/Info.hs +++ b/src/Handler/Info.hs @@ -5,7 +5,9 @@ import Handler.Utils import Handler.Info.TH import qualified Data.Map as Map +import Data.Map ((!)) import qualified Data.CaseInsensitive as CI +import qualified Data.Set as Set import qualified Database.Esqueleto as E import qualified Database.Esqueleto.Utils as E @@ -34,17 +36,26 @@ getLegalR = -- | Allgemeine Informationen getInfoR :: Handler Html -getInfoR = -- do +getInfoR = do + changelogEntries' <- runDB $ selectList [] [] + let changelogEntries = Map.fromListWith Set.union + [ (Down changelogItemFirstSeenFirstSeen, Set.singleton changelogItemFirstSeenItem) + | Entity _ ChangelogItemFirstSeen{..} <- changelogEntries' + ] + siteLayoutMsg MsgInfoHeading $ do setTitleI MsgInfoHeading let features = $(i18nWidgetFile "featureList") - changeLog = $(i18nWidgetFile "changelog") + changeLog = $(widgetFile "changelog") knownBugs = $(i18nWidgetFile "knownBugs") implementation = $(i18nWidgetFile "implementation") gitInfo :: Text gitInfo = $gitDescribe <> " (" <> $gitCommitDate <> ")" $(widgetFile "versionHistory") + where + changelogItems = $(i18nWidgetFiles "changelog") + getInfoLecturerR :: Handler Html getInfoLecturerR = @@ -67,9 +78,9 @@ getInfoLecturerR = -- new feature with given introduction date newFeat :: Integer -> Int -> Int -> WidgetFor UniWorX () - newFeat year month day = do + newFeat y m d = do currentTime <- liftIO getCurrentTime - let expiryTime = UTCTime (addGregorianMonthsRollOver 1 $ fromGregorian year month day) 0 + let expiryTime = UTCTime (addGregorianMonthsRollOver 1 $ fromGregorian y m d) 0 if currentTime > expiryTime then mempty else toWidget [whamlet| ^{iconTooltip tooltipNew (Just IconNew) False} |] diff --git a/src/Handler/Utils/DateTime.hs b/src/Handler/Utils/DateTime.hs index a321bebff..63bf227ac 100644 --- a/src/Handler/Utils/DateTime.hs +++ b/src/Handler/Utils/DateTime.hs @@ -213,9 +213,9 @@ formatDiffDays t setYear :: Integer -> Day -> Day -setYear year date = fromGregorian year month day +setYear year date = fromGregorian year m d where - (_,month,day) = toGregorian date + (_,m,d) = toGregorian date addOneWeek :: UTCTime -> UTCTime addOneWeek = addWeeks 1 @@ -295,7 +295,7 @@ formatTimeRangeMail = formatTimeRange' formatTimeMail formatGregorianW :: Integer -> Int -> Int -> Widget -formatGregorianW year month day = formatTimeW SelFormatDate $ fromGregorian year month day +formatGregorianW y m d = formatTimeW SelFormatDate $ fromGregorian y m d instance Csv.ToField ZonedTime where toField = Csv.toField . iso8601Show diff --git a/src/Model/Migration.hs b/src/Model/Migration.hs index 55d1ee4ca..27657bbe5 100644 --- a/src/Model/Migration.hs +++ b/src/Model/Migration.hs @@ -45,6 +45,10 @@ import Web.ServerSession.Backend.Persistent.Memcached (migrateMemcachedSqlStorag import Data.Conduit.Algorithms.FastCDC (FastCDCParameters(fastCDCMinBlockSize)) +import Data.Time.Format.ISO8601 (iso8601Show) + +import qualified Data.Time.Zones as TZ + -- Database versions must follow https://pvp.haskell.org: -- - Breaking changes are instances where manual migration is necessary (via customMigrations; i.e. changing a columns format) -- - Non-breaking changes are instances where the automatic migration done by persistent is sufficient (i.e. adding a column or table) @@ -168,6 +172,19 @@ migrateManual = do , ("user_ldap_primary_key", "CREATE INDEX user_ldap_primary_key ON \"user\" (ldap_primary_key)" ) , ("file_content_entry_chunk_hash", "CREATE INDEX file_content_entry_chunk_hash ON \"file_content_entry\" (chunk_hash)" ) ] + + recordedChangelogItems <- lift . lift $ selectList [] [] + let missingChangelogItems = Set.toList $ Set.fromList universeF `Set.difference` recordedChangelogItems' + where recordedChangelogItems' = Set.fromList [ changelogItemFirstSeenItem | Entity _ ChangelogItemFirstSeen{..} <- recordedChangelogItems ] + unless (null missingChangelogItems) $ do + now <- iso8601Show . localDay . TZ.utcToLocalTimeTZ appTZ <$> liftIO getCurrentTime + addMigration False $ + let sql = [st|INSERT INTO changelog_item_first_seen (item, first_seen) VALUES #{vals}|] + vals = Text.intercalate ", " $ do + item <- missingChangelogItems + return [st|('#{toPathPiece item}', '#{now}')|] + in sql + where addIndex :: Text -> Sql -> Migration addIndex ixName ixDef = do @@ -961,6 +978,15 @@ customMigrations = Map.fromListWith (>>) ALTER TABLE school ADD COLUMN "exam_discouraged_modes" jsonb NOT NULL DEFAULT #{ExamModeDNF predDNFFalse}; |] ) + , ( AppliedMigrationKey [migrationVersion|42.0.0|] [version|43.0.0|] + , unlessM (tableExists "changelog_item_first_seen") $ do + [executeQQ| + CREATE TABLE "changelog_item_first_seen" (PRIMARY KEY ("item"), "item" VARCHAR NOT NULL, "first_seen" DATE NOT NULL); + |] + insertMany_ [ ChangelogItemFirstSeen{..} + | (changelogItemFirstSeenItem, changelogItemFirstSeenFirstSeen) <- Map.toList changelogItemDays + ] + ) ] diff --git a/src/Model/Types.hs b/src/Model/Types.hs index b40e5c912..a8e437f17 100644 --- a/src/Model/Types.hs +++ b/src/Model/Types.hs @@ -17,3 +17,4 @@ import Model.Types.Allocation as Types import Model.Types.Languages as Types import Model.Types.File as Types import Model.Types.User as Types +import Model.Types.Changelog as Types diff --git a/src/Model/Types/Changelog.hs b/src/Model/Types/Changelog.hs new file mode 100644 index 000000000..37d9828d5 --- /dev/null +++ b/src/Model/Types/Changelog.hs @@ -0,0 +1,145 @@ +module Model.Types.Changelog + ( ChangelogItem(..) + , changelogItemMap + , ChangelogItemKind(..), _ChangelogItemFeature, _ChangelogItemBugfix + , classifyChangelogItem + , changelogItemDays + ) where + +import Import.NoModel + +import Model.Types.TH.PathPiece + +import qualified Data.Map as Map + + +mkI18nWidgetEnum "Changelog" "changelog" +derivePersistFieldPathPiece ''ChangelogItem +pathPieceJSONKey ''ChangelogItem +pathPieceJSON ''ChangelogItem +pathPieceHttpApiData ''ChangelogItem + +data ChangelogItemKind + = ChangelogItemFeature + | ChangelogItemBugfix + deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable) + deriving anyclass (Universe, Finite) + +makePrisms ''ChangelogItemKind + +classifyChangelogItem :: ChangelogItem -> ChangelogItemKind +classifyChangelogItem = \case + ChangelogHaskellCampusLogin -> ChangelogItemBugfix + ChangelogTooltipsWithoutJavascript -> ChangelogItemBugfix + ChangelogButtonsWorkWithoutJavascript -> ChangelogItemBugfix + ChangelogTableFormsWorkAfterAjax -> ChangelogItemBugfix + ChangelogPassingByPointsWorks -> ChangelogItemBugfix + ChangelogErrorMessagesForTableItemVanish -> ChangelogItemBugfix + ChangelogExamAchievementParticipantDuplication -> ChangelogItemBugfix + ChangelogFormsTimesReset -> ChangelogItemBugfix + _other -> ChangelogItemFeature + +changelogItemDays :: Map ChangelogItem Day +changelogItemDays = Map.fromListWithKey (\k d1 d2 -> bool (error $ "Duplicate changelog days for " <> show k) d1 $ d1 /= d2) + [ (ChangelogConfigurableDatetimeFormat, [day|2018-07-10|]) + , (ChangelogCourseListOverAllTerms, [day|2018-07-31|]) + , (ChangelogCorrectionsDisplayImprovements, [day|2018-07-31|]) + , (ChangelogHaskellCampusLogin, [day|2018-08-01|]) + , (ChangelogFileDownloadOption, [day|2018-08-06|]) + , (ChangelogSheetsNoSubmissionAndZipControl, [day|2018-09-18|]) + , (ChangelogSmartCorrectionDistribution, [day|2018-09-18|]) + , (ChangelogTableSummaries, [day|2018-09-18|]) + , (ChangelogPersonalInformation, [day|2018-09-18|]) + , (ChangelogCourseShorthandsWithinSchools, [day|2018-09-18|]) + , (ChangelogTooltipsWithoutJavascript, [day|2018-09-18|]) + , (ChangelogEmailNotifications, [day|2018-10-19|]) + , (ChangelogSupportWidget, [day|2018-10-19|]) + , (ChangelogAccountDeletionDuringTesting, [day|2018-10-19|]) + , (ChangelogImprovementsForCorrectors, [day|2018-11-09|]) + , (ChangelogButtonsWorkWithoutJavascript, [day|2018-11-09|]) + , (ChangelogTableFormsWorkAfterAjax, [day|2018-11-29|]) + , (ChangelogPassingByPointsWorks, [day|2018-11-30|]) + , (ChangelogErrorMessagesForTableItemVanish, [day|2019-01-16|]) + , (ChangelogAssignedCorrectionsFilters, [day|2019-01-16|]) + , (ChangelogCourseConvenienceLinks, [day|2019-01-16|]) + , (ChangelogAsidenav, [day|2019-01-30|]) + , (ChangelogCourseAssociatedStudyField, [day|2019-03-20|]) + , (ChangelogStudyFeatures, [day|2019-03-27|]) + , (ChangelogCourseAdministratorRoles, [day|2019-03-27|]) + , (ChangelogCourseAdministratorInvitations, [day|2019-04-20|]) + , (ChangelogCourseMessages, [day|2019-04-20|]) + , (ChangelogCorrectorsOnCourseShow, [day|2019-04-29|]) + , (ChangelogTutorials, [day|2019-04-29|]) + , (ChangelogCourseMaterials, [day|2019-05-04|]) + , (ChangelogDownloadAllSheetFiles, [day|2019-05-10|]) + , (ChangelogImprovedSubmittorUi, [day|2019-05-10|]) + , (ChangelogCourseRegisterByAdmin, [day|2019-05-13|]) + , (ChangelogReworkedAutomaticCorrectionDistribution, [day|2019-05-20|]) + , (ChangelogDownloadAllSheetFilesByType, [day|2019-06-07|]) + , (ChangelogSheetSpecificFiles, [day|2019-06-07|]) + , (ChangelogExams, [day|2019-06-26|]) + , (ChangelogCsvExamParticipants, [day|2019-07-23|]) + , (ChangelogAllocationCourseRegistration, [day|2019-08-12|]) + , (ChangelogAllocationApplications, [day|2019-08-19|]) + , (ChangelogCsvCourseApplications, [day|2019-08-27|]) + , (ChangelogAllocationsNotifications, [day|2019-09-05|]) + , (ChangelogConfigurableDisplayEmails, [day|2019-09-12|]) + , (ChangelogConfigurableDisplayNames, [day|2019-09-12|]) + , (ChangelogEstimateAllocatedCourseCapacity, [day|2019-09-12|]) + , (ChangelogNotificationExamRegistration, [day|2019-09-13|]) + , (ChangelogExamClosure, [day|2019-09-16|]) + , (ChangelogExamOfficeExamNotification, [day|2019-09-16|]) + , (ChangelogExamOffices, [day|2019-09-16|]) + , (ChangelogExamAchievementParticipantDuplication, [day|2019-09-25|]) + , (ChangelogFormsTimesReset, [day|2019-09-25|]) + , (ChangelogExamAutomaticResults, [day|2019-09-25|]) + , (ChangelogExamAutomaticBoni, [day|2019-09-25|]) + , (ChangelogAutomaticallyAcceptCourseApplications, [day|2019-09-27|]) + , (ChangelogCourseNews, [day|2019-10-01|]) + , (ChangelogCsvExportCourseParticipants, [day|2019-10-08|]) + , (ChangelogNotificationCourseParticipantViaAdmin, [day|2019-10-08|]) + , (ChangelogCsvExportCourseParticipantsFeatures, [day|2019-10-09|]) + , (ChangelogCourseOccurences, [day|2019-10-09|]) + , (ChangelogTutorialRegistrationViaParticipantTable, [day|2019-10-10|]) + , (ChangelogCsvExportCourseParticipantsRegisteredTutorials, [day|2019-10-10|]) + , (ChangelogCourseParticipantsSex, [day|2019-10-14|]) + , (ChangelogTutorialTutorControl, [day|2019-10-14|]) + , (ChangelogCsvOptionCharacterSet, [day|2019-10-23|]) + , (ChangelogCsvOptionTimestamp, [day|2019-10-23|]) + , (ChangelogEnglish, [day|2019-10-31|]) + , (ChangelogI18n, [day|2019-10-31|]) + , (ChangelogLmuInternalFields, [day|2019-11-28|]) + , (ChangelogNotificationSubmissionChanged, [day|2019-12-05|]) + , (ChangelogExportCourseParticipants, [day|2020-01-17|]) + , (ChangelogExternalExams, [day|2020-01-17|]) + , (ChangelogExamAutomaticRoomDistribution, [day|2020-01-29|]) + , (ChangelogWarningMultipleSemesters, [day|2020-01-30|]) + , (ChangelogExamAutomaticRoomDistributionBetterRulesDisplay, [day|2020-01-30|]) + , (ChangelogReworkedNavigation, [day|2020-02-07|]) + , (ChangelogExamCorrect, [day|2020-02-08|]) + , (ChangelogExamGradingMode, [day|2020-02-19|]) + , (ChangelogMarkdownEmails, [day|2020-02-23|]) + , (ChangelogMarkdownHtmlInput, [day|2020-02-23|]) + , (ChangelogBetterCsvImport, [day|2020-03-06|]) + , (ChangelogAdditionalDatetimeFormats, [day|2020-03-16|]) + , (ChangelogServerSideSessions, [day|2020-03-16|]) + , (ChangelogWebinterfaceAllocationAllocation, [day|2020-03-16|]) + , (ChangelogBetterTableCellColourCoding, [day|2020-03-16|]) + , (ChangelogCourseOccurrenceNotes, [day|2020-03-31|]) + , (ChangelogHideSystemMessages, [day|2020-04-15|]) + , (ChangelogNonAnonymisedCorrection, [day|2020-04-17|]) + , (ChangelogBetterCourseParticipantDetailPage, [day|2020-04-17|]) + , (ChangelogFaq, [day|2020-04-24|]) + , (ChangelogRegisteredSubmissionGroups, [day|2020-04-28|]) + , (ChangelogFormerCourseParticipants, [day|2020-05-05|]) + , (ChangelogBetterFileUploads, [day|2020-05-05|]) + , (ChangelogSheetPassAlways, [day|2020-05-23|]) + , (ChangelogBetterCourseCommunicationTutorials, [day|2020-05-25|]) + , (ChangelogAdditionalSheetNotifications, [day|2020-05-25|]) + , (ChangelogCourseParticipantsListAddSheets, [day|2020-06-14|]) + , (ChangelogYamlRatings, [day|2020-06-17|]) + , (ChangelogSubmissionOnlyExamRegistered, [day|2020-07-20|]) + , (ChangelogCourseVisibility, [day|2020-08-10|]) + , (ChangelogPersonalisedSheetFiles, [day|2020-08-10|]) + , (ChangelogAbolishCourseAssociatedStudyFeatures, [day|2020-08-28|]) + ] diff --git a/src/Utils/DateTime.hs b/src/Utils/DateTime.hs index dc2ce4677..0ef6ca5a0 100644 --- a/src/Utils/DateTime.hs +++ b/src/Utils/DateTime.hs @@ -12,6 +12,7 @@ module Utils.DateTime , nominalHour, nominalMinute , minNominalYear, avgNominalYear , module Zones + , day ) where import ClassyPrelude.Yesod hiding (lift) @@ -23,12 +24,14 @@ import Data.Time.Zones.TH as Zones (includeSystemTZ) import Data.Time.Zones (localTimeToUTCTZ, timeZoneForUTCTime) import Data.Time.Format (FormatTime) import Data.Time.Clock.System (systemEpochDay) +import qualified Data.Time.Format.ISO8601 as Time import qualified Data.Time.Format as Time import qualified Data.List.NonEmpty as NonEmpty import Language.Haskell.TH import Language.Haskell.TH.Syntax (Lift(..)) +import Language.Haskell.TH.Quote (QuasiQuoter(..)) import Instances.TH.Lift () import Data.Data (Data) @@ -144,3 +147,15 @@ nominalMinute = 60 minNominalYear, avgNominalYear :: NominalDiffTime minNominalYear = 365 * nominalDay avgNominalYear = fromRational $ 365.2425 * toRational nominalDay + +--------- +-- Day -- +--------- + +day :: QuasiQuoter +day = QuasiQuoter{..} + where + quotePat = error "day used as pattern" + quoteType = error "day used as type" + quoteDec = error "day used as declaration" + quoteExp dStr = maybe (fail $ "Could not parse ISO8601 day: “" <> dStr <> "”") (lift :: Day -> Q Exp) $ Time.iso8601ParseM dStr diff --git a/src/Utils/PathPiece.hs b/src/Utils/PathPiece.hs index 939f47058..1d466b689 100644 --- a/src/Utils/PathPiece.hs +++ b/src/Utils/PathPiece.hs @@ -8,6 +8,7 @@ module Utils.PathPiece , tuplePathPiece , pathPieceJSON, pathPieceJSONKey , pathPieceBinary + , pathPieceHttpApiData ) where import ClassyPrelude.Yesod @@ -40,6 +41,8 @@ import qualified Data.Binary as Binary import Control.Lens import Data.Generics.Product.Types +import Web.HttpApiData + mkFiniteFromPathPiece :: Name -> Q ([Dec], Exp) mkFiniteFromPathPiece finiteType = do @@ -229,3 +232,11 @@ pathPieceBinary tName get = Binary.get >>= maybe (fail $ "Could not parse value of " <> $(TH.lift $ nameBase tName) <> " via PathPiece") return . fromPathPiece put = Binary.put . toPathPiece |] + +pathPieceHttpApiData :: Name -> DecsQ +pathPieceHttpApiData tName + = [d| instance ToHttpApiData $(conT tName) where + toUrlPiece = toPathPiece + instance FromHttpApiData $(conT tName) where + parseUrlPiece = maybe (Left $ "Could not parse value of " <> $(TH.lift $ nameBase tName) <> " via PathPiece") Right . fromPathPiece + |] diff --git a/templates/changelog.hamlet b/templates/changelog.hamlet new file mode 100644 index 000000000..88f977759 --- /dev/null +++ b/templates/changelog.hamlet @@ -0,0 +1,14 @@ +$newline never +
                              + $forall (Down d, es) <- Map.toList changelogEntries +
                              toPathPiece d}> + ^{formatTimeW SelFormatDate d} +
                              +
                                + $forall e <- Set.toList es +
                              • toPathPiece e}> + $if is _ChangelogItemBugfix $ classifyChangelogItem e + + _{ChangelogItemBugfix} + : # + ^{changelogItems ! toPathPiece e} diff --git a/templates/i18n/changelog/abolish-course-associated-study-features.de-de-formal.hamlet b/templates/i18n/changelog/abolish-course-associated-study-features.de-de-formal.hamlet new file mode 100644 index 000000000..bdc6b06e0 --- /dev/null +++ b/templates/i18n/changelog/abolish-course-associated-study-features.de-de-formal.hamlet @@ -0,0 +1,4 @@ +$newline never +Kursassoziierte Studienfächer wurden abgeschafft. +
                                +Es werden nun an allen kursbezogenen Stellen jene Studiendaten angezeigt, die während des entsprechenden Semesters aktuell waren. diff --git a/templates/i18n/changelog/abolish-course-associated-study-features.en-eu.hamlet b/templates/i18n/changelog/abolish-course-associated-study-features.en-eu.hamlet new file mode 100644 index 000000000..06add0a69 --- /dev/null +++ b/templates/i18n/changelog/abolish-course-associated-study-features.en-eu.hamlet @@ -0,0 +1,4 @@ +$newline never +Abolished course-associated features of study. +
                                +In course-related contexts now all study features which were up to date during the relevant term are displayed. diff --git a/templates/i18n/changelog/account-deletion-during-testing.de-de-formal.hamlet b/templates/i18n/changelog/account-deletion-during-testing.de-de-formal.hamlet new file mode 100644 index 000000000..deecc7ecd --- /dev/null +++ b/templates/i18n/changelog/account-deletion-during-testing.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Benutzer können sich in der Testphase komplett selbst löschen diff --git a/templates/i18n/changelog/account-deletion-during-testing.en-eu.hamlet b/templates/i18n/changelog/account-deletion-during-testing.en-eu.hamlet new file mode 100644 index 000000000..c06dc9956 --- /dev/null +++ b/templates/i18n/changelog/account-deletion-during-testing.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +During testing users may completely delete their accounts diff --git a/templates/i18n/changelog/additional-datetime-formats.de-de-formal.hamlet b/templates/i18n/changelog/additional-datetime-formats.de-de-formal.hamlet new file mode 100644 index 000000000..14a463e23 --- /dev/null +++ b/templates/i18n/changelog/additional-datetime-formats.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Zusätzliche Uhrzeit- und Datumsformate diff --git a/templates/i18n/changelog/additional-datetime-formats.en-eu.hamlet b/templates/i18n/changelog/additional-datetime-formats.en-eu.hamlet new file mode 100644 index 000000000..5b8a068a5 --- /dev/null +++ b/templates/i18n/changelog/additional-datetime-formats.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Additional date and time formats diff --git a/templates/i18n/changelog/additional-sheet-notifications.de-de-formal.hamlet b/templates/i18n/changelog/additional-sheet-notifications.de-de-formal.hamlet new file mode 100644 index 000000000..0dc85d9f2 --- /dev/null +++ b/templates/i18n/changelog/additional-sheet-notifications.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Zusätzliche Benachrichtigungen für Übungsblätter diff --git a/templates/i18n/changelog/additional-sheet-notifications.en-eu.hamlet b/templates/i18n/changelog/additional-sheet-notifications.en-eu.hamlet new file mode 100644 index 000000000..2e15f4f5e --- /dev/null +++ b/templates/i18n/changelog/additional-sheet-notifications.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Additional notifications for exercise sheets diff --git a/templates/i18n/changelog/allocation-applications.de-de-formal.hamlet b/templates/i18n/changelog/allocation-applications.de-de-formal.hamlet new file mode 100644 index 000000000..e888c5003 --- /dev/null +++ b/templates/i18n/changelog/allocation-applications.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Bewerbungen für Zentralanmeldungen diff --git a/templates/i18n/changelog/allocation-applications.en-eu.hamlet b/templates/i18n/changelog/allocation-applications.en-eu.hamlet new file mode 100644 index 000000000..39c759990 --- /dev/null +++ b/templates/i18n/changelog/allocation-applications.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Applications for central allocations diff --git a/templates/i18n/changelog/allocation-course-registration.de-de-formal.hamlet b/templates/i18n/changelog/allocation-course-registration.de-de-formal.hamlet new file mode 100644 index 000000000..441fc07b2 --- /dev/null +++ b/templates/i18n/changelog/allocation-course-registration.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kurse zu Zentralanmeldungen eintragen diff --git a/templates/i18n/changelog/allocation-course-registration.en-eu.hamlet b/templates/i18n/changelog/allocation-course-registration.en-eu.hamlet new file mode 100644 index 000000000..736472525 --- /dev/null +++ b/templates/i18n/changelog/allocation-course-registration.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Registration of courses for central allocation diff --git a/templates/i18n/changelog/allocations-notifications.de-de-formal.hamlet b/templates/i18n/changelog/allocations-notifications.de-de-formal.hamlet new file mode 100644 index 000000000..9abca1630 --- /dev/null +++ b/templates/i18n/changelog/allocations-notifications.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Benachrichtigungen für Zentralanmeldungen diff --git a/templates/i18n/changelog/allocations-notifications.en-eu.hamlet b/templates/i18n/changelog/allocations-notifications.en-eu.hamlet new file mode 100644 index 000000000..8c4e6d58b --- /dev/null +++ b/templates/i18n/changelog/allocations-notifications.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Notifications for central allocations diff --git a/templates/i18n/changelog/asidenav.de-de-formal.hamlet b/templates/i18n/changelog/asidenav.de-de-formal.hamlet new file mode 100644 index 000000000..ed69dfe36 --- /dev/null +++ b/templates/i18n/changelog/asidenav.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Designänderungen diff --git a/templates/i18n/changelog/asidenav.en-eu.hamlet b/templates/i18n/changelog/asidenav.en-eu.hamlet new file mode 100644 index 000000000..f07e4024a --- /dev/null +++ b/templates/i18n/changelog/asidenav.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Design changes diff --git a/templates/i18n/changelog/assigned-corrections-filters.de-de-formal.hamlet b/templates/i18n/changelog/assigned-corrections-filters.de-de-formal.hamlet new file mode 100644 index 000000000..19140c401 --- /dev/null +++ b/templates/i18n/changelog/assigned-corrections-filters.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Liste zugewiesener Abgaben lassen sich nun filtern diff --git a/templates/i18n/changelog/assigned-corrections-filters.en-eu.hamlet b/templates/i18n/changelog/assigned-corrections-filters.en-eu.hamlet new file mode 100644 index 000000000..dfa3a45e2 --- /dev/null +++ b/templates/i18n/changelog/assigned-corrections-filters.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Filters for list of assigned corrections diff --git a/templates/i18n/changelog/automatically-accept-course-applications.de-de-formal.hamlet b/templates/i18n/changelog/automatically-accept-course-applications.de-de-formal.hamlet new file mode 100644 index 000000000..9a8d775ac --- /dev/null +++ b/templates/i18n/changelog/automatically-accept-course-applications.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Automatische Anmeldung von Bewerbern in Kursen, die nicht an einer Zentralanmeldung teilnehmen (nach Bewertung der Bewerbung) diff --git a/templates/i18n/changelog/automatically-accept-course-applications.en-eu.hamlet b/templates/i18n/changelog/automatically-accept-course-applications.en-eu.hamlet new file mode 100644 index 000000000..ce234699b --- /dev/null +++ b/templates/i18n/changelog/automatically-accept-course-applications.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Option to automatically accept applications for courses outside of central allocations diff --git a/templates/i18n/changelog/better-course-communication-tutorials.de-de-formal.hamlet b/templates/i18n/changelog/better-course-communication-tutorials.de-de-formal.hamlet new file mode 100644 index 000000000..fce341865 --- /dev/null +++ b/templates/i18n/changelog/better-course-communication-tutorials.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Besseres Verschicken von Kursmitteilungen an Tutoriumsteilnehmer diff --git a/templates/i18n/changelog/better-course-communication-tutorials.en-eu.hamlet b/templates/i18n/changelog/better-course-communication-tutorials.en-eu.hamlet new file mode 100644 index 000000000..89a056989 --- /dev/null +++ b/templates/i18n/changelog/better-course-communication-tutorials.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Better sending of course communications to tutorial participants diff --git a/templates/i18n/changelog/better-course-participant-detail-page.de-de-formal.hamlet b/templates/i18n/changelog/better-course-participant-detail-page.de-de-formal.hamlet new file mode 100644 index 000000000..40391a2ad --- /dev/null +++ b/templates/i18n/changelog/better-course-participant-detail-page.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Anzeige von Abgaben, Tutorien und Klausuren auf der Seite für einzelne Kursteilnehmer diff --git a/templates/i18n/changelog/better-course-participant-detail-page.en-eu.hamlet b/templates/i18n/changelog/better-course-participant-detail-page.en-eu.hamlet new file mode 100644 index 000000000..307cc232a --- /dev/null +++ b/templates/i18n/changelog/better-course-participant-detail-page.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Submissions, tutorials, and exams are now shown on the detail page for course participants diff --git a/templates/i18n/changelog/better-csv-import.de-de-formal.hamlet b/templates/i18n/changelog/better-csv-import.de-de-formal.hamlet new file mode 100644 index 000000000..857ac9be4 --- /dev/null +++ b/templates/i18n/changelog/better-csv-import.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Verbesserter Workflow & Fehlerbehandlung für CSV-Import diff --git a/templates/i18n/changelog/better-csv-import.en-eu.hamlet b/templates/i18n/changelog/better-csv-import.en-eu.hamlet new file mode 100644 index 000000000..f585e50b3 --- /dev/null +++ b/templates/i18n/changelog/better-csv-import.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Improved workflow and error-handling for CSV-import diff --git a/templates/i18n/changelog/better-file-uploads.de-de-formal.hamlet b/templates/i18n/changelog/better-file-uploads.de-de-formal.hamlet new file mode 100644 index 000000000..5cf99ec89 --- /dev/null +++ b/templates/i18n/changelog/better-file-uploads.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Verbesserte Handhabung von Datei-Uploads diff --git a/templates/i18n/changelog/better-file-uploads.en-eu.hamlet b/templates/i18n/changelog/better-file-uploads.en-eu.hamlet new file mode 100644 index 000000000..ff090f630 --- /dev/null +++ b/templates/i18n/changelog/better-file-uploads.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Improved handling of file uploads diff --git a/templates/i18n/changelog/better-table-cell-colour-coding.de-de-formal.hamlet b/templates/i18n/changelog/better-table-cell-colour-coding.de-de-formal.hamlet new file mode 100644 index 000000000..6a0cbff54 --- /dev/null +++ b/templates/i18n/changelog/better-table-cell-colour-coding.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Verbesserte Farbkodierung von Tabellenzellen diff --git a/templates/i18n/changelog/better-table-cell-colour-coding.en-eu.hamlet b/templates/i18n/changelog/better-table-cell-colour-coding.en-eu.hamlet new file mode 100644 index 000000000..1f0012e18 --- /dev/null +++ b/templates/i18n/changelog/better-table-cell-colour-coding.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Improved colour coding of table cells diff --git a/templates/i18n/changelog/buttons-work-without-javascript.de-de-formal.hamlet b/templates/i18n/changelog/buttons-work-without-javascript.de-de-formal.hamlet new file mode 100644 index 000000000..651a5c3e9 --- /dev/null +++ b/templates/i18n/changelog/buttons-work-without-javascript.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Zahlreiche Knöpfe/Formulare funktionieren wieder bei eingeschaltetem Javascript diff --git a/templates/i18n/changelog/buttons-work-without-javascript.en-eu.hamlet b/templates/i18n/changelog/buttons-work-without-javascript.en-eu.hamlet new file mode 100644 index 000000000..5ac1ddb5a --- /dev/null +++ b/templates/i18n/changelog/buttons-work-without-javascript.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Multiple buttons/forms no work again when JavaScript is enabled diff --git a/templates/i18n/changelog/configurable-datetime-format.de-de-formal.hamlet b/templates/i18n/changelog/configurable-datetime-format.de-de-formal.hamlet new file mode 100644 index 000000000..d637ae8fd --- /dev/null +++ b/templates/i18n/changelog/configurable-datetime-format.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Wählbares Format für Datum diff --git a/templates/i18n/changelog/configurable-datetime-format.en-eu.hamlet b/templates/i18n/changelog/configurable-datetime-format.en-eu.hamlet new file mode 100644 index 000000000..a3d12724d --- /dev/null +++ b/templates/i18n/changelog/configurable-datetime-format.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Configurable date and time formats diff --git a/templates/i18n/changelog/configurable-display-emails.de-de-formal.hamlet b/templates/i18n/changelog/configurable-display-emails.de-de-formal.hamlet new file mode 100644 index 000000000..93e8812fa --- /dev/null +++ b/templates/i18n/changelog/configurable-display-emails.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Anpassbare angezeigte E-Mail Adressen diff --git a/templates/i18n/changelog/configurable-display-emails.en-eu.hamlet b/templates/i18n/changelog/configurable-display-emails.en-eu.hamlet new file mode 100644 index 000000000..75e9ea7de --- /dev/null +++ b/templates/i18n/changelog/configurable-display-emails.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Configulable display emails diff --git a/templates/i18n/changelog/configurable-display-names.de-de-formal.hamlet b/templates/i18n/changelog/configurable-display-names.de-de-formal.hamlet new file mode 100644 index 000000000..1c02bad41 --- /dev/null +++ b/templates/i18n/changelog/configurable-display-names.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Anpassbare angezeigte Namen diff --git a/templates/i18n/changelog/configurable-display-names.en-eu.hamlet b/templates/i18n/changelog/configurable-display-names.en-eu.hamlet new file mode 100644 index 000000000..d0708619b --- /dev/null +++ b/templates/i18n/changelog/configurable-display-names.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Configurable display names diff --git a/templates/i18n/changelog/corrections-display-improvements.de-de-formal.hamlet b/templates/i18n/changelog/corrections-display-improvements.de-de-formal.hamlet new file mode 100644 index 000000000..3c7a1d5bd --- /dev/null +++ b/templates/i18n/changelog/corrections-display-improvements.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Viele Verbesserung zur Anzeige von Korrekturen diff --git a/templates/i18n/changelog/corrections-display-improvements.en-eu.hamlet b/templates/i18n/changelog/corrections-display-improvements.en-eu.hamlet new file mode 100644 index 000000000..bda6e1f73 --- /dev/null +++ b/templates/i18n/changelog/corrections-display-improvements.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Numerous improvements for display of corrections diff --git a/templates/i18n/changelog/correctors-on-course-show.de-de-formal.hamlet b/templates/i18n/changelog/correctors-on-course-show.de-de-formal.hamlet new file mode 100644 index 000000000..85398c03d --- /dev/null +++ b/templates/i18n/changelog/correctors-on-course-show.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Anzeige von Korrektoren auf den Kursseiten diff --git a/templates/i18n/changelog/correctors-on-course-show.en-eu.hamlet b/templates/i18n/changelog/correctors-on-course-show.en-eu.hamlet new file mode 100644 index 000000000..c67066085 --- /dev/null +++ b/templates/i18n/changelog/correctors-on-course-show.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Display of correctors on course overview pages diff --git a/templates/i18n/changelog/course-administrator-invitations.de-de-formal.hamlet b/templates/i18n/changelog/course-administrator-invitations.de-de-formal.hamlet new file mode 100644 index 000000000..bd9f67e09 --- /dev/null +++ b/templates/i18n/changelog/course-administrator-invitations.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Eintragen von Korrektoren und Kursverwaltern auch ohne bestehenden Account diff --git a/templates/i18n/changelog/course-administrator-invitations.en-eu.hamlet b/templates/i18n/changelog/course-administrator-invitations.en-eu.hamlet new file mode 100644 index 000000000..0cc985bf3 --- /dev/null +++ b/templates/i18n/changelog/course-administrator-invitations.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Configuration of course correctors and administrators without existing accounts diff --git a/templates/i18n/changelog/course-administrator-roles.de-de-formal.hamlet b/templates/i18n/changelog/course-administrator-roles.de-de-formal.hamlet new file mode 100644 index 000000000..b332852eb --- /dev/null +++ b/templates/i18n/changelog/course-administrator-roles.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kurse Veranstalter können nun mehrere Dozenten und Assistenten selbst eintragen diff --git a/templates/i18n/changelog/course-administrator-roles.en-eu.hamlet b/templates/i18n/changelog/course-administrator-roles.en-eu.hamlet new file mode 100644 index 000000000..6d4f7b3e7 --- /dev/null +++ b/templates/i18n/changelog/course-administrator-roles.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course administrators can now configure course administrators and assistants themselves diff --git a/templates/i18n/changelog/course-associated-study-field.de-de-formal.hamlet b/templates/i18n/changelog/course-associated-study-field.de-de-formal.hamlet new file mode 100644 index 000000000..260f5bb59 --- /dev/null +++ b/templates/i18n/changelog/course-associated-study-field.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kursanmeldung benötigen assoziertes Hauptfach (für Studierende mit mehreren Hauptfächern) diff --git a/templates/i18n/changelog/course-associated-study-field.en-eu.hamlet b/templates/i18n/changelog/course-associated-study-field.en-eu.hamlet new file mode 100644 index 000000000..75a164dfc --- /dev/null +++ b/templates/i18n/changelog/course-associated-study-field.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course enrollment requires association of a field of study (for students with multiple fields) diff --git a/templates/i18n/changelog/course-convenience-links.de-de-formal.hamlet b/templates/i18n/changelog/course-convenience-links.de-de-formal.hamlet new file mode 100644 index 000000000..891f0186a --- /dev/null +++ b/templates/i18n/changelog/course-convenience-links.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Links für Bequemlichkeiten hinzugefügt (z.B. aktuelles Übungsblatt) diff --git a/templates/i18n/changelog/course-convenience-links.en-eu.hamlet b/templates/i18n/changelog/course-convenience-links.en-eu.hamlet new file mode 100644 index 000000000..f39a3e6b8 --- /dev/null +++ b/templates/i18n/changelog/course-convenience-links.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Convenience links (i.e. current exercise sheet) diff --git a/templates/i18n/changelog/course-list-over-all-terms.de-de-formal.hamlet b/templates/i18n/changelog/course-list-over-all-terms.de-de-formal.hamlet new file mode 100644 index 000000000..631497915 --- /dev/null +++ b/templates/i18n/changelog/course-list-over-all-terms.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kursliste über alle Semester hinweg (Top-Level-Navigation "Kurse"), wird in Zukunft Filter/Suchfunktion erhalten diff --git a/templates/i18n/changelog/course-list-over-all-terms.en-eu.hamlet b/templates/i18n/changelog/course-list-over-all-terms.en-eu.hamlet new file mode 100644 index 000000000..91e876e31 --- /dev/null +++ b/templates/i18n/changelog/course-list-over-all-terms.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Overall course list for all semesters (see "Courses"), will have filters and search functions in the future diff --git a/templates/i18n/changelog/course-materials.de-de-formal.hamlet b/templates/i18n/changelog/course-materials.de-de-formal.hamlet new file mode 100644 index 000000000..c16c704d7 --- /dev/null +++ b/templates/i18n/changelog/course-materials.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kursmaterial diff --git a/templates/i18n/changelog/course-materials.en-eu.hamlet b/templates/i18n/changelog/course-materials.en-eu.hamlet new file mode 100644 index 000000000..5d59fa499 --- /dev/null +++ b/templates/i18n/changelog/course-materials.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course material diff --git a/templates/i18n/changelog/course-messages.de-de-formal.hamlet b/templates/i18n/changelog/course-messages.de-de-formal.hamlet new file mode 100644 index 000000000..1b4eab818 --- /dev/null +++ b/templates/i18n/changelog/course-messages.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Versand von Benachrichtigungen an Kursteilnehmer diff --git a/templates/i18n/changelog/course-messages.en-eu.hamlet b/templates/i18n/changelog/course-messages.en-eu.hamlet new file mode 100644 index 000000000..689483fba --- /dev/null +++ b/templates/i18n/changelog/course-messages.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Sending of course messages to participants diff --git a/templates/i18n/changelog/course-news.de-de-formal.hamlet b/templates/i18n/changelog/course-news.de-de-formal.hamlet new file mode 100644 index 000000000..3fbfc3a83 --- /dev/null +++ b/templates/i18n/changelog/course-news.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +"Aktuelles" für Kurse diff --git a/templates/i18n/changelog/course-news.en-eu.hamlet b/templates/i18n/changelog/course-news.en-eu.hamlet new file mode 100644 index 000000000..c6c43a3ab --- /dev/null +++ b/templates/i18n/changelog/course-news.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course news diff --git a/templates/i18n/changelog/course-occurences.de-de-formal.hamlet b/templates/i18n/changelog/course-occurences.de-de-formal.hamlet new file mode 100644 index 000000000..8688159dd --- /dev/null +++ b/templates/i18n/changelog/course-occurences.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kurstermine diff --git a/templates/i18n/changelog/course-occurences.en-eu.hamlet b/templates/i18n/changelog/course-occurences.en-eu.hamlet new file mode 100644 index 000000000..a7d77daed --- /dev/null +++ b/templates/i18n/changelog/course-occurences.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course occurrences diff --git a/templates/i18n/changelog/course-occurrence-notes.de-de-formal.hamlet b/templates/i18n/changelog/course-occurrence-notes.de-de-formal.hamlet new file mode 100644 index 000000000..0a8df117a --- /dev/null +++ b/templates/i18n/changelog/course-occurrence-notes.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Spalte für Notizen bei Kursterminen diff --git a/templates/i18n/changelog/course-occurrence-notes.en-eu.hamlet b/templates/i18n/changelog/course-occurrence-notes.en-eu.hamlet new file mode 100644 index 000000000..1051c42bf --- /dev/null +++ b/templates/i18n/changelog/course-occurrence-notes.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Column for adding notes to course events diff --git a/templates/i18n/changelog/course-participants-list-add-sheets.de-de-formal.hamlet b/templates/i18n/changelog/course-participants-list-add-sheets.de-de-formal.hamlet new file mode 100644 index 000000000..a52c5c6f4 --- /dev/null +++ b/templates/i18n/changelog/course-participants-list-add-sheets.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Auswertung des Übungsbetriebs unter „Kursteilnehmer“ diff --git a/templates/i18n/changelog/course-participants-list-add-sheets.en-eu.hamlet b/templates/i18n/changelog/course-participants-list-add-sheets.en-eu.hamlet new file mode 100644 index 000000000..e19954cb1 --- /dev/null +++ b/templates/i18n/changelog/course-participants-list-add-sheets.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Inclusion of exercise sheets under “Course participants” diff --git a/templates/i18n/changelog/course-participants-sex.de-de-formal.hamlet b/templates/i18n/changelog/course-participants-sex.de-de-formal.hamlet new file mode 100644 index 000000000..4e459b27c --- /dev/null +++ b/templates/i18n/changelog/course-participants-sex.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Optionale Anzeige des Geschlechts in Teilnehmerlisten u.Ä. diff --git a/templates/i18n/changelog/course-participants-sex.en-eu.hamlet b/templates/i18n/changelog/course-participants-sex.en-eu.hamlet new file mode 100644 index 000000000..198c7c8a9 --- /dev/null +++ b/templates/i18n/changelog/course-participants-sex.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Optionally display sex in (among others) lists of course participants diff --git a/templates/i18n/changelog/course-register-by-admin.de-de-formal.hamlet b/templates/i18n/changelog/course-register-by-admin.de-de-formal.hamlet new file mode 100644 index 000000000..edb6ec891 --- /dev/null +++ b/templates/i18n/changelog/course-register-by-admin.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kursverwalter können Teilnehmer hinzufügen diff --git a/templates/i18n/changelog/course-register-by-admin.en-eu.hamlet b/templates/i18n/changelog/course-register-by-admin.en-eu.hamlet new file mode 100644 index 000000000..48c54a7a6 --- /dev/null +++ b/templates/i18n/changelog/course-register-by-admin.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course administrators may enroll participants diff --git a/templates/i18n/changelog/course-shorthands-within-schools.de-de-formal.hamlet b/templates/i18n/changelog/course-shorthands-within-schools.de-de-formal.hamlet new file mode 100644 index 000000000..48a6d8d4c --- /dev/null +++ b/templates/i18n/changelog/course-shorthands-within-schools.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kurskürzel müssen nur innerhalb eines Instituts eindeutig sein diff --git a/templates/i18n/changelog/course-shorthands-within-schools.en-eu.hamlet b/templates/i18n/changelog/course-shorthands-within-schools.en-eu.hamlet new file mode 100644 index 000000000..ee559c2e8 --- /dev/null +++ b/templates/i18n/changelog/course-shorthands-within-schools.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course shorthands now only need to be unique within a department diff --git a/templates/i18n/changelog/course-visibility.de-de-formal.hamlet b/templates/i18n/changelog/course-visibility.de-de-formal.hamlet new file mode 100644 index 000000000..8592b6a43 --- /dev/null +++ b/templates/i18n/changelog/course-visibility.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kurse haben nun einen Sichtbarkeitszeitraum. diff --git a/templates/i18n/changelog/course-visibility.en-eu.hamlet b/templates/i18n/changelog/course-visibility.en-eu.hamlet new file mode 100644 index 000000000..d95f8e9d6 --- /dev/null +++ b/templates/i18n/changelog/course-visibility.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Courses now have a visibility period. diff --git a/templates/i18n/changelog/csv-course-applications.de-de-formal.hamlet b/templates/i18n/changelog/csv-course-applications.de-de-formal.hamlet new file mode 100644 index 000000000..04b0b816a --- /dev/null +++ b/templates/i18n/changelog/csv-course-applications.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Bewertung von Kurs-Bewerbungen via CSV diff --git a/templates/i18n/changelog/csv-course-applications.en-eu.hamlet b/templates/i18n/changelog/csv-course-applications.en-eu.hamlet new file mode 100644 index 000000000..cd75ffb4f --- /dev/null +++ b/templates/i18n/changelog/csv-course-applications.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Grading of course applications via CSV diff --git a/templates/i18n/changelog/csv-exam-participants.de-de-formal.hamlet b/templates/i18n/changelog/csv-exam-participants.de-de-formal.hamlet new file mode 100644 index 000000000..6b9bb4062 --- /dev/null +++ b/templates/i18n/changelog/csv-exam-participants.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Import & Export von CSV-Dateien für Klausurteilnehmer diff --git a/templates/i18n/changelog/csv-exam-participants.en-eu.hamlet b/templates/i18n/changelog/csv-exam-participants.en-eu.hamlet new file mode 100644 index 000000000..98f03ca6c --- /dev/null +++ b/templates/i18n/changelog/csv-exam-participants.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV import & export of exam participants diff --git a/templates/i18n/changelog/csv-export-course-participants-features.de-de-formal.hamlet b/templates/i18n/changelog/csv-export-course-participants-features.de-de-formal.hamlet new file mode 100644 index 000000000..6cc7fdcb7 --- /dev/null +++ b/templates/i18n/changelog/csv-export-course-participants-features.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV-Export für Liste von Kursteilnehmern exportiert nun optional alle Studiengangsdaten der Teilnehmer diff --git a/templates/i18n/changelog/csv-export-course-participants-features.en-eu.hamlet b/templates/i18n/changelog/csv-export-course-participants-features.en-eu.hamlet new file mode 100644 index 000000000..8e5edec78 --- /dev/null +++ b/templates/i18n/changelog/csv-export-course-participants-features.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV export of course participants now optionally includes all features of study diff --git a/templates/i18n/changelog/csv-export-course-participants-registered-tutorials.de-de-formal.hamlet b/templates/i18n/changelog/csv-export-course-participants-registered-tutorials.de-de-formal.hamlet new file mode 100644 index 000000000..8aeb6e503 --- /dev/null +++ b/templates/i18n/changelog/csv-export-course-participants-registered-tutorials.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV-Export für Liste von Kursteilnehmern exportiert nun auch die angemeldeten Tutorien diff --git a/templates/i18n/changelog/csv-export-course-participants-registered-tutorials.en-eu.hamlet b/templates/i18n/changelog/csv-export-course-participants-registered-tutorials.en-eu.hamlet new file mode 100644 index 000000000..64ae6f239 --- /dev/null +++ b/templates/i18n/changelog/csv-export-course-participants-registered-tutorials.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV export of course participants now includes registered tutorials diff --git a/templates/i18n/changelog/csv-export-course-participants.de-de-formal.hamlet b/templates/i18n/changelog/csv-export-course-participants.de-de-formal.hamlet new file mode 100644 index 000000000..9885bcace --- /dev/null +++ b/templates/i18n/changelog/csv-export-course-participants.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV-Export für Liste von Kursteilnehmern diff --git a/templates/i18n/changelog/csv-export-course-participants.en-eu.hamlet b/templates/i18n/changelog/csv-export-course-participants.en-eu.hamlet new file mode 100644 index 000000000..38de032e9 --- /dev/null +++ b/templates/i18n/changelog/csv-export-course-participants.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV export of course participants diff --git a/templates/i18n/changelog/csv-option-character-set.de-de-formal.hamlet b/templates/i18n/changelog/csv-option-character-set.de-de-formal.hamlet new file mode 100644 index 000000000..6b57d4aa5 --- /dev/null +++ b/templates/i18n/changelog/csv-option-character-set.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +CSV-Export-Option um den beim import und export verwendeten Zeichensatz einzustellen diff --git a/templates/i18n/changelog/csv-option-character-set.en-eu.hamlet b/templates/i18n/changelog/csv-option-character-set.en-eu.hamlet new file mode 100644 index 000000000..6ef50ec74 --- /dev/null +++ b/templates/i18n/changelog/csv-option-character-set.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Introduced CSV export option to set the character encoding used diff --git a/templates/i18n/changelog/csv-option-timestamp.de-de-formal.hamlet b/templates/i18n/changelog/csv-option-timestamp.de-de-formal.hamlet new file mode 100644 index 000000000..876527d8d --- /dev/null +++ b/templates/i18n/changelog/csv-option-timestamp.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Option um an die Namen aller heruntergeladenen CSV-Dateien einen Zeitstempel vorne anzuhängen diff --git a/templates/i18n/changelog/csv-option-timestamp.en-eu.hamlet b/templates/i18n/changelog/csv-option-timestamp.en-eu.hamlet new file mode 100644 index 000000000..0174c9d81 --- /dev/null +++ b/templates/i18n/changelog/csv-option-timestamp.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Introduced option to timestamp all exported CSV files diff --git a/templates/i18n/changelog/de-de-formal.hamlet b/templates/i18n/changelog/de-de-formal.hamlet deleted file mode 100644 index 76f81b8af..000000000 --- a/templates/i18n/changelog/de-de-formal.hamlet +++ /dev/null @@ -1,463 +0,0 @@ -$newline never -
                                -
                                - ^{formatGregorianW 2020 09 16} -
                                -
                                  -
                                • - Es kann nun die Ausgestaltung von Prüfungen angegeben werden. - -
                                  - ^{formatGregorianW 2020 08 28} -
                                  -
                                    -
                                  • - Kursassoziierte Studienfächer wurden abgeschafft. -
                                    - Es werden nun an allen kursbezogenen Stellen jene Studiendaten angezeigt, die während des entsprechenden Semesters aktuell waren. - -
                                    - ^{formatGregorianW 2020 08 10} -
                                    -
                                      -
                                    • - Kursverwalter können pro Teilnehmer personalisierte Übungsblatt-Dateien hinterlegen. -
                                    • - Kurse haben nun einen Sichtbarkeitszeitraum. - -
                                      - ^{formatGregorianW 2020 07 20} -
                                      -
                                        -
                                      • - Abgabe und Download von einzelnen Übungsblättern kann auf Prüfungsteilnehmer beschränkt werden. - -
                                        - ^{formatGregorianW 2020 06 17} -
                                        -
                                          -
                                        • - Neues (YAML-basiertes) Format für Bewertungsdateien - -
                                          - ^{formatGregorianW 2020 06 14} -
                                          -
                                            -
                                          • - Auswertung des Übungsbetriebs unter „Kursteilnehmer“ - -
                                            - ^{formatGregorianW 2020 05 25} -
                                            -
                                              -
                                            • - Zusätzliche Benachrichtigungen für Übungsblätter -
                                            • - Besseres Verschicken von Kursmitteilungen an Tutoriumsteilnehmer - -
                                              - ^{formatGregorianW 2020 05 23} -
                                              -
                                                -
                                              • - Bewertungsmodus für Übungsblätter „Automatisch bestanden, wenn korrigiert“ - -
                                                - ^{formatGregorianW 2020 05 05} -
                                                -
                                                  -
                                                • - Verbesserte Handhabung von Datei-Uploads -
                                                • - Verwaltung von ehemaligen Kursteilnehmern - -
                                                  - ^{formatGregorianW 2020 04 28} -
                                                  -
                                                    -
                                                  • - Registrierte/Feste Abgabegruppen - -
                                                    - ^{formatGregorianW 2020 04 24} -
                                                    -
                                                      -
                                                    • - Häufig gestellte Fragen - -
                                                      - ^{formatGregorianW 2020 04 17} -
                                                      -
                                                        -
                                                      • - Anzeige von Abgaben, Tutorien und Klausuren auf der Seite für einzelne Kursteilnehmer -
                                                      • - Nicht-anonymisierte Korrektur von Übungsblatt-Abgaben - -
                                                        - ^{formatGregorianW 2020 04 15} -
                                                        -
                                                          -
                                                        • - Verstecken von Systemnachrichten auf "Aktuelles" - -
                                                          - ^{formatGregorianW 2020 03 31} -
                                                          -
                                                            -
                                                          • - Spalte für Notizen bei Kursterminen - -
                                                            - ^{formatGregorianW 2020 03 16} -
                                                            -
                                                              -
                                                            • - Verbesserte Farbkodierung von Tabellenzellen -
                                                            • - Webinterface zur Berechnung und Durchführung von Zentralvergaben -
                                                            • - Umstieg auf Serverseitige Sessions -
                                                            • - Zusätzliche Uhrzeit- und Datumsformate - -
                                                              - ^{formatGregorianW 2020 03 06} -
                                                              -
                                                                -
                                                              • - Verbesserter Workflow & Fehlerbehandlung für CSV-Import - -
                                                                - ^{formatGregorianW 2020 02 23} -
                                                                -
                                                                  -
                                                                • - Alle HTML-Eingabefelder akzeptieren nun stattdessen Markdown -
                                                                • - Alle ausgehenden HTML E-Mails haben nun auch einen # - Markdown-Teil - -
                                                                  - ^{formatGregorianW 2020 02 19} -
                                                                  -
                                                                    -
                                                                  • - Prüfungen können nun angeben in welchem Format Leistungen # - eingetragen werden dürfen (Bestanden/Nicht Bestanden, # - Numerische Noten oder Gemischt) - -
                                                                    - ^{formatGregorianW 2020 02 08} -
                                                                    -
                                                                      -
                                                                    • - Oberfläche zum schnellen Eintragen von Prüfungsergebnissen - -
                                                                      - ^{formatGregorianW 2020 02 07} -
                                                                      -
                                                                        -
                                                                      • - Überarbeitete Navigation - -
                                                                        - ^{formatGregorianW 2020 01 30} -
                                                                        -
                                                                          -
                                                                        • - Verbesserung bei der Darstellung von Zuteilungsregeln nach der # - automatischen Verteilung von Klausurteilnehmern -
                                                                        • - Warnungen beim anlegen von Kursen, die auf mehrere zur Auswahl # - stehende Semester/Institute hinweisen - -
                                                                          - ^{formatGregorianW 2020 01 29} -
                                                                          -
                                                                            -
                                                                          • - Automatische Verteilung von Klausurteilnehmern auf # - Termine/Räume - -
                                                                            - ^{formatGregorianW 2020 01 17} -
                                                                            -
                                                                              -
                                                                            • - Eintragung von Ergebnissen für extern (nicht in Uni2work # - verwaltete) Klausuren zur Übermittlung an Prüfungsbeauftragte -
                                                                            • - Export von Listen von Kursteilnehmern zur Durchführung von # - Kursumfragen - -
                                                                              - ^{formatGregorianW 2019 12 05} -
                                                                              -
                                                                                -
                                                                              • Benachrichtigungen bei Änderungen an Übungsblatt-Abgaben - -
                                                                                - ^{formatGregorianW 2019 11 28} -
                                                                                -
                                                                                  -
                                                                                • Unterstützung für LMU-lokale Studiengänge - -
                                                                                  - ^{formatGregorianW 2019 10 31} -
                                                                                  -
                                                                                    -
                                                                                  • Unterstützung für Internationalisierung -
                                                                                  • Englische Übersetzung - -
                                                                                    - ^{formatGregorianW 2019 10 23} -
                                                                                    -
                                                                                      -
                                                                                    • Option um an die Namen aller heruntergeladenen CSV-Dateien einen Zeitstempel vorne anzuhängen -
                                                                                    • CSV-Export-Option um den beim import und export verwendeten Zeichensatz einzustellen - -
                                                                                      - ^{formatGregorianW 2019 10 14} -
                                                                                      -
                                                                                        -
                                                                                      • Kontrolle über Einstellungen eines Tutoriums kann an Tutoren deligiert werden -
                                                                                      • Optionale Anzeige des Geschlechts in Teilnehmerlisten u.Ä. - -
                                                                                        - ^{formatGregorianW 2019 10 10} -
                                                                                        -
                                                                                          -
                                                                                        • CSV-Export für Liste von Kursteilnehmern exportiert nun auch die angemeldeten Tutorien -
                                                                                        • Teilnehmer können von der Teilnehmerliste aus in Tutorien angemeldet werden - -
                                                                                          - ^{formatGregorianW 2019 10 09} -
                                                                                          -
                                                                                            -
                                                                                          • Kurstermine -
                                                                                          • CSV-Export für Liste von Kursteilnehmern exportiert nun optional alle Studiengangsdaten der Teilnehmer - -
                                                                                            - ^{formatGregorianW 2019 10 08} -
                                                                                            -
                                                                                              -
                                                                                            • Benachrichtigung bei nicht-eigenständiger Anmeldung zu einem Kurs -
                                                                                            • CSV-Export für Liste von Kursteilnehmern - -
                                                                                              - ^{formatGregorianW 2019 10 01} -
                                                                                              -
                                                                                                -
                                                                                              • "Aktuelles" für Kurse - -
                                                                                                - ^{formatGregorianW 2019 09 27} -
                                                                                                -
                                                                                                  -
                                                                                                • Automatische Anmeldung von Bewerbern in Kursen, die nicht an einer Zentralanmeldung teilnehmen (nach Bewertung der Bewerbung) - -
                                                                                                  - ^{formatGregorianW 2019 09 25} -
                                                                                                  -
                                                                                                    -
                                                                                                  • Automatische Berechnung von Prufüngsboni -
                                                                                                  • Automatische Berechnung von Prüfungsleistungen -
                                                                                                  • Bugfix: Uhrzeiten werden beim Laden eines Formulars nichtmehr zurückgesetzt -
                                                                                                  • Bugfix: Studierende tauchen in der Prüfungsleistungen-Tabelle nicht mehr mehrfach auf - -
                                                                                                    - ^{formatGregorianW 2019 09 16} -
                                                                                                    -
                                                                                                      -
                                                                                                    • Prüfungsverwaltung im System inkl. direkte Einsicht in relevante Prüfungsleistungen -
                                                                                                    • E-Mail-Benachrichtigungen an zuständige Prüfungsverwalter bei Abschluss einer Klausur -
                                                                                                    • Abschluss von Klausuren (d.h. Melden der Prüfungsleistungen an die Prüfungsverwalter) jetzt als Button, statt als voreingestellter Zeitpunkt - -
                                                                                                      - ^{formatGregorianW 2019 09 13} -
                                                                                                      -
                                                                                                        -
                                                                                                      • Benachrichtigungen bzgl. Klausur An- und Abmeldung - -
                                                                                                        - ^{formatGregorianW 2019 09 12} -
                                                                                                        -
                                                                                                          -
                                                                                                        • Abschätzung der durch Zentralanmeldung benötigten Kurskapazität -
                                                                                                        • Anpassbare angezeigte Namen -
                                                                                                        • Anpassbare angezeigte E-Mail Adressen - -
                                                                                                          - ^{formatGregorianW 2019 09 05} -
                                                                                                          -
                                                                                                            -
                                                                                                          • Benachrichtigungen für Zentralanmeldungen - -
                                                                                                            - ^{formatGregorianW 2019 08 27} -
                                                                                                            -
                                                                                                              -
                                                                                                            • Bewertung von Kurs-Bewerbungen via CSV - -
                                                                                                              - ^{formatGregorianW 2019 08 19} -
                                                                                                              -
                                                                                                                -
                                                                                                              • Bewerbungen für Zentralanmeldungen - -
                                                                                                                - ^{formatGregorianW 2019 08 12} -
                                                                                                                -
                                                                                                                  -
                                                                                                                • Kurse zu Zentralanmeldungen eintragen - -
                                                                                                                  - ^{formatGregorianW 2019 07 23} -
                                                                                                                  -
                                                                                                                    -
                                                                                                                  • Import & Export von CSV-Dateien für Klausurteilnehmer - -
                                                                                                                    - ^{formatGregorianW 2019 06 26} -
                                                                                                                    -
                                                                                                                      -
                                                                                                                    • Rudimentäre Unterstützung für Klausurbetrieb - -
                                                                                                                      - ^{formatGregorianW 2019 06 07} -
                                                                                                                      -
                                                                                                                        -
                                                                                                                      • Abgaben können bestimmte Dateinamen und Endungen erzwingen -
                                                                                                                      • Übungsblätter bieten nun Zip-Archive für alle veröffentlichte Dateien, bzw. Dateigruppen an - -
                                                                                                                        - ^{formatGregorianW 2019 05 20} -
                                                                                                                        -
                                                                                                                          -
                                                                                                                        • Komplett überarbeitete Funktionalität zur automatischen Verteilung von Korrekturen - -
                                                                                                                          - ^{formatGregorianW 2019 05 13} -
                                                                                                                          -
                                                                                                                            -
                                                                                                                          • Kursverwalter können Teilnehmer hinzufügen - -
                                                                                                                            - ^{formatGregorianW 2019 05 10} -
                                                                                                                            -
                                                                                                                              -
                                                                                                                            • Besseres Interface zum Einstellen von Abgebenden -
                                                                                                                            • Download von allen Dateien pro Kursmaterial/Übungsblatt - -
                                                                                                                              - ^{formatGregorianW 2019 05 04} -
                                                                                                                              -
                                                                                                                                -
                                                                                                                              • Kursmaterial - -
                                                                                                                                - ^{formatGregorianW 2019 04 29} -
                                                                                                                                -
                                                                                                                                  -
                                                                                                                                • Tutorien -
                                                                                                                                • Anzeige von Korrektoren auf den Kursseiten - -
                                                                                                                                  - ^{formatGregorianW 2019 04 20} -
                                                                                                                                  -
                                                                                                                                    -
                                                                                                                                  • Versand von Benachrichtigungen an Kursteilnehmer -
                                                                                                                                  • Eintragen von Korrektoren und Kursverwaltern auch ohne bestehenden Account - -
                                                                                                                                    - ^{formatGregorianW 2019 03 27} -
                                                                                                                                    -
                                                                                                                                      -
                                                                                                                                    • Kurse Veranstalter können nun mehrere Dozenten und Assistenten selbst eintragen -
                                                                                                                                    • Erfassung Studiengangsdaten - -
                                                                                                                                      - ^{formatGregorianW 2019 03 20} -
                                                                                                                                      -
                                                                                                                                        -
                                                                                                                                      • Kursanmeldung benötigen assoziertes Hauptfach (für Studierende mit mehreren Hauptfächern) - -
                                                                                                                                        - ^{formatGregorianW 2019 01 30} -
                                                                                                                                        -
                                                                                                                                          -
                                                                                                                                        • Designänderungen - -
                                                                                                                                          - ^{formatGregorianW 2019 01 16} -
                                                                                                                                          -
                                                                                                                                            -
                                                                                                                                          • Links für Bequemlichkeiten hinzugefügt (z.B. aktuelles Übungsblatt) -
                                                                                                                                          • Liste zugewiesener Abgaben lassen sich nun filtern -
                                                                                                                                          • Bugfix: Wenn zwischen Anzeige und Empfang eines Tabellen-Formulars Zeilen verschwinden wird nun eine sinnvolle Fehlermeldung angezeigt - -
                                                                                                                                            - ^{formatGregorianW 2018 11 30} -
                                                                                                                                            -
                                                                                                                                              -
                                                                                                                                            • Bugfix: Übungsblätter im "bestehen nach Punkten"-Modus werden wieder korrekt gespeichert - -
                                                                                                                                              - ^{formatGregorianW 2018 11 29} -
                                                                                                                                              -
                                                                                                                                                -
                                                                                                                                              • Bugfix: Formulare innerhalb von Tabellen funktionieren nun auch nach Javascript-Seitenwechsel oder Ändern der Sortierung - -
                                                                                                                                                - ^{formatGregorianW 2018 11 09} -
                                                                                                                                                -
                                                                                                                                                  -
                                                                                                                                                • Bugfix: Zahlreiche Knöpfe/Formulare funktionieren wieder bei eingeschaltetem Javascript -
                                                                                                                                                • Verschiedene Verbesserungen für Korrektoren - -
                                                                                                                                                  - ^{formatGregorianW 2018 10 19} -
                                                                                                                                                  -
                                                                                                                                                    -
                                                                                                                                                  • Benutzer können sich in der Testphase komplett selbst löschen -
                                                                                                                                                  • Hilfe Widget -
                                                                                                                                                  • Benachrichtigungen per eMail für einige Ereignisse - -
                                                                                                                                                    - ^{formatGregorianW 2018 09 18} -
                                                                                                                                                    -
                                                                                                                                                      -
                                                                                                                                                    • Tooltips funktionieren auch ohne JavaScript -
                                                                                                                                                    • Kurskürzel müssen nur innerhalb eines Instituts eindeutig sein -
                                                                                                                                                    • User Data zeigt nun alle momentan gespeicherten Datensätze an -
                                                                                                                                                    • Unterstützung von Tabellenzusammenfassungen, z.B. Punktsummen -
                                                                                                                                                    • Intelligente Verteilung von Abgaben auf Korrektoren (z.B. bei Krankheit) -
                                                                                                                                                    • Übungsblätter können Abgabe von Dateien verbieten und angeben ob ZIP-Archive entpackt werden sollen - -
                                                                                                                                                      - ^{formatGregorianW 2018 08 06} -
                                                                                                                                                      -
                                                                                                                                                        -
                                                                                                                                                      • Einführung einer Option, ob Dateien automatisch heruntergeladen werden sollen - -
                                                                                                                                                        - ^{formatGregorianW 2018 08 01} -
                                                                                                                                                        -
                                                                                                                                                          -
                                                                                                                                                        • Verbesserter Campus-Login
                                                                                                                                                          - (Ersatz einer C-Bibliothek mit undokumentierter Abhängigkeit durch selbst entwickelten Haskell-Code erlaubt nun auch Umlaute) - -
                                                                                                                                                          - ^{formatGregorianW 2018 07 31} -
                                                                                                                                                          -
                                                                                                                                                            -
                                                                                                                                                          • Viele Verbesserung zur Anzeige von Korrekturen -
                                                                                                                                                          • Kursliste über alle Semester hinweg (Top-Level-Navigation "Kurse"), wird in Zukunft Filter/Suchfunktion erhalten - -
                                                                                                                                                            - ^{formatGregorianW 2018 07 10} -
                                                                                                                                                            -
                                                                                                                                                              -
                                                                                                                                                            • Bugfixes -
                                                                                                                                                            • Wählbares Format für Datum diff --git a/templates/i18n/changelog/download-all-sheet-files-by-type.de-de-formal.hamlet b/templates/i18n/changelog/download-all-sheet-files-by-type.de-de-formal.hamlet new file mode 100644 index 000000000..ec5dd6cb2 --- /dev/null +++ b/templates/i18n/changelog/download-all-sheet-files-by-type.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Übungsblätter bieten nun Zip-Archive für alle veröffentlichte Dateien, bzw. Dateigruppen an diff --git a/templates/i18n/changelog/download-all-sheet-files-by-type.en-eu.hamlet b/templates/i18n/changelog/download-all-sheet-files-by-type.en-eu.hamlet new file mode 100644 index 000000000..7daf597e5 --- /dev/null +++ b/templates/i18n/changelog/download-all-sheet-files-by-type.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Download of all files for exercise sheets (by classification) as ZIP archives diff --git a/templates/i18n/changelog/download-all-sheet-files.de-de-formal.hamlet b/templates/i18n/changelog/download-all-sheet-files.de-de-formal.hamlet new file mode 100644 index 000000000..f9b635b41 --- /dev/null +++ b/templates/i18n/changelog/download-all-sheet-files.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Download von allen Dateien pro Kursmaterial/Übungsblatt diff --git a/templates/i18n/changelog/download-all-sheet-files.en-eu.hamlet b/templates/i18n/changelog/download-all-sheet-files.en-eu.hamlet new file mode 100644 index 000000000..636a6a933 --- /dev/null +++ b/templates/i18n/changelog/download-all-sheet-files.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Download of all files for course material/exercise sheets diff --git a/templates/i18n/changelog/email-notifications.de-de-formal.hamlet b/templates/i18n/changelog/email-notifications.de-de-formal.hamlet new file mode 100644 index 000000000..777ca2eaa --- /dev/null +++ b/templates/i18n/changelog/email-notifications.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Benachrichtigungen per eMail für einige Ereignisse diff --git a/templates/i18n/changelog/email-notifications.en-eu.hamlet b/templates/i18n/changelog/email-notifications.en-eu.hamlet new file mode 100644 index 000000000..46c66d505 --- /dev/null +++ b/templates/i18n/changelog/email-notifications.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Email notifications for some events diff --git a/templates/i18n/changelog/en-eu.hamlet b/templates/i18n/changelog/en-eu.hamlet deleted file mode 100644 index 5c9da9a2c..000000000 --- a/templates/i18n/changelog/en-eu.hamlet +++ /dev/null @@ -1,460 +0,0 @@ -$newline never -
                                                                                                                                                              -
                                                                                                                                                              - ^{formatGregorianW 2020 09 16} -
                                                                                                                                                              -
                                                                                                                                                                -
                                                                                                                                                              • - Exam design can now be specified. - -
                                                                                                                                                                - ^{formatGregorianW 2020 08 28} -
                                                                                                                                                                -
                                                                                                                                                                  -
                                                                                                                                                                • - Abolished course-associated features of study. -
                                                                                                                                                                  - In course-related contexts now all study features which were up to date during the relevant term are displayed. - -
                                                                                                                                                                  - ^{formatGregorianW 2020 08 10} -
                                                                                                                                                                  -
                                                                                                                                                                    -
                                                                                                                                                                  • - Course administrators can now assign personalised exercise sheet files to course participants. -
                                                                                                                                                                  • - Courses now have a visibility period. - -
                                                                                                                                                                    - ^{formatGregorianW 2020 07 20} -
                                                                                                                                                                    -
                                                                                                                                                                      -
                                                                                                                                                                    • - Submission for and download of exercise sheets may be restricted to participants who are registered for an exam. - -
                                                                                                                                                                      - ^{formatGregorianW 2020 06 17} -
                                                                                                                                                                      -
                                                                                                                                                                        -
                                                                                                                                                                      • - New (YAML-based) format for correction files - -
                                                                                                                                                                        - ^{formatGregorianW 2020 06 14} -
                                                                                                                                                                        -
                                                                                                                                                                          -
                                                                                                                                                                        • - Inclusion of exercise sheets under “Course participants” - -
                                                                                                                                                                          - ^{formatGregorianW 2020 05 25} -
                                                                                                                                                                          -
                                                                                                                                                                            -
                                                                                                                                                                          • - Additional notifications for exercise sheets -
                                                                                                                                                                          • - Better sending of course communications to tutorial participants - -
                                                                                                                                                                            - ^{formatGregorianW 2020 05 23} -
                                                                                                                                                                            -
                                                                                                                                                                              -
                                                                                                                                                                            • - Grading mode for exercise sheets “Automatically passed when corrected” - -
                                                                                                                                                                              - ^{formatGregorianW 2020 05 05} -
                                                                                                                                                                              -
                                                                                                                                                                                -
                                                                                                                                                                              • - Improved handling of file uploads -
                                                                                                                                                                              • - Management of former course participants - -
                                                                                                                                                                                - ^{formatGregorianW 2020 04 28} -
                                                                                                                                                                                -
                                                                                                                                                                                  -
                                                                                                                                                                                • - Registered submission groups - -
                                                                                                                                                                                  - ^{formatGregorianW 2020 04 24} -
                                                                                                                                                                                  -
                                                                                                                                                                                    -
                                                                                                                                                                                  • - Frequently asked questions - -
                                                                                                                                                                                    - ^{formatGregorianW 2020 04 17} -
                                                                                                                                                                                    -
                                                                                                                                                                                      -
                                                                                                                                                                                    • - Submissions, tutorials, and exams are now shown on the detail page for course participants -
                                                                                                                                                                                    • - Non-anonymized correction of sheet submissions - -
                                                                                                                                                                                      - ^{formatGregorianW 2020 04 15} -
                                                                                                                                                                                      -
                                                                                                                                                                                        -
                                                                                                                                                                                      • - Hiding of system messages on "News" - -
                                                                                                                                                                                        - ^{formatGregorianW 2020 03 31} -
                                                                                                                                                                                        -
                                                                                                                                                                                          -
                                                                                                                                                                                        • - Column for adding notes to course events - -
                                                                                                                                                                                          - ^{formatGregorianW 2020 03 16} -
                                                                                                                                                                                          -
                                                                                                                                                                                            -
                                                                                                                                                                                          • - Improved colour coding of table cells -
                                                                                                                                                                                          • - Webinterface for computation of central allocations -
                                                                                                                                                                                          • - Switch to server-side sessions -
                                                                                                                                                                                          • - Additional date and time formats - -
                                                                                                                                                                                            - ^{formatGregorianW 2020 03 06} -
                                                                                                                                                                                            -
                                                                                                                                                                                              -
                                                                                                                                                                                            • - Improved workflow and error-handling for CSV-import - -
                                                                                                                                                                                              - ^{formatGregorianW 2020 02 23} -
                                                                                                                                                                                              -
                                                                                                                                                                                                -
                                                                                                                                                                                              • - All HTML-inputs now accept Markdown instead -
                                                                                                                                                                                              • - All HTML-Emails now include a Markdown version - -
                                                                                                                                                                                                - ^{formatGregorianW 2020 02 19} -
                                                                                                                                                                                                -
                                                                                                                                                                                                  -
                                                                                                                                                                                                • - Exams may now specify in which format results are expected to # - entered (passed/failed, numeric grades, or mixed) - -
                                                                                                                                                                                                  - ^{formatGregorianW 2020 02 08} -
                                                                                                                                                                                                  -
                                                                                                                                                                                                    -
                                                                                                                                                                                                  • - Interface for quick entering of exam achievements - -
                                                                                                                                                                                                    - ^{formatGregorianW 2020 02 07} -
                                                                                                                                                                                                    -
                                                                                                                                                                                                      -
                                                                                                                                                                                                    • - Reworked navigation - -
                                                                                                                                                                                                      - ^{formatGregorianW 2020 01 30} -
                                                                                                                                                                                                      -
                                                                                                                                                                                                        -
                                                                                                                                                                                                      • - Improvements in display of assignment rules after automated # - distribution of exam participants -
                                                                                                                                                                                                      • - Display of a warning if multiple semesters/departments are # - available when creating a course - -
                                                                                                                                                                                                        - ^{formatGregorianW 2020 01 29} -
                                                                                                                                                                                                        -
                                                                                                                                                                                                          -
                                                                                                                                                                                                        • - Automated distribution of exam participants over configured # - occurrences/rooms - -
                                                                                                                                                                                                          - ^{formatGregorianW 2020 01 17} -
                                                                                                                                                                                                          -
                                                                                                                                                                                                            -
                                                                                                                                                                                                          • - Support for uploading results of external exams (not managed # - within Uni2work). -
                                                                                                                                                                                                          • - Export of lists of course participants - -
                                                                                                                                                                                                            - ^{formatGregorianW 2019 12 05} -
                                                                                                                                                                                                            -
                                                                                                                                                                                                              -
                                                                                                                                                                                                            • Notifications when exercise sheet submissions are changed - -
                                                                                                                                                                                                              - ^{formatGregorianW 2019 11 28} -
                                                                                                                                                                                                              -
                                                                                                                                                                                                                -
                                                                                                                                                                                                              • Support for LMU-internal terms of study - -
                                                                                                                                                                                                                - ^{formatGregorianW 2019 10 31} -
                                                                                                                                                                                                                -
                                                                                                                                                                                                                  -
                                                                                                                                                                                                                • Support for internationalisation -
                                                                                                                                                                                                                • English translation - -
                                                                                                                                                                                                                  - ^{formatGregorianW 2019 10 23} -
                                                                                                                                                                                                                  -
                                                                                                                                                                                                                    -
                                                                                                                                                                                                                  • Introduced option to timestamp all exported CSV files -
                                                                                                                                                                                                                  • Introduced CSV export option to set the character encoding used - -
                                                                                                                                                                                                                    - ^{formatGregorianW 2019 10 14} -
                                                                                                                                                                                                                    -
                                                                                                                                                                                                                      -
                                                                                                                                                                                                                    • Control of settings for a tutorial may be delegated to the respective tutors -
                                                                                                                                                                                                                    • Optionally display sex in (among others) lists of course participants - -
                                                                                                                                                                                                                      - ^{formatGregorianW 2019 10 10} -
                                                                                                                                                                                                                      -
                                                                                                                                                                                                                        -
                                                                                                                                                                                                                      • CSV export of course participants now includes registered tutorials -
                                                                                                                                                                                                                      • Course participant may be registered for tutorials via the course participant table - -
                                                                                                                                                                                                                        - ^{formatGregorianW 2019 10 09} -
                                                                                                                                                                                                                        -
                                                                                                                                                                                                                          -
                                                                                                                                                                                                                        • Course occurrences -
                                                                                                                                                                                                                        • CSV export of course participants now optionally includes all features of study - -
                                                                                                                                                                                                                          - ^{formatGregorianW 2019 10 08} -
                                                                                                                                                                                                                          -
                                                                                                                                                                                                                            -
                                                                                                                                                                                                                          • Users are notified if they are enrolled in courses by administrators -
                                                                                                                                                                                                                          • CSV export of course participants - -
                                                                                                                                                                                                                            - ^{formatGregorianW 2019 10 01} -
                                                                                                                                                                                                                            -
                                                                                                                                                                                                                              -
                                                                                                                                                                                                                            • Course news - -
                                                                                                                                                                                                                              - ^{formatGregorianW 2019 09 27} -
                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                -
                                                                                                                                                                                                                              • Option to automatically accept applications for courses outside of central allocations - -
                                                                                                                                                                                                                                - ^{formatGregorianW 2019 09 25} -
                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                • Automatic computation of exam boni -
                                                                                                                                                                                                                                • Automatic computation of exam results -
                                                                                                                                                                                                                                • Bugfix: Times are no longer reset when loading a form -
                                                                                                                                                                                                                                • Bugfix: Participants are no longer duplicated in the exam achievements table - -
                                                                                                                                                                                                                                  - ^{formatGregorianW 2019 09 16} -
                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                  • Exam offices (including direct access to relevant exam achievements) -
                                                                                                                                                                                                                                  • Email notifications to relevant exam offices when exams are closed -
                                                                                                                                                                                                                                  • Closure of exams (i.e. notification of relevant exam offices) is now a button instead of a predetermined time - -
                                                                                                                                                                                                                                    - ^{formatGregorianW 2019 09 13} -
                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                    • Notifications for exam registration and deregistration - -
                                                                                                                                                                                                                                      - ^{formatGregorianW 2019 09 12} -
                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                      • Estimation of course capacity required to satisfy central allocations -
                                                                                                                                                                                                                                      • Configurable display names -
                                                                                                                                                                                                                                      • Configulable display emails - -
                                                                                                                                                                                                                                        - ^{formatGregorianW 2019 09 05} -
                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                        • Notifications for central allocations - -
                                                                                                                                                                                                                                          - ^{formatGregorianW 2019 08 27} -
                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                          • Grading of course applications via CSV - -
                                                                                                                                                                                                                                            - ^{formatGregorianW 2019 08 19} -
                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                            • Applications for central allocations - -
                                                                                                                                                                                                                                              - ^{formatGregorianW 2019 08 12} -
                                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                              • Registration of courses for central allocation - -
                                                                                                                                                                                                                                                - ^{formatGregorianW 2019 07 23} -
                                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                                • CSV import & export of exam participants - -
                                                                                                                                                                                                                                                  - ^{formatGregorianW 2019 06 26} -
                                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                                  • Rudimentary support for exams - -
                                                                                                                                                                                                                                                    - ^{formatGregorianW 2019 06 07} -
                                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                                    • Exercise sheets can enforce certain file names and extensions -
                                                                                                                                                                                                                                                    • Download of all files for exercise sheets (by classification) as ZIP archives - -
                                                                                                                                                                                                                                                      - ^{formatGregorianW 2019 05 20} -
                                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                                      • Completely reworked automatic distribution of corrections - -
                                                                                                                                                                                                                                                        - ^{formatGregorianW 2019 05 13} -
                                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                                        • Course administrators may enroll participants - -
                                                                                                                                                                                                                                                          - ^{formatGregorianW 2019 05 10} -
                                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                                          • Improved interface for configuring submittors -
                                                                                                                                                                                                                                                          • Download of all files for course material/exercise sheets - -
                                                                                                                                                                                                                                                            - ^{formatGregorianW 2019 05 04} -
                                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                                            • Course material - -
                                                                                                                                                                                                                                                              - ^{formatGregorianW 2019 04 29} -
                                                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                                              • Tutorials -
                                                                                                                                                                                                                                                              • Display of correctors on course overview pages - -
                                                                                                                                                                                                                                                                - ^{formatGregorianW 2019 04 20} -
                                                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                                                • Sending of course messages to participants -
                                                                                                                                                                                                                                                                • Configuration of course correctors and administrators without existing accounts - -
                                                                                                                                                                                                                                                                  - ^{formatGregorianW 2019 03 27} -
                                                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                                                  • Course administrators can now configure course administrators and assistants themselves -
                                                                                                                                                                                                                                                                  • Features of study - -
                                                                                                                                                                                                                                                                    - ^{formatGregorianW 2019 03 20} -
                                                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                                                    • Course enrollment requires association of a field of study (for students with multiple fields) - -
                                                                                                                                                                                                                                                                      - ^{formatGregorianW 2019 01 30} -
                                                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                                                      • Design changes - -
                                                                                                                                                                                                                                                                        - ^{formatGregorianW 2019 01 16} -
                                                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                                                        • Convenience links (i.e. current exercise sheet) -
                                                                                                                                                                                                                                                                        • Filters for list of assigned corrections -
                                                                                                                                                                                                                                                                        • Bugfix: Proper error message for if entries vanish between generation of table form and submission - -
                                                                                                                                                                                                                                                                          - ^{formatGregorianW 2018 11 30} -
                                                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                                                          • Bugfix: Exercise sheets in "passing by points"-mode now saved correctly again - -
                                                                                                                                                                                                                                                                            - ^{formatGregorianW 2018 11 29} -
                                                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                                                            • Bugfix: Table forms now work after JavaScript page changes and changes in sorting - -
                                                                                                                                                                                                                                                                              - ^{formatGregorianW 2018 11 09} -
                                                                                                                                                                                                                                                                              -
                                                                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                                                              • Bugfix: Multiple buttons/forms no work again when JavaScript is enabled -
                                                                                                                                                                                                                                                                              • Multiple improvements for correctors - -
                                                                                                                                                                                                                                                                                - ^{formatGregorianW 2018 10 19} -
                                                                                                                                                                                                                                                                                -
                                                                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                                                                • During testing users may completely delete their accounts -
                                                                                                                                                                                                                                                                                • Support widget -
                                                                                                                                                                                                                                                                                • Email notifications for some events - -
                                                                                                                                                                                                                                                                                  - ^{formatGregorianW 2018 09 18} -
                                                                                                                                                                                                                                                                                  -
                                                                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                                                                  • Tooltips now work without JavaScript -
                                                                                                                                                                                                                                                                                  • Course shorthands now only need to be unique within a department -
                                                                                                                                                                                                                                                                                  • Personal information now shows all currently saved data -
                                                                                                                                                                                                                                                                                  • Support for table summaries e.g. sums of exercise points -
                                                                                                                                                                                                                                                                                  • Smart distribution of corrections among correctors (e.g. when some are sick) -
                                                                                                                                                                                                                                                                                  • Exercise sheets may prohibit submission of files and determine whether ZIP archives should be unpacked automatically - -
                                                                                                                                                                                                                                                                                    - ^{formatGregorianW 2018 08 06} -
                                                                                                                                                                                                                                                                                    -
                                                                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                                                                    • Option whether files should be downloaded automatically - -
                                                                                                                                                                                                                                                                                      - ^{formatGregorianW 2018 08 01} -
                                                                                                                                                                                                                                                                                      -
                                                                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                                                                      • Improved campus login
                                                                                                                                                                                                                                                                                        - (Replacement of a C-library with undocumented runtime dependencies with a new haskell-library now supports special characters) - -
                                                                                                                                                                                                                                                                                        - ^{formatGregorianW 2018 07 31} -
                                                                                                                                                                                                                                                                                        -
                                                                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                                                                        • Numerous improvements for display of corrections -
                                                                                                                                                                                                                                                                                        • Overall course list for all semesters (see "Courses"), will have filters and search functions in the future - -
                                                                                                                                                                                                                                                                                          - ^{formatGregorianW 2018 07 10} -
                                                                                                                                                                                                                                                                                          -
                                                                                                                                                                                                                                                                                            -
                                                                                                                                                                                                                                                                                          • Bugfixes -
                                                                                                                                                                                                                                                                                          • Configurable date and time formats diff --git a/templates/i18n/changelog/english.de-de-formal.hamlet b/templates/i18n/changelog/english.de-de-formal.hamlet new file mode 100644 index 000000000..371162e62 --- /dev/null +++ b/templates/i18n/changelog/english.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Englische Übersetzung diff --git a/templates/i18n/changelog/english.en-eu.hamlet b/templates/i18n/changelog/english.en-eu.hamlet new file mode 100644 index 000000000..d8738d110 --- /dev/null +++ b/templates/i18n/changelog/english.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +English translation diff --git a/templates/i18n/changelog/error-messages-for-table-item-vanish.de-de-formal.hamlet b/templates/i18n/changelog/error-messages-for-table-item-vanish.de-de-formal.hamlet new file mode 100644 index 000000000..62e49bce9 --- /dev/null +++ b/templates/i18n/changelog/error-messages-for-table-item-vanish.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Wenn zwischen Anzeige und Empfang eines Tabellen-Formulars Zeilen verschwinden wird nun eine sinnvolle Fehlermeldung angezeigt diff --git a/templates/i18n/changelog/error-messages-for-table-item-vanish.en-eu.hamlet b/templates/i18n/changelog/error-messages-for-table-item-vanish.en-eu.hamlet new file mode 100644 index 000000000..edfc5be15 --- /dev/null +++ b/templates/i18n/changelog/error-messages-for-table-item-vanish.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Proper error message for if entries vanish between generation of table form and submission diff --git a/templates/i18n/changelog/estimate-allocated-course-capacity.de-de-formal.hamlet b/templates/i18n/changelog/estimate-allocated-course-capacity.de-de-formal.hamlet new file mode 100644 index 000000000..c4aef0773 --- /dev/null +++ b/templates/i18n/changelog/estimate-allocated-course-capacity.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Abschätzung der durch Zentralanmeldung benötigten Kurskapazität diff --git a/templates/i18n/changelog/estimate-allocated-course-capacity.en-eu.hamlet b/templates/i18n/changelog/estimate-allocated-course-capacity.en-eu.hamlet new file mode 100644 index 000000000..e1bc828d5 --- /dev/null +++ b/templates/i18n/changelog/estimate-allocated-course-capacity.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Estimation of course capacity required to satisfy central allocations diff --git a/templates/i18n/changelog/exam-achievement-participant-duplication.de-de-formal.hamlet b/templates/i18n/changelog/exam-achievement-participant-duplication.de-de-formal.hamlet new file mode 100644 index 000000000..26b56ca5b --- /dev/null +++ b/templates/i18n/changelog/exam-achievement-participant-duplication.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Studierende tauchen in der Prüfungsleistungen-Tabelle nicht mehr mehrfach auf diff --git a/templates/i18n/changelog/exam-achievement-participant-duplication.en-eu.hamlet b/templates/i18n/changelog/exam-achievement-participant-duplication.en-eu.hamlet new file mode 100644 index 000000000..65b8865c6 --- /dev/null +++ b/templates/i18n/changelog/exam-achievement-participant-duplication.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Participants are no longer duplicated in the exam achievements table diff --git a/templates/i18n/changelog/exam-automatic-boni.de-de-formal.hamlet b/templates/i18n/changelog/exam-automatic-boni.de-de-formal.hamlet new file mode 100644 index 000000000..11e8399a5 --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-boni.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Automatische Berechnung von Prufüngsboni diff --git a/templates/i18n/changelog/exam-automatic-boni.en-eu.hamlet b/templates/i18n/changelog/exam-automatic-boni.en-eu.hamlet new file mode 100644 index 000000000..ec884088e --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-boni.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Automatic computation of exam boni diff --git a/templates/i18n/changelog/exam-automatic-results.de-de-formal.hamlet b/templates/i18n/changelog/exam-automatic-results.de-de-formal.hamlet new file mode 100644 index 000000000..fbff163a2 --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-results.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Automatische Berechnung von Prüfungsleistungen diff --git a/templates/i18n/changelog/exam-automatic-results.en-eu.hamlet b/templates/i18n/changelog/exam-automatic-results.en-eu.hamlet new file mode 100644 index 000000000..4ba89dd6c --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-results.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Automatic computation of exam results diff --git a/templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.de-de-formal.hamlet b/templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.de-de-formal.hamlet new file mode 100644 index 000000000..e89db47e3 --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Verbesserung bei der Darstellung von Zuteilungsregeln nach der # +automatischen Verteilung von Klausurteilnehmern diff --git a/templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.en-eu.hamlet b/templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.en-eu.hamlet new file mode 100644 index 000000000..e121190d4 --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-room-distribution-better-rules-display.en-eu.hamlet @@ -0,0 +1,3 @@ +$newline never +Improvements in display of assignment rules after automated # +distribution of exam participants diff --git a/templates/i18n/changelog/exam-automatic-room-distribution.de-de-formal.hamlet b/templates/i18n/changelog/exam-automatic-room-distribution.de-de-formal.hamlet new file mode 100644 index 000000000..beaee8e45 --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-room-distribution.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Automatische Verteilung von Klausurteilnehmern auf # +Termine/Räume diff --git a/templates/i18n/changelog/exam-automatic-room-distribution.en-eu.hamlet b/templates/i18n/changelog/exam-automatic-room-distribution.en-eu.hamlet new file mode 100644 index 000000000..eb8bee890 --- /dev/null +++ b/templates/i18n/changelog/exam-automatic-room-distribution.en-eu.hamlet @@ -0,0 +1,3 @@ +$newline never +Automated distribution of exam participants over configured # +occurrences/rooms diff --git a/templates/i18n/changelog/exam-closure.de-de-formal.hamlet b/templates/i18n/changelog/exam-closure.de-de-formal.hamlet new file mode 100644 index 000000000..09bd1831f --- /dev/null +++ b/templates/i18n/changelog/exam-closure.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Abschluss von Klausuren (d.h. Melden der Prüfungsleistungen an die Prüfungsverwalter) jetzt als Button, statt als voreingestellter Zeitpunkt diff --git a/templates/i18n/changelog/exam-closure.en-eu.hamlet b/templates/i18n/changelog/exam-closure.en-eu.hamlet new file mode 100644 index 000000000..8ac8d4d91 --- /dev/null +++ b/templates/i18n/changelog/exam-closure.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Closure of exams (i.e. notification of relevant exam offices) is now a button instead of a predetermined time diff --git a/templates/i18n/changelog/exam-correct.de-de-formal.hamlet b/templates/i18n/changelog/exam-correct.de-de-formal.hamlet new file mode 100644 index 000000000..80b2ae165 --- /dev/null +++ b/templates/i18n/changelog/exam-correct.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Oberfläche zum schnellen Eintragen von Prüfungsergebnissen diff --git a/templates/i18n/changelog/exam-correct.en-eu.hamlet b/templates/i18n/changelog/exam-correct.en-eu.hamlet new file mode 100644 index 000000000..31d78b839 --- /dev/null +++ b/templates/i18n/changelog/exam-correct.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Interface for quick entering of exam achievements diff --git a/templates/i18n/changelog/exam-design.de-de-formal.hamlet b/templates/i18n/changelog/exam-design.de-de-formal.hamlet new file mode 100644 index 000000000..c915f96ae --- /dev/null +++ b/templates/i18n/changelog/exam-design.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Es kann nun die Ausgestaltung von Prüfungen angegeben werden. diff --git a/templates/i18n/changelog/exam-design.en-eu.hamlet b/templates/i18n/changelog/exam-design.en-eu.hamlet new file mode 100644 index 000000000..f143eaf87 --- /dev/null +++ b/templates/i18n/changelog/exam-design.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Exam design can now be specified. diff --git a/templates/i18n/changelog/exam-grading-mode.de-de-formal.hamlet b/templates/i18n/changelog/exam-grading-mode.de-de-formal.hamlet new file mode 100644 index 000000000..365979cb1 --- /dev/null +++ b/templates/i18n/changelog/exam-grading-mode.de-de-formal.hamlet @@ -0,0 +1,4 @@ +$newline never +Prüfungen können nun angeben in welchem Format Leistungen # +eingetragen werden dürfen (Bestanden/Nicht Bestanden, # +Numerische Noten oder Gemischt) diff --git a/templates/i18n/changelog/exam-grading-mode.en-eu.hamlet b/templates/i18n/changelog/exam-grading-mode.en-eu.hamlet new file mode 100644 index 000000000..2bd95b20a --- /dev/null +++ b/templates/i18n/changelog/exam-grading-mode.en-eu.hamlet @@ -0,0 +1,3 @@ +$newline never +Exams may now specify in which format results are expected to # +entered (passed/failed, numeric grades, or mixed) diff --git a/templates/i18n/changelog/exam-office-exam-notification.de-de-formal.hamlet b/templates/i18n/changelog/exam-office-exam-notification.de-de-formal.hamlet new file mode 100644 index 000000000..79aa1b674 --- /dev/null +++ b/templates/i18n/changelog/exam-office-exam-notification.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +E-Mail-Benachrichtigungen an zuständige Prüfungsverwalter bei Abschluss einer Klausur diff --git a/templates/i18n/changelog/exam-office-exam-notification.en-eu.hamlet b/templates/i18n/changelog/exam-office-exam-notification.en-eu.hamlet new file mode 100644 index 000000000..fafba7921 --- /dev/null +++ b/templates/i18n/changelog/exam-office-exam-notification.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Email notifications to relevant exam offices when exams are closed diff --git a/templates/i18n/changelog/exam-offices.de-de-formal.hamlet b/templates/i18n/changelog/exam-offices.de-de-formal.hamlet new file mode 100644 index 000000000..97b7d6aa2 --- /dev/null +++ b/templates/i18n/changelog/exam-offices.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Prüfungsverwaltung im System inkl. direkte Einsicht in relevante Prüfungsleistungen diff --git a/templates/i18n/changelog/exam-offices.en-eu.hamlet b/templates/i18n/changelog/exam-offices.en-eu.hamlet new file mode 100644 index 000000000..d98e5b971 --- /dev/null +++ b/templates/i18n/changelog/exam-offices.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Exam offices (including direct access to relevant exam achievements) diff --git a/templates/i18n/changelog/exams.de-de-formal.hamlet b/templates/i18n/changelog/exams.de-de-formal.hamlet new file mode 100644 index 000000000..2478ad901 --- /dev/null +++ b/templates/i18n/changelog/exams.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Rudimentäre Unterstützung für Klausurbetrieb diff --git a/templates/i18n/changelog/exams.en-eu.hamlet b/templates/i18n/changelog/exams.en-eu.hamlet new file mode 100644 index 000000000..22331b95c --- /dev/null +++ b/templates/i18n/changelog/exams.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Rudimentary support for exams diff --git a/templates/i18n/changelog/export-course-participants.de-de-formal.hamlet b/templates/i18n/changelog/export-course-participants.de-de-formal.hamlet new file mode 100644 index 000000000..330e565cb --- /dev/null +++ b/templates/i18n/changelog/export-course-participants.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Export von Listen von Kursteilnehmern zur Durchführung von # +Kursumfragen diff --git a/templates/i18n/changelog/export-course-participants.en-eu.hamlet b/templates/i18n/changelog/export-course-participants.en-eu.hamlet new file mode 100644 index 000000000..dff9d3afd --- /dev/null +++ b/templates/i18n/changelog/export-course-participants.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Export of lists of course participants diff --git a/templates/i18n/changelog/external-exams.de-de-formal.hamlet b/templates/i18n/changelog/external-exams.de-de-formal.hamlet new file mode 100644 index 000000000..1cb914736 --- /dev/null +++ b/templates/i18n/changelog/external-exams.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Eintragung von Ergebnissen für extern (nicht in Uni2work # +verwaltete) Klausuren zur Übermittlung an Prüfungsbeauftragte diff --git a/templates/i18n/changelog/external-exams.en-eu.hamlet b/templates/i18n/changelog/external-exams.en-eu.hamlet new file mode 100644 index 000000000..ddcfaa17b --- /dev/null +++ b/templates/i18n/changelog/external-exams.en-eu.hamlet @@ -0,0 +1,3 @@ +$newline never +Support for uploading results of external exams (not managed # +within Uni2work). diff --git a/templates/i18n/changelog/faq.de-de-formal.hamlet b/templates/i18n/changelog/faq.de-de-formal.hamlet new file mode 100644 index 000000000..b7cb0faae --- /dev/null +++ b/templates/i18n/changelog/faq.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Häufig gestellte Fragen diff --git a/templates/i18n/changelog/faq.en-eu.hamlet b/templates/i18n/changelog/faq.en-eu.hamlet new file mode 100644 index 000000000..793deef80 --- /dev/null +++ b/templates/i18n/changelog/faq.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Frequently asked questions diff --git a/templates/i18n/changelog/file-download-option.de-de-formal.hamlet b/templates/i18n/changelog/file-download-option.de-de-formal.hamlet new file mode 100644 index 000000000..0e90a1de4 --- /dev/null +++ b/templates/i18n/changelog/file-download-option.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Einführung einer Option, ob Dateien automatisch heruntergeladen werden sollen diff --git a/templates/i18n/changelog/file-download-option.en-eu.hamlet b/templates/i18n/changelog/file-download-option.en-eu.hamlet new file mode 100644 index 000000000..d94d11672 --- /dev/null +++ b/templates/i18n/changelog/file-download-option.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Option whether files should be downloaded automatically diff --git a/templates/i18n/changelog/former-course-participants.de-de-formal.hamlet b/templates/i18n/changelog/former-course-participants.de-de-formal.hamlet new file mode 100644 index 000000000..c27e0c570 --- /dev/null +++ b/templates/i18n/changelog/former-course-participants.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Verwaltung von ehemaligen Kursteilnehmern diff --git a/templates/i18n/changelog/former-course-participants.en-eu.hamlet b/templates/i18n/changelog/former-course-participants.en-eu.hamlet new file mode 100644 index 000000000..1d19bf080 --- /dev/null +++ b/templates/i18n/changelog/former-course-participants.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Management of former course participants diff --git a/templates/i18n/changelog/forms-times-reset.de-de-formal.hamlet b/templates/i18n/changelog/forms-times-reset.de-de-formal.hamlet new file mode 100644 index 000000000..26807e292 --- /dev/null +++ b/templates/i18n/changelog/forms-times-reset.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Uhrzeiten werden beim Laden eines Formulars nichtmehr zurückgesetzt diff --git a/templates/i18n/changelog/forms-times-reset.en-eu.hamlet b/templates/i18n/changelog/forms-times-reset.en-eu.hamlet new file mode 100644 index 000000000..8dc6ebf9e --- /dev/null +++ b/templates/i18n/changelog/forms-times-reset.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Times are no longer reset when loading a form diff --git a/templates/i18n/changelog/haskell-campus-login.de-de-formal.hamlet b/templates/i18n/changelog/haskell-campus-login.de-de-formal.hamlet new file mode 100644 index 000000000..94fff57ef --- /dev/null +++ b/templates/i18n/changelog/haskell-campus-login.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Verbesserter Campus-Login
                                                                                                                                                                                                                                                                                            + (Ersatz einer C-Bibliothek mit undokumentierter Abhängigkeit durch selbst entwickelten Haskell-Code erlaubt nun auch Umlaute) diff --git a/templates/i18n/changelog/haskell-campus-login.en-eu.hamlet b/templates/i18n/changelog/haskell-campus-login.en-eu.hamlet new file mode 100644 index 000000000..2ede4fd22 --- /dev/null +++ b/templates/i18n/changelog/haskell-campus-login.en-eu.hamlet @@ -0,0 +1,4 @@ +$newline never +Improved campus login +
                                                                                                                                                                                                                                                                                            +(Replacement of a C-library with undocumented runtime dependencies with a new haskell-library now supports special characters) diff --git a/templates/i18n/changelog/hide-system-messages.de-de-formal.hamlet b/templates/i18n/changelog/hide-system-messages.de-de-formal.hamlet new file mode 100644 index 000000000..47f163c5c --- /dev/null +++ b/templates/i18n/changelog/hide-system-messages.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Verstecken von Systemnachrichten auf "Aktuelles" diff --git a/templates/i18n/changelog/hide-system-messages.en-eu.hamlet b/templates/i18n/changelog/hide-system-messages.en-eu.hamlet new file mode 100644 index 000000000..c6d995976 --- /dev/null +++ b/templates/i18n/changelog/hide-system-messages.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Hiding of system messages on "News" diff --git a/templates/i18n/changelog/i18n.de-de-formal.hamlet b/templates/i18n/changelog/i18n.de-de-formal.hamlet new file mode 100644 index 000000000..f53b70215 --- /dev/null +++ b/templates/i18n/changelog/i18n.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Unterstützung für Internationalisierung diff --git a/templates/i18n/changelog/i18n.en-eu.hamlet b/templates/i18n/changelog/i18n.en-eu.hamlet new file mode 100644 index 000000000..5deb3a8bf --- /dev/null +++ b/templates/i18n/changelog/i18n.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Support for internationalisation diff --git a/templates/i18n/changelog/improved-submittor-ui.de-de-formal.hamlet b/templates/i18n/changelog/improved-submittor-ui.de-de-formal.hamlet new file mode 100644 index 000000000..2443d00bb --- /dev/null +++ b/templates/i18n/changelog/improved-submittor-ui.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Besseres Interface zum Einstellen von Abgebenden diff --git a/templates/i18n/changelog/improved-submittor-ui.en-eu.hamlet b/templates/i18n/changelog/improved-submittor-ui.en-eu.hamlet new file mode 100644 index 000000000..67d7c8354 --- /dev/null +++ b/templates/i18n/changelog/improved-submittor-ui.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Improved interface for configuring submittors diff --git a/templates/i18n/changelog/improvements-for-correctors.de-de-formal.hamlet b/templates/i18n/changelog/improvements-for-correctors.de-de-formal.hamlet new file mode 100644 index 000000000..f3b24f805 --- /dev/null +++ b/templates/i18n/changelog/improvements-for-correctors.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Verschiedene Verbesserungen für Korrektoren diff --git a/templates/i18n/changelog/improvements-for-correctors.en-eu.hamlet b/templates/i18n/changelog/improvements-for-correctors.en-eu.hamlet new file mode 100644 index 000000000..9ff709525 --- /dev/null +++ b/templates/i18n/changelog/improvements-for-correctors.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Multiple improvements for correctors diff --git a/templates/i18n/changelog/lmu-internal-fields.de-de-formal.hamlet b/templates/i18n/changelog/lmu-internal-fields.de-de-formal.hamlet new file mode 100644 index 000000000..87828d0a2 --- /dev/null +++ b/templates/i18n/changelog/lmu-internal-fields.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +nterstützung für LMU-lokale Studiengänge diff --git a/templates/i18n/changelog/lmu-internal-fields.en-eu.hamlet b/templates/i18n/changelog/lmu-internal-fields.en-eu.hamlet new file mode 100644 index 000000000..70b5404d0 --- /dev/null +++ b/templates/i18n/changelog/lmu-internal-fields.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Support for LMU-internal terms of study diff --git a/templates/i18n/changelog/markdown-emails.de-de-formal.hamlet b/templates/i18n/changelog/markdown-emails.de-de-formal.hamlet new file mode 100644 index 000000000..f6df727d2 --- /dev/null +++ b/templates/i18n/changelog/markdown-emails.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Alle ausgehenden HTML E-Mails haben nun auch einen # +Markdown-Teil diff --git a/templates/i18n/changelog/markdown-emails.en-eu.hamlet b/templates/i18n/changelog/markdown-emails.en-eu.hamlet new file mode 100644 index 000000000..b7ba9725b --- /dev/null +++ b/templates/i18n/changelog/markdown-emails.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +All HTML-Emails now include a Markdown version diff --git a/templates/i18n/changelog/markdown-html-input.de-de-formal.hamlet b/templates/i18n/changelog/markdown-html-input.de-de-formal.hamlet new file mode 100644 index 000000000..c294ba4f4 --- /dev/null +++ b/templates/i18n/changelog/markdown-html-input.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Alle HTML-Eingabefelder akzeptieren nun stattdessen Markdown diff --git a/templates/i18n/changelog/markdown-html-input.en-eu.hamlet b/templates/i18n/changelog/markdown-html-input.en-eu.hamlet new file mode 100644 index 000000000..66827a18f --- /dev/null +++ b/templates/i18n/changelog/markdown-html-input.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +All HTML-inputs now accept Markdown instead diff --git a/templates/i18n/changelog/non-anonymised-correction.de-de-formal.hamlet b/templates/i18n/changelog/non-anonymised-correction.de-de-formal.hamlet new file mode 100644 index 000000000..6c93b3774 --- /dev/null +++ b/templates/i18n/changelog/non-anonymised-correction.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Nicht-anonymisierte Korrektur von Übungsblatt-Abgaben diff --git a/templates/i18n/changelog/non-anonymised-correction.en-eu.hamlet b/templates/i18n/changelog/non-anonymised-correction.en-eu.hamlet new file mode 100644 index 000000000..daf480fb6 --- /dev/null +++ b/templates/i18n/changelog/non-anonymised-correction.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Non-anonymised correction of sheet submissions diff --git a/templates/i18n/changelog/notification-course-participant-via-admin.de-de-formal.hamlet b/templates/i18n/changelog/notification-course-participant-via-admin.de-de-formal.hamlet new file mode 100644 index 000000000..3fd710199 --- /dev/null +++ b/templates/i18n/changelog/notification-course-participant-via-admin.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Benachrichtigung bei nicht-eigenständiger Anmeldung zu einem Kurs diff --git a/templates/i18n/changelog/notification-course-participant-via-admin.en-eu.hamlet b/templates/i18n/changelog/notification-course-participant-via-admin.en-eu.hamlet new file mode 100644 index 000000000..beed385b0 --- /dev/null +++ b/templates/i18n/changelog/notification-course-participant-via-admin.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Users are notified if they are enrolled in courses by administrators diff --git a/templates/i18n/changelog/notification-exam-registration.de-de-formal.hamlet b/templates/i18n/changelog/notification-exam-registration.de-de-formal.hamlet new file mode 100644 index 000000000..bdb42ea4c --- /dev/null +++ b/templates/i18n/changelog/notification-exam-registration.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Benachrichtigungen bzgl. Klausur An- und Abmeldung diff --git a/templates/i18n/changelog/notification-exam-registration.en-eu.hamlet b/templates/i18n/changelog/notification-exam-registration.en-eu.hamlet new file mode 100644 index 000000000..b52c6288b --- /dev/null +++ b/templates/i18n/changelog/notification-exam-registration.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Notifications for exam registration and deregistration diff --git a/templates/i18n/changelog/notification-submission-changed.de-de-formal.hamlet b/templates/i18n/changelog/notification-submission-changed.de-de-formal.hamlet new file mode 100644 index 000000000..2eec02e9b --- /dev/null +++ b/templates/i18n/changelog/notification-submission-changed.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Benachrichtigungen bei Änderungen an Übungsblatt-Abgaben diff --git a/templates/i18n/changelog/notification-submission-changed.en-eu.hamlet b/templates/i18n/changelog/notification-submission-changed.en-eu.hamlet new file mode 100644 index 000000000..0a39d8036 --- /dev/null +++ b/templates/i18n/changelog/notification-submission-changed.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Notifications when exercise sheet submissions are changed diff --git a/templates/i18n/changelog/passing-by-points-works.de-de-formal.hamlet b/templates/i18n/changelog/passing-by-points-works.de-de-formal.hamlet new file mode 100644 index 000000000..2b419a475 --- /dev/null +++ b/templates/i18n/changelog/passing-by-points-works.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Übungsblätter im "bestehen nach Punkten"-Modus werden wieder korrekt gespeichert diff --git a/templates/i18n/changelog/passing-by-points-works.en-eu.hamlet b/templates/i18n/changelog/passing-by-points-works.en-eu.hamlet new file mode 100644 index 000000000..8133c76d6 --- /dev/null +++ b/templates/i18n/changelog/passing-by-points-works.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Exercise sheets in "passing by points"-mode now saved correctly again diff --git a/templates/i18n/changelog/personal-information.de-de-formal.hamlet b/templates/i18n/changelog/personal-information.de-de-formal.hamlet new file mode 100644 index 000000000..12d8df961 --- /dev/null +++ b/templates/i18n/changelog/personal-information.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +User Data zeigt nun alle momentan gespeicherten Datensätze an diff --git a/templates/i18n/changelog/personal-information.en-eu.hamlet b/templates/i18n/changelog/personal-information.en-eu.hamlet new file mode 100644 index 000000000..3f632adfa --- /dev/null +++ b/templates/i18n/changelog/personal-information.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Personal information now shows all currently saved data diff --git a/templates/i18n/changelog/personalised-sheet-files.de-de-formal.hamlet b/templates/i18n/changelog/personalised-sheet-files.de-de-formal.hamlet new file mode 100644 index 000000000..3ff79975f --- /dev/null +++ b/templates/i18n/changelog/personalised-sheet-files.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kursverwalter können pro Teilnehmer personalisierte Übungsblatt-Dateien hinterlegen. diff --git a/templates/i18n/changelog/personalised-sheet-files.en-eu.hamlet b/templates/i18n/changelog/personalised-sheet-files.en-eu.hamlet new file mode 100644 index 000000000..38abb48dd --- /dev/null +++ b/templates/i18n/changelog/personalised-sheet-files.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course administrators can now assign personalised exercise sheet files to course participants. diff --git a/templates/i18n/changelog/registered-submission-groups.de-de-formal.hamlet b/templates/i18n/changelog/registered-submission-groups.de-de-formal.hamlet new file mode 100644 index 000000000..b03c60e19 --- /dev/null +++ b/templates/i18n/changelog/registered-submission-groups.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Registrierte/Feste Abgabegruppen diff --git a/templates/i18n/changelog/registered-submission-groups.en-eu.hamlet b/templates/i18n/changelog/registered-submission-groups.en-eu.hamlet new file mode 100644 index 000000000..86401501f --- /dev/null +++ b/templates/i18n/changelog/registered-submission-groups.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Registered submission groups diff --git a/templates/i18n/changelog/reworked-automatic-correction-distribution.de-de-formal.hamlet b/templates/i18n/changelog/reworked-automatic-correction-distribution.de-de-formal.hamlet new file mode 100644 index 000000000..ea5be96ab --- /dev/null +++ b/templates/i18n/changelog/reworked-automatic-correction-distribution.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Komplett überarbeitete Funktionalität zur automatischen Verteilung von Korrekturen diff --git a/templates/i18n/changelog/reworked-automatic-correction-distribution.en-eu.hamlet b/templates/i18n/changelog/reworked-automatic-correction-distribution.en-eu.hamlet new file mode 100644 index 000000000..2519bfc2b --- /dev/null +++ b/templates/i18n/changelog/reworked-automatic-correction-distribution.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Completely reworked automatic distribution of corrections diff --git a/templates/i18n/changelog/reworked-navigation.de-de-formal.hamlet b/templates/i18n/changelog/reworked-navigation.de-de-formal.hamlet new file mode 100644 index 000000000..df5c97eb3 --- /dev/null +++ b/templates/i18n/changelog/reworked-navigation.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Überarbeitete Navigation diff --git a/templates/i18n/changelog/reworked-navigation.en-eu.hamlet b/templates/i18n/changelog/reworked-navigation.en-eu.hamlet new file mode 100644 index 000000000..d0a8f4acb --- /dev/null +++ b/templates/i18n/changelog/reworked-navigation.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Reworked navigation diff --git a/templates/i18n/changelog/server-side-sessions.de-de-formal.hamlet b/templates/i18n/changelog/server-side-sessions.de-de-formal.hamlet new file mode 100644 index 000000000..a5bb95a5d --- /dev/null +++ b/templates/i18n/changelog/server-side-sessions.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Umstieg auf Serverseitige Sessions diff --git a/templates/i18n/changelog/server-side-sessions.en-eu.hamlet b/templates/i18n/changelog/server-side-sessions.en-eu.hamlet new file mode 100644 index 000000000..daaec4162 --- /dev/null +++ b/templates/i18n/changelog/server-side-sessions.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Switch to server-side sessions diff --git a/templates/i18n/changelog/sheet-pass-always.de-de-formal.hamlet b/templates/i18n/changelog/sheet-pass-always.de-de-formal.hamlet new file mode 100644 index 000000000..7efb631dd --- /dev/null +++ b/templates/i18n/changelog/sheet-pass-always.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Bewertungsmodus für Übungsblätter „Automatisch bestanden, wenn korrigiert“ diff --git a/templates/i18n/changelog/sheet-pass-always.en-eu.hamlet b/templates/i18n/changelog/sheet-pass-always.en-eu.hamlet new file mode 100644 index 000000000..9dc1be192 --- /dev/null +++ b/templates/i18n/changelog/sheet-pass-always.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Grading mode for exercise sheets “Automatically passed when corrected” diff --git a/templates/i18n/changelog/sheet-specific-files.de-de-formal.hamlet b/templates/i18n/changelog/sheet-specific-files.de-de-formal.hamlet new file mode 100644 index 000000000..655c2f59e --- /dev/null +++ b/templates/i18n/changelog/sheet-specific-files.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Abgaben können bestimmte Dateinamen und Endungen erzwingen diff --git a/templates/i18n/changelog/sheet-specific-files.en-eu.hamlet b/templates/i18n/changelog/sheet-specific-files.en-eu.hamlet new file mode 100644 index 000000000..0fe463ce5 --- /dev/null +++ b/templates/i18n/changelog/sheet-specific-files.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Exercise sheets can enforce certain file names and extensions diff --git a/templates/i18n/changelog/sheets-no-submission-and-zip-control.de-de-formal.hamlet b/templates/i18n/changelog/sheets-no-submission-and-zip-control.de-de-formal.hamlet new file mode 100644 index 000000000..2535950c6 --- /dev/null +++ b/templates/i18n/changelog/sheets-no-submission-and-zip-control.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Übungsblätter können Abgabe von Dateien verbieten und angeben ob ZIP-Archive entpackt werden sollen diff --git a/templates/i18n/changelog/sheets-no-submission-and-zip-control.en-eu.hamlet b/templates/i18n/changelog/sheets-no-submission-and-zip-control.en-eu.hamlet new file mode 100644 index 000000000..d326c95c6 --- /dev/null +++ b/templates/i18n/changelog/sheets-no-submission-and-zip-control.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Exercise sheets may prohibit submission of files and determine whether ZIP archives should be unpacked automatically diff --git a/templates/i18n/changelog/smart-correction-distribution.de-de-formal.hamlet b/templates/i18n/changelog/smart-correction-distribution.de-de-formal.hamlet new file mode 100644 index 000000000..8ac982dc1 --- /dev/null +++ b/templates/i18n/changelog/smart-correction-distribution.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Intelligente Verteilung von Abgaben auf Korrektoren (z.B. bei Krankheit) diff --git a/templates/i18n/changelog/smart-correction-distribution.en-eu.hamlet b/templates/i18n/changelog/smart-correction-distribution.en-eu.hamlet new file mode 100644 index 000000000..a32f620ce --- /dev/null +++ b/templates/i18n/changelog/smart-correction-distribution.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Smart distribution of corrections among correctors (e.g. when some are sick) diff --git a/templates/i18n/changelog/study-features.de-de-formal.hamlet b/templates/i18n/changelog/study-features.de-de-formal.hamlet new file mode 100644 index 000000000..eda05416e --- /dev/null +++ b/templates/i18n/changelog/study-features.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Erfassung Studiengangsdaten diff --git a/templates/i18n/changelog/study-features.en-eu.hamlet b/templates/i18n/changelog/study-features.en-eu.hamlet new file mode 100644 index 000000000..b60f28efc --- /dev/null +++ b/templates/i18n/changelog/study-features.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Features of study diff --git a/templates/i18n/changelog/submission-only-exam-registered.de-de-formal.hamlet b/templates/i18n/changelog/submission-only-exam-registered.de-de-formal.hamlet new file mode 100644 index 000000000..f31394e24 --- /dev/null +++ b/templates/i18n/changelog/submission-only-exam-registered.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Abgabe und Download von einzelnen Übungsblättern kann auf Prüfungsteilnehmer beschränkt werden. diff --git a/templates/i18n/changelog/submission-only-exam-registered.en-eu.hamlet b/templates/i18n/changelog/submission-only-exam-registered.en-eu.hamlet new file mode 100644 index 000000000..75573ad74 --- /dev/null +++ b/templates/i18n/changelog/submission-only-exam-registered.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Submission for and download of exercise sheets may be restricted to participants who are registered for an exam. diff --git a/templates/i18n/changelog/support-widget.de-de-formal.hamlet b/templates/i18n/changelog/support-widget.de-de-formal.hamlet new file mode 100644 index 000000000..3ebaf3968 --- /dev/null +++ b/templates/i18n/changelog/support-widget.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Hilfe Widget diff --git a/templates/i18n/changelog/support-widget.en-eu.hamlet b/templates/i18n/changelog/support-widget.en-eu.hamlet new file mode 100644 index 000000000..91ab58a44 --- /dev/null +++ b/templates/i18n/changelog/support-widget.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Support widget diff --git a/templates/i18n/changelog/table-forms-work-after-ajax.de-de-formal.hamlet b/templates/i18n/changelog/table-forms-work-after-ajax.de-de-formal.hamlet new file mode 100644 index 000000000..31e533e6d --- /dev/null +++ b/templates/i18n/changelog/table-forms-work-after-ajax.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Formulare innerhalb von Tabellen funktionieren nun auch nach Javascript-Seitenwechsel oder Ändern der Sortierung diff --git a/templates/i18n/changelog/table-forms-work-after-ajax.en-eu.hamlet b/templates/i18n/changelog/table-forms-work-after-ajax.en-eu.hamlet new file mode 100644 index 000000000..ec019f5d7 --- /dev/null +++ b/templates/i18n/changelog/table-forms-work-after-ajax.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Table forms now work after JavaScript page changes and changes in sorting diff --git a/templates/i18n/changelog/table-summaries.de-de-formal.hamlet b/templates/i18n/changelog/table-summaries.de-de-formal.hamlet new file mode 100644 index 000000000..038a794fd --- /dev/null +++ b/templates/i18n/changelog/table-summaries.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Unterstützung von Tabellenzusammenfassungen, z.B. Punktsummen diff --git a/templates/i18n/changelog/table-summaries.en-eu.hamlet b/templates/i18n/changelog/table-summaries.en-eu.hamlet new file mode 100644 index 000000000..0ea031cd0 --- /dev/null +++ b/templates/i18n/changelog/table-summaries.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Support for table summaries e.g. sums of exercise points diff --git a/templates/i18n/changelog/tooltips-without-javascript.de-de-formal.hamlet b/templates/i18n/changelog/tooltips-without-javascript.de-de-formal.hamlet new file mode 100644 index 000000000..1f548b67a --- /dev/null +++ b/templates/i18n/changelog/tooltips-without-javascript.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Tooltips funktionieren auch ohne JavaScript diff --git a/templates/i18n/changelog/tooltips-without-javascript.en-eu.hamlet b/templates/i18n/changelog/tooltips-without-javascript.en-eu.hamlet new file mode 100644 index 000000000..59106c624 --- /dev/null +++ b/templates/i18n/changelog/tooltips-without-javascript.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Tooltips now work without JavaScript diff --git a/templates/i18n/changelog/tutorial-registration-via-participant-table.de-de-formal.hamlet b/templates/i18n/changelog/tutorial-registration-via-participant-table.de-de-formal.hamlet new file mode 100644 index 000000000..a3997c034 --- /dev/null +++ b/templates/i18n/changelog/tutorial-registration-via-participant-table.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Teilnehmer können von der Teilnehmerliste aus in Tutorien angemeldet werden diff --git a/templates/i18n/changelog/tutorial-registration-via-participant-table.en-eu.hamlet b/templates/i18n/changelog/tutorial-registration-via-participant-table.en-eu.hamlet new file mode 100644 index 000000000..e4d7633a8 --- /dev/null +++ b/templates/i18n/changelog/tutorial-registration-via-participant-table.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Course participant may be registered for tutorials via the course participant table diff --git a/templates/i18n/changelog/tutorial-tutor-control.de-de-formal.hamlet b/templates/i18n/changelog/tutorial-tutor-control.de-de-formal.hamlet new file mode 100644 index 000000000..6853ae9de --- /dev/null +++ b/templates/i18n/changelog/tutorial-tutor-control.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Kontrolle über Einstellungen eines Tutoriums kann an Tutoren deligiert werden diff --git a/templates/i18n/changelog/tutorial-tutor-control.en-eu.hamlet b/templates/i18n/changelog/tutorial-tutor-control.en-eu.hamlet new file mode 100644 index 000000000..e410c8a07 --- /dev/null +++ b/templates/i18n/changelog/tutorial-tutor-control.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Control of settings for a tutorial may be delegated to the respective tutors diff --git a/templates/i18n/changelog/tutorials.de-de-formal.hamlet b/templates/i18n/changelog/tutorials.de-de-formal.hamlet new file mode 100644 index 000000000..db67205c4 --- /dev/null +++ b/templates/i18n/changelog/tutorials.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Tutorien diff --git a/templates/i18n/changelog/tutorials.en-eu.hamlet b/templates/i18n/changelog/tutorials.en-eu.hamlet new file mode 100644 index 000000000..e64b7c128 --- /dev/null +++ b/templates/i18n/changelog/tutorials.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Tutorials diff --git a/templates/i18n/changelog/warning-multiple-semesters.de-de-formal.hamlet b/templates/i18n/changelog/warning-multiple-semesters.de-de-formal.hamlet new file mode 100644 index 000000000..43adb0b82 --- /dev/null +++ b/templates/i18n/changelog/warning-multiple-semesters.de-de-formal.hamlet @@ -0,0 +1,3 @@ +$newline never +Warnungen beim anlegen von Kursen, die auf mehrere zur Auswahl # +stehende Semester/Institute hinweisen diff --git a/templates/i18n/changelog/warning-multiple-semesters.en-eu.hamlet b/templates/i18n/changelog/warning-multiple-semesters.en-eu.hamlet new file mode 100644 index 000000000..2bdcaba7d --- /dev/null +++ b/templates/i18n/changelog/warning-multiple-semesters.en-eu.hamlet @@ -0,0 +1,3 @@ +$newline never +Display of a warning if multiple semesters/departments are # +available when creating a course diff --git a/templates/i18n/changelog/webinterface-allocation-allocation.de-de-formal.hamlet b/templates/i18n/changelog/webinterface-allocation-allocation.de-de-formal.hamlet new file mode 100644 index 000000000..912269c07 --- /dev/null +++ b/templates/i18n/changelog/webinterface-allocation-allocation.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Webinterface zur Berechnung und Durchführung von Zentralvergaben diff --git a/templates/i18n/changelog/webinterface-allocation-allocation.en-eu.hamlet b/templates/i18n/changelog/webinterface-allocation-allocation.en-eu.hamlet new file mode 100644 index 000000000..8aacb0b66 --- /dev/null +++ b/templates/i18n/changelog/webinterface-allocation-allocation.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +Webinterface for computation of central allocations diff --git a/templates/i18n/changelog/yaml-ratings.de-de-formal.hamlet b/templates/i18n/changelog/yaml-ratings.de-de-formal.hamlet new file mode 100644 index 000000000..12a3f32fc --- /dev/null +++ b/templates/i18n/changelog/yaml-ratings.de-de-formal.hamlet @@ -0,0 +1,2 @@ +$newline never +Neues (YAML-basiertes) Format für Bewertungsdateien diff --git a/templates/i18n/changelog/yaml-ratings.en-eu.hamlet b/templates/i18n/changelog/yaml-ratings.en-eu.hamlet new file mode 100644 index 000000000..c7ba4bd99 --- /dev/null +++ b/templates/i18n/changelog/yaml-ratings.en-eu.hamlet @@ -0,0 +1,2 @@ +$newline never +New (YAML-based) format for correction files diff --git a/templates/versionHistory.hamlet b/templates/versionHistory.hamlet index 8e2fe9b2d..352923959 100644 --- a/templates/versionHistory.hamlet +++ b/templates/versionHistory.hamlet @@ -15,8 +15,7 @@ $newline never

                                                                                                                                                                                                                                                                                            _{MsgVersionHistory} -

                                                                                                                                                                                                                                                                                            - ^{changeLog} + ^{changeLog}

                                                                                                                                                                                                                                                                                            diff --git a/test/Database/Fill.hs b/test/Database/Fill.hs index 4c4b0581c..aad31a85b 100644 --- a/test/Database/Fill.hs +++ b/test/Database/Fill.hs @@ -78,9 +78,9 @@ fillDb = do -> WeekDay -> (Day -> UTCTime) -> UTCTime - termTime next gSeason weekOffset fromEnd day = ($ utctDay) + termTime next gSeason weekOffset fromEnd d = ($ utctDay) where - utctDay = fromWeekDate wYear wWeek $ fromEnum day + utctDay = fromWeekDate wYear wWeek $ fromEnum d (wYear, wWeek, _) = toWeekDate . addDays (round $ 7 * weekOffset) $ fromGregorian gYear rMonth rDay gYear = year $ seasonTerm next gSeason (rMonth, rDay)