attempt to fix build by removing derive Typeable (likely no effect)

This commit is contained in:
Steffen Jost 2023-01-20 09:17:50 +01:00
parent 7f0a45fa4a
commit f208d2aa99
164 changed files with 479 additions and 493 deletions

View File

@ -58,7 +58,7 @@ import qualified Control.Retry as Retry
data Normal k = Normal
{ dAvg :: k
, dRelDev :: Centi
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
sampleN :: (Random.MonadSplit g m, RandomGen g) => (k -> Centi -> k) -> Normal k -> m k
sampleN scale Normal{..}
@ -101,7 +101,7 @@ instance PathPiece DiffTime where
data LoadSimulation
= LoadSheetDownload
| LoadSheetSubmission
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''LoadSimulation $ camelToPathPiece' 1
@ -112,7 +112,7 @@ data LoadOptions = LoadOptions
, loadToken :: Maybe Jwt
, loadTerm :: TermId, loadSchool :: SchoolId, loadCourse :: CourseShorthand, loadSheet :: SheetName
, loadUploadChunks :: Normal Natural, loadUploadChunkSize :: Normal Natural
} deriving (Eq, Ord, Show, Generic, Typeable)
} deriving (Eq, Ord, Show, Generic)
instance Default LoadOptions where
def = LoadOptions
@ -127,7 +127,7 @@ instance Default LoadOptions where
data SimulationOptions = SimulationOptions
{ simParallel :: Natural
, simDelay, simDuration :: Normal DiffTime
} deriving (Eq, Ord, Show, Generic, Typeable)
} deriving (Eq, Ord, Show, Generic)
instance Default SimulationOptions where
def = SimulationOptions

View File

@ -63,7 +63,7 @@ PersonalisedSheetFile
content FileContentReference Maybe
modified UTCTime
UniquePersonalisedSheetFile sheet user type title
deriving Eq Ord Read Show Typeable Generic
deriving Eq Ord Read Show Generic
FallbackPersonalisedSheetFilesKey
course CourseId OnDeleteCascade OnUpdateCascade

View File

@ -383,7 +383,7 @@ makeFoundation appSettings''@AppSettings{..} = do
data SessionStoreException
= SessionStoreNotAvailable
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Exception SessionStoreException
mkSessionStore :: forall m.

View File

@ -35,7 +35,7 @@ import GHC.Stack
data AuditRemoteException
= ARUnsupportedSocketKind
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
instance Exception AuditRemoteException
@ -80,7 +80,7 @@ getRemote = handle testHandler $ do
data AuditException
= AuditRemoteException AuditRemoteException
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
instance Exception AuditException

View File

@ -210,7 +210,7 @@ data Transaction
, transactionUser :: UserId
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = camelToPathPiece' 1

View File

@ -20,7 +20,7 @@ import qualified Data.CaseInsensitive as CI
data DummyMessage = MsgDummyIdent
| MsgDummyIdentPlaceholder
| MsgDummyNoFormData
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
dummyForm :: ( RenderMessage (HandlerSite m) FormMessage

View File

@ -44,13 +44,13 @@ deriving newtype instance Ord Ldap.Attr
data CampusLogin = CampusLogin
{ campusIdent :: CI Text
, campusPassword :: Text
} deriving (Generic, Typeable)
} deriving (Generic)
data CampusMessage = MsgCampusIdentPlaceholder
| MsgCampusIdent
| MsgCampusPassword
| MsgCampusPasswordPlaceholder
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
findUser :: LdapConf -> Ldap -> Text -> [Ldap.Attr] -> IO [Ldap.SearchEntry]
@ -107,7 +107,7 @@ ldapUserEmail = Ldap.Attr "mail" :|
data CampusUserException = CampusUserLdapError LdapPoolError
| CampusUserNoResult
| CampusUserAmbiguous
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
instance Exception CampusUserException
@ -173,7 +173,7 @@ campusUserMatr' pool mode
newtype ADInvalidCredentials = ADInvalidCredentials ADError
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving newtype (Universe, Finite, Enum, Bounded, PathPiece, ToJSON, FromJSON, ToJSONKey, FromJSONKey)
isUnusualADError :: ADError -> Bool

View File

@ -34,7 +34,7 @@ data ADError
| ADAccountExpired
| ADPasswordMustChange
| ADAccountLockedOut
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''ADError $ camelToPathPiece' 1

View File

@ -24,13 +24,13 @@ import qualified Yesod.Auth.Message as Msg
data HashLogin = HashLogin
{ hashIdent :: CI Text
, hashPassword :: Text
} deriving (Generic, Typeable)
} deriving (Generic)
data PWHashMessage = MsgPWHashIdent
| MsgPWHashIdentPlaceholder
| MsgPWHashPassword
| MsgPWHashPasswordPlaceholder
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
hashForm :: ( RenderMessage (HandlerSite m) FormMessage

View File

@ -15,7 +15,7 @@ import Control.Arrow (left)
newtype UnliftIOExceptTError e = UnliftIOExceptTError { getUnliftIOExceptTError :: e }
deriving (Read, Show, Generic, Typeable)
deriving (Read, Show, Generic)
deriving newtype (Exception)

View File

@ -13,10 +13,8 @@ import qualified Data.Binary as Binary
import qualified Data.CryptoID.Class.ImplicitNamespace as I
newtype CryptoIDDecryption ciphertext plaintext = CryptoIDDecryption plaintext
deriving (Typeable)
newtype CryptoIDEncryption ciphertext plaintext = CryptoIDEncryption ciphertext
deriving (Typeable)
newtype CryptoIDDecryption ciphertext plaintext = CryptoIDDecryption plaintext
newtype CryptoIDEncryption ciphertext plaintext = CryptoIDEncryption ciphertext
encrypt :: forall plaintext ciphertext m.
( I.HasCryptoID ciphertext plaintext (HandlerFor (HandlerSite m))

View File

@ -16,7 +16,6 @@ import qualified Language.Haskell.TH.Syntax as TH
deriving instance Generic TimeOfDay
deriving instance Typeable TimeOfDay
instance Hashable TimeOfDay

View File

@ -22,7 +22,6 @@ import Data.Binary (Binary)
deriving instance Generic LiteralType
deriving instance Typeable LiteralType
instance Hashable LiteralType
instance Binary LiteralType
@ -30,7 +29,6 @@ instance NFData LiteralType
deriving instance Generic PersistValue
deriving instance Typeable PersistValue
instance Hashable PersistValue
instance Binary PersistValue

View File

@ -90,7 +90,7 @@ type BearerAuthSite site
-- Access Control
newtype InvalidAuthTag = InvalidAuthTag Text
deriving (Eq, Ord, Show, Read, Generic, Typeable)
deriving (Eq, Ord, Show, Read, Generic)
instance Exception InvalidAuthTag
@ -251,7 +251,7 @@ data AuthContext = AuthContext
{ authCtxAuth :: Maybe (AuthId UniWorX)
, authCtxBearer :: Maybe (BearerToken UniWorX)
, authActiveTags :: AuthTagActive
} deriving (Generic, Typeable)
} deriving (Generic)
deriving stock instance Eq (AuthId UniWorX) => Eq AuthContext
deriving stock instance Ord (AuthId UniWorX) => Ord AuthContext
@ -276,7 +276,7 @@ getAuthContext = liftHandler $ do
return authCtx
newtype IsDryRun = MkIsDryRun { unIsDryRun :: Bool }
deriving stock (Read, Show, Generic, Typeable)
deriving stock (Read, Show, Generic)
deriving newtype (Eq, Ord)
deriving (Semigroup, Monoid) via Any
@ -475,7 +475,7 @@ data AuthorizationCacheKey
| AuthCacheLecturerList | AuthCacheExternalExamStaffList | AuthCacheCorrectorList | AuthCacheExamCorrectorList | AuthCacheTutorList | AuthCacheSubmissionGroupUserList
| AuthCacheCourseRegisteredList TermId SchoolId CourseShorthand
| AuthCacheVisibleSystemMessages
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Hashable, Binary)
cacheAPSchoolFunction :: BearerAuthSite UniWorX

View File

@ -345,7 +345,7 @@ embedRenderMessageVariant ''UniWorX ''ShortSex ("Short" <>)
data SheetType'
= NotGraded' | Normal' | Bonus' | Informational' | ExamPartPoints'
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving (Universe, Finite)
classifySheetType :: SheetType a -> SheetType'
@ -360,7 +360,7 @@ nullaryPathPiece ''SheetType' (camelToPathPiece . dropSuffix "'")
embedRenderMessage ''UniWorX ''SheetType' $ ("SheetType" <>) . fromMaybe (error "Expected SheetType' to have '") . stripSuffix "'"
newtype SheetArchiveFileTypeDirectory = SheetArchiveFileTypeDirectory SheetFileType
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving newtype (Enum, Bounded, Universe, Finite)
embedRenderMessageVariant ''UniWorX ''SheetArchiveFileTypeDirectory $ ("SheetArchiveFileTypeDirectory" <>) . concat . drop 1 . splitCamel
@ -470,7 +470,7 @@ embedRenderMessageVariant ''UniWorX ''ErrorResponseTitle ("ErrorResponseTitle" <
newtype UniWorXMessages = UniWorXMessages [SomeMessage UniWorX]
deriving stock (Generic, Typeable)
deriving stock (Generic)
deriving newtype (Semigroup, Monoid)
instance IsList UniWorXMessages where

View File

@ -40,7 +40,7 @@ import Utils.TH.AlphaConversion (alphaConvE)
newtype MsgFile f g = MsgFile
{ msgFileContent :: InsOrdHashMap String (f (MsgDef f g))
} deriving (Generic, Typeable)
} deriving (Generic)
deriving stock instance Eq (f (MsgDef f g)) => Eq (MsgFile f g)
deriving stock instance Show (f (MsgDef f g)) => Show (MsgFile f g)
@ -54,18 +54,18 @@ data MsgDef f g = MsgDef
{ msgDefVars :: InsOrdHashMap String (f (g TH.Type))
, msgDefContent :: [MsgDefContent]
, msgDefAnnotations :: Set MsgDefAnnotation
} deriving (Generic, Typeable)
} deriving (Generic)
deriving stock instance Eq (f (g TH.Type)) => Eq (MsgDef f g)
deriving stock instance Show (f (g TH.Type)) => Show (MsgDef f g)
data MsgDefContent = MsgDefContentLiteral String
| MsgDefContentSplice Bool {- Recurse? -} TH.Exp
deriving (Eq, Ord, Show, Generic, Typeable)
deriving (Eq, Ord, Show, Generic)
data MsgDefAnnotation = MsgDefIdenticalOk
| MsgDefEmptyOk
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
makePrisms ''MsgDefContent
makePrisms ''MsgDefAnnotation

