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.Common

Documentation

class LiftedStatement fs t res where Source #

Minimal complete definition

liftDbExp

Methods

liftDbExp :: DbStatement fs t -> res Source #

Instances

((~) * res [DbResult ts], AllHaveFromRowInstance ts, MonadEffect Basic m) => LiftedStatement fs ts (m res) Source # 

Methods

liftDbExp :: DbStatement fs ts -> m res Source #

((~) ([*] -> *) (DbStatement fs) dbs, (~) [*] ts1 ts2) => LiftedStatement fs ts1 (dbs ts2) Source # 

Methods

liftDbExp :: DbStatement fs ts1 -> dbs ts2 Source #

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

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

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

type AllRows table res = (Table table, LiftedStatement Unfiltered '[table] res) Source #

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

allRowsProxy :: forall table res proxy. (Table table, LiftedStatement Unfiltered '[table] res) => proxy table -> res Source #

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

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

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

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

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

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

dmapAll :: (Mappable map, CanMap f, TableSetVars Mapping tables) => (Variables Mapping tables -> map) -> DbStatement f tables -> DbStatement Mapped '[MapResult map] Source #

class Dmap' t where Source #

Minimal complete definition

dmap'

Methods

dmap' :: t Source #

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 #

(GroupMappable map, (~) Bool (InterpretAsGroupMap map) True, (~) [*] t3 ((:) * (GroupMapResult map) ([] *)), (~) (ResultType -> [*] -> *) t2 DbStatement, (~) (* -> *) t1 ((->) LiftedRep LiftedRep (GroupStatement group tables)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep ((AsAggregate group, DbStatement Grouped tables) -> map))) => Dmap' (t0 (t1 (t2 Folded t3))) Source # 

Methods

dmap' :: t0 (t1 (t2 Folded t3)) Source #

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

(Mappable map, CanMap f, TableSetVars Mapping tables, (~) [*] t3 ((:) * (MapResult map) ([] *)), (~) (ResultType -> [*] -> *) t2 DbStatement, (~) (* -> *) t1 ((->) LiftedRep LiftedRep (DbStatement f tables)), (~) (* -> *) t0 ((->) LiftedRep LiftedRep (ListToTuple * (Var Mapping) tables -> map))) => Dmap' (t0 (t1 (t2 Mapped t3))) Source # 

Methods

dmap' :: t0 (t1 (t2 Mapped t3)) Source #

class LiftedMapStatement fs t res where Source #

Minimal complete definition

liftMapStatement

Methods

liftMapStatement :: DbStatement fs '[t] -> res Source #

Instances

((~) * res [WithoutOnly ts], MonadEffect Basic m, FromRow ts, NoOnly ts) => LiftedMapStatement fs ts (m res) Source # 

Methods

liftMapStatement :: DbStatement fs ((* ': ts) [*]) -> m res Source #

((~) ([*] -> *) (DbStatement fs) dbs, (~) [*] ((:) * ts1 ([] *)) ts2) => LiftedMapStatement fs ts1 (dbs ts2) Source # 

Methods

liftMapStatement :: DbStatement fs ((* ': ts1) [*]) -> dbs ts2 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 #

class interpretAsGroupMap ~ InterpretAsGroupMap res => LiftedAggregation (interpretAsGroupMap :: Bool) aggr res where Source #

Minimal complete definition

liftAggregation

Instances

((~) * (GroupMappableThing (AggregationResult aggr) AM) aggStat, Aggregatable aggr, (~) Bool (InterpretAsGroupMap aggStat) True) => LiftedAggregation True aggr aggStat Source # 

Methods

liftAggregation :: AggregateStatement aggr AM -> aggStat Source #

((~) * res (AggregationResult aggr), MonadEffect Basic m, FromRow res, (~) Bool (InterpretAsGroupMap (m res)) i) => LiftedAggregation i aggr (m res) Source # 

Methods

liftAggregation :: AggregateStatement aggr AM -> m res Source #

((~) (AM -> *) (GroupMappableThing (AggregationResult aggr)) aggStat, (~) AM m AM, Aggregatable aggr, (~) Bool (InterpretAsGroupMap (aggStat m)) i) => LiftedAggregation i aggr (aggStat m) Source # 

Methods

liftAggregation :: AggregateStatement aggr AM -> aggStat m 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 #

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

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