data-basic-0.3.0.0: A database library with a focus on ease of use, type safety and useful error messages

Safe HaskellNone
LanguageHaskell2010

Internal.Data.Basic.Types

Synopsis

Documentation

newtype Var (ctx :: VarContext) (a :: *) Source #

Constructors

Var Int 

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 # 

Methods

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 # 

Methods

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 # 

Methods

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 # 

Methods

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 # 

Methods

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 # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 (Var t4 t5)))) Source #

Eq (Var ctx a) Source # 

Methods

(==) :: Var ctx a -> Var ctx a -> Bool #

(/=) :: Var ctx a -> Var ctx a -> Bool #

Ord (Var ctx a) Source # 

Methods

compare :: Var ctx a -> Var ctx a -> Ordering #

(<) :: Var ctx a -> Var ctx a -> Bool #

(<=) :: Var ctx a -> Var ctx a -> Bool #

(>) :: Var ctx a -> Var ctx a -> Bool #

(>=) :: Var ctx a -> Var ctx a -> Bool #

max :: Var ctx a -> Var ctx a -> Var ctx a #

min :: Var ctx a -> Var ctx a -> Var ctx a #

Read (Var ctx a) Source # 

Methods

readsPrec :: Int -> ReadS (Var ctx a) #

readList :: ReadS [Var ctx a] #

readPrec :: ReadPrec (Var ctx a) #

readListPrec :: ReadPrec [Var ctx a] #

Show (Var ctx a) Source # 

Methods

showsPrec :: Int -> Var ctx a -> ShowS #

show :: Var ctx a -> String #

showList :: [Var ctx a] -> ShowS #

Table t => MappableBase (Var Mapping t) Source # 

Associated Types

type MapResultBase (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 # 

newtype Key Source #

Constructors

Key Int 

Instances

data Cached Source #

Constructors

Live 
Cached 

newtype Entity (entKind :: EntityKind) a Source #

Constructors

Entity 

Fields

Instances

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t7 (Identity (Entity (WithFieldSet name entKind) t)), (~) * t6 t, (~) EntityKind t5 entKind, (~) (* -> * -> *) t4 ((->) LiftedRep LiftedRep), (~) * t3 (TableFieldType t name), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity t3)) (t4 (Entity t5 t6) t7))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity t3)) (t4 (Entity t5 t6) t7)) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t7 t, (~) EntityKind t6 (WithFieldSet name entKind), (~) (* -> *) t5 Identity, (~) (* -> *) t4 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) * t3 (TableFieldType t name), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity t3)) (t4 (t5 (Entity t6 t7))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity t3)) (t4 (t5 (Entity t6 t7)))) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t5 (Entity (WithFieldSet name entKind) t), (~) * t4 t, (~) EntityKind t3 entKind, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name) -> Identity (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Entity t3 t4) (Identity t5)))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Entity t3 t4) (Identity t5))) Source #

(TableField t name, SupportedModifyAccess Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name), (~) * t4 t, (~) EntityKind t3 (WithFieldSet name entKind), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (ExistingValue Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) (TableFieldType t name) -> Identity (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Identity (Entity t3 t4))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Identity (Entity t3 t4)))) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t9 (Const * (TableFieldType t name) (Entity entKind t)), (~) * t8 t, (~) EntityKind t7 entKind, (~) (* -> * -> *) t6 ((->) LiftedRep LiftedRep), (~) * t5 (TableFieldType t name), (~) * t4 (TableFieldType t name), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (TableFieldType t name)), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 t5)) (t6 (Entity t7 t8) t9))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 t5)) (t6 (Entity t7 t8) t9)) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t7 (Entity entKind t), (~) * t6 (TableFieldType t name), (~) (* -> * -> *) t5 (Const *), (~) * t4 t, (~) EntityKind t3 entKind, (~) (* -> * -> *) t2 ((->) LiftedRep LiftedRep), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (TableFieldType t name -> Const * (TableFieldType t name) (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (Entity t3 t4) (t5 t6 t7)))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Entity t3 t4) (t5 t6 t7))) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t9 t, (~) EntityKind t8 entKind, (~) (* -> *) t7 (Const * (TableFieldType t name)), (~) (* -> *) t6 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) * t5 (TableFieldType t name), (~) * t4 (TableFieldType t name), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (TableFieldType t name)), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 t5)) (t6 (t7 (Entity t8 t9))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 t5)) (t6 (t7 (Entity t8 t9)))) Source #

(TableField t name, EqualOrError Bool (Not (Elem Symbol name (MissingFieldsNames (MissingFields entKind)))) True ((:<>:) ((:<>:) (Text "Field ") (ShowType Symbol name)) (Text " is not set")), (~) * t6 t, (~) EntityKind t5 entKind, (~) * t4 (TableFieldType t name), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity entKind t)), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (TableFieldType t name -> Const * (TableFieldType t name) (TableFieldType t name))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy name))) => FieldOpticProxy (t0 (t1 (t2 (t3 t4 (Entity t5 t6))))) Source # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (t3 t4 (Entity t5 t6)))) Source #

