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

Data.Basic

Synopsis

Documentation

data Key Source #

Instances

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 (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 AllRows table res = (Table table, LiftedStatement Unfiltered '[table] res) Source #

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 # 

type VirtualTable foreignKeyName res = (ForeignKeyConstraint foreignKeyName, AllFieldsMatch (ForeignKeyToFields foreignKeyName) (ForeignKeyFromFields foreignKeyName) (ForeignKeyTo foreignKeyName) (ForeignKeyFrom foreignKeyName), LiftedStatement Filtered '[ForeignKeyFrom foreignKeyName] res) Source #

virtualTableLens :: forall foreignKeyName c res. VirtualTable foreignKeyName res => Getter' (Entity (FromDb c) (ForeignKeyTo foreignKeyName)) res Source #

type Getter' s a = PolyOptic (Const a) s s a a Source #

class FieldOpticProxy t Source #

Minimal complete definition

fieldOpticProxy

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 (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, 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 #

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

fieldOptic :: forall name o. FieldOpticProxy (Proxy name -> o) => o Source #

class ForeignKeyLensProxy t Source #

Minimal complete definition

foreignKeyLensProxy

Instances

((ForeignKeyConstraint fk, ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t4 (Entity entKind (ForeignKeyFrom fk) -> Identity (Entity (WithFieldsSet (ForeignKeyFromFields fk) entKind) (ForeignKeyFrom fk))), (~) * t3 (Entity (FromDb c) (ForeignKeyTo fk)), (~) (* -> *) t2 ((->) LiftedRep LiftedRep ()), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (Identity t3)) t4)) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (Identity t3)) t4) Source #

((ForeignKeyConstraint fk, ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t3 (Entity (WithFieldsSet (ForeignKeyFromFields fk) entKind) (ForeignKeyFrom fk)), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity entKind (ForeignKeyFrom fk))), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (() -> Identity (Entity (FromDb c) (ForeignKeyTo fk)))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (Identity t3)))) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (Identity t3))) Source #

((ForeignKeyConstraint fk, MonadEffect Basic m, Table (ForeignKeyFrom fk), Table (ForeignKeyTo fk), ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t6 (Entity (FromDb Live) (ForeignKeyFrom fk) -> Const * (m (Entity (FromDb Live) (ForeignKeyTo fk))) (Entity (FromDb Live) (ForeignKeyFrom fk))), (~) * t5 (m (Entity (FromDb Live) (ForeignKeyTo fk))), (~) * t4 (m (Entity (FromDb Live) (ForeignKeyTo fk))), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (m (Entity (FromDb Live) (ForeignKeyTo fk)))), (~) (* -> * -> *) t1 ((->) LiftedRep LiftedRep), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (t3 t4 t5)) t6)) Source # 

Methods

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

((ForeignKeyConstraint fk, MonadEffect Basic m, Table (ForeignKeyFrom fk), Table (ForeignKeyTo fk), ForeignKeyFieldsMatch fk (ForeignKeyFromFields fk) (ForeignKeyToFields fk)), (~) * t5 (Entity (FromDb Live) (ForeignKeyFrom fk)), (~) * t4 (m (Entity (FromDb Live) (ForeignKeyTo fk))), (~) (* -> * -> *) t3 (Const *), (~) (* -> *) t2 ((->) LiftedRep LiftedRep (Entity (FromDb Live) (ForeignKeyFrom fk))), (~) (* -> *) t1 ((->) LiftedRep LiftedRep (m (Entity (FromDb Live) (ForeignKeyTo fk)) -> Const * (m (Entity (FromDb Live) (ForeignKeyTo fk))) (m (Entity (FromDb Live) (ForeignKeyTo fk))))), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (proxy fk))) => ForeignKeyLensProxy (t0 (t1 (t2 (t3 t4 t5)))) Source # 

Methods

foreignKeyLensProxy :: t0 (t1 (t2 (t3 t4 t5))) Source #

foreignKeyLens :: forall name o. ForeignKeyLensProxy (Proxy name -> o) => o Source #

class (Effect e, Monad m) => MonadEffect e (m :: * -> *) #

Minimal complete definition

effect

Instances

(MonadEffect e m, Monad (t m), CanLift e t) => MonadEffect e (t m) 

Methods

effect :: EffMethods e (t m) #

(Effect e, Monad m, CanLift e (RuntimeImplemented e)) => MonadEffect e (RuntimeImplemented e m) 
(Monad m, (~) * a b) => MonadEffect (Early a) (ExceptT (EarlyValue b) m) 

