| Portability | unknown |
|---|---|
| Stability | experimental |
| Maintainer | ex8k.hibino@gmail.com |
| Safe Haskell | None |
Database.Relational.Query.Documentation
Description
This module is documentation module for relational record.
- query :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat r)
- queryMaybe :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat (Maybe r))
- on :: MonadQuery m => Projection Flat (Maybe Bool) -> m ()
- wheres :: MonadRestrict Flat m => Projection Flat (Maybe Bool) -> m ()
- groupBy :: MonadAggregate m => Projection Flat r -> m (Projection Aggregated r)
- having :: MonadRestrict Aggregated m => Projection Aggregated (Maybe Bool) -> m ()
- inner :: Relation () a -> Relation () b -> [JoinRestriction a b] -> Relation () (a, b)
- left :: Relation () a -> Relation () b -> [JoinRestriction a (Maybe b)] -> Relation () (a, Maybe b)
- right :: Relation () a -> Relation () b -> [JoinRestriction (Maybe a) b] -> Relation () (Maybe a, b)
- full :: Relation () a -> Relation () b -> [JoinRestriction (Maybe a) (Maybe b)] -> Relation () (Maybe a, Maybe b)
- on' :: ([JoinRestriction a b] -> Relation pc (a, b)) -> [JoinRestriction a b] -> Relation pc (a, b)
- relation :: QuerySimple (Projection Flat r) -> Relation () r
- aggregateRelation :: QueryAggregate (Projection Aggregated r) -> Relation () r
- (.=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.<.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.<=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.>=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- (.<>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- casesOrElse :: (SqlProjectable p, ProjectableShowSql p) => [(p (Maybe Bool), p a)] -> p a -> p a
- case' :: (SqlProjectable p, ProjectableShowSql p) => p a -> [(p a, p b)] -> p b -> p b
- in' :: (SqlProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool)
- and' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- or' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
- isNothing :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)
- isJust :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)
- fromMaybe :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c r
- not' :: (SqlProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool)
- exists :: (SqlProjectable p, ProjectableShowSql p) => ListProjection (Projection Exists) r -> p (Maybe Bool)
- (.||.) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p a
- (.+.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- (.-.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- (./.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- (.*.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
- negate' :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a
- fromIntegral' :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p a -> p b
- showNum :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p a -> p b
- sum' :: (Num a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)
- avg :: (Num a, Fractional b, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe b)
- max' :: (Ord a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)
- min' :: (Ord a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)
- every :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)
- any' :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)
- some' :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)
- rank :: Projection OverWindow Int64
- denseRank :: Projection OverWindow Int64
- rowNumber :: Projection OverWindow Int64
- percentRank :: Projection OverWindow Double
- cumeDist :: Projection OverWindow Double
- union :: Relation () a -> Relation () a -> Relation () a
- except :: Relation () a -> Relation () a -> Relation () a
- intersect :: Relation () a -> Relation () a -> Relation () a
- (?+?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
- negateMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a)
- sumMaybe :: (Num a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe a) -> p ac (Maybe a)
- query' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat r)
- left' :: Relation pa a -> Relation pb b -> [JoinRestriction a (Maybe b)] -> Relation (pa, pb) (a, Maybe b)
- relation' :: QuerySimple (PlaceHolders p, Projection Flat r) -> Relation p r
- union' :: Relation p a -> Relation q a -> Relation (p, q) a
- prepareNoFetch :: (UntypeableNoFetch s, IConnection conn) => conn -> s p -> IO (PreparedStatement p ())
- bind :: ToSql SqlValue p => PreparedStatement p a -> p -> BoundStatement a
- execute :: BoundStatement a -> IO (ExecutedStatement a)
- executeNoFetch :: BoundStatement () -> IO Integer
- prepareQuery :: IConnection conn => conn -> Query p a -> IO (PreparedQuery p a)
- fetch :: FromSql SqlValue a => ExecutedStatement a -> IO (Maybe a)
- runQuery :: (IConnection conn, ToSql SqlValue p, FromSql SqlValue a) => conn -> Query p a -> p -> IO [a]
- prepareInsert :: IConnection conn => conn -> Insert a -> IO (PreparedInsert a)
- runInsert :: (IConnection conn, ToSql SqlValue a) => conn -> Insert a -> a -> IO Integer
- prepareInsertQuery :: IConnection conn => conn -> InsertQuery p -> IO (PreparedInsertQuery p)
- runInsertQuery :: (IConnection conn, ToSql SqlValue p) => conn -> InsertQuery p -> p -> IO Integer
- prepareUpdate :: IConnection conn => conn -> Update p -> IO (PreparedUpdate p)
- runUpdate :: (IConnection conn, ToSql SqlValue p) => conn -> Update p -> p -> IO Integer
- prepareDelete :: IConnection conn => conn -> Delete p -> IO (PreparedDelete p)
- runDelete :: (IConnection conn, ToSql SqlValue p) => conn -> Delete p -> p -> IO Integer
- prepareKeyUpdate :: IConnection conn => conn -> KeyUpdate p a -> IO (PreparedKeyUpdate p a)
- bindKeyUpdate :: ToSql SqlValue a => PreparedKeyUpdate p a -> a -> BoundStatement ()
- runKeyUpdate :: (IConnection conn, ToSql SqlValue a) => conn -> KeyUpdate p a -> a -> IO Integer
Concepts
User inferface of Relational Record has main two part of modules.
Database.Relational.Query- Relational Query Building DSL
Database.HDBC.Record- Database Operation Actions
Relational Query Building DSL
Relatoinal Query (Database.Relational.Query) module defines Typed DSL to build complex SQL query.
Monadic Query Context Building
This DSL accumulates query structures into monadic context.
Monadic Operators
Some operators are defined to build query structures in monadic context.
query and queryMaybe operators grow query product of monadic context like join operation of SQL.
on operator appends a new condition into recent join product condition.
groupBy operator aggregates flat projection value.
wheres and having operators appends a new condition into whole query condition.
having only accepts aggregated projection value.
query :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat r)
Join subquery. Query result is not Maybe.
queryMaybe :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat (Maybe r))
Join subquery. Query result is Maybe.
on :: MonadQuery m => Projection Flat (Maybe Bool) -> m ()
Add restriction to last join. Projection type version.
wheres :: MonadRestrict Flat m => Projection Flat (Maybe Bool) -> m ()
Add restriction to this query. Projection type version.
Arguments
| :: MonadAggregate m | |
| => Projection Flat r | Projection to add into group by |
| -> m (Projection Aggregated r) | Result context and aggregated projection |
Add GROUP BY term into context and get aggregated projection.
having :: MonadRestrict Aggregated m => Projection Aggregated (Maybe Bool) -> m ()
Add restriction to this aggregated query. Aggregated Projection type version.
Direct Join Operators
Not monadic style join is supported by some direct join operators.
inner, left, right, full operators can construct join products directly like SQL.
on' specifies condition of join product.
Arguments
| :: Relation () a | Left query to join |
| -> Relation () b | Right query to join |
| -> [JoinRestriction a b] | Join restrictions |
| -> Relation () (a, b) | Result joined relation |
Direct inner join.
Arguments
| :: Relation () a | Left query to join |
| -> Relation () b | Right query to join |
| -> [JoinRestriction a (Maybe b)] | Join restrictions |
| -> Relation () (a, Maybe b) | Result joined relation |
Direct left outer join.
Arguments
| :: Relation () a | Left query to join |
| -> Relation () b | Right query to join |
| -> [JoinRestriction (Maybe a) b] | Join restrictions |
| -> Relation () (Maybe a, b) | Result joined relation |
Direct right outer join.
Arguments
| :: Relation () a | Left query to join |
| -> Relation () b | Right query to join |
| -> [JoinRestriction (Maybe a) (Maybe b)] | Join restrictions |
| -> Relation () (Maybe a, Maybe b) | Result joined relation |
Direct full outer join.
on' :: ([JoinRestriction a b] -> Relation pc (a, b)) -> [JoinRestriction a b] -> Relation pc (a, b)
Apply restriction for direct join style.
Finalize Context
Several operators are defined to finalize query monadic context.
relation operator finalizes flat (not aggregated) query monadic context,
and aggregateRelation operator finalizes aggregated query monadic context.
relation :: QuerySimple (Projection Flat r) -> Relation () r
Finalize QuerySimple monad and generate Relation.
aggregateRelation :: QueryAggregate (Projection Aggregated r) -> Relation () r
Finalize QueryAggregate monad and geneate Relation.
Projection Operators
Some operators are defined to caluculate projections.
(.=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Compare operator corresponding SQL = .
(.<.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Compare operator corresponding SQL < .
(.<=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Compare operator corresponding SQL <= .
(.>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Compare operator corresponding SQL > .
(.>=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Compare operator corresponding SQL >= .
(.<>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Compare operator corresponding SQL <> .
Arguments
| :: (SqlProjectable p, ProjectableShowSql p) | |
| => [(p (Maybe Bool), p a)] | Each when clauses |
| -> p a | Else result projection |
| -> p a | Result projection |
Same as caseSearch, but you can write like list casesOrElse clause.
Arguments
| :: (SqlProjectable p, ProjectableShowSql p) | |
| => p a | Projection value to match |
| -> [(p a, p b)] | Each when clauses |
| -> p b | Else result projection |
| -> p b | Result projection |
Simple case operator correnponding SQL simple CASE. Like, CASE x WHEN v THEN a WHEN w THEN b ... ELSE c END
in' :: (SqlProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool)
Binary operator corresponding SQL IN .
and' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Logical operator corresponding SQL AND .
or' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)
Logical operator corresponding SQL OR .
isNothing :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)
Operator corresponding SQL IS NULL , and extended against record types.
isJust :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)
Operator corresponding SQL NOT (... IS NULL) , and extended against record type.
fromMaybe :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c r
Operator from maybe type using record extended isNull.
not' :: (SqlProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool)
Logical operator corresponding SQL NOT .
exists :: (SqlProjectable p, ProjectableShowSql p) => ListProjection (Projection Exists) r -> p (Maybe Bool)
Logical operator corresponding SQL EXISTS .
(.||.) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p a
Concatinate operator corresponding SQL || .
(.+.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
Number operator corresponding SQL + .
(.-.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
Number operator corresponding SQL - .
(./.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
Number operator corresponding SQL / .
(.*.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a
Number operator corresponding SQL * .
negate' :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a
Number negate uni-operator corresponding SQL -.
fromIntegral' :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p a -> p b
Number fromIntegral uni-operator.
showNum :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p a -> p b
Unsafely show number into string-like type in projections.
Aggregate and Window Functions
Typed aggregate operators are defined. Aggregated value types is distinguished with Flat value types.
sum' :: (Num a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)
Aggregation function SUM.
avg :: (Num a, Fractional b, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe b)
Aggregation function AVG.
max' :: (Ord a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)
Aggregation function MAX.
min' :: (Ord a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)
Aggregation function MIN.
every :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)
Aggregation function EVERY.
any' :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)
Aggregation function ANY.
some' :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)
Aggregation function SOME.
rank :: Projection OverWindow Int64
RANK() term.
denseRank :: Projection OverWindow Int64
DENSE_RANK() term.
rowNumber :: Projection OverWindow Int64
ROW_NUMBER() term.
percentRank :: Projection OverWindow Double
PERCENT_RANK() term.
cumeDist :: Projection OverWindow Double
CUME_DIST() term.
Set Operators
Several operators are defined to manipulate relation set.
Maybe Projections
Operators of projection and aggregation are also provided Maybe type versions.
(?+?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)
Number operator corresponding SQL + .
negateMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a)
Number negate uni-operator corresponding SQL -.
sumMaybe :: (Num a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe a) -> p ac (Maybe a)
Aggregation function SUM.
Placeholders
Some operators are defined to realize type safe placeholder.
query' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat r)
Join subquery with place-holder parameter p. query result is not Maybe.
Arguments
| :: Relation pa a | Left query to join |
| -> Relation pb b | Right query to join |
| -> [JoinRestriction a (Maybe b)] | Join restrictions |
| -> Relation (pa, pb) (a, Maybe b) | Result joined relation |
Direct left outer join with place-holder parameters.
relation' :: QuerySimple (PlaceHolders p, Projection Flat r) -> Relation p r
Finalize QuerySimple monad and generate Relation with place-holder parameter p.
union' :: Relation p a -> Relation q a -> Relation (p, q) a
Union of two relations with place-holder parameters.
Database Operations
Some actions are defined for database site effects.
Generalized Statement
Actions to manage generalized SQL statements.
prepareNoFetch :: (UntypeableNoFetch s, IConnection conn) => conn -> s p -> IO (PreparedStatement p ())
Generalized prepare inferred from UntypeableNoFetch instance.
bind :: ToSql SqlValue p => PreparedStatement p a -> p -> BoundStatement a
Typed operation to bind parameters. Infered RecordToSql is used.
execute :: BoundStatement a -> IO (ExecutedStatement a)
Typed execute operation.
executeNoFetch :: BoundStatement () -> IO Integer
Typed execute operation. Only get result.
Select
Actions to manage SELECT statements.
Arguments
| :: IConnection conn | |
| => conn | Database connection |
| -> Query p a | Typed query |
| -> IO (PreparedQuery p a) | Result typed prepared query with parameter type |
Same as prepare.
Arguments
| :: (IConnection conn, ToSql SqlValue p, FromSql SqlValue a) | |
| => conn | Database connection |
| -> Query p a | Query to get record type |
| -> p | Parameter type |
| -> IO [a] | Action to get records |
Prepare SQL, bind parameters, execute statement and lazily fetch all records.
Insert Values
Actions to manage INSERT ... VALUES ... statements.
prepareInsert :: IConnection conn => conn -> Insert a -> IO (PreparedInsert a)
Same as prepare.
runInsert :: (IConnection conn, ToSql SqlValue a) => conn -> Insert a -> a -> IO Integer
Prepare insert statement, bind parameters, execute statement and get execution result.
Insert Select Results
Actions to manage INSERT ... SELECT ... statements.
prepareInsertQuery :: IConnection conn => conn -> InsertQuery p -> IO (PreparedInsertQuery p)
Same as prepare.
runInsertQuery :: (IConnection conn, ToSql SqlValue p) => conn -> InsertQuery p -> p -> IO Integer
Prepare insert statement, bind parameters, execute statement and get execution result.
Update
Actions to manage UPDATE statements.
prepareUpdate :: IConnection conn => conn -> Update p -> IO (PreparedUpdate p)
Same as prepare.
runUpdate :: (IConnection conn, ToSql SqlValue p) => conn -> Update p -> p -> IO Integer
Prepare update statement, bind parameters, execute statement and get execution result.
Delete
Actions to manage DELETE statements.
prepareDelete :: IConnection conn => conn -> Delete p -> IO (PreparedDelete p)
Same as prepare.
runDelete :: (IConnection conn, ToSql SqlValue p) => conn -> Delete p -> p -> IO Integer
Prepare delete statement, bind parameters, execute statement and get execution result.
Update by Key
Actions to manage UPDATE statements which updates columns other than specified key of the records selected by specified key.
prepareKeyUpdate :: IConnection conn => conn -> KeyUpdate p a -> IO (PreparedKeyUpdate p a)
Same as prepare.
bindKeyUpdate :: ToSql SqlValue a => PreparedKeyUpdate p a -> a -> BoundStatement ()
Typed operation to bind parameters for PreparedKeyUpdate type.
runKeyUpdate :: (IConnection conn, ToSql SqlValue a) => conn -> KeyUpdate p a -> a -> IO Integer
Prepare insert statement, bind parameters, execute statement and get execution result.