AllSatisfy Symbol (EqableField a) (SetFields (MissingFields entKind) a) => Eq (Entity entKind a) Source # 

Methods

(==) :: Entity entKind a -> Entity entKind a -> Bool #

(/=) :: Entity entKind a -> Entity entKind a -> Bool #

(AllSatisfy Symbol (OrdableField a) (SetFields (MissingFields entKind) a), Eq (Entity entKind a)) => Ord (Entity entKind a) Source # 

Methods

compare :: Entity entKind a -> Entity entKind a -> Ordering #

(<) :: Entity entKind a -> Entity entKind a -> Bool #

(<=) :: Entity entKind a -> Entity entKind a -> Bool #

(>) :: Entity entKind a -> Entity entKind a -> Bool #

(>=) :: Entity entKind a -> Entity entKind a -> Bool #

max :: Entity entKind a -> Entity entKind a -> Entity entKind a #

min :: Entity entKind a -> Entity entKind a -> Entity entKind a #

ToJSON (Entity entKind a) => Show (Entity entKind a) Source # 

Methods

showsPrec :: Int -> Entity entKind a -> ShowS #

show :: Entity entKind a -> String #

showList :: [Entity entKind a] -> ShowS #

(IsSubset Symbol (SetFields fs a) (SetFields fs a), AllTypesSatisfy JSONableField a (SetFields fs a)) => ToJSON (Entity (Fresh fs) a) Source # 

Methods

toJSON :: Entity (Fresh fs) a -> Value #

toEncoding :: Entity (Fresh fs) a -> Encoding #

toJSONList :: [Entity (Fresh fs) a] -> Value #

toEncodingList :: [Entity (Fresh fs) a] -> Encoding #

(IsSubset Symbol (TableFields a) (TableFields a), AllTypesSatisfy JSONableField a (TableFields a)) => ToJSON (Entity (FromDb Live) a) Source # 
(GetEntityFromValue (SetFields miss a) a, SetEqual MissingField (MissingFieldsFromValue (SetFields miss a) a) miss) => FromJSON (Entity (Fresh miss) a) Source # 

Methods

parseJSON :: Value -> Parser (Entity (Fresh miss) a) #

parseJSONList :: Value -> Parser [Entity (Fresh miss) a] #

FromRow a => FromRow (Entity l a) Source # 

Methods

fromRow :: RowParser (Entity l a) #

((~) [Symbol] fs (TableFields a), (~) [*] ts (TableFieldTypes a fs), FoldCompositeIntoEntity fs ts a, FieldParsers ts, Table a) => FromField (Entity (FromDb Live) a) Source # 

getEntity :: forall entKind a entKind a. Iso (Entity entKind a) (Entity entKind a) a a Source #

toFreshEntity :: forall fs c a. Entity (FromDb c) a -> Entity (Fresh fs) a Source #

reorderMissingFieldsTo :: forall fs2 fs1 a. SetEqual fs1 fs2 => Entity (Fresh fs1) a -> Entity (Fresh fs2) a Source #

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

capsFieldName

Methods

capsFieldName :: proxy s -> Text Source #

Instances

KnownSymbol (CapsName t s) => HasCapsFieldName t s Source # 

Methods

capsFieldName :: proxy s -> Text Source #

class AllSatisfy (TableField table) fields => AllTypesSatisfy (c :: * -> Symbol -> Constraint) (table :: *) (fields :: [Symbol]) where Source #

Minimal complete definition

mapFields

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 # 

Methods

mapFields :: IsSubset Symbol [Symbol] (SetFields (MissingFields entKind) table) => (forall (proxy :: Symbol -> *) (n :: Symbol) x. c x n => proxy n -> x -> a) -> Entity entKind table -> [a] Source #

(TableField table x, c (TableFieldType table x) x, AllTypesSatisfy c table xs) => AllTypesSatisfy c table ((:) Symbol x xs) Source # 

Methods