Methods

effect :: EffMethods (Early a) (ExceptT (EarlyValue b) m) #

Monad m => MonadEffect (HandleException e) (ExceptT e m) 
Monad m => MonadEffect (State s) (StateT s m) 

Methods

effect :: EffMethods (State s) (StateT s m) #

TypeError Constraint (UnhandledError a b) => MonadEffect (Signal a b) IO 

Methods

effect :: EffMethods (Signal a b) IO #

Monad m => MonadEffect (Signal a b) (MaybeT m) 

Methods

effect :: EffMethods (Signal a b) (MaybeT m) #

(Monad m, (~) * b c) => MonadEffect (Signal a c) (RuntimeImplemented (Signal a b) m) 
(Show e, Monad m) => MonadEffect (Signal e b) (ExceptT SomeSignal m) 
Monad m => MonadEffect (Signal e b) (ExceptT e m) 

Methods

effect :: EffMethods (Signal e b) (ExceptT e m) #

data Basic Source #

Instances

Effect Basic Source # 

Associated Types

data EffMethods Basic (m :: * -> *) :: * #

type CanLift Basic (t :: (* -> *) -> * -> *) :: Constraint #

data EffMethods Basic Source # 
data EffMethods Basic = BasicMethods {}
type CanLift Basic t Source # 

allRows :: forall tableName table res. (TableName table ~ tableName, AllRows table res) => res Source #

ddelete :: (LiftedStatement Deleted '[table] res, Selection f, Table table) => DbStatement f '[table] -> res Source #

dupdate :: (MonadEffect Basic m, FromRow table, Selection f) => (Var Updating table -> UpdateExp fields table) -> DbStatement f '[table] -> m [Entity (FromDb Live) table] Source #

insert :: (CanInsert entKind table, MonadEffect Basic m, FromRow table) => Entity entKind table -> m (Entity (FromDb Live) table) Source #

dfilter :: (LiftedStatement Filtered tables res, TableSetVars Filtering tables, Selection f) => (Variables Filtering tables -> ConditionExp) -> DbStatement f tables -> res Source #

save :: forall table pk fields c m. (Table table, Just pk ~ TablePrimaryKey table, fields ~ UniqueFields pk, PrimaryKeyMatch fields table, SetAllFields (TableFields table) table, MonadEffect Basic m) => Entity (FromDb c) table -> m (Entity (FromDb Live) table) Source #

dtake :: (LiftedStatement Limited tables res, CanTake f) => Int -> DbStatement f tables -> res Source #

djoin :: LiftedStatement Unfiltered (tables1 ++ tables2) res => DbStatement Unfiltered tables1 -> DbStatement Unfiltered tables2 -> res Source #

dsortOn :: (LiftedStatement Sorted tables res, TableSetVars Sorting tables, Sortable ord, Selection f) => (Variables Sorting tables -> ord) -> DbStatement f tables -> res Source #

dfoldMap :: forall tables aggr f res. (Aggregatable aggr, CanAggregate f, TableSetVars Folding tables, LiftedAggregation (InterpretAsGroupMap res) aggr res) => (Variables Folding tables -> aggr) -> DbStatement f tables -> res Source #

dmap :: forall f res a b m (ts :: [*]) t. (Dmap' ((a -> b) -> m ts -> DbStatement f '[t]), LiftedMapStatement f t res) => (a -> b) -> m ts -> res Source #

dgroupOn :: (Groupable group, TableSetVars Grouping tables, Selection f) => (Variables Grouping tables -> group) -> DbStatement f tables -> GroupStatement group tables Source #

rawQuery :: forall a r m. (MonadEffect Basic m, FromRow a, ToRow r) => Text -> r -> m [Entity (FromDb Live) a] Source #

(<.) :: ComparableInDbExp a b => a -> b -> ConditionExp infix 4 Source #

(>.) :: ComparableInDbExp a b => a -> b -> ConditionExp infix 4 Source #

(==.) :: ComparableInDbExp a b => a -> b -> ConditionExp infix 4 Source #

(/=.) :: ComparableInDbExp a b => a -> b -> ConditionExp infix 4 Source #

(<=.) :: ComparableInDbExp a b => a -> b -> ConditionExp infix 4 Source #

(>=.) :: ComparableInDbExp a b => a -> b -> ConditionExp infix 4 Source #

data ConditionExp where Source #

Constructors

In :: LiteralCollection collection a => DbExp k a -> collection -> ConditionExp 

newtype Avg a Source #

Constructors