View File

@ -25,7 +25,7 @@ data instance ButtonClass UniWorX
| BCDanger
| BCLink
| BCMassInputAdd | BCMassInputDelete
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
instance PathPiece (ButtonClass UniWorX) where

View File

@ -380,7 +380,7 @@ breadcrumb SwaggerJsonR = breadcrumb SwaggerR
data NavQuickView
= NavQuickViewFavourite
| NavQuickViewPageActionSecondary
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving (Universe, Finite)
navQuick :: NavQuickView -> (NavQuickView -> Any)
@ -394,17 +394,17 @@ data NavType
{ navMethod :: StdMethod
, navData :: [(Text, Text)]
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Hashable, Binary)
makeLenses_ ''NavType
makePrisms ''NavType
data NavLevel = NavLevelTop | NavLevelInner
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
data NavHeaderRole = NavHeaderPrimary | NavHeaderSecondary
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
data NavAccess = NavAccessDB (ReaderT SqlReadBackend Handler Bool)
| NavAccessHandler (Handler Bool)
@ -465,7 +465,7 @@ data Nav
}
| NavFooter
{ navLink :: NavLink
} deriving (Generic, Typeable)
} deriving (Generic)
makeLenses_ ''Nav
makePrisms ''Nav
@ -479,7 +479,7 @@ type family ChildrenNavChildren a where
data NavigationCacheKey
= NavCacheRouteAccess AuthContext NavType (Route UniWorX)
deriving (Generic, Typeable)
deriving (Generic)
deriving stock instance Eq (AuthId UniWorX) => Eq NavigationCacheKey
deriving stock instance Ord (AuthId UniWorX) => Ord NavigationCacheKey

View File

@ -51,7 +51,7 @@ data CourseFavouriteToggleButton
= BtnCourseFavouriteToggleManual
| BtnCourseFavouriteToggleAutomatic
| BtnCourseFavouriteToggleOff
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''CourseFavouriteToggleButton $ camelToPathPiece' 4
@ -105,7 +105,7 @@ storedFavouriteReason tid ssh csh muid = fmap unValueFirst . E.select . E.from $
data MemcachedKeyFavourites
= MemcachedKeyFavouriteQuickActions (TermId, SchoolId, CourseShorthand) AuthContext (NonEmpty Lang)
deriving (Generic, Typeable)
deriving (Generic)
deriving instance Eq AuthContext => Eq MemcachedKeyFavourites
deriving instance Read AuthContext => Read MemcachedKeyFavourites
@ -115,7 +115,7 @@ deriving instance Binary AuthContext => Binary MemcachedKeyFavourites
data MemcachedLimitKeyFavourites
= MemcachedLimitKeyFavourites
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Hashable, Binary)

View File

@ -51,14 +51,14 @@ type SMTPPool = Pool SMTPConnection
data SomeSessionStorage
= SessionStorageMemcachedSql { sessionStorageMemcachedSql :: MemcachedSqlStorage SessionMap }
| SessionStorageAcid { sessionStorageAcid :: AcidStorage SessionMap }
deriving (Generic, Typeable)
deriving (Generic)
makePrisms ''SomeSessionStorage
data AppMemcached = AppMemcached
{ memcachedKey :: AEAD.Key
, memcachedConn :: Memcached.Connection
} deriving (Generic, Typeable)
} deriving (Generic)
makeLenses_ ''AppMemcached
@ -66,7 +66,7 @@ data AppMemcachedLocal = AppMemcachedLocal
{ memcachedLocalARC :: ARCHandle (Fingerprint, Lazy.ByteString) Int (NFDynamic, Maybe POSIXTime)
, memcachedLocalHandleInvalidations :: Async ()
, memcachedLocalInvalidationQueue :: TVar (Seq (Fingerprint, Lazy.ByteString))
} deriving (Generic, Typeable)
} deriving (Generic)
makeLenses_ ''AppMemcachedLocal
@ -104,7 +104,7 @@ data UniWorX = UniWorX
, appVolatileClusterSettingsCache :: TVar VolatileClusterSettingsCache
, appStartTime :: UTCTime -- for Status Page
, appAvsQuery :: Maybe AvsQuery
} deriving (Typeable)
}
makeLenses_ ''UniWorX
instance HasInstanceID UniWorX InstanceId where

View File

@ -17,7 +17,7 @@ data UpsertCampusUserMode
| UpsertCampusUserLoginOther { upsertCampusUserIdent :: UserIdent } -- erlaubt keinen späteren Login
| UpsertCampusUserLdapSync { upsertCampusUserIdent :: UserIdent }
| UpsertCampusUserGuessUser
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
makeLenses_ ''UpsertCampusUserMode
makePrisms ''UpsertCampusUserMode

View File

@ -130,7 +130,7 @@ data CampusUserConversionException
| CampusUserInvalidMatriculation
| CampusUserInvalidFeaturesOfStudy Text
| CampusUserInvalidAssociatedSchools Text
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Exception)
_upsertCampusUserMode :: Traversal' (Creds UniWorX) UpsertCampusUserMode

View File

@ -41,7 +41,7 @@ single = uncurry Map.singleton
-- Button only needed in AVS TEST; further buttons see below
data ButtonAvsTest = BtnCheckLicences | BtnSynchLicences
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonAvsTest
instance Finite ButtonAvsTest
@ -279,7 +279,7 @@ type SynchDBRow = (E.Value AvsPersonId, E.Value AvsLicence, Entity Qualification
-- Buttons only needed for AVS Synching
data ButtonAvsImportUnknown = BtnAvsImportUnknown
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonAvsImportUnknown
instance Finite ButtonAvsImportUnknown
nullaryPathPiece ''ButtonAvsImportUnknown camelToPathPiece
@ -288,7 +288,7 @@ instance Button UniWorX ButtonAvsImportUnknown where
btnClasses BtnAvsImportUnknown = [BCIsButton, BCPrimary]
data ButtonAvsRevokeUnknown = BtnAvsRevokeUnknown
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonAvsRevokeUnknown
instance Finite ButtonAvsRevokeUnknown
nullaryPathPiece ''ButtonAvsRevokeUnknown camelToPathPiece
@ -300,7 +300,7 @@ instance Button UniWorX ButtonAvsRevokeUnknown where
data LicenceTableAction = LicenceTableChangeAvs
| LicenceTableRevokeFDrive
| LicenceTableGrantFDrive
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''LicenceTableAction $ camelToPathPiece' 2
@ -311,7 +311,7 @@ data LicenceTableActionData = LicenceTableChangeAvsData
| LicenceTableGrantFDriveData { licenceTableChangeFDriveQId :: QualificationId
, licenceTableChangeFDriveEnd :: Day
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
postProblemAvsSynchR, getProblemAvsSynchR :: Handler Html

View File

@ -35,7 +35,7 @@ import Handler.Admin.Test.Download (testDownload)
-- BEGIN - Buttons needed only here
data ButtonCreate = CreateMath | CreateInf | CrashApp -- Dummy for Example
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonCreate
instance Finite ButtonCreate

View File

@ -30,7 +30,7 @@ data TestDownloadMode
= TestDownloadDirect
| TestDownloadInTransaction
| TestDownloadFromDatabase
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite, Binary)
nullaryPathPiece ''TestDownloadMode $ camelToPathPiece' 2
@ -40,7 +40,7 @@ data TestDownloadOptions = TestDownloadOptions
{ dlSeed :: Random.Seed
, dlMaxSize, dlChunkSize :: Int
, dlMode :: TestDownloadMode
} deriving (Generic, Typeable)
} deriving (Generic)
deriving anyclass (Binary)
testDownloadForm :: Form TestDownloadOptions

View File

@ -38,10 +38,10 @@ data BTFImpersonate
{ btfiCount :: Int64
, btfiWeightActivity :: Bool
}
deriving (Eq, Ord, Generic, Typeable)
deriving (Eq, Ord, Generic)
data BTFImpersonate' = BTFINone' | BTFISingle' | BTFIRandom'
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving (Universe, Finite, Hashable)
nullaryPathPiece ''BTFImpersonate' $ let noNone n | n == "none" = "impersonate-" <> n
| otherwise = n
@ -56,7 +56,7 @@ data BearerTokenForm = BearerTokenForm
, btfAddAuth :: Maybe AuthDNF
, btfExpiresAt :: Maybe (Maybe UTCTime)
, btfStartsAt :: Maybe UTCTime
} deriving (Generic, Typeable)
} deriving (Generic)
bearerTokenForm :: WForm Handler (FormResult BearerTokenForm)
bearerTokenForm = do

View File