mapFields :: IsSubset Symbol ((Symbol ': x) xs) (SetFields (MissingFields entKind) table) => (forall (proxy :: Symbol -> *) (n :: Symbol) a. c a n => proxy n -> a -> a) -> Entity entKind table -> [a] Source #

class (KnownSymbol n, ToJSON a) => JSONableField a (n :: Symbol) Source #

Instances

class GetEntityFromValue (fs :: [Symbol]) a where Source #

Minimal complete definition

getEntityFromObject

Associated Types

type MissingFieldsFromValue fs a :: [MissingField] 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

foldCompositeIntoEntity

Methods

foldCompositeIntoEntity :: Entity entKind a -> Composite ts -> Entity (Fresh '[]) a Source #

Instances

FoldCompositeIntoEntity ([] Symbol) ([] *) a Source # 
(TableField a f, (~) * (TableFieldType a f) t, FoldCompositeIntoEntity fs ts a) => FoldCompositeIntoEntity ((:) Symbol f fs) ((:) * t ts) a Source # 

Methods

foldCompositeIntoEntity :: Entity entKind a -> Composite ((* ': t) ts) -> Entity (Fresh [MissingField]) 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

newEntity

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 #

Methods

newEntity :: Entity (Fresh (TableRequiredFields table)) table 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 IsDbExp a :: Bool where ... Source #

Equations

IsDbExp (DbExp k a) = True 
IsDbExp a = False 

type family KindOfDbExp a :: ExpressionKind where ... Source #

Equations

KindOfDbExp (DbExp k a) = k 
KindOfDbExp a = LiteralExp 

type family IsDbStatement (m :: k -> *) :: Bool where ... Source #

class ValueAsDbExp' (IsDbExp a) a b => ValueAsDbExp a b where Source #

Minimal complete definition

valueAsDbExp

Methods

valueAsDbExp :: a -> DbExp (KindOfDbExp a) b Source #

Instances

class ValueAsDbExp' (isDbExp :: Bool) a b where Source #

Minimal complete definition

valueAsDbExp'

Methods

valueAsDbExp' :: a -> DbExp (KindOfDbExp a) b Source #

Instances

((~) * a b, ToField a, (~) ExpressionKind (KindOfDbExp a) LiteralExp) => ValueAsDbExp' False a b Source # 

Methods

valueAsDbExp' :: a -> DbExp (KindOfDbExp a) b Source #

(~) * (DbExp k b) a => ValueAsDbExp' True a b Source # 

Methods

valueAsDbExp' :: a -> DbExp (KindOfDbExp a) b Source #

type family CapsName table name where ... Source #

Equations

CapsName table name = CapsName' name (TableFieldCapsName table name) 

type family CapsName' name capsName where ... Source #

Equations

CapsName' name Nothing = name 
CapsName' name (Just cName) = cName 

class (KnownSymbol name, KnownSymbol (CapsName table name), IsDbExp (TableFieldType table name) ~ False) => TableField (table :: *) (name :: Symbol) where Source #

Minimal complete definition

tableFieldLens

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 # 

Associated Types

type TableFieldType User ("id" :: Symbol) :: * Source #

type TableFieldCapsName User ("id" :: Symbol) :: Maybe Symbol Source #

TableField User "location" Source # 

Associated Types

type TableFieldType User ("location" :: Symbol) :: * Source #

type TableFieldCapsName User ("location" :: Symbol) :: Maybe Symbol Source #

TableField User "name" Source # 

Associated Types

type TableFieldType User ("name" :: Symbol) :: * Source #

type TableFieldCapsName User ("name" :: Symbol) :: Maybe Symbol Source #

TableField Post "author" Source # 

Associated Types

type TableFieldType Post ("author" :: Symbol) :: * Source #

type TableFieldCapsName Post ("author" :: Symbol) :: Maybe Symbol Source #

TableField Post "id" Source # 

Associated Types

type TableFieldType Post ("id" :: Symbol) :: * Source #

type TableFieldCapsName Post ("id" :: Symbol) :: Maybe Symbol Source #

TableField Post "name" Source # 

Associated Types

type TableFieldType Post ("name" :: Symbol) :: * Source #

type TableFieldCapsName Post ("name" :: Symbol) :: Maybe Symbol Source #

class (AllSatisfy (TableField (UniqueTable name)) (UniqueFields name), KnownSymbol name) => UniqueConstraint (name :: Symbol) Source #

Associated Types

type UniqueTable name :: * Source #

type UniqueFields name :: [Symbol] Source #

type family MissingFieldName (f :: MissingField) :: Symbol where ... Source #

type family MissingFieldsNames (fs :: [MissingField]) :: [Symbol] where ... Source #

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 #

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

makeVars

Methods

makeVars :: Variables ctx tables Source #

Instances

TableSetVars ctx ([] *) Source # 

Methods

makeVars :: Variables ctx [*] Source #

TableSetVars ctx ((:) * a ((:) * b ((:) * c ([] *)))) Source # 

Methods

makeVars :: Variables ctx ((* ': a) ((* ': b) ((* ': c) [*]))) Source #

TableSetVars ctx ((:) * a ((:) * b ([] *))) Source # 

Methods

makeVars :: Variables ctx ((* ': a) ((* ': b) [*])) Source #

TableSetVars ctx ((:) * a ([] *)) Source # 

Methods

makeVars :: Variables ctx ((* ': a) [*]) Source #

type family Selection (t :: ResultType) :: Constraint where ... Source #

Equations

Selection Filtered = () 
Selection Unfiltered = () 

type family CanTake (t :: ResultType) :: Constraint where ... Source #

Equations

CanTake Filtered = () 
CanTake Unfiltered = () 
CanTake Sorted = () 
CanTake Mapped = () 

type family CanAggregate (t :: ResultType) :: Constraint where ... Source #

type family CanMap (f :: ResultType) :: Constraint where ... Source #

Equations

CanMap Unfiltered = () 
CanMap Filtered = () 
CanMap Grouped = () 
CanMap Sorted = () 

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 #

data DbStatement (resultType :: ResultType) (ts :: [*]) where Source #

Constructors

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] 

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 # 

Methods

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 # 

Methods

dmap' :: t0 (t1 (GroupStatement t2 t3) t4) Source #

data AM 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 # 

Methods

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 # 

Methods

fieldOpticProxy :: t0 (t1 (t2 (Var t3 t4) (t5 (UpdateExp t6 t7)))) Source #

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

(ValueAsDbExp a b, Ord b) => ComparableInDbExp a (DbExp k b) Source # 
(~) * a b => LiteralCollection * (DbExp k a) b Source # 
Ord a => AggregatableBase (Min (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Min (DbExp f a)) :: * Source #

Ord a => AggregatableBase (Max (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Max (DbExp f a)) :: * Source #

Num a => AggregatableBase (Sum (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Sum (DbExp f a)) :: * Source #

AggregatableBase (List (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (List (DbExp f a)) :: * Source #

AggregatableBase (Only (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Only (DbExp f a)) :: * Source #

AggregatableBase (Count (DbExp f a)) Source # 
Num a => AggregatableBase (Avg (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Avg (DbExp f a)) :: * Source #

((~) ExpressionKind k LiteralExp, Num a, ToField a) => Num (DbExp k a) Source # 

Methods

(+) :: DbExp k a -> DbExp k a -> DbExp k a #

(-) :: DbExp k a -> DbExp k a -> DbExp k a #

(*) :: DbExp k a -> DbExp k a -> DbExp k a #

negate :: DbExp k a -> DbExp k a #

abs :: DbExp k a -> DbExp k a #

signum :: DbExp k a -> DbExp k a #

fromInteger :: Integer -> DbExp k a #

(~) ExpressionKind k LiteralExp => IsString (DbExp k Text) Source # 

Methods

fromString :: String -> DbExp k Text #

MappableBase (DbExp k a) Source # 

Associated Types

type MapResultBase (DbExp k a) :: * Source #

Groupable (DbExp k a) Source # 

Associated Types

type AsAggregate (DbExp k a) :: * Source #

Ord a => Sortable (DbExp k a) Source # 
(ValueAsDbExp b a, Ord a) => ComparableInDbExp (DbExp k a) b Source # 
type AggregationBaseResult (Min (DbExp f a)) Source # 
type AggregationBaseResult (Max (DbExp f a)) Source # 
type AggregationBaseResult (Sum (DbExp f a)) Source # 
type AggregationBaseResult (List (DbExp f a)) Source # 
type AggregationBaseResult (Only (DbExp f a)) Source # 
type AggregationBaseResult (Count (DbExp f a)) Source # 
type AggregationBaseResult (Avg (DbExp f a)) Source # 
type MapResultBase (DbExp k a) Source # 
type MapResultBase (DbExp k a) = Only a
type AsAggregate (DbExp k a) Source # 

data SomeDbExp where Source #

Constructors

SomeDbExp :: DbExp k a -> SomeDbExp 
SomeVar :: Var k a -> SomeDbExp 

class Sortable ord where Source #

Minimal complete definition

getOrdering

Instances

Sortable a => Sortable (Down a) Source # 
(Sortable a, Sortable b) => Sortable (a, b) Source # 

Methods

getOrdering :: (a, b) -> [(SomeDbExp, SortDirection)] Source #

Ord a => Sortable (DbExp k a) Source # 
(Sortable a, Sortable b, Sortable c) => Sortable (a, b, c) Source # 

Methods

getOrdering :: (a, b, c) -> [(SomeDbExp, SortDirection)] Source #

class LiteralCollection collection a | collection -> a where Source #

Minimal complete definition

getLiteralCollection

Methods

getLiteralCollection :: collection -> [SomeDbExp] Source #

Instances

class Groupable group where Source #

Minimal complete definition

getGrouping, asAggregate

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 # 

Associated Types

type AsAggregate (a, b) :: * Source #

Methods

getGrouping :: (a, b) -> [SomeDbExp] Source #

asAggregate :: (a, b) -> AsAggregate (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 # 

Associated Types

type AsAggregate (DbExp k a) :: * Source #

(Groupable a, Groupable b, Groupable c) => Groupable (a, b, c) Source # 

Associated Types

type AsAggregate (a, b, c) :: * Source #

Methods

getGrouping :: (a, b, c) -> [SomeDbExp] Source #

asAggregate :: (a, b, c) -> AsAggregate (a, b, c) Source #

(Groupable a, Groupable b, Groupable c, Groupable d) => Groupable (a, b, c, d) Source # 

Associated Types

type AsAggregate (a, b, c, d) :: * Source #

Methods

getGrouping :: (a, b, c, d) -> [SomeDbExp] Source #

asAggregate :: (a, b, c, d) -> AsAggregate (a, b, c, d) Source #

type family GroupMapResultBase a where ... Source #

class GroupMappableBase map where Source #

Minimal complete definition

getGroupMappingBase

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

getMappingBase

Associated Types

type MapResultBase map :: * Source #

Methods

getMappingBase :: map -> [SomeDbExp] Source #

Instances

Table t => MappableBase (Var Mapping t) Source # 

Associated Types

type MapResultBase (Var Mapping t) :: * Source #

MappableBase (DbExp k a) Source # 

Associated Types

type MapResultBase (DbExp k a) :: * Source #

class Mappable map where Source #

Minimal complete definition

getMapping

Methods

getMapping :: map -> [SomeDbExp] Source #

Instances

MappableBase a => Mappable a Source # 

Methods

getMapping :: a -> [SomeDbExp] Source #

(MappableBase a, MappableBase b) => Mappable (a, b) Source # 

Methods

getMapping :: (a, b) -> [SomeDbExp] Source #

(MappableBase a, MappableBase b, MappableBase c) => Mappable (a, b, c) Source # 

Methods

getMapping :: (a, b, c) -> [SomeDbExp] Source #

(MappableBase a, MappableBase b, MappableBase c, MappableBase d) => Mappable (a, b, c, d) Source # 

Methods

getMapping :: (a, b, c, d) -> [SomeDbExp] Source #

(MappableBase a, MappableBase b, MappableBase c, MappableBase d, MappableBase e) => Mappable (a, b, c, d, e) Source # 

Methods

getMapping :: (a, b, c, d, e) -> [SomeDbExp] Source #

newtype Avg a Source #

Constructors

Avg a 

Instances

newtype Count a Source #

Constructors

Count a 

newtype Only a Source #

Constructors

Only a 

class AggregatableBase aggr where Source #

Minimal complete definition

getAggregatingBase

Associated Types

type AggregationBaseResult aggr :: * Source #

Instances

BadAggregateBaseError Constraint => AggregatableBase a Source # 
Ord a => AggregatableBase (Min (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Min (DbExp f a)) :: * Source #

Ord a => AggregatableBase (Max (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Max (DbExp f a)) :: * Source #

Num a => AggregatableBase (Sum (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Sum (DbExp f a)) :: * Source #

AggregatableBase (List (Var Folding a)) Source # 
AggregatableBase (List (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (List (DbExp f a)) :: * Source #

AggregatableBase (Only (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Only (DbExp f a)) :: * Source #

AggregatableBase (Count (DbExp f a)) Source # 
Num a => AggregatableBase (Avg (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (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") 

nameText :: forall name. KnownSymbol name => Text Source #

newtype Max a :: * -> * #

Constructors

Max 

Fields

Instances

Monad Max

Since: 4.9.0.0

Methods

(>>=) :: Max a -> (a -> Max b) -> Max b #

(>>) :: Max a -> Max b -> Max b #

return :: a -> Max a #

fail :: String -> Max a #

Functor Max

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Max a -> Max b #

(<$) :: a -> Max b -> Max a #

MonadFix Max

Since: 4.9.0.0

Methods

mfix :: (a -> Max a) -> Max a #

Applicative Max

Since: 4.9.0.0

Methods

pure :: a -> Max a #

(<*>) :: Max (a -> b) -> Max a -> Max b #

liftA2 :: (a -> b -> c) -> Max a -> Max b -> Max c #

(*>) :: Max a -> Max b -> Max b #

(<*) :: Max a -> Max b -> Max a #

Foldable Max

Since: 4.9.0.0

Methods

fold :: Monoid m => Max m -> m #

foldMap :: Monoid m => (a -> m) -> Max a -> m #

foldr :: (a -> b -> b) -> b -> Max a -> b #

foldr' :: (a -> b -> b) -> b -> Max a -> b #

foldl :: (b -> a -> b) -> b -> Max a -> b #

foldl' :: (b -> a -> b) -> b -> Max a -> b #

foldr1 :: (a -> a -> a) -> Max a -> a #

foldl1 :: (a -> a -> a) -> Max a -> a #

toList :: Max a -> [a] #

null :: Max a -> Bool #

length :: Max a -> Int #

elem :: Eq a => a -> Max a -> Bool #

maximum :: Ord a => Max a -> a #

minimum :: Ord a => Max a -> a #

sum :: Num a => Max a -> a #

product :: Num a => Max a -> a #

Traversable Max

Since: 4.9.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Max a -> f (Max b) #

sequenceA :: Applicative f => Max (f a) -> f (Max a) #

mapM :: Monad m => (a -> m b) -> Max a -> m (Max b) #

sequence :: Monad m => Max (m a) -> m (Max a) #

ToJSON1 Max 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Max a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Max a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Max a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Max a] -> Encoding #

FromJSON1 Max 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Max a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Max a] #

Bounded a => Bounded (Max a) 

Methods

minBound :: Max a #

maxBound :: Max a #

Enum a => Enum (Max a)

Since: 4.9.0.0

Methods

succ :: Max a -> Max a #

pred :: Max a -> Max a #

toEnum :: Int -> Max a #

fromEnum :: Max a -> Int #

enumFrom :: Max a -> [Max a] #

enumFromThen :: Max a -> Max a -> [Max a] #

enumFromTo :: Max a -> Max a -> [Max a] #

enumFromThenTo :: Max a -> Max a -> Max a -> [Max a] #

Eq a => Eq (Max a) 

Methods

(==) :: Max a -> Max a -> Bool #

(/=) :: Max a -> Max a -> Bool #

Data a => Data (Max a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Max a -> c (Max a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Max a) #

toConstr :: Max a -> Constr #

dataTypeOf :: Max a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Max a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Max a)) #

gmapT :: (forall b. Data b => b -> b) -> Max a -> Max a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Max a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Max a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Max a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Max a -> m (Max a) #

Num a => Num (Max a)

Since: 4.9.0.0

Methods

(+) :: Max a -> Max a -> Max a #

(-) :: Max a -> Max a -> Max a #

(*) :: Max a -> Max a -> Max a #

negate :: Max a -> Max a #

abs :: Max a -> Max a #

signum :: Max a -> Max a #

fromInteger :: Integer -> Max a #

Ord a => Ord (Max a) 

Methods

compare :: Max a -> Max a -> Ordering #

(<) :: Max a -> Max a -> Bool #

(<=) :: Max a -> Max a -> Bool #

(>) :: Max a -> Max a -> Bool #

(>=) :: Max a -> Max a -> Bool #

max :: Max a -> Max a -> Max a #

min :: Max a -> Max a -> Max a #

Read a => Read (Max a) 
Show a => Show (Max a) 

Methods

showsPrec :: Int -> Max a -> ShowS #

show :: Max a -> String #

showList :: [Max a] -> ShowS #

Generic (Max a) 

Associated Types

type Rep (Max a) :: * -> * #

Methods

from :: Max a -> Rep (Max a) x #

to :: Rep (Max a) x -> Max a #

Ord a => Semigroup (Max a)

Since: 4.9.0.0

Methods

(<>) :: Max a -> Max a -> Max a #

sconcat :: NonEmpty (Max a) -> Max a #

stimes :: Integral b => b -> Max a -> Max a #

(Ord a, Bounded a) => Monoid (Max a)

Since: 4.9.0.0

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

ToJSON a => ToJSON (Max a) 

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

FromJSON a => FromJSON (Max a) 

Methods

parseJSON :: Value -> Parser (Max a) #

parseJSONList :: Value -> Parser [Max a] #

Wrapped (Max a) 

Associated Types

type Unwrapped (Max a) :: * #

Methods

_Wrapped' :: Iso' (Max a) (Unwrapped (Max a)) #

Ord a => AggregatableBase (Max (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Max (DbExp f a)) :: * Source #

Generic1 * Max 

Associated Types

type Rep1 Max (f :: Max -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Max f a #

to1 :: Rep1 Max f a -> f a #

(~) * t (Max b) => Rewrapped (Max a) t 
type Rep (Max a) 
type Rep (Max a) = D1 * (MetaData "Max" "Data.Semigroup" "base" True) (C1 * (MetaCons "Max" PrefixI True) (S1 * (MetaSel (Just Symbol "getMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))
type Unwrapped (Max a) 
type Unwrapped (Max a) = a
type AggregationBaseResult (Max (DbExp f a)) Source # 
type Rep1 * Max 
type Rep1 * Max = D1 * (MetaData "Max" "Data.Semigroup" "base" True) (C1 * (MetaCons "Max" PrefixI True) (S1 * (MetaSel (Just Symbol "getMax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Min a :: * -> * #

Constructors

Min 

Fields

Instances

Monad Min

Since: 4.9.0.0

Methods

(>>=) :: Min a -> (a -> Min b) -> Min b #

(>>) :: Min a -> Min b -> Min b #

return :: a -> Min a #

fail :: String -> Min a #

Functor Min

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Min a -> Min b #

(<$) :: a -> Min b -> Min a #

MonadFix Min

Since: 4.9.0.0

Methods

mfix :: (a -> Min a) -> Min a #

Applicative Min

Since: 4.9.0.0

Methods

pure :: a -> Min a #

(<*>) :: Min (a -> b) -> Min a -> Min b #

liftA2 :: (a -> b -> c) -> Min a -> Min b -> Min c #

(*>) :: Min a -> Min b -> Min b #

(<*) :: Min a -> Min b -> Min a #

Foldable Min

Since: 4.9.0.0

Methods

fold :: Monoid m => Min m -> m #

foldMap :: Monoid m => (a -> m) -> Min a -> m #

foldr :: (a -> b -> b) -> b -> Min a -> b #

foldr' :: (a -> b -> b) -> b -> Min a -> b #

foldl :: (b -> a -> b) -> b -> Min a -> b #

foldl' :: (b -> a -> b) -> b -> Min a -> b #

foldr1 :: (a -> a -> a) -> Min a -> a #

foldl1 :: (a -> a -> a) -> Min a -> a #

toList :: Min a -> [a] #

null :: Min a -> Bool #

length :: Min a -> Int #

elem :: Eq a => a -> Min a -> Bool #

maximum :: Ord a => Min a -> a #

minimum :: Ord a => Min a -> a #

sum :: Num a => Min a -> a #

product :: Num a => Min a -> a #

Traversable Min

Since: 4.9.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Min a -> f (Min b) #

sequenceA :: Applicative f => Min (f a) -> f (Min a) #

mapM :: Monad m => (a -> m b) -> Min a -> m (Min b) #

sequence :: Monad m => Min (m a) -> m (Min a) #

ToJSON1 Min 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Min a -> Value #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Min a] -> Value #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Min a -> Encoding #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Min a] -> Encoding #

FromJSON1 Min 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Min a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Min a] #

Bounded a => Bounded (Min a) 

Methods

minBound :: Min a #

maxBound :: Min a #

Enum a => Enum (Min a)

Since: 4.9.0.0

Methods

succ :: Min a -> Min a #

pred :: Min a -> Min a #

toEnum :: Int -> Min a #

fromEnum :: Min a -> Int #

enumFrom :: Min a -> [Min a] #

enumFromThen :: Min a -> Min a -> [Min a] #

enumFromTo :: Min a -> Min a -> [Min a] #

enumFromThenTo :: Min a -> Min a -> Min a -> [Min a] #

Eq a => Eq (Min a) 

Methods

(==) :: Min a -> Min a -> Bool #

(/=) :: Min a -> Min a -> Bool #

Data a => Data (Min a) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Min a -> c (Min a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Min a) #

toConstr :: Min a -> Constr #

dataTypeOf :: Min a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Min a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Min a)) #

gmapT :: (forall b. Data b => b -> b) -> Min a -> Min a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Min a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Min a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Min a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Min a -> m (Min a) #

Num a => Num (Min a)

Since: 4.9.0.0

Methods

(+) :: Min a -> Min a -> Min a #

(-) :: Min a -> Min a -> Min a #

(*) :: Min a -> Min a -> Min a #

negate :: Min a -> Min a #

abs :: Min a -> Min a #

signum :: Min a -> Min a #

fromInteger :: Integer -> Min a #

Ord a => Ord (Min a) 

Methods

compare :: Min a -> Min a -> Ordering #

(<) :: Min a -> Min a -> Bool #

(<=) :: Min a -> Min a -> Bool #

(>) :: Min a -> Min a -> Bool #

(>=) :: Min a -> Min a -> Bool #

max :: Min a -> Min a -> Min a #

min :: Min a -> Min a -> Min a #

Read a => Read (Min a) 
Show a => Show (Min a) 

Methods

showsPrec :: Int -> Min a -> ShowS #

show :: Min a -> String #

showList :: [Min a] -> ShowS #

Generic (Min a) 

Associated Types

type Rep (Min a) :: * -> * #

Methods

from :: Min a -> Rep (Min a) x #

to :: Rep (Min a) x -> Min a #

Ord a => Semigroup (Min a)

Since: 4.9.0.0

Methods

(<>) :: Min a -> Min a -> Min a #

sconcat :: NonEmpty (Min a) -> Min a #

stimes :: Integral b => b -> Min a -> Min a #

(Ord a, Bounded a) => Monoid (Min a)

Since: 4.9.0.0

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

ToJSON a => ToJSON (Min a) 

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

FromJSON a => FromJSON (Min a) 

Methods

parseJSON :: Value -> Parser (Min a) #

parseJSONList :: Value -> Parser [Min a] #

Wrapped (Min a) 

Associated Types

type Unwrapped (Min a) :: * #

Methods

_Wrapped' :: Iso' (Min a) (Unwrapped (Min a)) #

Ord a => AggregatableBase (Min (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Min (DbExp f a)) :: * Source #

Generic1 * Min 

Associated Types

type Rep1 Min (f :: Min -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Min f a #

to1 :: Rep1 Min f a -> f a #

(~) * t (Min b) => Rewrapped (Min a) t 
type Rep (Min a) 
type Rep (Min a) = D1 * (MetaData "Min" "Data.Semigroup" "base" True) (C1 * (MetaCons "Min" PrefixI True) (S1 * (MetaSel (Just Symbol "getMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))
type Unwrapped (Min a) 
type Unwrapped (Min a) = a
type AggregationBaseResult (Min (DbExp f a)) Source # 
type Rep1 * Min 
type Rep1 * Min = D1 * (MetaData "Min" "Data.Semigroup" "base" True) (C1 * (MetaCons "Min" PrefixI True) (S1 * (MetaSel (Just Symbol "getMin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype Sum a :: * -> * #

Monoid under addition.

Constructors

Sum 

Fields

Instances

Monad Sum

Since: 4.8.0.0

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

(>>) :: Sum a -> Sum b -> Sum b #

return :: a -> Sum a #

fail :: String -> Sum a #

Functor Sum

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Applicative Sum

Since: 4.8.0.0

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Foldable Sum

Since: 4.8.0.0

Methods

fold :: Monoid m => Sum m -> m #

foldMap :: Monoid m => (a -> m) -> Sum a -> m #

foldr :: (a -> b -> b) -> b -> Sum a -> b #

foldr' :: (a -> b -> b) -> b -> Sum a -> b #

foldl :: (b -> a -> b) -> b -> Sum a -> b #

foldl' :: (b -> a -> b) -> b -> Sum a -> b #

foldr1 :: (a -> a -> a) -> Sum a -> a #

foldl1 :: (a -> a -> a) -> Sum a -> a #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

elem :: Eq a => a -> Sum a -> Bool #

maximum :: Ord a => Sum a -> a #

minimum :: Ord a => Sum a -> a #

sum :: Num a => Sum a -> a #

product :: Num a => Sum a -> a #

Traversable Sum

Since: 4.8.0.0

Methods

traverse :: Applicative f => (a -> f b) -> Sum a -> f (Sum b) #

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) #

mapM :: Monad m => (a -> m b) -> Sum a -> m (Sum b) #

sequence :: Monad m => Sum (m a) -> m (Sum a) #

Representable Sum 

Associated Types

type Rep (Sum :: * -> *) :: * #

Methods

tabulate :: (Rep Sum -> a) -> Sum a #

index :: Sum a -> Rep Sum -> a #

Bounded a => Bounded (Sum a) 

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a) 

Methods

(==) :: Sum a -> Sum a -> Bool #

(/=) :: Sum a -> Sum a -> Bool #

Data a => Data (Sum a)

Since: 4.8.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Sum a -> c (Sum a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Sum a) #

toConstr :: Sum a -> Constr #

dataTypeOf :: Sum a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Sum a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Sum a)) #

gmapT :: (forall b. Data b => b -> b) -> Sum a -> Sum a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Sum a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Sum a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Sum a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Sum a -> m (Sum a) #

Num a => Num (Sum a) 

Methods

(+) :: Sum a -> Sum a -> Sum a #

(-) :: Sum a -> Sum a -> Sum a #

(*) :: Sum a -> Sum a -> Sum a #

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Ord a => Ord (Sum a) 

Methods

compare :: Sum a -> Sum a -> Ordering #

(<) :: Sum a -> Sum a -> Bool #

(<=) :: Sum a -> Sum a -> Bool #

(>) :: Sum a -> Sum a -> Bool #

(>=) :: Sum a -> Sum a -> Bool #

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Read a => Read (Sum a) 
Show a => Show (Sum a) 

Methods

showsPrec :: Int -> Sum a -> ShowS #

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a) 

Associated Types

type Rep (Sum a) :: * -> * #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Num a => Semigroup (Sum a)

Since: 4.9.0.0

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Monoid (Sum a)

Since: 2.1

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Wrapped (Sum a) 

Associated Types

type Unwrapped (Sum a) :: * #

Methods

_Wrapped' :: Iso' (Sum a) (Unwrapped (Sum a)) #

Num a => AggregatableBase (Sum (DbExp f a)) Source # 

Associated Types

type AggregationBaseResult (Sum (DbExp f a)) :: * Source #

Generic1 * Sum 

Associated Types

type Rep1 Sum (f :: Sum -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 Sum f a #

to1 :: Rep1 Sum f a -> f a #

(~) * t (Sum b) => Rewrapped (Sum a) t 
type Rep Sum 
type Rep Sum = ()
type Rep (Sum a) 
type Rep (Sum a) = D1 * (MetaData "Sum" "Data.Monoid" "base" True) (C1 * (MetaCons "Sum" PrefixI True) (S1 * (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))
type Unwrapped (Sum a) 
type Unwrapped (Sum a) = a
type AggregationBaseResult (Sum (DbExp f a)) Source # 
type Rep1 * Sum 
type Rep1 * Sum = D1 * (MetaData "Sum" "Data.Monoid" "base" True) (C1 * (MetaCons "Sum" PrefixI True) (S1 * (MetaSel (Just Symbol "getSum") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))