Avg a 

Instances

newtype Count a Source #

Constructors

Count a 

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 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 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))

newtype PGArray a :: * -> * #

Wrap a list for use as a PostgreSQL array.

Constructors

PGArray 

Fields

Instances

Functor PGArray 

Methods

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

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

Eq a => Eq (PGArray a) 

Methods

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

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

Ord a => Ord (PGArray a) 

Methods

compare :: PGArray a -> PGArray a -> Ordering #

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

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

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

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

max :: PGArray a -> PGArray a -> PGArray a #

min :: PGArray a -> PGArray a -> PGArray a #

Read a => Read (PGArray a) 
Show a => Show (PGArray a) 

Methods

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

show :: PGArray a -> String #

showList :: [PGArray a] -> ShowS #

(FromField a, Typeable * a) => FromField (PGArray a)

any postgresql array whose elements are compatible with type a

ToField a => ToField (PGArray a) 

Methods

toField :: PGArray a -> Action #

handleBasicPsql :: MonadIO m => Connection -> RuntimeImplemented Basic (RuntimeImplemented Logging (ExceptT BasicException m)) a -> m a Source #

Handles SQL by querying a PostgreSQL database. Writes logs to console.

connectPostgreSQL :: ByteString -> IO Connection #

Attempt to make a connection based on a libpq connection string. See https://www.postgresql.org/docs/9.5/static/libpq-connect.html#LIBPQ-CONNSTRING for more information. Also note that environment variables also affect parameters not provided, parameters provided as the empty string, and a few other things; see https://www.postgresql.org/docs/9.5/static/libpq-envars.html for details. Here is an example with some of the most commonly used parameters:

host='db.somedomain.com' port=5432 ...

This attempts to connect to db.somedomain.com:5432. Omitting the port will normally default to 5432.

On systems that provide unix domain sockets, omitting the host parameter will cause libpq to attempt to connect via unix domain sockets. The default filesystem path to the socket is constructed from the port number and the DEFAULT_PGSOCKET_DIR constant defined in the pg_config_manual.h header file. Connecting via unix sockets tends to use the peer authentication method, which is very secure and does not require a password.

On Windows and other systems without unix domain sockets, omitting the host will default to localhost.

... dbname='postgres' user='postgres' password='secret \' \\ pw'

This attempts to connect to a database named postgres with user postgres and password secret ' \ pw. Backslash characters will have to be double-quoted in literal Haskell strings, of course. Omitting dbname and user will both default to the system username that the client process is running as.

Omitting password will default to an appropriate password found in the pgpass file, or no password at all if a matching line is not found. See https://www.postgresql.org/docs/9.5/static/libpq-pgpass.html for more information regarding this file.

As all parameters are optional and the defaults are sensible, the empty connection string can be useful for development and exploratory use, assuming your system is set up appropriately.

On Unix, such a setup would typically consist of a local postgresql server listening on port 5432, as well as a system user, database user, and database sharing a common name, with permissions granted to the user on the database.

On Windows, in addition you will either need pg_hba.conf to specify the use of the trust authentication method for the connection, which may not be appropriate for multiuser or production machines, or you will need to use a pgpass file with the password or md5 authentication methods.

See https://www.postgresql.org/docs/9.5/static/client-authentication.html for more information regarding the authentication process.

SSL/TLS will typically "just work" if your postgresql server supports or requires it. However, note that libpq is trivially vulnerable to a MITM attack without setting additional SSL connection parameters. In particular, sslmode needs to be set to require, verify-ca, or verify-full in order to perform certificate validation. When sslmode is require, then you will also need to specify a sslrootcert file, otherwise no validation of the server's identity will be performed. Client authentication via certificates is also possible via the sslcert and sslkey parameters. See https://www.postgresql.org/docs/9.5/static/libpq-ssl.html for detailed information regarding libpq and SSL.

