exigo-schema-0.2.0.2: database schema for exigo marking/assessment tools

Safe HaskellNone
LanguageHaskell2010

Exigo.Persistent.Schema

Contents

Description

Basic database schema for exigo tools.

The assumption is that the schema will actually be composed of this, base, schema, plus subsidiary ones for individual assessments.

Synopsis

Database entities

Represents a student

data Student Source #

Constructors

Student 
Instances
Eq Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

(==) :: Student -> Student -> Bool #

(/=) :: Student -> Student -> Bool #

Show Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep Student :: Type -> Type #

Methods

from :: Student -> Rep Student x #

to :: Rep Student x -> Student #

Binary Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

put :: Student -> Put #

get :: Get Student #

putList :: [Student] -> Put #

FromJSON Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser Student

parseJSONList :: Value -> Parser [Student]

ToJSON Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Student -> Value

toEncoding :: Student -> Encoding

toJSONList :: [Student] -> Value

toEncodingList :: [Student] -> Encoding

PersistEntity Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type PersistEntityBackend Student :: Type

data Key Student :: Type #

data EntityField Student a :: Type

data Unique Student :: Type

Methods

keyToValues :: Key Student -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key Student)

persistIdField :: EntityField Student (Key Student)

entityDef :: Monad m => m Student -> EntityDef

persistFieldDef :: EntityField Student typ -> FieldDef

toPersistFields :: Student -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text Student

persistUniqueKeys :: Student -> [Unique Student]

persistUniqueToFieldNames :: Unique Student -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique Student -> [PersistValue]

fieldLens :: EntityField Student field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity Student -> f (Entity Student)

PersistField Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Student -> PersistValue

fromPersistValue :: PersistValue -> Either Text Student

PersistFieldSql Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy Student -> SqlType