@ -27,12 +27,12 @@ instance IsInvitableJunction Lecturer where
type InvitationFor Lecturer = Course
data InvitableJunction Lecturer = JunctionLecturer
{ jLecturerType :: LecturerType
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData Lecturer = InvDBDataLecturer
{ invDBLecturerType :: Maybe LecturerType
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData Lecturer = InvTokenDataLecturer
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\Lecturer{..} -> (lecturerUser, lecturerCourse, JunctionLecturer lecturerType))

View File

@ -30,7 +30,7 @@ type TutorialIdent = CI Text
data ButtonCourseRegisterMode = BtnCourseRegisterConfirm | BtnCourseRegisterAbort
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe ButtonCourseRegisterMode
instance Finite ButtonCourseRegisterMode
@ -50,7 +50,7 @@ data CourseRegisterAction
= CourseRegisterActionAddParticipant
| CourseRegisterActionAddTutorialMember
-- | CourseRegisterActionUnknownPerson
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe CourseRegisterAction
instance Finite CourseRegisterAction
@ -67,7 +67,7 @@ data CourseRegisterActionData
-- | CourseRegisterActionUnknownPersonData -- pseudo-action; just for display
-- { crActUnknownPersonIdent :: Text
-- }
deriving (Eq, Ord, Show, Generic, Typeable)
deriving (Eq, Ord, Show, Generic)
makeLenses_ ''CourseRegisterActionData
makePrisms ''CourseRegisterActionData
@ -97,7 +97,7 @@ courseRegisterRenderAction act = [whamlet|^{userWidget (view _2 (crActUser act))
data AddUserRequest = AddUserRequest
{ auReqUsers :: Set UserSearchKey
, auReqTutorial :: Maybe TutorialIdent
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data AddParticipantsResult = AddParticipantsResult
@ -106,7 +106,7 @@ data AddParticipantsResult = AddParticipantsResult
, aurAlreadyTutorialMember
, aurRegisterSuccess
, aurTutorialSuccess :: Set UserId
} deriving (Read, Show, Generic, Typeable)
} deriving (Read, Show, Generic)
instance Semigroup AddParticipantsResult where
(<>) = mappenddefault

View File

@ -23,7 +23,7 @@ import qualified Database.Esqueleto.Utils as E
-- Dedicated CourseRegistrationButton
data ButtonCourseRegister = BtnCourseRegister | BtnCourseDeregister
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonCourseRegister
instance Finite ButtonCourseRegister
nullaryPathPiece ''ButtonCourseRegister $ camelToPathPiece' 1

View File

@ -37,7 +37,7 @@ import qualified Data.Text.Lazy as LT
data ExamAction = ExamDeregister
| ExamSetResult
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''ExamAction $ camelToPathPiece' 1
embedRenderMessage ''UniWorX ''ExamAction $ Text.replace "Exam" "ExamUser"
@ -46,7 +46,7 @@ data ExamActionData = ExamDeregisterData
| ExamSetResultData (Maybe ExamResultPassedGrade)
data TutorialAction = TutorialDeregister
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''TutorialAction $ camelToPathPiece' 1
embedRenderMessage ''UniWorX ''TutorialAction $ Text.replace "Tutorial" "TutorialUser"

View File

@ -196,7 +196,7 @@ data UserTableCsv = UserTableCsv
, csvUserTutorials :: ([TutorialName], Map (CI Text) (Maybe TutorialName))
, csvUserExams :: [ExamName]
, csvUserSheets :: Map SheetName (SheetType (), Maybe Points)
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
makeLenses_ ''UserTableCsv
instance Csv.ToNamedRecord UserTableCsv where
@ -245,7 +245,7 @@ instance CsvColumnsExplained UserTableCsv where
newtype UserCsvExportData = UserCsvExportData
{ csvUserIncludeSheets :: Bool
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
instance Default UserCsvExportData where
def = UserCsvExportData False
@ -279,17 +279,17 @@ data UserTableJson = UserTableJson
, jsonUserTutorialGroups :: Map (CI Text) (Maybe TutorialName)
, jsonUserExams :: Set ExamName
, jsonUserSheets :: Map SheetName UserTableJsonSheetResult
} deriving (Generic, Typeable)
} deriving (Generic)
data UserTableJsonSheetResult = UserTableJsonSheetResult
{ jsonSheetType :: SheetType UserTableJsonSheetTypeExamPartRef
, jsonPoints :: Maybe Points
} deriving (Generic, Typeable)
} deriving (Generic)
data UserTableJsonSheetTypeExamPartRef = UserTableJsonSheetTypeExamPartRef
{ jsonExam :: ExamName
, jsonExamPart :: ExamPartNumber
} deriving (Generic, Typeable)
} deriving (Generic)
deriveToJSON defaultOptions
{ fieldLabelModifier = camelToPathPiece' 1
@ -325,7 +325,7 @@ data CourseUserAction = CourseUserSendMail
| CourseUserReRegister
| CourseUserDeregister
| CourseUserDownloadPersonalisedSheetFiles
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe CourseUserAction
instance Finite CourseUserAction
@ -350,7 +350,7 @@ data CourseUserActionData = CourseUserSendMailData
{ downloadPersonalisedFilesForSheet :: SheetName
, downloadPersonalisedFilesAnonMode :: PersonalisedSheetFilesDownloadAnonymous
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
makeCourseUserTable :: forall h p cols act act'.

View File

@ -29,7 +29,7 @@ data AddRecipientsResult = AddRecipientsResult
, aurNoCourseRegistration
, aurSuccess
, aurSuccessCourse :: [UserEmail]
} deriving (Read, Show, Generic, Typeable)
} deriving (Read, Show, Generic)
instance Semigroup AddRecipientsResult where
(<>) = mappenddefault

View File

@ -21,7 +21,7 @@ import Database.Persist.Sql (updateWhereCount)
newtype ExamAutoOccurrenceCalculateForm = ExamAutoOccurrenceCalculateForm
{ eaofConfig :: ExamAutoOccurrenceConfig
} deriving stock (Eq, Ord, Read, Show, Generic, Typeable)
} deriving stock (Eq, Ord, Read, Show, Generic)
deriving newtype (Default, FromJSON, ToJSON)
makeLenses_ ''ExamAutoOccurrenceCalculateForm
@ -30,7 +30,7 @@ data ExamAutoOccurrenceAcceptForm = ExamAutoOccurrenceAcceptForm
{ eaofMapping :: ExamOccurrenceMapping ExamOccurrenceId
, eaofAssignment :: Map UserId (Maybe ExamOccurrenceId)
, eaofSuccess :: Bool
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ fieldLabelModifier = camelToPathPiece' 1
@ -41,7 +41,7 @@ data ExamAutoOccurrenceButton
| BtnExamAutoOccurrenceAccept
| BtnExamAutoOccurrenceNudgeUp | BtnExamAutoOccurrenceNudgeDown
| BtnExamAutoOccurrenceIgnore | BtnExamAutoOccurrenceReconsider
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ExamAutoOccurrenceButton
instance Finite ExamAutoOccurrenceButton

View File

@ -25,11 +25,11 @@ import qualified Data.HashSet as HashSet
instance IsInvitableJunction ExamCorrector where
type InvitationFor ExamCorrector = Exam
data InvitableJunction ExamCorrector = JunctionExamCorrector
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData ExamCorrector = InvDBDataExamCorrector
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData ExamCorrector = InvTokenDataExamCorrector
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\ExamCorrector{..} -> (examCorrectorUser, examCorrectorExam, JunctionExamCorrector))

View File

@ -25,7 +25,7 @@ import qualified Database.Esqueleto.Utils as E
data ExamEditException
= ExamEditExamNameTaken ExamName
| ExamEditWouldBreakSheetTypeReference
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Exception)
embedRenderMessage ''UniWorX ''ExamEditException id

View File

@ -68,7 +68,7 @@ data ExamOccurrenceForm = ExamOccurrenceForm
, eofStart :: UTCTime
, eofEnd :: Maybe UTCTime
, eofDescription :: Maybe StoredMarkup
} deriving (Show, Eq, Generic, Typeable)
} deriving (Show, Eq, Generic)
instance Ord ExamOccurrenceForm where
compare = mconcat
@ -88,7 +88,7 @@ data ExamPartForm = ExamPartForm
, epfName :: Maybe ExamPartName
, epfMaxPoints :: Maybe Points
, epfWeight :: Rational
} deriving (Read, Show, Eq, Generic, Typeable)
} deriving (Read, Show, Eq, Generic)
instance Ord ExamPartForm where
compare = mconcat

View File

@ -21,7 +21,7 @@ data ButtonExamRegister = BtnExamRegisterOccurrence
| BtnExamSwitchOccurrence
| BtnExamRegister
| BtnExamDeregister
deriving (Enum, Bounded, Eq, Ord, Read, Show, Generic, Typeable)
deriving (Enum, Bounded, Eq, Ord, Read, Show, Generic)
instance Universe ButtonExamRegister
instance Finite ButtonExamRegister
nullaryPathPiece ''ButtonExamRegister $ camelToPathPiece' 2

View File