handleBasicPsqlWithLogging :: forall m a. (MonadEffects '[Logging, Signal BasicException Query] m, MonadIO m) => Connection -> RuntimeImplemented Basic m a -> m a Source #

Handles SQL by querying a PostgreSQL database. Leaves logs unhandled.

throwBasicToIO :: forall m a. MonadIO m => ExceptT BasicException m a -> m a Source #

prettyPrintSummary :: MonadIO m => Int -> RuntimeImplemented Logging m a -> m a #

Print out the logs in rich format. Truncates at the given length. Logs will contain: message, timestamp, data, user and the call stack.

mkFromFile :: FilePath -> Q [Dec] Source #

Generates haskell code from an SQL file.

mkFromFiles :: [FilePath] -> Q [Dec] Source #

Generates haskell code from multiple SQL files.

printToFile :: [FilePath] -> FilePath -> Q [Dec] Source #

Allows you to print generated template haskell code to a file

class FromRow a where #

A collection type that can be converted from a sequence of fields. Instances are provided for tuples up to 10 elements and lists of any length.

Note that instances can be defined outside of postgresql-simple, which is often useful. For example, here's an instance for a user-defined pair:

data User = User { name :: String, fileQuota :: Int }

instance FromRow User where
    fromRow = User <$> field <*> field

The number of calls to field must match the number of fields returned in a single row of the query result. Otherwise, a ConversionFailed exception will be thrown.

Note that field evaluates its result to WHNF, so the caveats listed in mysql-simple and very early versions of postgresql-simple no longer apply. Instead, look at the caveats associated with user-defined implementations of fromField.

Methods

fromRow :: RowParser a #

Instances

FromRow User # 
FromRow Post # 
FromField a => FromRow [a] 

Methods

fromRow :: RowParser [a] #

FromField a => FromRow (Maybe [a]) 

Methods

fromRow :: RowParser (Maybe [a]) #

(FromField a, FromField b) => FromRow (Maybe (a, b)) 

Methods

fromRow :: RowParser (Maybe (a, b)) #

(FromField a, FromField b, FromField c) => FromRow (Maybe (a, b, c)) 

Methods

fromRow :: RowParser (Maybe (a, b, c)) #

(FromField a, FromField b, FromField c, FromField d) => FromRow (Maybe (a, b, c, d)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d)) #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (Maybe (a, b, c, d, e)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (Maybe (a, b, c, d, e, f)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (Maybe (a, b, c, d, e, f, g)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (Maybe (a, b, c, d, e, f, g, h)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (Maybe (a, b, c, d, e, f, g, h, i)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i)) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (Maybe (a, b, c, d, e, f, g, h, i, j)) 

Methods

fromRow :: RowParser (Maybe (a, b, c, d, e, f, g, h, i, j)) #

FromField a => FromRow (Maybe (Vector a)) 

Methods

fromRow :: RowParser (Maybe (Vector a)) #

FromField a => FromRow (Maybe (Only a)) 

Methods

fromRow :: RowParser (Maybe (Only a)) #

FromField a => FromRow (Vector a) 

Methods

fromRow :: RowParser (Vector a) #

FromField a => FromRow (Only a) 

Methods

fromRow :: RowParser (Only a) #

(FromField a, FromField b) => FromRow (a, b) 

Methods

fromRow :: RowParser (a, b) #

(FromRow a, FromRow b) => FromRow ((:.) a b) 

Methods

fromRow :: RowParser (a :. b) #

FromRow a => FromRow (Entity l a) # 

Methods

fromRow :: RowParser (Entity l a) #

(FromField a, FromField b, FromField c) => FromRow (a, b, c) 

Methods

fromRow :: RowParser (a, b, c) #

(FromField a, FromField b, FromField c, FromField d) => FromRow (a, b, c, d) 

Methods

fromRow :: RowParser (a, b, c, d) #

(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (a, b, c, d, e) 

Methods

fromRow :: RowParser (a, b, c, d, e) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (a, b, c, d, e, f) 

Methods

fromRow :: RowParser (a, b, c, d, e, f) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (a, b, c, d, e, f, g) 

Methods

fromRow :: RowParser (a, b, c, d, e, f, g) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (a, b, c, d, e, f, g, h) 

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (a, b, c, d, e, f, g, h, i) 

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i) #

(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (a, b, c, d, e, f, g, h, i, j) 

Methods

fromRow :: RowParser (a, b, c, d, e, f, g, h, i, j) #

data Cached Source #

Constructors

Live 
Cached 

delem :: LiteralCollection collection a => DbExp k a -> collection -> ConditionExp Source #

type GettableField entKind field = FieldIsGettable field (MissingFields entKind) Source #

type ModifyableField table entKind field = SupportedModifyAccess (FieldIsGettableBool field (MissingFields entKind)) (TableFieldType table field) Source #

A field that's settable, but also potentially gettable (if it's already set). If it is gettable then you can modify it, otherwise you can just set it.

type SettableField table entKind field = ModifyableField table entKind field Source #

A synonym for ModifyableField. It still checks if the field is already set.

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) 

executeQuery :: (ToRow r, MonadEffect Basic m) => Text -> r -> m () Source #

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