Eq (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep (Key Student) :: Type -> Type #

Methods

from :: Key Student -> Rep (Key Student) x #

to :: Rep (Key Student) x -> Key Student #

Binary (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

put :: Key Student -> Put #

get :: Get (Key Student) #

putList :: [Key Student] -> Put #

FromJSON (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key Student)

parseJSONList :: Value -> Parser [Key Student]

FromJSON (Entity Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Entity Student)

parseJSONList :: Value -> Parser [Entity Student]

ToJSON (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key Student -> Value

toEncoding :: Key Student -> Encoding

toJSONList :: [Key Student] -> Value

toEncodingList :: [Key Student] -> Encoding

ToJSON (Entity Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Entity Student -> Value

toEncoding :: Entity Student -> Encoding

toJSONList :: [Entity Student] -> Value

toEncodingList :: [Entity Student] -> Encoding

PersistField (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key Student -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Student)

FromHttpApiData (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key Student) -> SqlType

ToHttpApiData (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Student = D1 (MetaData "Student" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" False) (C1 (MetaCons "Student" PrefixI True) (S1 (MetaSel (Just "studentStudNo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "studentName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))
data EntityField Student typ Source # 
Instance details

Defined in Exigo.Persistent.Schema

data EntityField Student typ where
newtype Key Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Student = SqlBackend
data Unique Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

data Unique Student
type Rep (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep (Key Student) = D1 (MetaData "Key" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" True) (C1 (MetaCons "StudentKey" PrefixI True) (S1 (MetaSel (Just "unStudentKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Submission made by a Student

data Submission Source #

Instances
Eq Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep Submission :: Type -> Type #

Binary Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser Submission

parseJSONList :: Value -> Parser [Submission]

ToJSON Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Submission -> Value

toEncoding :: Submission -> Encoding

toJSONList :: [Submission] -> Value

toEncodingList :: [Submission] -> Encoding

PersistEntity Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type PersistEntityBackend Submission :: Type

data Key Submission :: Type #

data EntityField Submission a :: Type

data Unique Submission :: Type

Methods

keyToValues :: Key Submission -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key Submission)

persistIdField :: EntityField Submission (Key Submission)

entityDef :: Monad m => m Submission -> EntityDef

persistFieldDef :: EntityField Submission typ -> FieldDef

toPersistFields :: Submission -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text Submission

persistUniqueKeys :: Submission -> [Unique Submission]

persistUniqueToFieldNames :: Unique Submission -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique Submission -> [PersistValue]

fieldLens :: EntityField Submission field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity Submission -> f (Entity Submission)

PersistField Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Submission -> PersistValue

fromPersistValue :: PersistValue -> Either Text Submission

PersistFieldSql Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy Submission -> SqlType

Eq (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key Submission)

parseJSONList :: Value -> Parser [Key Submission]

FromJSON (Entity Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Entity Submission)

parseJSONList :: Value -> Parser [Entity Submission]

ToJSON (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key Submission -> Value

toEncoding :: Key Submission -> Encoding

toJSONList :: [Key Submission] -> Value

toEncodingList :: [Key Submission] -> Encoding

ToJSON (Entity Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Entity Submission -> Value

toEncoding :: Entity Submission -> Encoding

toJSONList :: [Entity Submission] -> Value

toEncodingList :: [Entity Submission] -> Encoding

PersistField (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key Submission -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Submission)

FromHttpApiData (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key Submission) -> SqlType

ToHttpApiData (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Submission = D1 (MetaData "Submission" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" False) (C1 (MetaCons "Submission" PrefixI True) (S1 (MetaSel (Just "submissionStudent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Key Student)) :*: (S1 (MetaSel (Just "submissionStudentLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "submissionPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath))))
data EntityField Submission typ Source # 
Instance details

Defined in Exigo.Persistent.Schema

data EntityField Submission typ where
newtype Key Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Submission = SqlBackend
data Unique Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

data Unique Submission

A late penalty applied

data LatePenalty Source #

Instances
Eq LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep LatePenalty :: Type -> Type #

Binary LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser LatePenalty

parseJSONList :: Value -> Parser [LatePenalty]

ToJSON LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: LatePenalty -> Value

toEncoding :: LatePenalty -> Encoding

toJSONList :: [LatePenalty] -> Value

toEncodingList :: [LatePenalty] -> Encoding

PersistEntity LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type PersistEntityBackend LatePenalty :: Type

data Key LatePenalty :: Type #

data EntityField LatePenalty a :: Type

data Unique LatePenalty :: Type

Methods

keyToValues :: Key LatePenalty -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key LatePenalty)

persistIdField :: EntityField LatePenalty (Key LatePenalty)

entityDef :: Monad m => m LatePenalty -> EntityDef

persistFieldDef :: EntityField LatePenalty typ -> FieldDef

toPersistFields :: LatePenalty -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text LatePenalty

persistUniqueKeys :: LatePenalty -> [Unique LatePenalty]

persistUniqueToFieldNames :: Unique LatePenalty -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique LatePenalty -> [PersistValue]

fieldLens :: EntityField LatePenalty field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity LatePenalty -> f (Entity LatePenalty)

PersistField LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: LatePenalty -> PersistValue

fromPersistValue :: PersistValue -> Either Text LatePenalty

PersistFieldSql LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy LatePenalty -> SqlType

Eq (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key LatePenalty)

parseJSONList :: Value -> Parser [Key LatePenalty]

FromJSON (Entity LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Entity LatePenalty)

parseJSONList :: Value -> Parser [Entity LatePenalty]

ToJSON (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key LatePenalty -> Value

toEncoding :: Key LatePenalty -> Encoding

toJSONList :: [Key LatePenalty] -> Value

toEncodingList :: [Key LatePenalty] -> Encoding

ToJSON (Entity LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Entity LatePenalty -> Value

toEncoding :: Entity LatePenalty -> Encoding

toJSONList :: [Entity LatePenalty] -> Value

toEncodingList :: [Entity LatePenalty] -> Encoding

PersistField (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key LatePenalty -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key LatePenalty)

FromHttpApiData (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key LatePenalty) -> SqlType

ToHttpApiData (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep LatePenalty = D1 (MetaData "LatePenalty" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" False) (C1 (MetaCons "LatePenalty" PrefixI True) (S1 (MetaSel (Just "latePenaltyStudent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Key Student)) :*: S1 (MetaSel (Just "latePenaltyDaysLate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))
data EntityField LatePenalty typ Source # 
Instance details

Defined in Exigo.Persistent.Schema

data EntityField LatePenalty typ where
newtype Key LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend LatePenalty = SqlBackend
data Unique LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

data Unique LatePenalty

Runtime access to schema

Saved entities from this schema

savedMainModel :: [EntityDef] Source #

Keys for entities

data family Key record :: Type #

Instances
Eq (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Eq (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Eq (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep (Key Student) :: Type -> Type #

Methods

from :: Key Student -> Rep (Key Student) x #

to :: Rep (Key Student) x -> Key Student #

Binary (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

put :: Key Student -> Put #

get :: Get (Key Student) #

putList :: [Key Student] -> Put #

FromJSON (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key LatePenalty)

parseJSONList :: Value -> Parser [Key LatePenalty]

FromJSON (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key Submission)

parseJSONList :: Value -> Parser [Key Submission]

FromJSON (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key Student)

parseJSONList :: Value -> Parser [Key Student]

ToJSON (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key LatePenalty -> Value

toEncoding :: Key LatePenalty -> Encoding

toJSONList :: [Key LatePenalty] -> Value

toEncodingList :: [Key LatePenalty] -> Encoding

ToJSON (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key Submission -> Value

toEncoding :: Key Submission -> Encoding

toJSONList :: [Key Submission] -> Value

toEncodingList :: [Key Submission] -> Encoding

ToJSON (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key Student -> Value

toEncoding :: Key Student -> Encoding

toJSONList :: [Key Student] -> Value

toEncodingList :: [Key Student] -> Encoding

PersistField (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key LatePenalty -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key LatePenalty)

PersistField (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key Submission -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Submission)

PersistField (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key Student -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Student)

FromHttpApiData (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

FromHttpApiData (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

FromHttpApiData (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key LatePenalty) -> SqlType

PersistFieldSql (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key Submission) -> SqlType

PersistFieldSql (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key Student) -> SqlType

ToHttpApiData (Key LatePenalty) 
Instance details

Defined in Exigo.Persistent.Schema

ToHttpApiData (Key Submission) 
Instance details

Defined in Exigo.Persistent.Schema

ToHttpApiData (Key Student) 
Instance details

Defined in Exigo.Persistent.Schema

(PersistEntity a, PersistEntityBackend a ~ backend, IsPersistBackend backend) => RawSql (Key a) 
Instance details

Defined in Database.Persist.Sql.Class

Methods

rawSqlCols :: (DBName -> Text) -> Key a -> (Int, [Text])

rawSqlColCountReason :: Key a -> String

rawSqlProcessRow :: [PersistValue] -> Either Text (Key a)

newtype Key LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

newtype Key Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

newtype Key Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep (Key Student) = D1 (MetaData "Key" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" True) (C1 (MetaCons "StudentKey" PrefixI True) (S1 (MetaSel (Just "unStudentKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

Instances

pattern StudentId :: () => typ ~ StudentId => EntityField Student typ Source #

pattern SubmissionId :: () => typ ~ SubmissionId => EntityField Submission typ Source #

pattern LatePenaltyId :: () => typ ~ LatePenaltyId => EntityField LatePenalty typ Source #

pattern StudentStudNo :: () => typ ~ Text => EntityField Student typ Source #

pattern StudentName :: () => typ ~ Text => EntityField Student typ Source #

pattern SubmissionStudent :: () => typ ~ Key Student => EntityField Submission typ Source #

pattern SubmissionStudentLogin :: () => typ ~ Text => EntityField Submission typ Source #

pattern SubmissionPath :: () => typ ~ FilePath => EntityField Submission typ Source #

pattern LatePenaltyStudent :: () => typ ~ Key Student => EntityField LatePenalty typ Source #

pattern LatePenaltyDaysLate :: () => typ ~ Int => EntityField LatePenalty typ Source #

data LatePenalty Source #

Instances
Eq LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep LatePenalty :: Type -> Type #

Binary LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser LatePenalty

parseJSONList :: Value -> Parser [LatePenalty]

ToJSON LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: LatePenalty -> Value

toEncoding :: LatePenalty -> Encoding

toJSONList :: [LatePenalty] -> Value

toEncodingList :: [LatePenalty] -> Encoding

PersistEntity LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type PersistEntityBackend LatePenalty :: Type

data Key LatePenalty :: Type #

data EntityField LatePenalty a :: Type

data Unique LatePenalty :: Type

Methods

keyToValues :: Key LatePenalty -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key LatePenalty)

persistIdField :: EntityField LatePenalty (Key LatePenalty)

entityDef :: Monad m => m LatePenalty -> EntityDef

persistFieldDef :: EntityField LatePenalty typ -> FieldDef

toPersistFields :: LatePenalty -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text LatePenalty

persistUniqueKeys :: LatePenalty -> [Unique LatePenalty]

persistUniqueToFieldNames :: Unique LatePenalty -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique LatePenalty -> [PersistValue]

fieldLens :: EntityField LatePenalty field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity LatePenalty -> f (Entity LatePenalty)

PersistField LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: LatePenalty -> PersistValue

fromPersistValue :: PersistValue -> Either Text LatePenalty

PersistFieldSql LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy LatePenalty -> SqlType

Eq (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key LatePenalty)

parseJSONList :: Value -> Parser [Key LatePenalty]

FromJSON (Entity LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Entity LatePenalty)

parseJSONList :: Value -> Parser [Entity LatePenalty]

ToJSON (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key LatePenalty -> Value

toEncoding :: Key LatePenalty -> Encoding

toJSONList :: [Key LatePenalty] -> Value

toEncodingList :: [Key LatePenalty] -> Encoding

ToJSON (Entity LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Entity LatePenalty -> Value

toEncoding :: Entity LatePenalty -> Encoding

toJSONList :: [Entity LatePenalty] -> Value

toEncodingList :: [Entity LatePenalty] -> Encoding

PersistField (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key LatePenalty -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key LatePenalty)

FromHttpApiData (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key LatePenalty) -> SqlType

ToHttpApiData (Key LatePenalty) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep LatePenalty = D1 (MetaData "LatePenalty" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" False) (C1 (MetaCons "LatePenalty" PrefixI True) (S1 (MetaSel (Just "latePenaltyStudent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Key Student)) :*: S1 (MetaSel (Just "latePenaltyDaysLate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)))
data EntityField LatePenalty typ Source # 
Instance details

Defined in Exigo.Persistent.Schema

data EntityField LatePenalty typ where
newtype Key LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend LatePenalty = SqlBackend
data Unique LatePenalty Source # 
Instance details

Defined in Exigo.Persistent.Schema

data Unique LatePenalty

data Submission Source #

Instances
Eq Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep Submission :: Type -> Type #

Binary Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser Submission

parseJSONList :: Value -> Parser [Submission]

ToJSON Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Submission -> Value

toEncoding :: Submission -> Encoding

toJSONList :: [Submission] -> Value

toEncodingList :: [Submission] -> Encoding

PersistEntity Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type PersistEntityBackend Submission :: Type

data Key Submission :: Type #

data EntityField Submission a :: Type

data Unique Submission :: Type

Methods

keyToValues :: Key Submission -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key Submission)

persistIdField :: EntityField Submission (Key Submission)

entityDef :: Monad m => m Submission -> EntityDef

persistFieldDef :: EntityField Submission typ -> FieldDef

toPersistFields :: Submission -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text Submission

persistUniqueKeys :: Submission -> [Unique Submission]

persistUniqueToFieldNames :: Unique Submission -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique Submission -> [PersistValue]

fieldLens :: EntityField Submission field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity Submission -> f (Entity Submission)

PersistField Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Submission -> PersistValue

fromPersistValue :: PersistValue -> Either Text Submission

PersistFieldSql Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy Submission -> SqlType

Eq (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

FromJSON (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key Submission)

parseJSONList :: Value -> Parser [Key Submission]

FromJSON (Entity Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Entity Submission)

parseJSONList :: Value -> Parser [Entity Submission]

ToJSON (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key Submission -> Value

toEncoding :: Key Submission -> Encoding

toJSONList :: [Key Submission] -> Value

toEncodingList :: [Key Submission] -> Encoding

ToJSON (Entity Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Entity Submission -> Value

toEncoding :: Entity Submission -> Encoding

toJSONList :: [Entity Submission] -> Value

toEncodingList :: [Entity Submission] -> Encoding

PersistField (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key Submission -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Submission)

FromHttpApiData (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key Submission) -> SqlType

ToHttpApiData (Key Submission) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Submission = D1 (MetaData "Submission" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" False) (C1 (MetaCons "Submission" PrefixI True) (S1 (MetaSel (Just "submissionStudent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Key Student)) :*: (S1 (MetaSel (Just "submissionStudentLogin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "submissionPath") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 FilePath))))
data EntityField Submission typ Source # 
Instance details

Defined in Exigo.Persistent.Schema

data EntityField Submission typ where
newtype Key Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Submission = SqlBackend
data Unique Submission Source # 
Instance details

Defined in Exigo.Persistent.Schema

data Unique Submission

data Student Source #

Constructors

Student 
Instances
Eq Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

(==) :: Student -> Student -> Bool #

(/=) :: Student -> Student -> Bool #

Show Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep Student :: Type -> Type #

Methods

from :: Student -> Rep Student x #

to :: Rep Student x -> Student #

Binary Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

put :: Student -> Put #

get :: Get Student #

putList :: [Student] -> Put #

FromJSON Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser Student

parseJSONList :: Value -> Parser [Student]

ToJSON Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Student -> Value

toEncoding :: Student -> Encoding

toJSONList :: [Student] -> Value

toEncodingList :: [Student] -> Encoding

PersistEntity Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type PersistEntityBackend Student :: Type

data Key Student :: Type #

data EntityField Student a :: Type

data Unique Student :: Type

Methods

keyToValues :: Key Student -> [PersistValue]

keyFromValues :: [PersistValue] -> Either Text (Key Student)

persistIdField :: EntityField Student (Key Student)

entityDef :: Monad m => m Student -> EntityDef

persistFieldDef :: EntityField Student typ -> FieldDef

toPersistFields :: Student -> [SomePersistField]

fromPersistValues :: [PersistValue] -> Either Text Student

persistUniqueKeys :: Student -> [Unique Student]

persistUniqueToFieldNames :: Unique Student -> [(HaskellName, DBName)]

persistUniqueToValues :: Unique Student -> [PersistValue]

fieldLens :: EntityField Student field -> forall (f :: Type -> Type). Functor f => (field -> f field) -> Entity Student -> f (Entity Student)

PersistField Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Student -> PersistValue

fromPersistValue :: PersistValue -> Either Text Student

PersistFieldSql Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy Student -> SqlType

Eq (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Ord (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Read (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Show (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Generic (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Associated Types

type Rep (Key Student) :: Type -> Type #

Methods

from :: Key Student -> Rep (Key Student) x #

to :: Rep (Key Student) x -> Key Student #

Binary (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

put :: Key Student -> Put #

get :: Get (Key Student) #

putList :: [Key Student] -> Put #

FromJSON (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Key Student)

parseJSONList :: Value -> Parser [Key Student]

FromJSON (Entity Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

parseJSON :: Value -> Parser (Entity Student)

parseJSONList :: Value -> Parser [Entity Student]

ToJSON (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Key Student -> Value

toEncoding :: Key Student -> Encoding

toJSONList :: [Key Student] -> Value

toEncodingList :: [Key Student] -> Encoding

ToJSON (Entity Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toJSON :: Entity Student -> Value

toEncoding :: Entity Student -> Encoding

toJSONList :: [Entity Student] -> Value

toEncodingList :: [Entity Student] -> Encoding

PersistField (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

toPersistValue :: Key Student -> PersistValue

fromPersistValue :: PersistValue -> Either Text (Key Student)

FromHttpApiData (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PathPiece (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

PersistFieldSql (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

Methods

sqlType :: Proxy (Key Student) -> SqlType

ToHttpApiData (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep Student = D1 (MetaData "Student" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" False) (C1 (MetaCons "Student" PrefixI True) (S1 (MetaSel (Just "studentStudNo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "studentName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))
data EntityField Student typ Source # 
Instance details

Defined in Exigo.Persistent.Schema

data EntityField Student typ where
newtype Key Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

type PersistEntityBackend Student = SqlBackend
data Unique Student Source # 
Instance details

Defined in Exigo.Persistent.Schema

data Unique Student
type Rep (Key Student) Source # 
Instance details

Defined in Exigo.Persistent.Schema

type Rep (Key Student) = D1 (MetaData "Key" "Exigo.Persistent.Schema" "exigo-schema-0.2.0.2-DeXFrsw77m68daoCWSOKM2" True) (C1 (MetaCons "StudentKey" PrefixI True) (S1 (MetaSel (Just "unStudentKey") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

savedMainModel :: [EntityDef] Source #