@ -31,14 +31,14 @@ instance IsInvitableJunction ExamRegistration where
data InvitableJunction ExamRegistration = JunctionExamRegistration
{ jExamRegistrationOccurrence :: Maybe ExamOccurrenceId
, jExamRegistrationTime :: UTCTime
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData ExamRegistration = InvDBDataExamRegistration
{ invDBExamRegistrationOccurrence :: Maybe ExamOccurrenceId
, invDBExamRegistrationDeadline :: UTCTime
, invDBExamRegistrationCourseRegister :: Bool
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData ExamRegistration = InvTokenDataExamRegistration
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\ExamRegistration{..} -> (examRegistrationUser, examRegistrationExam, JunctionExamRegistration examRegistrationOccurrence examRegistrationTime))

View File

@ -298,7 +298,7 @@ data ExamUserAction = ExamUserDeregister
| ExamUserSetResult
| ExamUserAcceptComputedResult
| ExamUserResetToComputedResult
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe ExamUserAction
instance Finite ExamUserAction
@ -328,7 +328,7 @@ data ExamUserCsvActionClass
| ExamUserCsvOverrideResult
| ExamUserCsvSetCourseNote
| ExamUserCsvDeregister
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
embedRenderMessage ''UniWorX ''ExamUserCsvActionClass id
data ExamUserCsvAction
@ -366,7 +366,7 @@ data ExamUserCsvAction
{ examUserCsvActUser :: UserId
, examUserCsvActCourseNote :: Maybe StoredMarkup
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = over Text.packed $ Text.intercalate "-" . map Text.toLower . drop 3 . dropEnd 1 . splitCamel
, fieldLabelModifier = camelToPathPiece' 4
@ -379,7 +379,7 @@ data ExamUserCsvException
| ExamUserCsvExceptionNoMatchingStudyFeatures
| ExamUserCsvExceptionNoMatchingOccurrence
| ExamUserCsvExceptionMismatchedGradingMode ExamGradingMode ExamGradingMode
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
instance Exception ExamUserCsvException

View File

@ -30,7 +30,7 @@ import Handler.Utils.StudyFeatures
data ButtonCloseExam = BtnCloseExam
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonCloseExam
instance Finite ButtonCloseExam
@ -84,7 +84,7 @@ examCloseWidget dest eId = do
data ButtonFinishExam = BtnFinishExam
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonFinishExam
instance Finite ButtonFinishExam
@ -211,7 +211,7 @@ instance CsvColumnsExplained ExamUserTableCsv where
]
data ExamUserAction = ExamUserMarkSynchronised
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe ExamUserAction
instance Finite ExamUserAction
@ -224,7 +224,7 @@ data ExamUserCsvExportData = ExamUserCsvExportData
{ csvEUserMarkSynchronised :: Bool
, csvEUserSetLabel :: Bool
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
-- | View a list of all users' grades that the current user has access to

View File

@ -25,7 +25,7 @@ import qualified Data.Set as Set
data ExamAction = ExamSetLabel | ExamRemoveLabel
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''ExamAction $ camelToPathPiece' 1
@ -35,7 +35,7 @@ data ExamActionData = ExamSetLabelData
{ easlNewLabel :: ExamOfficeLabelId
}
| ExamRemoveLabelData
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data ExamsTableFilterProj = ExamsTableFilterProj

View File

@ -20,7 +20,7 @@ data ExamOfficeFieldMode
= EOFNotSubscribed
| EOFSubscribed
| EOFForced
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
embedRenderMessage ''UniWorX ''ExamOfficeFieldMode $ concat . set (ix 0) "ExamOfficeField" . splitCamel
instance Universe ExamOfficeFieldMode
instance Finite ExamOfficeFieldMode

View File

@ -29,13 +29,13 @@ import qualified Data.HashSet as HashSet
instance IsInvitableJunction ExamOfficeUser where
type InvitationFor ExamOfficeUser = User
data InvitableJunction ExamOfficeUser = JunctionExamOfficeUser
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData ExamOfficeUser = InvDBDataExamOfficeUser
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData ExamOfficeUser = InvTokenDataExamOfficeUser
{ invTokenExamOfficeUserOffice :: CryptoUUIDUser
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\ExamOfficeUser{..} -> (examOfficeUserUser, examOfficeUserOffice, JunctionExamOfficeUser))

View File

@ -22,11 +22,11 @@ import qualified Data.HashSet as HashSet
instance IsInvitableJunction ExternalExamStaff where
type InvitationFor ExternalExamStaff = ExternalExam
data InvitableJunction ExternalExamStaff = JunctionExternalExamStaff
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData ExternalExamStaff = InvDBDataExternalExamStaff
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData ExternalExamStaff = InvTokenDataExternalExamStaff
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\ExternalExamStaff{..} -> (externalExamStaffUser, externalExamStaffExam, JunctionExternalExamStaff))

View File

@ -53,7 +53,7 @@ single = uncurry Map.singleton
-- Button only needed here
data ButtonManualLms = BtnLmsEnqueue | BtnLmsDequeue
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonManualLms
instance Finite ButtonManualLms
@ -302,7 +302,7 @@ instance HasUser LmsTableData where
data LmsTableAction = LmsActNotify
| LmsActRenewNotify
| LmsActRenewPin
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe LmsTableAction
instance Finite LmsTableAction
@ -313,7 +313,7 @@ embedRenderMessage ''UniWorX ''LmsTableAction id
data LmsTableActionData = LmsActNotifyData
| LmsActRenewNotifyData
| LmsActRenewPinData -- no longer used
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
isNotifyAct :: LmsTableActionData -> Bool
isNotifyAct LmsActNotifyData = True

View File

@ -63,13 +63,13 @@ instance CsvColumnsExplained LmsResultTableCsv where
single k v = singletonMap k [whamlet|_{v}|]
data LmsResultCsvActionClass = LmsResultInsert | LmsResultUpdate
deriving (Eq, Ord, Read, Show, Generic, Typeable, Enum, Bounded)
deriving (Eq, Ord, Read, Show, Generic, Enum, Bounded)
embedRenderMessage ''UniWorX ''LmsResultCsvActionClass id
-- By coincidence the action type is identical to LmsResultTableCsv
data LmsResultCsvAction = LmsResultInsertData { lmsResultInsertIdent :: LmsIdent, lmsResultInsertSuccess :: Day }
| LmsResultUpdateData { lmsResultInsertIdent :: LmsIdent, lmsResultInsertSuccess :: Day }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = camelToPathPiece'' 2 1 -- LmsResultInsertData -> insert
@ -79,7 +79,7 @@ deriveJSON defaultOptions
data LmsResultCsvException
= LmsResultCsvExceptionDuplicatedKey -- TODO: this is not used anywhere?!
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
instance Exception LmsResultCsvException
embedRenderMessage ''UniWorX ''LmsResultCsvException id

View File

@ -62,12 +62,12 @@ instance CsvColumnsExplained LmsUserlistTableCsv where
data LmsUserlistCsvActionClass = LmsUserlistInsert | LmsUserlistUpdate
deriving (Eq, Ord, Read, Show, Generic, Typeable, Enum, Bounded)
deriving (Eq, Ord, Read, Show, Generic, Enum, Bounded)
embedRenderMessage ''UniWorX ''LmsUserlistCsvActionClass id
data LmsUserlistCsvAction = LmsUserlistInsertData { lmsUserlistInsertIdent :: LmsIdent, lmsUserlistInsertFailed :: Bool }
| LmsUserlistUpdateData { lmsUserlistInsertIdent :: LmsIdent, lmsUserlistInsertFailed :: Bool }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = camelToPathPiece'' 2 1 -- LmsUserlistInsertData -> insert
@ -78,7 +78,7 @@ deriveJSON defaultOptions
data LmsUserlistCsvException
= LmsUserlistCsvExceptionDuplicatedKey -- TODO: this is not used anywhere?!
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
instance Exception LmsUserlistCsvException
embedRenderMessage ''UniWorX ''LmsUserlistCsvException id

View File

@ -30,7 +30,7 @@ import qualified Data.Conduit.List as C
data ParticipantEntry = ParticipantEntry
{ peCourse :: CourseName
, peEmail :: UserEmail
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
instance ToNamedRecord ParticipantEntry where
toNamedRecord ParticipantEntry{..} = Csv.namedRecord

View File

@ -56,7 +56,7 @@ data MetaPinRenewal = MetaPinRenewal
, mppClosing :: Maybe Text
, mppSupervisor:: Maybe Text
}
deriving (Eq, Ord, Show, Generic, Typeable)
deriving (Eq, Ord, Show, Generic)
-- TODO: just for testing, remove in production
instance Default MetaPinRenewal where
@ -125,7 +125,7 @@ mprToMetaUser entUser@Entity{entityVal = u} mpr = do
data PJTableAction = PJActAcknowledge
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe PJTableAction
@ -135,7 +135,7 @@ embedRenderMessage ''UniWorX ''PJTableAction id
-- Not yet needed, since there is no additional data for now:
data PJTableActionData = PJActAcknowledgeData
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
type PJTableExpr = ( E.SqlExpr (Entity PrintJob)
`E.LeftOuterJoin` E.SqlExpr (Maybe (Entity User))

View File

@ -84,7 +84,7 @@ data NotificationTriggerKind
| NTKCorrector
| NTKCourseLecturer
| NTKFunctionary SchoolFunction
deriving (Eq, Ord, Generic, Typeable)
deriving (Eq, Ord, Generic)
deriveFinite ''NotificationTriggerKind
instance RenderMessage UniWorX NotificationTriggerKind where
@ -375,7 +375,7 @@ validateSettings User{..} = do
data ButtonResetTokens = BtnResetTokens
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonResetTokens
instance Finite ButtonResetTokens
@ -386,7 +386,7 @@ instance Button UniWorX ButtonResetTokens where
btnClasses BtnResetTokens = [BCIsButton, BCDanger]
data ProfileAnchor = ProfileSettings | ProfileResetTokens
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe ProfileAnchor
instance Finite ProfileAnchor
@ -1053,7 +1053,7 @@ postUserNotificationR cID = do
data ButtonSetDisplayEmail = BtnSetDisplayEmail
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ButtonSetDisplayEmail
instance Finite ButtonSetDisplayEmail

View File

@ -25,13 +25,13 @@ instance IsInvitableJunction SheetCorrector where
data InvitableJunction SheetCorrector = JunctionSheetCorrector
{ jSheetCorrectorLoad :: Load
, jSheetCorrectorState :: CorrectorState
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData SheetCorrector = InvDBDataSheetCorrector
{ invDBSheetCorrectorLoad :: Load
, invDBSheetCorrectorState :: CorrectorState
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData SheetCorrector = InvTokenDataSheetCorrector
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\SheetCorrector{..} -> (sheetCorrectorUser, sheetCorrectorSheet, JunctionSheetCorrector sheetCorrectorLoad sheetCorrectorState))

View File

@ -63,21 +63,21 @@ data PersonalisedSheetFileUnresolved a
= PSFUnresolvedDirectory a
| PSFUnresolvedCollatable Text a
| PSFUnresolved a
deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Functor, Foldable, Traversable, Generic)
makePrisms ''PersonalisedSheetFileUnresolved
data PersonalisedSheetFilesRestriction
= PSFRExamRegistered { psfrExam :: ExamId }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
makeLenses_ ''PersonalisedSheetFilesRestriction
data PersonalisedSheetFilesForm = PersonalisedSheetFilesForm
{ psffAnonymous :: PersonalisedSheetFilesDownloadAnonymous
, psffRestrictions :: Set PersonalisedSheetFilesRestriction
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
embedRenderMessage ''UniWorX ''PersonalisedSheetFilesDownloadAnonymous id
@ -312,7 +312,7 @@ data PersonalisedSheetFilesKeyException
| FallbackPersonalisedSheetFilesKeysExhausted
| PersonalisedSheetFilesKeyInsufficientContext
| PersonalisedSheetFilesKeyNotFound
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Exception)
newPersonalisedFilesKey :: forall m.

View File

@ -32,7 +32,7 @@ data PrettifyState
| PrettifyFlowSequence PrettifyState
| PrettifyBlockSequence PrettifyState
| PrettifySeed | PrettifySeedDone
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)

View File

@ -39,7 +39,7 @@ data PersonalisedSheetFilesDownloadAnonymous
| PersonalisedSheetFilesDownloadSurnames
| PersonalisedSheetFilesDownloadMatriculations
| PersonalisedSheetFilesDownloadGroups
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''PersonalisedSheetFilesDownloadAnonymous $ camelToPathPiece' 4
@ -47,7 +47,7 @@ makePrisms ''PersonalisedSheetFilesDownloadAnonymous
newtype PersonalisedSheetFilesSeed = PersonalisedSheetFilesSeed (Digest (SHAKE256 144))
deriving (Eq, Ord, Read, Show, Lift, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Lift, Generic)
deriving newtype ( PersistField
, PathPiece, ToHttpApiData, FromHttpApiData, ToJSON, FromJSON
, Hashable, NFData
@ -55,8 +55,7 @@ newtype PersonalisedSheetFilesSeed = PersonalisedSheetFilesSeed (Digest (SHAKE25
, Binary
)
newtype PersonalisedSheetFilesSeedKey = PersonalisedSheetFilesSeedKey { psfskKeyMaterial :: ByteString }
deriving (Typeable)
newtype PersonalisedSheetFilesSeedKey = PersonalisedSheetFilesSeedKey { psfskKeyMaterial :: ByteString }
deriving newtype (ByteArrayAccess)
-- | Does not actually show any key material
@ -94,4 +93,4 @@ mkPersonalisedSheetFilesSeed k u = PersonalisedSheetFilesSeed . Crypto.kmacGetDi
data PersonalisedSheetFilesKeySet = PersonalisedSheetFilesKeySet
{ psfksCryptoID :: CryptoIDKey
, psfksSeed :: Maybe PersonalisedSheetFilesSeedKey
} deriving (Show, Typeable)
} deriving (Show)

View File

@ -13,7 +13,7 @@ import Handler.Utils
data ButtonGeneratePseudonym = BtnGenerate
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonGeneratePseudonym
instance Finite ButtonGeneratePseudonym

View File

@ -288,7 +288,7 @@ assignHandler tid ssh csh cid assignSids = do
data ButtonSubmissionsAssign
= BtnSubmissionsAssign SheetName
| BtnSubmissionsAssignAll
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
derivePathPiece ''ButtonSubmissionsAssign (camelToPathPiece' 2) "--"
instance RenderMessage UniWorX ButtonSubmissionsAssign where

View File

@ -269,7 +269,7 @@ data CorrectionTableCsvQualification
= CorrectionTableCsvNoQualification
| CorrectionTableCsvQualifySheet
| CorrectionTableCsvQualifyCourse
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
correctionTableCsvHeader :: Bool -- ^ @showCorrector@
@ -309,7 +309,7 @@ data CorrectionTableCsvSettings = forall filename sheetName.
newtype CorrectionTableCsvExportData = CorrectionTableCsvExportData
{ csvCorrectionSingleSubmittors :: Bool
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
instance Default CorrectionTableCsvExportData where
def = CorrectionTableCsvExportData False

View File

@ -24,11 +24,11 @@ import qualified Data.HashSet as HashSet
instance IsInvitableJunction SubmissionUser where
type InvitationFor SubmissionUser = Submission
data InvitableJunction SubmissionUser = JunctionSubmissionUser
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData SubmissionUser = InvDBDataSubmissionUser
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData SubmissionUser = InvTokenDataSubmissionUser
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\SubmissionUser{..} -> (submissionUserUser, submissionUserSubmission, JunctionSubmissionUser))

View File

@ -24,7 +24,7 @@ data SubmissionDoneMode
= SubmissionDoneNever
| SubmissionDoneByFile
| SubmissionDoneAlways
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''SubmissionDoneMode $ camelToPathPiece' 2
embedRenderMessage ''UniWorX ''SubmissionDoneMode id

View File

@ -353,7 +353,7 @@ postMessageListR = do
data ButtonSystemMessageHide
= BtnSystemMessageHide
| BtnSystemMessageUnhide
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''ButtonSystemMessageHide $ camelToPathPiece' 3
embedRenderMessage ''UniWorX ''ButtonSystemMessageHide id

View File

@ -23,11 +23,11 @@ import qualified Data.HashSet as HashSet
instance IsInvitableJunction Tutor where
type InvitationFor Tutor = Tutorial
data InvitableJunction Tutor = JunctionTutor
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData Tutor = InvDBDataTutor
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData Tutor = InvTokenDataTutor
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\Tutor{..} -> (tutorUser, tutorTutorial, JunctionTutor))

View File

@ -29,7 +29,7 @@ data TutorialUserAction
= TutorialUserGrantQualification
| TutorialUserSendMail
| TutorialUserDeregister
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe TutorialUserAction
instance Finite TutorialUserAction
@ -43,7 +43,7 @@ data TutorialUserActionData
}
| TutorialUserSendMailData
| TutorialUserDeregisterData{}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
getTUsersR, postTUsersR :: TermId -> SchoolId -> CourseShorthand -> TutorialName -> Handler Html

View File

@ -11,7 +11,7 @@ import Import
data UploadResponse
= UploadResponseNoToken
deriving (Eq, Ord, Show, Generic, Typeable)
deriving (Eq, Ord, Show, Generic)
deriveJSON defaultOptions
{ tagSingleConstructors = True

View File

@ -56,7 +56,7 @@ hijackUserForm csrf = do
-- hasUser = _entityVal
data UserAction = UserLdapSync | UserAddSupervisor | UserSetSupervisor | UserRemoveSupervisor
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''UserAction $ camelToPathPiece' 1
@ -67,7 +67,7 @@ data UserActionData = UserLdapSyncData
| UserAddSupervisorData { getActionSupervisors :: Set Text, getActionRerouteNotifications :: Bool }
| UserSetSupervisorData { getActionSupervisors :: Set Text, getActionRerouteNotifications :: Bool }
| UserRemoveSupervisorData
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
isNotSetSupervisor :: UserActionData -> Bool
isNotSetSupervisor UserSetSupervisorData{} = False
@ -80,7 +80,7 @@ isActionSupervisor _ = False
data AllUsersAction = AllUsersLdapSync
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''AllUsersAction $ camelToPathPiece' 1
@ -396,7 +396,7 @@ postAdminHijackUserR cID = do
data ButtonAuthMode = BtnAuthLDAP | BtnAuthPWHash | BtnPasswordReset
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ButtonAuthMode
instance Finite ButtonAuthMode
@ -408,7 +408,7 @@ instance Button UniWorX ButtonAuthMode where
data UserAssimilateButton = BtnUserAssimilate
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
instance Button UniWorX UserAssimilateButton where
@ -716,16 +716,16 @@ instance IsInvitableJunction UserFunction where
data InvitableJunction UserFunction = JunctionUserFunction
{ jFunction :: SchoolFunction
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationDBData UserFunction = InvDBDataUserFunction
{ invDBUserFunctionDeadline :: UTCTime
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
data InvitationTokenData UserFunction = InvTokenDataUserFunction
{ invTokenUserFunctionSchool :: SchoolShorthand
, invTokenUserFunctionFunction :: SchoolFunction
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_InvitableJunction = iso
(\UserFunction{..} -> (userFunctionUser, userFunctionSchool, JunctionUserFunction userFunctionFunction))

View File

@ -55,7 +55,7 @@ data AvsException
| AvsPersonSearchEmpty -- AvsPersonSearch returned empty result
| AvsPersonSearchAmbiguous -- AvsPersonSearch returned more than one result
| AvsSetLicencesFailed Text -- AvsSetLicence total failure
deriving (Show, Eq, Ord, Generic, Typeable)
deriving (Show, Eq, Ord, Generic)
instance Exception AvsException
{-

View File

@ -30,7 +30,7 @@ data RecipientGroup = RGCourseParticipants | RGCourseLecturers | RGCourseCorrect
| RGTutorialParticipants CryptoUUIDTutorial
| RGExamRegistered CryptoUUIDExam
| RGSheetSubmittor CryptoUUIDSheet
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance LowerBounded RecipientGroup where
minBound' = RGCourseParticipants
@ -42,7 +42,7 @@ pathPieceJSON ''RecipientGroup
data RecipientCategory
= RecipientGroup RecipientGroup
| RecipientCustom
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance LowerBounded RecipientCategory where
minBound' = RecipientGroup minBound'
@ -60,7 +60,7 @@ pathPieceJSONKey ''RecipientCategory
data CommunicationButton
= BtnCommunicationSend
| BtnCommunicationTest
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''CommunicationButton $ camelToPathPiece' 2

View File

@ -32,7 +32,7 @@ import qualified Network.Wai as W
data DownloadTokenRestriction
= DownloadRestrictSingle { downloadRestrictReference :: FileContentReference }
| DownloadRestrictMultiple
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = camelToPathPiece' 2
, fieldLabelModifier = camelToPathPiece' 2

View File

@ -226,7 +226,7 @@ examBonusGrade exam@Exam{..} bonusInp = (mBonus, ) . examGrade exam mBonus
data ExamAutoOccurrenceIgnoreRooms
= ExamAutoOccurrenceIgnoreRooms {eaoirIgnored :: Set ExamOccurrenceId, eaoirSorted :: Bool}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Default ExamAutoOccurrenceIgnoreRooms where
def = ExamAutoOccurrenceIgnoreRooms Set.empty False
@ -242,7 +242,7 @@ data ExamAutoOccurrenceConfig = ExamAutoOccurrenceConfig
, eaocFinenessCost :: Rational -- ^ Cost factor incentivising shorter common prefixes on breaks between rooms
, eaocNudge :: Map ExamOccurrenceId Integer
, eaocNudgeSize :: Rational
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
instance Default ExamAutoOccurrenceConfig where
def = ExamAutoOccurrenceConfig
@ -263,7 +263,7 @@ data ExamAutoOccurrenceException
| ExamAutoOccurrenceExceptionNotEnoughSpace
| ExamAutoOccurrenceExceptionNoUsers
| ExamAutoOccurrenceExceptionRoomTooSmall
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
instance Exception ExamAutoOccurrenceException

View File

@ -37,7 +37,7 @@ import Handler.Utils.StudyFeatures
data ExternalExamUserMode = EEUMUsers | EEUMGrades
deriving (Eq, Ord, Read, Show, Bounded, Enum, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Bounded, Enum, Generic)
instance Universe ExternalExamUserMode
instance Finite ExternalExamUserMode
nullaryPathPiece ''ExternalExamUserMode $ camelToPathPiece' 1
@ -127,7 +127,7 @@ data ExternalExamUserAction
| ExternalExamUserEditOccurrence
| ExternalExamUserEditResult
| ExternalExamUserDelete
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe ExternalExamUserAction
instance Finite ExternalExamUserAction
nullaryPathPiece ''ExternalExamUserAction $ camelToPathPiece' 3
@ -142,13 +142,13 @@ data ExternalExamUserActionData
data ExternalExamUserCsvExportDataGrades = ExternalExamUserCsvExportDataGrades
{ csvEEUserMarkSynchronised :: Bool
, csvEEUserSetLabel :: Bool
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
data ExamUserCsvException
= ExamUserCsvExceptionNoMatchingUser
| ExamUserCsvExceptionNoOccurrenceTime
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
instance Exception ExamUserCsvException
@ -160,7 +160,7 @@ data ExternalExamUserCsvActionClass
| ExternalExamUserCsvDeregister
| ExternalExamUserCsvSetTime
| ExternalExamUserCsvSetResult
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
embedRenderMessage ''UniWorX ''ExternalExamUserCsvActionClass id
data ExternalExamUserCsvAction
@ -180,7 +180,7 @@ data ExternalExamUserCsvAction
| ExternalExamUserCsvDeregisterData
{ externalExamUserCsvActRegistration :: ExternalExamResultId
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = over Text.packed $ Text.intercalate "-" . map Text.toLower . drop 4 . dropEnd 1 . splitCamel
, fieldLabelModifier = camelToPathPiece' 5

View File

@ -38,7 +38,7 @@ import qualified Data.ByteString as ByteString
data SourceFilesException
= SourceFilesMismatchedHashes
| SourceFilesContentUnavailable
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Exception)
makePrisms ''SourceFilesException

View File

@ -88,7 +88,7 @@ import qualified Data.List.NonEmpty as NonEmpty
data ButtonDelete = BtnDelete
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonDelete
instance Finite ButtonDelete
@ -99,7 +99,7 @@ instance Button UniWorX ButtonDelete where
btnClasses BtnDelete = [BCIsButton, BCDanger]
data ButtonSave = BtnSave
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonSave
instance Finite ButtonSave
@ -116,7 +116,7 @@ instance Button UniWorX ButtonSave where
data ButtonHandIn = BtnHandIn
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonHandIn
instance Finite ButtonHandIn
@ -128,7 +128,7 @@ instance Button UniWorX ButtonHandIn where
data ButtonConfirm = BtnConfirm
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonConfirm
instance Finite ButtonConfirm
@ -144,7 +144,7 @@ instance Button UniWorX ButtonConfirm where
data ButtonRegister = BtnRegister | BtnDeregister
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonRegister
instance Finite ButtonRegister
@ -156,7 +156,7 @@ instance Button UniWorX ButtonRegister where
btnClasses BtnDeregister = [BCIsButton, BCDanger]
data ButtonHijack = BtnHijack
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonHijack
instance Finite ButtonHijack
@ -167,7 +167,7 @@ instance Button UniWorX ButtonHijack where
btnClasses BtnHijack = [BCIsButton, BCDefault]
data ButtonSubmitDelete = BtnSubmit' | BtnDelete'
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic, Typeable)
deriving (Enum, Eq, Ord, Bounded, Read, Show, Generic)
instance Universe ButtonSubmitDelete
instance Finite ButtonSubmitDelete
@ -769,7 +769,7 @@ submissionModeForm prev = explainedMultiActionA actions opts (fslI MsgUtilSheetS
data ExamBonusRule' = ExamBonusManual'
| ExamBonusPoints'
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ExamBonusRule'
instance Finite ExamBonusRule'
@ -804,7 +804,7 @@ data ExamOccurrenceRule' = ExamRoomManual'
| ExamRoomSurname'
| ExamRoomMatriculation'
| ExamRoomRandom'
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ExamOccurrenceRule'
instance Finite ExamOccurrenceRule'
@ -830,7 +830,7 @@ examOccurrenceRuleForm = fmap reverseClassify . areq (selectField optionsFinite)
ExamRoomRandom' -> ExamRoomRandom
data ExamGradingRule' = ExamGradingKey'
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ExamGradingRule'
instance Finite ExamGradingRule'
@ -1423,7 +1423,7 @@ data JsonFieldKind
= JsonFieldNormal
| JsonFieldLarge
| JsonFieldHidden
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
deriving anyclass (Universe, Finite)
jsonField :: ( ToJSON a, FromJSON a
@ -2044,7 +2044,7 @@ examField optMsg cId = hoistField liftHandler . selectField' optMsg . fmap (fmap
data CsvFormatOptions' = CsvFormatOptionsPreset' CsvPreset
| CsvFormatOptionsCustom'
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveFinite ''CsvFormatOptions'
instance PathPiece CsvFormatOptions' where
toPathPiece = \case
@ -2200,7 +2200,7 @@ labeledCheckBoxView label theId name attrs val isReq = $(widgetFile "widgets/fie
newtype CourseParticipantStateIsActive = CourseParticipantStateIsActive { getCourseParticipantStateIsActive :: Bool }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving newtype (Universe, Finite)
embedRenderMessageVariant ''UniWorX ''CourseParticipantStateIsActive $ \case
@ -2224,7 +2224,7 @@ data CustomPresetFormOption p
= CPFONone
| CPFOPreset p
| CPFOCustom
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveFinite ''CustomPresetFormOption
derivePathPiece ''CustomPresetFormOption (camelToPathPiece' 1) "--"
@ -2362,12 +2362,12 @@ roomReferenceForm' noneOpt fs mPrev = multiActionAOpts opts opts' fs $ fmap clas
newtype I18nLangs = I18nLangs { unI18nLangs :: Set I18nLang }
deriving newtype (ToJSON, FromJSON, MonoFoldable, Semigroup, Monoid, Lattice, BoundedJoinSemiLattice)
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
type instance Element I18nLangs = I18nLang
newtype I18nLang = I18nLang { unI18nLang :: Lang }
deriving newtype (PathPiece, ToJSON, FromJSON, ToJSONKey, FromJSONKey)
deriving (Eq, Generic, Typeable, Read, Show)
deriving (Eq, Generic, Read, Show)
instance Ord I18nLang where
compare = mconcat

View File

@ -50,7 +50,7 @@ $(mapM tupleBoxCoord [2..4])
newtype ListLength = ListLength { unListLength :: Natural }
deriving newtype (Num, Integral, Real, Enum, PathPiece)
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
makeWrapped ''ListLength
@ -61,7 +61,7 @@ instance BoundedJoinSemiLattice ListLength where
newtype ListPosition = ListPosition { unListPosition :: Natural }
deriving newtype (Num, Integral, Real, Enum, PathPiece, ToJSON, FromJSON, ToJSONKey, FromJSONKey)
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
makeWrapped ''ListPosition
@ -88,7 +88,7 @@ instance Liveliness ListLength where
newtype EnumLiveliness enum = EnumLiveliness { unEnumLiveliness :: IntSet }
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
deriving newtype (Lattice, BoundedJoinSemiLattice)
makeWrapped ''EnumLiveliness
@ -96,7 +96,7 @@ makeWrapped ''EnumLiveliness
newtype EnumPosition enum = EnumPosition { unEnumPosition :: enum }
deriving newtype (Enum, Bounded, PathPiece, ToJSON, FromJSON, ToJSONKey, FromJSONKey)
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
makeWrapped ''EnumPosition
@ -118,13 +118,13 @@ class Ord coord => LowerBounded coord where
minBound' :: coord
newtype BoundedLiveliness coord = BoundedLiveliness { unBoundedLiveliness :: Set coord }
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
deriving newtype (Lattice, BoundedJoinSemiLattice, BoundedMeetSemiLattice)
makeWrapped ''BoundedLiveliness
newtype BoundedPosition coord = BoundedPosition { unBoundedPosition :: coord }
deriving newtype (Enum, Bounded, PathPiece, ToJSON, FromJSON, ToJSONKey, FromJSONKey, LowerBounded)
deriving (Eq, Ord, Generic, Typeable, Read, Show)
deriving (Eq, Ord, Generic, Read, Show)
makeWrapped ''BoundedPosition
instance (LowerBounded coord, PathPiece coord, ToJSON coord, FromJSON coord, ToJSONKey coord, FromJSONKey coord, Ord coord) => IsBoxCoord (BoundedPosition coord) where
@ -137,7 +137,7 @@ instance (LowerBounded coord, PathPiece coord, ToJSON coord, FromJSON coord, ToJ
newtype MapLiveliness l1 l2 = MapLiveliness { unMapLiveliness :: Map (BoxCoord l1) l2 }
deriving (Generic, Typeable)
deriving (Generic)
makeWrapped ''MapLiveliness
@ -169,7 +169,7 @@ miDeleteList dat pos
data ButtonMassInput coord
= MassInputAddDimension Natural coord
| MassInputDeleteCell coord
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance PathPiece coord => PathPiece (ButtonMassInput coord) where
toPathPiece = \case
@ -204,7 +204,7 @@ data MassInputFieldName coord
| MassInputAddButton { miName :: Text, miCoord :: coord }
| MassInputDeleteButton { miName :: Text, miCoord :: coord }
| MassInputCell { miName :: Text, miCoord :: coord, miCellField :: Text }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance IsBoxCoord coord => PathPiece (MassInputFieldName coord) where
toPathPiece = \case
@ -246,7 +246,7 @@ instance IsBoxCoord coord => PathPiece (MassInputFieldName coord) where
]
data MassInputException = MassInputInvalidShape
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Exception MassInputException

View File

@ -16,7 +16,7 @@ import qualified Data.Map as Map
data OccurrenceScheduleKind = ScheduleKindWeekly
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe OccurrenceScheduleKind
instance Finite OccurrenceScheduleKind
@ -26,7 +26,7 @@ embedRenderMessage ''UniWorX ''OccurrenceScheduleKind id
data OccurrenceExceptionKind = ExceptionKindOccur
| ExceptionKindNoOccur
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe OccurrenceExceptionKind
instance Finite OccurrenceExceptionKind

View File

@ -147,7 +147,7 @@ data InvitationTokenConfig = InvitationTokenConfig
, itAddAuth :: Maybe AuthDNF
, itExpiresAt :: Maybe (Maybe UTCTime)
, itStartsAt :: Maybe UTCTime
} deriving (Generic, Typeable)
} deriving (Generic)
data InvitationTokenRestriction junction = IsInvitableJunction junction => InvitationTokenRestriction
{ itEmail :: UserEmail
@ -342,7 +342,7 @@ deleteInvitation invitationFor = deleteInvitationsF @junction invitationFor . Id
data ButtonInvite = BtnInviteAccept | BtnInviteDecline
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
instance Universe ButtonInvite
instance Finite ButtonInvite

View File

@ -100,7 +100,7 @@ data MemcachedValue = MemcachedValue
{ mNonce :: AEAD.Nonce
, mExpiry :: Maybe POSIXTime
, mCiphertext :: ByteString
} deriving (Generic, Typeable)
} deriving (Generic)
putExpiry :: Maybe POSIXTime -> Binary.Put
putExpiry mExp = Binary.put $ fromMaybe 0 expEnc
@ -151,7 +151,7 @@ memcachedAvailable = getsYesod $ is _Just . appMemcached
data MemcachedException = MemcachedException Memcached.MemcachedException
| MemcachedInvalidExpiry Expiry
deriving (Show, Typeable)
deriving (Show)
deriving anyclass (Exception)
@ -281,7 +281,7 @@ memcachedByInvalidate (Binary.encode -> k) _ = arc >> memcache
data MemcachedLocalInvalidateMsg = MemcachedLocalInvalidateMsg
{ mLocalInvalidateType :: Fingerprint
, mLocalInvalidateKey :: Lazy.ByteString
} deriving (Eq, Ord, Show, Typeable)
} deriving (Eq, Ord, Show)
instance Binary MemcachedLocalInvalidateMsg where
get = Binary.label "MemcachedLocalInvalidateMsg" $ do
@ -318,8 +318,7 @@ manageMemcachedLocalInvalidations localARC iQueue = PostgresqlChannelManager
}
newtype MemcachedUnkeyed a = MemcachedUnkeyed { unMemcachedUnkeyed :: a }
deriving (Typeable)
newtype MemcachedUnkeyed a = MemcachedUnkeyed { unMemcachedUnkeyed :: a }
deriving newtype (Eq, Ord, Show, Binary)
instance NFData a => NFData (MemcachedUnkeyed a) where
rnf = rnf . unMemcachedUnkeyed
@ -370,8 +369,7 @@ memcachedBy :: forall a m k.
memcachedBy mExp k = memcachedWith (memcachedByGet k, \x -> x <$ memcachedBySet mExp k x)
newtype MemcachedUnkeyedLoc a = MemcachedUnkeyedLoc { unMemcachedUnkeyedLoc :: a }
deriving (Typeable)
newtype MemcachedUnkeyedLoc a = MemcachedUnkeyedLoc { unMemcachedUnkeyedLoc :: a }
deriving newtype (Eq, Ord, Show, Binary)
instance NFData a => NFData (MemcachedUnkeyedLoc a) where
rnf MemcachedUnkeyedLoc{..} = rnf unMemcachedUnkeyedLoc
@ -381,8 +379,7 @@ memcachedHere = do
loc <- location
[e| \mExp -> fmap unMemcachedUnkeyedLoc . memcachedBy mExp loc . fmap MemcachedUnkeyedLoc |]
newtype MemcachedKeyedLoc a = MemcachedKeyedLoc { unMemcachedKeyedLoc :: a }
deriving (Typeable)
newtype MemcachedKeyedLoc a = MemcachedKeyedLoc { unMemcachedKeyedLoc :: a }
deriving newtype (Eq, Ord, Show, Binary)
instance NFData a => NFData (MemcachedKeyedLoc a) where
rnf MemcachedKeyedLoc{..} = rnf unMemcachedKeyedLoc
@ -597,7 +594,7 @@ memcacheAuthHereMax = do
data AsyncTimeoutException = AsyncTimeoutReturnTypeDoesNotMatchComputationKey
deriving (Show, Typeable)
deriving (Show)
deriving anyclass (Exception)
data DynamicAsync = forall a. DynamicAsync !(TypeRep a) !(Async a)

View File

@ -27,7 +27,7 @@ import Text.HTML.SanitizeXSS (sanitizeBalance)
data HtmlFieldKind
= HtmlFieldNormal
| HtmlFieldSmall
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe HtmlFieldKind
instance Finite HtmlFieldKind

View File

@ -51,7 +51,7 @@ data PrettifyState
| PrettifyRating
| PrettifyRatingDone
| PrettifyComment
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
formatRating :: MsgRendererS UniWorX -> DateTimeFormatter -> CryptoFileNameSubmission -> Rating -> Lazy.ByteString

View File

@ -62,7 +62,7 @@ fetchSheetIdCourseId tid ssh cid shn = bimap E.unValue E.unValue <$> fetchSheetA
data ResolveSheetTypeException
= ResolveSheetTypeExamPartUnavailable SqlBackendKey
| ResolveSheetTypeForeignExam
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Exception)
resolveSheetType :: ( MonadThrow m

View File

@ -38,7 +38,7 @@ data UserTableStudyFeature = UserTableStudyFeature
, userTableDegree :: Text
, userTableSemester :: Int
, userTableFieldType :: StudyFieldType
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
makeLenses_ ''UserTableStudyFeature
deriveJSON defaultOptions
@ -46,7 +46,7 @@ deriveJSON defaultOptions
} ''UserTableStudyFeature
newtype UserTableStudyFeatures = UserTableStudyFeatures (Set UserTableStudyFeature)
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving newtype ( ToJSON, FromJSON
, Semigroup, Monoid
)

View File

@ -66,7 +66,7 @@ import Data.Char (isAlphaNum)
data AssignSubmissionException = NoCorrectors
| NoCorrectorsByProportion
| SubmissionsNotFound (NonNull (Set SubmissionId))
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Exception AssignSubmissionException
@ -301,7 +301,7 @@ data SubmissionDownloadAnonymous = SubmissionDownloadAnonymous
| SubmissionDownloadSurnames
| SubmissionDownloadMatriculations
| SubmissionDownloadGroups
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''SubmissionDownloadAnonymous $ camelToPathPiece' 2
@ -420,7 +420,7 @@ data SubmissionSinkState = SubmissionSinkState
{ sinkSeenRating :: Last Rating'
, sinkSubmissionTouched :: Any
, sinkFilenames :: Set FilePath
} deriving (Show, Eq, Generic, Typeable)
} deriving (Show, Eq, Generic)
instance Semigroup SubmissionSinkState where
(<>) = mappenddefault
@ -955,7 +955,7 @@ submissionDeleteRoute drRecords = DeleteRoute
data CorrectionInvisibleReason
= CorrectionInvisibleExamUnfinished
| CorrectionInvisibleRatingNotDone
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
embedRenderMessage ''UniWorX ''CorrectionInvisibleReason id

View File

@ -404,7 +404,7 @@ psToPi PaginationSettings{..} = PaginationInput
data DBCsvActionMode = DBCsvActionNew | DBCsvActionExisting | DBCsvActionMissing
deriving (Read, Show, Eq, Ord, Enum, Bounded, Generic, Typeable)
deriving (Read, Show, Eq, Ord, Enum, Bounded, Generic)
instance Universe DBCsvActionMode
instance Finite DBCsvActionMode
@ -415,7 +415,7 @@ deriveJSON defaultOptions
data ButtonCsvMode = BtnCsvExport | BtnCsvImport | BtnCsvImportConfirm | BtnCsvImportAbort
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe ButtonCsvMode
instance Finite ButtonCsvMode
@ -483,7 +483,7 @@ data DBCsvException k'
| DBCsvUnavailableActionRequested
{ dbCsvActions :: Set Value
}
deriving (Show, Typeable)
deriving (Show)
makeLenses_ ''DBCsvException

View File

@ -83,7 +83,7 @@ _Sortable = prism' fromSortable $ \x -> ($ x) . toSortable <$> pSortable
data DBTableInvalid = DBTIRowsMissing Int
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Exception DBTableInvalid

View File

@ -33,7 +33,7 @@ import qualified Database.Esqueleto.Internal.Internal as E
type STKey = Int -- for convenience, assmued identical to field StudyTermNameCandidateKey
data FailedCandidateInference = FailedCandidateInference [Entity StudyTerms]
deriving (Typeable, Show)
deriving (Show)
instance Exception FailedCandidateInference
-- Default Instance

View File

@ -119,7 +119,7 @@ data GuessUserInfo
{ guessUserSurname :: UserSurname }
| GuessUserFirstName
{ guessUserFirstName :: UserFirstName }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Binary GuessUserInfo
makeLenses_ ''GuessUserInfo
@ -129,7 +129,7 @@ data NameMatchQuality
| NameMatchPrefix
| NameMatchPermutation
| NameMatchEqual
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
matchesName :: Textual t
=> t -- ^ haystack
@ -257,7 +257,7 @@ guessUser (((Set.toList . toNullable) <$>) . Set.toList . dnfTerms -> criteria)
data UserAssimilateException = UserAssimilateException
{ userAssimilateOldUser, userAssimilateNewUser :: UserId
, userAssimilateException :: UserAssimilateExceptionReason
} deriving (Eq, Ord, Show, Generic, Typeable)
} deriving (Eq, Ord, Show, Generic)
deriving anyclass (Exception)
data UserAssimilateExceptionReason
@ -271,7 +271,7 @@ data UserAssimilateExceptionReason
| UserAssimilateTutorialParticipantCollidingRegGroups (Entity TutorialParticipant) (Entity TutorialParticipant)
| UserAssimilateCouldNotDetermineUserIdents
| UserAssimilateConflictingLmsQualifications (Set.Set QualificationId)
deriving (Eq, Ord, Show, Generic, Typeable)
deriving (Eq, Ord, Show, Generic)
assimilateUser :: UserId -- ^ @newUserId@
-> UserId -- ^ @oldUserId@

View File

@ -61,7 +61,7 @@ instance Default ZipInfo where
data ConsumeZipException
= ConsumeZipUnZipException SomeException
| ConsumeZipUnexpectedContent
deriving (Show, Generic, Typeable)
deriving (Show, Generic)
deriving anyclass (Exception)

View File

@ -93,7 +93,7 @@ import System.Clock
data JobQueueException = JInvalid QueuedJobId QueuedJob
| JLocked QueuedJobId InstanceId UTCTime
| JNonexistant QueuedJobId
deriving (Read, Show, Eq, Generic, Typeable)
deriving (Read, Show, Eq, Generic)
instance Exception JobQueueException

View File

@ -366,7 +366,7 @@ dispatchJobInjectFiles = JobHandlerException . maybeT_ $ do
data RechunkFileException
= RechunkFileExceptionHashMismatch
{ oldHash, newHash :: FileContentReference }
deriving (Eq, Ord, Show, Generic, Typeable)
deriving (Eq, Ord, Show, Generic)
deriving anyclass (Exception)
dispatchJobRechunkFiles :: JobHandler UniWorX

View File

@ -19,7 +19,7 @@ import Jobs.Queue
data SynchroniseLdapException
= SynchroniseLdapNoLdap
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Exception SynchroniseLdapException
dispatchJobSynchroniseLdap :: Natural -> Natural -> Natural -> JobHandler UniWorX

View File

@ -117,7 +117,7 @@ data Job
| JobLmsDequeue { jQualification :: QualificationId }
| JobLmsUserlist { jQualification :: QualificationId }
| JobLmsResults { jQualification :: QualificationId }
deriving (Eq, Ord, Show, Read, Generic, Typeable)
deriving (Eq, Ord, Show, Read, Generic)
data Notification
= NotificationSubmissionRated { nSubmission :: SubmissionId }
| NotificationSheetActive { nSheet :: SheetId }
@ -144,7 +144,7 @@ data Notification
| NotificationQualificationExpiry { nQualification :: QualificationId, nExpiry :: Day }
| NotificationQualificationExpired { nQualification :: QualificationId, nExpiry :: Day }
| NotificationQualificationRenewal { nQualification :: QualificationId }
deriving (Eq, Ord, Show, Read, Generic, Typeable)
deriving (Eq, Ord, Show, Read, Generic)
instance Hashable Job
instance NFData Job
@ -200,7 +200,7 @@ data JobCtlPrewarmSource
{ jcpsSheet :: SheetId
, jcpsSheetFileType :: SheetFileType
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Hashable, NFData)
makeLenses_ ''JobCtlPrewarmSource
@ -228,7 +228,7 @@ data JobCtl = JobCtlFlush
| JobCtlGenerateHealthReport HealthCheck
| JobCtlTest
| JobCtlSleep Micro -- ^ For debugging
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriving anyclass (Hashable, NFData)
makePrisms ''JobCtl
@ -255,8 +255,7 @@ data JobHandler site
= JobHandlerAtomic (YesodJobDB site ())
| JobHandlerException (HandlerFor site ())
| forall a. JobHandlerAtomicWithFinalizer (YesodJobDB site a) (a -> HandlerFor site ())
| forall a. JobHandlerAtomicDeferrableWithFinalizer (ReaderT SqlReadBackend (HandlerFor site) a) (a -> HandlerFor site ())
deriving (Typeable)
| forall a. JobHandlerAtomicDeferrableWithFinalizer (ReaderT SqlReadBackend (HandlerFor site) a) (a -> HandlerFor site ())
makePrisms ''JobHandler
@ -265,7 +264,7 @@ data JobWorkerState
= JobWorkerBusy
| JobWorkerExecJobCtl { jobWorkerJobCtl :: JobCtl }
| JobWorkerExecJob { jobWorkerJob :: Job }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
makeLenses_ ''JobWorkerState
@ -302,7 +301,7 @@ data JobContext = JobContext
data JobPriority = JobPrioBatch | JobPrioRealtime
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Enum, Bounded, Read, Show, Generic)
instance Universe JobPriority
instance Finite JobPriority
instance NFData JobPriority
@ -316,7 +315,7 @@ prioritiseJob JobCtlDetermineCrontab = JobPrioRealtime
prioritiseJob _ = JobPrioBatch
data JobNoQueueSame = JobNoQueueSame | JobNoQueueSameTag
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
jobNoQueueSame :: Job -> Maybe JobNoQueueSame

View File

@ -17,7 +17,6 @@ import Jose.Jwt
deriving instance Ord Jwt
deriving instance Read Jwt
deriving instance Generic Jwt
deriving instance Typeable Jwt
deriving anyclass instance NFData Jwt
instance PathPiece Jwt where
@ -30,6 +29,5 @@ derivePersistFieldPathPiece ''Jwt
deriving instance Generic JwtError
deriving instance Typeable JwtError
instance Exception JwtError

View File

@ -48,7 +48,7 @@ data LdapExecutor = LdapExecutor
data LdapPoolError = LdapPoolTimeout
| LdapError LdapError
| LdapLineTooLong | LdapHostNotResolved String | LdapHostCannotConnect String [IOException]
deriving (Eq, Show, Generic, Typeable)
deriving (Eq, Show, Generic)
deriving anyclass (Exception)

View File

@ -204,7 +204,7 @@ data MailContext = MailContext
{ mcLanguages :: Languages
, mcDateTimeFormat :: SelDateTimeFormat -> DateTimeFormat
, mcCsvOptions :: CsvOptions
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ fieldLabelModifier = intercalate "-" . map toLower . drop 1 . splitCamel
@ -253,7 +253,7 @@ getMailMsgRenderer = do
data MailException = MailNotAvailable
| MailNoSenderSpecified
| MailNoRecipientsSpecified
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
instance Exception MailException

View File

@ -80,7 +80,7 @@ instance HasFileReference SheetFile where
data FileReferenceResidual SheetFile = SheetFileResidual
{ sheetFileResidualSheet :: SheetId
, sheetFileResidualType :: SheetFileType
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
_FileReference
= iso (\SheetFile{..} -> ( FileReference
@ -115,7 +115,7 @@ instance HasFileReference PersonalisedSheetFile where
{ personalisedSheetFileResidualSheet :: SheetId
, personalisedSheetFileResidualUser :: UserId
, personalisedSheetFileResidualType :: SheetFileType
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
_FileReference
= iso (\PersonalisedSheetFile{..} -> ( FileReference
@ -152,7 +152,7 @@ instance HasFileReference SubmissionFile where
{ submissionFileResidualSubmission :: SubmissionId
, submissionFileResidualIsUpdate
, submissionFileResidualIsDeletion :: Bool
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
_FileReference
= iso (\SubmissionFile{..} -> ( FileReference
@ -187,7 +187,7 @@ instance IsFileReference SubmissionFile where
instance HasFileReference CourseNewsFile where
newtype FileReferenceResidual CourseNewsFile
= CourseNewsFileResidual { courseNewsFileResidualNews :: CourseNewsId }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_FileReference
= iso (\CourseNewsFile{..} -> ( FileReference
@ -216,7 +216,7 @@ instance IsFileReference CourseNewsFile where
instance HasFileReference MaterialFile where
newtype FileReferenceResidual MaterialFile
= MaterialFileResidual { materialFileResidualMaterial :: MaterialId }
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
_FileReference
= iso (\MaterialFile{..} -> ( FileReference

View File

@ -92,7 +92,7 @@ data ManualMigration
| Migration20210208StudyFeaturesRelevanceCachedUUIDs
| Migration20210318CrontabSubmissionRatedNotification
| Migration20210608SeparateTermActive
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite)
nullaryPathPiece ''ManualMigration $ \t@(splitCamel -> verbs) -> case verbs of

View File

@ -86,7 +86,7 @@ data Transaction
, transactionExam :: Current.ExamName
, transactionUser :: Current.UserIdent
}
deriving (Eq, Ord, Read, Show, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Generic)
deriveJSON defaultOptions
{ constructorTagModifier = camelToPathPiece' 1

View File

@ -34,7 +34,7 @@ deriving instance Lift Version
data MigrationVersion = InitialVersion | MigrationVersion Version
deriving (Eq, Ord, Show, Read, Generic, Typeable, Data, Lift)
deriving (Eq, Ord, Show, Read, Generic, Data, Lift)
deriveJSON defaultOptions
{ constructorTagModifier = toLower . fromJust . stripSuffix "Version"

View File

@ -22,13 +22,13 @@ data Rating = Rating
, ratingCorrectorName :: Maybe Text
, ratingSheetType :: SheetType RatingExamPartReference
, ratingValues :: Rating'
} deriving (Read, Show, Eq, Generic, Typeable)
} deriving (Read, Show, Eq, Generic)
deriving anyclass (NFData)
data RatingExamPartReference = RatingExamPartReference
{ ratingExamName :: ExamName
, ratingExamPartNumber :: ExamPartNumber
} deriving (Read, Show, Eq, Ord, Generic, Typeable)
} deriving (Read, Show, Eq, Ord, Generic)
deriving anyclass (NFData)
data Rating' = Rating'
@ -36,7 +36,7 @@ data Rating' = Rating'
, ratingComment :: Maybe Text
, ratingTime :: Maybe UTCTime
, ratingDone :: Bool
} deriving (Read, Show, Eq, Generic, Typeable)
} deriving (Read, Show, Eq, Generic)
deriving anyclass (NFData)
deriveJSON defaultOptions
@ -50,7 +50,7 @@ data RatingValidityException
| RatingNotExpected -- ^ Rating not expected
| RatingBinaryExpected -- ^ Rating must be 0 or 1
| RatingPointsRequired -- ^ Rating without points for sheet that requires there to be points
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
deriving anyclass (Exception)
data RatingParseLegacyException
@ -58,7 +58,7 @@ data RatingParseLegacyException
| RatingMissingSeparator -- ^ Could not split rating header from comments
| RatingMultiple -- ^ Encountered multiple point values in rating
| RatingInvalid Text -- ^ Failed to parse rating point value
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
deriving anyclass (Exception)
data RatingParseException
@ -68,7 +68,7 @@ data RatingParseException
| RatingYAMLException String -- ^ Could not parse YAML
| RatingYAMLCommentNotUnicode UnicodeException
| RatingYAMLNotUnicode String
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
deriving anyclass (Exception)
data RatingException
@ -77,7 +77,7 @@ data RatingException
| RatingParseException RatingParseException
| RatingParseLegacyException RatingParseLegacyException
| RatingValidityException RatingValidityException
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
deriving anyclass (Exception)
data RatingFileException
@ -89,5 +89,5 @@ data RatingFileException
{ ratingExceptionSubmission :: CryptoFileNameSubmission
, ratingException :: RatingException
}
deriving (Show, Eq, Generic, Typeable)
deriving (Show, Eq, Generic)
deriving anyclass (Exception)

View File

@ -12,7 +12,7 @@ data SubmissionSinkException = DuplicateFileTitle FilePath
| RatingWithoutUpdate
| ForeignRating CryptoFileNameSubmission
| InvalidFileTitleExtension FilePath
deriving (Typeable, Show)
deriving (Show)
instance Exception SubmissionSinkException
@ -22,6 +22,6 @@ data SubmissionMultiSinkException
, _submissionSinkFedFile :: Maybe FilePath
, _submissionSinkException :: SubmissionSinkException
}
deriving (Typeable, Show)
deriving (Show)
instance Exception SubmissionMultiSinkException

View File

@ -53,7 +53,7 @@ import qualified Data.CryptoID.Class.ImplicitNamespace as I
data BearerTokenRouteMode
= BearerTokenRouteEval -- ^ Token is not to be evaluated for routes outside of the given restriction
| BearerTokenRouteAccess -- ^ Token may be evaluated for routes outside of the given restriction, but not if the initial request was outside the restriction
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic, Typeable)
deriving (Eq, Ord, Read, Show, Enum, Bounded, Generic)
deriving anyclass (Universe, Finite, Hashable, Binary)
nullaryPathPiece ''BearerTokenRouteMode $ camelToPathPiece' 3
pathPieceJSON ''BearerTokenRouteMode
@ -82,7 +82,7 @@ data BearerToken site = BearerToken
, bearerIssuedFor :: ClusterId
, bearerExpiresAt
, bearerStartsAt :: Maybe UTCTime
} deriving (Generic, Typeable)
} deriving (Generic)
deriving stock instance (Eq (AuthId site), Eq (Route site)) => Eq (BearerToken site)
deriving stock instance (Ord (AuthId site), Ord (Route site)) => Ord (BearerToken site)

View File

@ -31,7 +31,7 @@ data SessionToken sess = SessionToken
, sessionIssuedFor :: ClusterId
, sessionExpiresAt
, sessionStartsAt :: Maybe UTCTime
} deriving (Eq, Ord, Read, Show, Generic, Typeable)
} deriving (Eq, Ord, Read, Show, Generic)
makeLenses_ ''SessionToken
instance HasTokenIdentifier (SessionToken sess) TokenId where

Some files were not shown because too many files have changed in this diff Show More