Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal.Data.Basic.Types
- data VarContext
- newtype Var (ctx :: VarContext) (a :: *) = Var Int
- newtype Key = Key Int
- data MissingField
- data Cached
- data EntityKind
- = Fresh [MissingField]
- | FromDb Cached
- newtype Entity (entKind :: EntityKind) a = Entity {
- _getEntity :: a
- getEntity :: forall entKind a entKind a. Iso (Entity entKind a) (Entity entKind a) a a
- toFreshEntity :: forall fs c a. Entity (FromDb c) a -> Entity (Fresh fs) a
- reorderMissingFieldsTo :: forall fs2 fs1 a. SetEqual fs1 fs2 => Entity (Fresh fs1) a -> Entity (Fresh fs2) a
- data FieldConstraint
- type family MissingFields (entKind :: EntityKind) :: [MissingField] where ...
- type SetFields (missing :: [MissingField]) (table :: *) = TableFields table `Without` MissingFieldsNames missing
- type family TableFieldTypes (a :: *) (fs :: [Symbol]) :: [*] where ...
- class KnownSymbol (CapsName t s) => HasCapsFieldName t (s :: Symbol) where
- class AllSatisfy (TableField table) fields => AllTypesSatisfy (c :: * -> Symbol -> Constraint) (table :: *) (fields :: [Symbol]) where
- class (KnownSymbol n, ToJSON a) => JSONableField a (n :: Symbol)
- class GetEntityFromValue (fs :: [Symbol]) a where
- type MissingFieldsFromValue fs a :: [MissingField]
- class (TableField table field, Ord (TableFieldType table field)) => OrdableField table field
- class (TableField table field, Eq (TableFieldType table field)) => EqableField table field
- class TableFieldTypes a fs ~ ts => FoldCompositeIntoEntity fs ts a where
- compositeToEntity :: forall a fs ts. (fs ~ TableFields a, ts ~ TableFieldTypes a fs, FoldCompositeIntoEntity fs ts a, Table a) => Composite ts -> Entity (Fresh '[]) a
- type family SameTypes toTable (toFields :: [Symbol]) fromTable (fromFields :: [Symbol]) :: Constraint where ...
- class (KnownSymbol (TableName table), AllSatisfy (TableField table) (TableFields table), AllSatisfy KnownSymbol (TableFields table), AllSatisfy (ValidConstraint table) (TableConstraints table), AllTypesSatisfy (TypeSatisfies ToField) table (TableFields table), OnMaybe (() :: Constraint) PrimaryKeyConstraint (TablePrimaryKey table), FromRow table) => Table table where
- type TableName table = (name :: Symbol) | name -> table
- type TableFields table :: [Symbol]
- type TableConstraints table :: [FieldConstraint]
- type TablePrimaryKey table :: Maybe Symbol
- type TableRequiredFields table :: [MissingField]
- class ValidConstraint (table :: *) (constr :: FieldConstraint)
- getDbFields :: forall table. Table table => [Text]
- type family IsDbExp a :: Bool where ...
- type family KindOfDbExp a :: ExpressionKind where ...
- type family IsDbStatement (m :: k -> *) :: Bool where ...
- class ValueAsDbExp' (IsDbExp a) a b => ValueAsDbExp a b where
- class ValueAsDbExp' (isDbExp :: Bool) a b where
- type family CapsName table name where ...
- type family CapsName' name capsName where ...
- class (KnownSymbol name, KnownSymbol (CapsName table name), IsDbExp (TableFieldType table name) ~ False) => TableField (table :: *) (name :: Symbol) where
- type TableFieldType table name :: *
- type TableFieldCapsName table name :: Maybe Symbol
- class (UniqueConstraint name, AllTypesSatisfy NotNull (UniqueTable name) (UniqueFields name)) => PrimaryKeyConstraint (name :: Symbol)
- class (AllSatisfy (TableField (UniqueTable name)) (UniqueFields name), KnownSymbol name) => UniqueConstraint (name :: Symbol) where
- type UniqueTable name :: *
- type UniqueFields name :: [Symbol]
- class (KnownSymbol name, AllSatisfy (TableField (ForeignKeyFrom name)) (ForeignKeyFromFields name), AllSatisfy (TableField (ForeignKeyTo name)) (ForeignKeyToFields name), SameTypes (ForeignKeyTo name) (ForeignKeyToFields name) (ForeignKeyFrom name) (ForeignKeyFromFields name)) => ForeignKeyConstraint (name :: Symbol) where
- type ForeignKeyFrom name :: *
- type ForeignKeyTo name :: *
- type ForeignKeyFromFields name :: [Symbol]
- type ForeignKeyToFields name :: [Symbol]
- type family MissingFieldName (f :: MissingField) :: Symbol where ...
- type family MissingFieldsNames (fs :: [MissingField]) :: [Symbol] where ...
- type family WithFieldSet (field :: Symbol) (entKind :: EntityKind) :: EntityKind where ...
- type family WithFieldsSet (fields :: [Symbol]) (entKind :: EntityKind) :: EntityKind where ...
- type family WithoutMissingField (name :: Symbol) (fs :: [MissingField]) :: [MissingField] where ...
- type family WithoutMissingFields (fields :: [Symbol]) (fs :: [MissingField]) :: [MissingField] where ...
- type CanInsert entKind table = (Table table, CanInsertFresh (MissingFields entKind) table)
- type family CanInsert' (entKind :: EntityKind) (table :: *) :: Constraint where ...
- type CanInsertFresh (missing :: [MissingField]) (table :: *) = (CanInsertMissing missing, SetFields missing table `IsSubset` SetFields missing table, AllSatisfy (HasCapsFieldName table) (SetFields missing table), AllTypesSatisfy (TypeSatisfies ToField) table (SetFields missing table))
- type family CanInsertMissing (fs :: [MissingField]) :: Constraint where ...
- type CanUpdate table pk = (KnownSymbol pk, Table table, SetFields '[] table `IsSubset` SetFields '[] table)
- type DbResult list = ListToTuple (Entity (FromDb Live)) list
- type Variables ctx list = ListToTuple (Var ctx) list
- class TableSetVars ctx (tables :: [*]) where
- data BoolOp
- data ResultType
- type family Selection (t :: ResultType) :: Constraint where ...
- type family CanTake (t :: ResultType) :: Constraint where ...
- type family CanAggregate (t :: ResultType) :: Constraint where ...
- type family CanMap (f :: ResultType) :: Constraint where ...
- type FieldIsGettableBool field missing = Not (field `Elem` MissingFieldsNames missing)
- type FieldIsGettable field missing = CheckWithError (FieldIsGettableBool field missing) ((ErrorText "Field " :<>: ShowType field) :<>: ErrorText " is not set")
- type FieldIsNotSet field setFields = CheckWithError (Not (Elem field setFields)) ((ErrorText "Cannot update the field " :<>: ShowType field) :<>: ErrorText " because it's already updated in this expression")
- varFromUpdateExp :: UpdateExp fields t -> Var Updating t
- type family ListToSimpleTuple (l :: [*]) :: * where ...
- type family TupleToList (map :: *) :: [*] where ...
- type FlattenTuple t = ListToSimpleTuple (TupleToList t)
- data DbStatement (resultType :: ResultType) (ts :: [*]) where
- Table :: Table table => proxy (TableName table) -> DbStatement Unfiltered '[table]
- Filter :: (TableSetVars Filtering tables, Selection f) => (Variables Filtering tables -> ConditionExp) -> DbStatement f tables -> DbStatement Filtered tables
- Join :: DbStatement Unfiltered tables1 -> DbStatement Unfiltered tables2 -> DbStatement Unfiltered (tables1 ++ tables2)
- Raw :: ToRow r => Text -> r -> DbStatement RawQueried a
- Execute :: ToRow r => Text -> r -> DbStatement RawQueried '[]
- Insert :: CanInsert missing table => Entity missing table -> DbStatement Inserted '[table]
- Delete :: (Selection f, Table table) => DbStatement f '[table] -> DbStatement Deleted '[table]
- Update :: Selection f => (Var Updating table -> UpdateExp fields table) -> DbStatement f '[table] -> DbStatement Updated '[a]
- SortOn :: (Selection f, TableSetVars Sorting tables, Sortable ord) => (Variables Sorting tables -> ord) -> DbStatement f tables -> DbStatement Sorted tables
- Take :: CanTake f => Int -> DbStatement f tables -> DbStatement Limited tables
- Map :: (Mappable map, CanMap f, TableSetVars Mapping tables) => (Variables Mapping tables -> map) -> DbStatement f tables -> DbStatement Mapped '[MapResult map]
- AsGroup :: TableSetVars Grouping tables => DbStatement f tables -> DbStatement Grouped tables
- GroupMap :: GroupMappable map => ((AsAggregate group, DbStatement Grouped tables) -> map) -> GroupStatement group tables -> DbStatement Folded '[GroupMapResult map]
- data GroupStatement group tables where
- GroupOn :: (Selection f, TableSetVars Grouping tables, Groupable group) => (Variables Grouping tables -> group) -> DbStatement f tables -> GroupStatement group tables
- data AM = AM
- data AggregateStatement aggr (marker :: AM) where
- Aggregate :: (Aggregatable aggr, CanAggregate f, TableSetVars Folding tables) => (Variables Folding tables -> aggr) -> DbStatement f tables -> AggregateStatement aggr AM
- data UpdateExp (fields :: [Symbol]) (table :: *) where
- NoUpdate :: Var Updating table -> UpdateExp '[] table
- SetField :: (TableField table fieldName, FieldIsNotSet fieldName fields) => proxy fieldName -> UpdateExp fields table -> DbExp k (TableFieldType table fieldName) -> UpdateExp (fieldName ': fields) table
- data ConditionExp where
- Compare :: Ord a => Comparison -> DbExp k1 a -> DbExp k2 a -> ConditionExp
- BoolOp :: BoolOp -> ConditionExp -> ConditionExp -> ConditionExp
- IsNull :: DbExp FieldExp (Maybe a) -> ConditionExp
- IsNotNull :: DbExp FieldExp (Maybe a) -> ConditionExp
- In :: LiteralCollection collection a => DbExp k a -> collection -> ConditionExp
- Like :: Bool -> DbExp FieldExp Text -> Text -> ConditionExp
- BoolLit :: Bool -> ConditionExp
- data ExpressionKind
- data DbExp (kind :: ExpressionKind) a where
- Field :: TableField table fieldName => proxy1 table -> proxy2 fieldName -> Var anyCtx table -> DbExp FieldExp (TableFieldType table fieldName)
- Literal :: ToField a => a -> DbExp LiteralExp a
- data SomeDbExp where
- class Sortable ord where
- class LiteralCollection collection a | collection -> a where
- class Groupable group where
- type AsAggregate group :: *
- data GroupMappableThing res (am :: AM) where
- GroupMappableDbExp :: DbExp k a -> GroupMappableThing a AM
- GroupMappableVar :: Var k a -> GroupMappableThing (Entity (FromDb Live) a) AM
- GroupMappableAggr :: Aggregatable aggr => AggregateStatement aggr AM -> GroupMappableThing (AggregationResult aggr) AM
- type family GroupMapResultBase a where ...
- class GroupMappableBase map where
- type family GroupMapResult (map :: *) :: * where ...
- class GroupMappable map where
- type family InterpretAsGroupMap (a :: *) :: Bool where ...
- class MappableBase map where
- type MapResultBase map :: *
- type family MapResult (map :: *) :: * where ...
- class Mappable map where
- getAggr :: AggregateStatement aggr AM -> aggr
- newtype Avg a = Avg a
- newtype Count a = Count a
- newtype Only a = Only a
- newtype List a = List a
- class AggregatableBase aggr where
- type AggregationBaseResult aggr :: *
- type family BadAggregateBaseError where ...
- type family AggregationResult (aggr :: *) where ...
- class Aggregatable aggr where
- nameText :: forall name. KnownSymbol name => Text
- module Internal.Data.Basic.TypeLevel
- newtype Max a :: * -> * = Max {
- getMax :: a
- newtype Min a :: * -> * = Min {
- getMin :: a
- newtype Sum a :: * -> * = Sum {
- getSum :: a
Documentation
newtype Var (ctx :: VarContext) (a :: *) Source #
Instances
AggregatableBase (List (Var Folding a)) Source # | |
(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t7 (Identity (UpdateExp ((:) Symbol name ([] Symbol)) t)), (~) * t6 t, (~) VarContext t5 Updating, (~) (* -> * -> *) t4 ((->) LiftedRep LiftedRep), (~) * t3 val, (~) (* -> *) t2 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity t3)) (t4 (Var t5 t6) t7))) Source # | |
(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t5 (UpdateExp ((:) Symbol name ([] Symbol)) t), (~) * t4 t, (~) VarContext t3 Updating, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (Identity t5)))) Source # | |
(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t7 t, (~) [Symbol] t6 ((:) Symbol name ([] Symbol)), (~) (* -> *) t5 Identity, (~) * t4 t, (~) VarContext t3 Updating, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (t5 (UpdateExp t6 t7))))) Source # | |
(TableField t name, (~) * t9 (Const * (DbExp FieldExp (TableFieldType t name)) (Var anyCtx t)), (~) * t8 t, (~) VarContext t7 anyCtx, (~) (* -> * -> *) t6 ((->) LiftedRep LiftedRep), (~) * t5 (DbExp FieldExp (TableFieldType t name)), (~) * t4 (DbExp FieldExp (TableFieldType t name)), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 t5)) (t6 (Var t7 t8) t9))) Source # | |
(TableField t name, (~) * t7 (Var anyCtx t), (~) * t6 (DbExp FieldExp (TableFieldType t name)), (~) (* -> * -> *) t5 (Const *), (~) * t4 t, (~) VarContext t3 anyCtx, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Const * (DbExp FieldExp (TableFieldType t name)) (DbExp FieldExp (TableFieldType t name)))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (t5 t6 t7)))) Source # | |
(TableField t name, (~) * t5 t, (~) VarContext t4 anyCtx, (~) (* -> *) t3 (Const * (DbExp FieldExp (TableFieldType t name))), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Var anyCtx t)), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Const * (DbExp FieldExp (TableFieldType t name)) (DbExp FieldExp (TableFieldType t name)))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 (Var t4 t5))))) Source # | |
Eq (Var ctx a) Source # | |
Ord (Var ctx a) Source # | |
Read (Var ctx a) Source # | |
Show (Var ctx a) Source # | |
Table t => MappableBase (Var Mapping t) Source # | |
(Table a, (~) (Maybe Symbol) (TablePrimaryKey a) (Just Symbol pk), AllSatisfy Symbol (TableField a) (UniqueFields pk)) => Groupable (Var Grouping a) Source # | |
type AggregationBaseResult (List (Var Folding a)) Source # | |
type MapResultBase (Var Mapping t) Source # | |
type AsAggregate (Var Grouping a) Source # | |
data MissingField Source #
Defines MissingField
kind.
Constructors
Required Symbol | |
DynamicDefault Symbol |
data EntityKind Source #
Constructors
Fresh [MissingField] | |
FromDb Cached |
newtype Entity (entKind :: EntityKind) a Source #
Constructors
Entity | |
Fields
|
Instances
reorderMissingFieldsTo :: forall fs2 fs1 a. SetEqual fs1 fs2 => Entity (Fresh fs1) a -> Entity (Fresh fs2) a Source #
data FieldConstraint Source #
Constructors
Unique Symbol | |
ForeignKey Symbol |
type family MissingFields (entKind :: EntityKind) :: [MissingField] where ... Source #
Equations
MissingFields (Fresh missing) = missing | |
MissingFields (FromDb c) = '[] |
type SetFields (missing :: [MissingField]) (table :: *) = TableFields table `Without` MissingFieldsNames missing Source #
type family TableFieldTypes (a :: *) (fs :: [Symbol]) :: [*] where ... Source #
Equations
TableFieldTypes a '[] = '[] | |
TableFieldTypes a (f ': fs) = TableFieldType a f ': TableFieldTypes a fs |
class KnownSymbol (CapsName t s) => HasCapsFieldName t (s :: Symbol) where Source #
Minimal complete definition
Methods
capsFieldName :: proxy s -> Text Source #
Instances
KnownSymbol (CapsName t s) => HasCapsFieldName t s Source # | |
class AllSatisfy (TableField table) fields => AllTypesSatisfy (c :: * -> Symbol -> Constraint) (table :: *) (fields :: [Symbol]) where Source #
Minimal complete definition
Methods
mapFields :: fields `IsSubset` SetFields (MissingFields entKind) table => (forall proxy n x. c x n => proxy n -> x -> a) -> Entity entKind table -> [a] Source #
Instances
AllTypesSatisfy c table ([] Symbol) Source # | |
(TableField table x, c (TableFieldType table x) x, AllTypesSatisfy c table xs) => AllTypesSatisfy c table ((:) Symbol x xs) Source # | |
class (KnownSymbol n, ToJSON a) => JSONableField a (n :: Symbol) Source #
Instances
(KnownSymbol n, ToJSON a) => JSONableField a n Source # | |
class GetEntityFromValue (fs :: [Symbol]) a where Source #
Minimal complete definition
Associated Types
type MissingFieldsFromValue fs a :: [MissingField] Source #
Methods
getEntityFromObject :: Value -> Parser (Entity (Fresh (MissingFieldsFromValue fs a)) a) Source #
Instances
Table a => GetEntityFromValue ([] Symbol) a Source # | |
(GetEntityFromValue fs a, FromJSON (TableFieldType a f), TableField a f) => GetEntityFromValue ((:) Symbol f fs) a Source # | |
class (TableField table field, Ord (TableFieldType table field)) => OrdableField table field Source #
Instances
(TableField table field, Ord (TableFieldType table field)) => OrdableField table field Source # | |
class (TableField table field, Eq (TableFieldType table field)) => EqableField table field Source #
Instances
(TableField table field, Eq (TableFieldType table field)) => EqableField table field Source # | |
class TableFieldTypes a fs ~ ts => FoldCompositeIntoEntity fs ts a where Source #
Minimal complete definition
Instances
FoldCompositeIntoEntity ([] Symbol) ([] *) a Source # | |
(TableField a f, (~) * (TableFieldType a f) t, FoldCompositeIntoEntity fs ts a) => FoldCompositeIntoEntity ((:) Symbol f fs) ((:) * t ts) a Source # | |
compositeToEntity :: forall a fs ts. (fs ~ TableFields a, ts ~ TableFieldTypes a fs, FoldCompositeIntoEntity fs ts a, Table a) => Composite ts -> Entity (Fresh '[]) a Source #
type family SameTypes toTable (toFields :: [Symbol]) fromTable (fromFields :: [Symbol]) :: Constraint where ... Source #
Equations
SameTypes toTable '[] fromTable '[] = () | |
SameTypes toTable (x ': xs) fromTable (y ': ys) = (TableFieldType toTable x ~ TableFieldType fromTable y, SameTypes toTable xs fromTable ys) |
class (KnownSymbol (TableName table), AllSatisfy (TableField table) (TableFields table), AllSatisfy KnownSymbol (TableFields table), AllSatisfy (ValidConstraint table) (TableConstraints table), AllTypesSatisfy (TypeSatisfies ToField) table (TableFields table), OnMaybe (() :: Constraint) PrimaryKeyConstraint (TablePrimaryKey table), FromRow table) => Table table where Source #
Minimal complete definition
Associated Types
type TableName table = (name :: Symbol) | name -> table Source #
type TableFields table :: [Symbol] Source #
type TableConstraints table :: [FieldConstraint] Source #
type TablePrimaryKey table :: Maybe Symbol Source #
type TableRequiredFields table :: [MissingField] Source #
class ValidConstraint (table :: *) (constr :: FieldConstraint) Source #
Instances
(ForeignKeyConstraint name, (~) * table (ForeignKeyFrom name)) => ValidConstraint table (ForeignKey name) Source # | |
(UniqueConstraint name, (~) * table (UniqueTable name)) => ValidConstraint table (Unique name) Source # | |
getDbFields :: forall table. Table table => [Text] Source #
type family KindOfDbExp a :: ExpressionKind where ... Source #
Equations
KindOfDbExp (DbExp k a) = k | |
KindOfDbExp a = LiteralExp |
type family IsDbStatement (m :: k -> *) :: Bool where ... Source #
Equations
IsDbStatement (DbStatement r) = True | |
IsDbStatement a = False |
class ValueAsDbExp' (IsDbExp a) a b => ValueAsDbExp a b where Source #
Minimal complete definition
Methods
valueAsDbExp :: a -> DbExp (KindOfDbExp a) b Source #
Instances
ValueAsDbExp' (IsDbExp a) a b => ValueAsDbExp a b Source # | |
class ValueAsDbExp' (isDbExp :: Bool) a b where Source #
Minimal complete definition
Methods
valueAsDbExp' :: a -> DbExp (KindOfDbExp a) b Source #
Instances
((~) * a b, ToField a, (~) ExpressionKind (KindOfDbExp a) LiteralExp) => ValueAsDbExp' False a b Source # | |
(~) * (DbExp k b) a => ValueAsDbExp' True a b Source # | |
type family CapsName table name where ... Source #
Equations
CapsName table name = CapsName' name (TableFieldCapsName table name) |
class (KnownSymbol name, KnownSymbol (CapsName table name), IsDbExp (TableFieldType table name) ~ False) => TableField (table :: *) (name :: Symbol) where Source #
Minimal complete definition
Associated Types
type TableFieldType table name :: * Source #
type TableFieldCapsName table name :: Maybe Symbol Source #
Methods
tableFieldLens :: Lens' table (TableFieldType table name) Source #
Instances
TableField User "id" Source # | |
TableField User "location" Source # | |
TableField User "name" Source # | |
TableField Post "author" Source # | |
TableField Post "id" Source # | |
TableField Post "name" Source # | |
class (UniqueConstraint name, AllTypesSatisfy NotNull (UniqueTable name) (UniqueFields name)) => PrimaryKeyConstraint (name :: Symbol) Source #
class (AllSatisfy (TableField (UniqueTable name)) (UniqueFields name), KnownSymbol name) => UniqueConstraint (name :: Symbol) Source #
class (KnownSymbol name, AllSatisfy (TableField (ForeignKeyFrom name)) (ForeignKeyFromFields name), AllSatisfy (TableField (ForeignKeyTo name)) (ForeignKeyToFields name), SameTypes (ForeignKeyTo name) (ForeignKeyToFields name) (ForeignKeyFrom name) (ForeignKeyFromFields name)) => ForeignKeyConstraint (name :: Symbol) Source #
Associated Types
type ForeignKeyFrom name :: * Source #
type ForeignKeyTo name :: * Source #
type ForeignKeyFromFields name :: [Symbol] Source #
type ForeignKeyToFields name :: [Symbol] Source #
type family MissingFieldName (f :: MissingField) :: Symbol where ... Source #
Equations
MissingFieldName (Required s) = s | |
MissingFieldName (DynamicDefault s) = s |
type family MissingFieldsNames (fs :: [MissingField]) :: [Symbol] where ... Source #
Equations
MissingFieldsNames '[] = '[] | |
MissingFieldsNames (f ': fs) = MissingFieldName f ': MissingFieldsNames fs |
type family WithFieldSet (field :: Symbol) (entKind :: EntityKind) :: EntityKind where ... Source #
Equations
WithFieldSet field (FromDb c) = FromDb c | |
WithFieldSet field (Fresh missing) = Fresh (WithoutMissingField field missing) |
type family WithFieldsSet (fields :: [Symbol]) (entKind :: EntityKind) :: EntityKind where ... Source #
Equations
WithFieldsSet '[] entKind = entKind | |
WithFieldsSet (f ': fs) entKind = WithFieldSet f (WithFieldsSet fs entKind) | |
WithFieldsSet field (FromDb c) = FromDb c |
type family WithoutMissingField (name :: Symbol) (fs :: [MissingField]) :: [MissingField] where ... Source #
Equations
WithoutMissingField name '[] = '[] | |
WithoutMissingField name (Required name ': fs) = fs | |
WithoutMissingField name (DynamicDefault name ': fs) = fs | |
WithoutMissingField name (f ': fs) = f ': WithoutMissingField name fs |
type family WithoutMissingFields (fields :: [Symbol]) (fs :: [MissingField]) :: [MissingField] where ... Source #
Equations
WithoutMissingFields '[] ms = ms | |
WithoutMissingFields (f ': fs) ms = WithoutMissingField f (WithoutMissingFields fs ms) |
type CanInsert entKind table = (Table table, CanInsertFresh (MissingFields entKind) table) Source #
type family CanInsert' (entKind :: EntityKind) (table :: *) :: Constraint where ... Source #
Equations
CanInsert' (Fresh missing) table = CanInsertFresh missing table | |
CanInsert' (FromDb c) table = () |
type CanInsertFresh (missing :: [MissingField]) (table :: *) = (CanInsertMissing missing, SetFields missing table `IsSubset` SetFields missing table, AllSatisfy (HasCapsFieldName table) (SetFields missing table), AllTypesSatisfy (TypeSatisfies ToField) table (SetFields missing table)) Source #
type family CanInsertMissing (fs :: [MissingField]) :: Constraint where ... Source #
Equations
CanInsertMissing '[] = () | |
CanInsertMissing (DynamicDefault name ': fs) = CanInsertMissing fs | |
CanInsertMissing (f ': fs) = TypeError ((ErrorText "Can't insert entity because the required field " :<>: ShowType (MissingFieldName f)) :<>: ErrorText " is not set") |
type CanUpdate table pk = (KnownSymbol pk, Table table, SetFields '[] table `IsSubset` SetFields '[] table) Source #
type Variables ctx list = ListToTuple (Var ctx) list Source #
class TableSetVars ctx (tables :: [*]) where Source #
Minimal complete definition
data ResultType Source #
type family Selection (t :: ResultType) :: Constraint where ... Source #
Equations
Selection Filtered = () | |
Selection Unfiltered = () |
type family CanTake (t :: ResultType) :: Constraint where ... Source #
type family CanAggregate (t :: ResultType) :: Constraint where ... Source #
Equations
CanAggregate Filtered = () | |
CanAggregate Unfiltered = () | |
CanAggregate Grouped = () |
type family CanMap (f :: ResultType) :: Constraint where ... Source #
type FieldIsGettableBool field missing = Not (field `Elem` MissingFieldsNames missing) Source #
type FieldIsGettable field missing = CheckWithError (FieldIsGettableBool field missing) ((ErrorText "Field " :<>: ShowType field) :<>: ErrorText " is not set") Source #
type FieldIsNotSet field setFields = CheckWithError (Not (Elem field setFields)) ((ErrorText "Cannot update the field " :<>: ShowType field) :<>: ErrorText " because it's already updated in this expression") Source #
type family ListToSimpleTuple (l :: [*]) :: * where ... Source #
Equations
ListToSimpleTuple '[] = () | |
ListToSimpleTuple '[a] = Only a | |
ListToSimpleTuple '[a, b] = (a, b) | |
ListToSimpleTuple '[a, b, c] = (a, b, c) | |
ListToSimpleTuple '[a, b, c, d] = (a, b, c, d) | |
ListToSimpleTuple '[a, b, c, d, e] = (a, b, c, d, e) |
type family TupleToList (map :: *) :: [*] where ... Source #
Equations
TupleToList () = '[] | |
TupleToList (Only a) = TupleToList a | |
TupleToList (a, b) = TupleToList a ++ TupleToList b | |
TupleToList (a, b, c) = (TupleToList a ++ TupleToList b) ++ TupleToList c | |
TupleToList (a, b, c, d) = ((TupleToList a ++ TupleToList b) ++ TupleToList c) ++ TupleToList d | |
TupleToList (a, b, c, d, e) = (((TupleToList a ++ TupleToList b) ++ TupleToList c) ++ TupleToList d) ++ TupleToList e | |
TupleToList a = '[a] |
type FlattenTuple t = ListToSimpleTuple (TupleToList t) Source #
data DbStatement (resultType :: ResultType) (ts :: [*]) where Source #
Constructors
Instances
(Mappable map, CanMap f, TableSetVars Mapping tables, (~) * t4 (DbStatement Mapped ((:) * (MapResult map) ([] *))), (~) [*] t3 tables, (~) ResultType t2 f, (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (ListToTuple * (Var Mapping) tables -> map))) => Dmap' (t0 (t1 (DbStatement t2 t3) t4)) Source # | |
data GroupStatement group tables where Source #
Constructors
GroupOn :: (Selection f, TableSetVars Grouping tables, Groupable group) => (Variables Grouping tables -> group) -> DbStatement f tables -> GroupStatement group tables |
Instances
(GroupMappable map, (~) Bool (InterpretAsGroupMap map) True, (~) * t4 (DbStatement Folded ((:) * (GroupMapResult map) ([] *))), (~) [*] t3 tables, (~) * t2 group, (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep ((AsAggregate group, DbStatement Grouped tables) -> map))) => Dmap' (t0 (t1 (GroupStatement t2 t3) t4)) Source # | |
A kind and type used so LiftAggregation can differentiate types like `m a` from
AggregateStatement
by their kind.
Constructors
AM |
data AggregateStatement aggr (marker :: AM) where Source #
Constructors
Aggregate :: (Aggregatable aggr, CanAggregate f, TableSetVars Folding tables) => (Variables Folding tables -> aggr) -> DbStatement f tables -> AggregateStatement aggr AM |
data UpdateExp (fields :: [Symbol]) (table :: *) where Source #
Constructors
NoUpdate :: Var Updating table -> UpdateExp '[] table | |
SetField :: (TableField table fieldName, FieldIsNotSet fieldName fields) => proxy fieldName -> UpdateExp fields table -> DbExp k (TableFieldType table fieldName) -> UpdateExp (fieldName ': fields) table |
Instances
(TableField t name, EqualOrError Bool (Not (Elem Symbol name fields)) True ((:<>:) ((:<>:) (Text "Cannot update the field ") (ShowType Symbol name)) (Text " because it's already updated in this expression")), ValueAsDbExp val (TableFieldType t name), (~) * t5 (Identity (UpdateExp ((:) Symbol name fields) t)), (~) * t4 t, (~) [Symbol] t3 fields, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (UpdateExp t3 t4) t5))) Source # | |
(ValueAsDbExp val (TableFieldType t name), TableField t name, (~) * t7 t, (~) [Symbol] t6 ((:) Symbol name ([] Symbol)), (~) (* -> *) t5 Identity, (~) * t4 t, (~) VarContext t3 Updating, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbExp FieldExp (TableFieldType t name) -> Identity val)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Var t3 t4) (t5 (UpdateExp t6 t7))))) Source # | |
data ConditionExp where Source #
Constructors
Compare :: Ord a => Comparison -> DbExp k1 a -> DbExp k2 a -> ConditionExp | |
BoolOp :: BoolOp -> ConditionExp -> ConditionExp -> ConditionExp | |
IsNull :: DbExp FieldExp (Maybe a) -> ConditionExp | |
IsNotNull :: DbExp FieldExp (Maybe a) -> ConditionExp | |
In :: LiteralCollection collection a => DbExp k a -> collection -> ConditionExp | |
Like :: Bool -> DbExp FieldExp Text -> Text -> ConditionExp | |
BoolLit :: Bool -> ConditionExp |
data ExpressionKind Source #
Constructors
FieldExp | |
LiteralExp |
data DbExp (kind :: ExpressionKind) a where Source #
Constructors
Field :: TableField table fieldName => proxy1 table -> proxy2 fieldName -> Var anyCtx table -> DbExp FieldExp (TableFieldType table fieldName) | |
Literal :: ToField a => a -> DbExp LiteralExp a |
Instances
class Sortable ord where Source #
Minimal complete definition
Methods
getOrdering :: ord -> [(SomeDbExp, SortDirection)] Source #
class LiteralCollection collection a | collection -> a where Source #
Minimal complete definition
Methods
getLiteralCollection :: collection -> [SomeDbExp] Source #
Instances
(~) * (DbExp b x) a => LiteralCollection * [a] x Source # | |
(~) * a b => LiteralCollection * (DbExp k a) b Source # | |
(LiteralCollection k a x, LiteralCollection k b x) => LiteralCollection k (a, b) x Source # | |
(LiteralCollection k a x, LiteralCollection k b x, LiteralCollection k c x) => LiteralCollection k (a, b, c) x Source # | |
class Groupable group where Source #
Minimal complete definition
Associated Types
type AsAggregate group :: * Source #
Wrapps every DbExp in the tuple with the GroupMappableDbExp
Methods
getGrouping :: group -> [SomeDbExp] Source #
asAggregate :: group -> AsAggregate group Source #
Instances
(Groupable a, Groupable b) => Groupable (a, b) Source # | |
(Table a, (~) (Maybe Symbol) (TablePrimaryKey a) (Just Symbol pk), AllSatisfy Symbol (TableField a) (UniqueFields pk)) => Groupable (Var Grouping a) Source # | |
Groupable (DbExp k a) Source # | |
(Groupable a, Groupable b, Groupable c) => Groupable (a, b, c) Source # | |
(Groupable a, Groupable b, Groupable c, Groupable d) => Groupable (a, b, c, d) Source # | |
data GroupMappableThing res (am :: AM) where Source #
Constructors
GroupMappableDbExp :: DbExp k a -> GroupMappableThing a AM | |
GroupMappableVar :: Var k a -> GroupMappableThing (Entity (FromDb Live) a) AM | |
GroupMappableAggr :: Aggregatable aggr => AggregateStatement aggr AM -> GroupMappableThing (AggregationResult aggr) AM |
type family GroupMapResultBase a where ... Source #
Equations
GroupMapResultBase (GroupMappableThing res AM) = res |
class GroupMappableBase map where Source #
Minimal complete definition
Methods
getGroupMappingBase :: map -> [(AggregateFunction, SomeDbExp)] Source #
Instances
(~) * (GroupMappableThing res AM) a => GroupMappableBase a Source # | |
type family GroupMapResult (map :: *) :: * where ... Source #
Equations
GroupMapResult (a, b) = FlattenTuple (GroupMapResultBase a, GroupMapResultBase b) | |
GroupMapResult (a, b, c) = FlattenTuple (GroupMapResultBase a, GroupMapResultBase b, GroupMapResultBase c) | |
GroupMapResult (a, b, c, d) = FlattenTuple (GroupMapResultBase a, GroupMapResultBase b, GroupMapResultBase c, GroupMapResultBase d) | |
GroupMapResult (a, b, c, d, e) = FlattenTuple (GroupMapResultBase a, GroupMapResultBase b, GroupMapResultBase c, GroupMapResultBase d, GroupMapResultBase e) | |
GroupMapResult a = FlattenTuple (Only (GroupMapResultBase a)) |
class GroupMappable map where Source #
Minimal complete definition
Methods
getGroupMapping :: map -> [(AggregateFunction, SomeDbExp)] Source #
Instances
GroupMappableBase (m a) => GroupMappable (m a) Source # | |
(GroupMappableBase a, GroupMappableBase b) => GroupMappable (a, b) Source # | |
(GroupMappableBase a, GroupMappableBase b, GroupMappableBase c) => GroupMappable (a, b, c) Source # | |
(GroupMappableBase a, GroupMappableBase b, GroupMappableBase c, GroupMappableBase d) => GroupMappable (a, b, c, d) Source # | |
(GroupMappableBase a, GroupMappableBase b, GroupMappableBase c, GroupMappableBase d, GroupMappableBase e) => GroupMappable (a, b, c, d, e) Source # | |
type family InterpretAsGroupMap (a :: *) :: Bool where ... Source #
So dfoldMap knows to behave like an expression when used inside of a dmap
Equations
InterpretAsGroupMap (a, b) = True | |
InterpretAsGroupMap (a, b, c) = True | |
InterpretAsGroupMap (a, b, c, d) = True | |
InterpretAsGroupMap (a, b, c, d, e) = True | |
InterpretAsGroupMap (a, b, c, d, e, f) = True | |
InterpretAsGroupMap (m (a :: *)) = False | |
InterpretAsGroupMap a = True |
class MappableBase map where Source #
Minimal complete definition
Associated Types
type MapResultBase map :: * Source #
Methods
getMappingBase :: map -> [SomeDbExp] Source #
Instances
Table t => MappableBase (Var Mapping t) Source # | |
MappableBase (DbExp k a) Source # | |
type family MapResult (map :: *) :: * where ... Source #
Equations
MapResult (a, b) = FlattenTuple (MapResultBase a, MapResultBase b) | |
MapResult (a, b, c) = FlattenTuple (MapResultBase a, MapResultBase b, MapResultBase c) | |
MapResult (a, b, c, d) = FlattenTuple (MapResultBase a, MapResultBase b, MapResultBase c, MapResultBase d) | |
MapResult (a, b, c, d, e) = FlattenTuple (MapResultBase a, MapResultBase b, MapResultBase c, MapResultBase d, MapResultBase e) | |
MapResult a = MapResultBase a |
class Mappable map where Source #
Minimal complete definition
Methods
getMapping :: map -> [SomeDbExp] Source #
Instances
MappableBase a => Mappable a Source # | |
(MappableBase a, MappableBase b) => Mappable (a, b) Source # | |
(MappableBase a, MappableBase b, MappableBase c) => Mappable (a, b, c) Source # | |
(MappableBase a, MappableBase b, MappableBase c, MappableBase d) => Mappable (a, b, c, d) Source # | |
(MappableBase a, MappableBase b, MappableBase c, MappableBase d, MappableBase e) => Mappable (a, b, c, d, e) Source # | |
getAggr :: AggregateStatement aggr AM -> aggr Source #
Constructors
Avg a |
Constructors
Count a |
Instances
AggregatableBase (Count (DbExp f a)) Source # | |
type AggregationBaseResult (Count (DbExp f a)) Source # | |
Constructors
Only a |
Instances
AggregatableBase (Only (DbExp f a)) Source # | |
type AggregationBaseResult (Only (DbExp f a)) Source # | |
Constructors
List a |
class AggregatableBase aggr where Source #
Minimal complete definition
Associated Types
type AggregationBaseResult aggr :: * Source #
Methods
getAggregatingBase :: aggr -> (AggregateFunction, SomeDbExp) Source #
Instances
BadAggregateBaseError Constraint => AggregatableBase a Source # | |
Ord a => AggregatableBase (Min (DbExp f a)) Source # | |
Ord a => AggregatableBase (Max (DbExp f a)) Source # | |
Num a => AggregatableBase (Sum (DbExp f a)) Source # | |
AggregatableBase (List (Var Folding a)) Source # | |
AggregatableBase (List (DbExp f a)) Source # | |
AggregatableBase (Only (DbExp f a)) Source # | |
AggregatableBase (Count (DbExp f a)) Source # | |
Num a => AggregatableBase (Avg (DbExp f a)) Source # | |
type family BadAggregateBaseError where ... Source #
Equations
BadAggregateBaseError = TypeError (((ErrorText "The only types that can exist in a fold expression are expressions involving entity fields wrapped in one of the Monoid newtypes." :$$: ErrorText "Along with the newtypes from Data.Monoid (Max, Min, Sum), there are Avg, Count and List.") :$$: ErrorText "List can be applied to the whole entity, instead of just to it's fields.") :$$: ErrorText "Example: dfoldMap (\\e -> (Max (e ^. height), Avg (e ^. weigth))) t") |
type family AggregationResult (aggr :: *) where ... Source #
Equations
AggregationResult (a, b) = (AggregationBaseResult a, AggregationBaseResult b) | |
AggregationResult (a, b, c) = (AggregationBaseResult a, AggregationBaseResult b, AggregationBaseResult c) | |
AggregationResult a = Only (AggregationBaseResult a) |
class Aggregatable aggr where Source #
Minimal complete definition
Methods
getAggregating :: aggr -> [(AggregateFunction, SomeDbExp)] Source #
Instances
AggregatableBase a => Aggregatable a Source # | |
(AggregatableBase a, AggregatableBase b) => Aggregatable (a, b) Source # | |
(AggregatableBase a, AggregatableBase b, AggregatableBase c) => Aggregatable (a, b, c) Source # | |
nameText :: forall name. KnownSymbol name => Text Source #
Instances
Monad Max | Since: 4.9.0.0 |
Functor Max | Since: 4.9.0.0 |
MonadFix Max | Since: 4.9.0.0 |
Applicative Max | Since: 4.9.0.0 |
Foldable Max | Since: 4.9.0.0 |
Traversable Max | Since: 4.9.0.0 |
ToJSON1 Max | |
FromJSON1 Max | |
Bounded a => Bounded (Max a) | |
Enum a => Enum (Max a) | Since: 4.9.0.0 |
Eq a => Eq (Max a) | |
Data a => Data (Max a) | |
Num a => Num (Max a) | Since: 4.9.0.0 |
Ord a => Ord (Max a) | |
Read a => Read (Max a) | |
Show a => Show (Max a) | |
Generic (Max a) | |
Ord a => Semigroup (Max a) | Since: 4.9.0.0 |
(Ord a, Bounded a) => Monoid (Max a) | Since: 4.9.0.0 |
ToJSON a => ToJSON (Max a) | |
FromJSON a => FromJSON (Max a) | |
Wrapped (Max a) | |
Ord a => AggregatableBase (Max (DbExp f a)) Source # | |
Generic1 * Max | |
(~) * t (Max b) => Rewrapped (Max a) t | |
type Rep (Max a) | |
type Unwrapped (Max a) | |
type AggregationBaseResult (Max (DbExp f a)) Source # | |
type Rep1 * Max | |
Instances
Monad Min | Since: 4.9.0.0 |
Functor Min | Since: 4.9.0.0 |
MonadFix Min | Since: 4.9.0.0 |
Applicative Min | Since: 4.9.0.0 |
Foldable Min | Since: 4.9.0.0 |
Traversable Min | Since: 4.9.0.0 |
ToJSON1 Min | |
FromJSON1 Min | |
Bounded a => Bounded (Min a) | |
Enum a => Enum (Min a) | Since: 4.9.0.0 |
Eq a => Eq (Min a) | |
Data a => Data (Min a) | |
Num a => Num (Min a) | Since: 4.9.0.0 |
Ord a => Ord (Min a) | |
Read a => Read (Min a) | |
Show a => Show (Min a) | |
Generic (Min a) | |
Ord a => Semigroup (Min a) | Since: 4.9.0.0 |
(Ord a, Bounded a) => Monoid (Min a) | Since: 4.9.0.0 |
ToJSON a => ToJSON (Min a) | |
FromJSON a => FromJSON (Min a) | |
Wrapped (Min a) | |
Ord a => AggregatableBase (Min (DbExp f a)) Source # | |
Generic1 * Min | |
(~) * t (Min b) => Rewrapped (Min a) t | |
type Rep (Min a) | |
type Unwrapped (Min a) | |
type AggregationBaseResult (Min (DbExp f a)) Source # | |
type Rep1 * Min | |
Monoid under addition.
Instances
Monad Sum | Since: 4.8.0.0 |
Functor Sum | Since: 4.8.0.0 |
Applicative Sum | Since: 4.8.0.0 |
Foldable Sum | Since: 4.8.0.0 |
Traversable Sum | Since: 4.8.0.0 |
Representable Sum | |
Bounded a => Bounded (Sum a) | |
Eq a => Eq (Sum a) | |
Data a => Data (Sum a) | Since: 4.8.0.0 |
Num a => Num (Sum a) | |
Ord a => Ord (Sum a) | |
Read a => Read (Sum a) | |
Show a => Show (Sum a) | |
Generic (Sum a) | |
Num a => Semigroup (Sum a) | Since: 4.9.0.0 |
Num a => Monoid (Sum a) | Since: 2.1 |
Wrapped (Sum a) | |
Num a => AggregatableBase (Sum (DbExp f a)) Source # | |
Generic1 * Sum | |
(~) * t (Sum b) => Rewrapped (Sum a) t | |
type Rep Sum | |
type Rep (Sum a) | |
type Unwrapped (Sum a) | |
type AggregationBaseResult (Sum (DbExp f a)) Source # | |
type Rep1 * Sum | |