Copyright | 2015-2017 Kei Hibino |
---|---|
License | BSD3 |
Maintainer | ex8k.hibino@gmail.com |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
This module defines arrow version combinators which improves type-safty on building queries. Referencing the local projections may cause to break the result query. It is possible to controls injection of previous local projections by restricting domain type of arrow. This idea is imported from Opaleye:
- https://github.com/tomjaguarpaw/haskell-opaleye
- https://github.com/khibino/haskell-relational-record/issues/19
Importing this module instead of Database.Relational.Query enables to build query using arrow combinators.
- module Database.Relational.Query
- all' :: MonadQuery m => QueryA m () ()
- distinct :: MonadQuery m => QueryA m () ()
- query :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> QueryA m () (Projection Flat r)
- queryMaybe :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> QueryA m () (Projection Flat (Maybe r))
- query' :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation p r -> QueryA m () (PlaceHolders p, Projection Flat r)
- queryMaybe' :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation p r -> QueryA m () (PlaceHolders p, Projection Flat (Maybe r))
- queryList :: MonadQualify ConfigureQuery m => (Projection c a -> Relation () r) -> QueryA m (Projection c a) (ListProjection (Projection c) r)
- queryList' :: MonadQualify ConfigureQuery m => (Projection c a -> Relation p r) -> QueryA m (Projection c a) (PlaceHolders p, ListProjection (Projection c) r)
- queryExists :: MonadQualify ConfigureQuery m => (Projection c a -> Relation () r) -> QueryA m (Projection c a) (ListProjection (Projection Exists) r)
- queryExists' :: MonadQualify ConfigureQuery m => (Projection c a -> Relation p r) -> QueryA m (Projection c a) (PlaceHolders p, ListProjection (Projection Exists) r)
- queryListU :: MonadQualify ConfigureQuery m => Relation () r -> QueryA m () (ListProjection (Projection c) r)
- queryListU' :: MonadQualify ConfigureQuery m => Relation p r -> QueryA m () (PlaceHolders p, ListProjection (Projection c) r)
- queryScalar :: (MonadQualify ConfigureQuery m, ScalarDegree r) => (Projection c a -> UniqueRelation () c r) -> QueryA m (Projection c a) (Projection c (Maybe r))
- queryScalar' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => (Projection c a -> UniqueRelation p c r) -> QueryA m (Projection c a) (PlaceHolders p, Projection c (Maybe r))
- queryScalarU :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation () c r -> QueryA m () (Projection c (Maybe r))
- queryScalarU' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation p c r -> QueryA m () (PlaceHolders p, Projection c (Maybe r))
- uniqueQuery' :: UniqueRelation p c r -> QueryA QueryUnique () (PlaceHolders p, Projection c r)
- uniqueQueryMaybe' :: UniqueRelation p c r -> QueryA QueryUnique () (PlaceHolders p, Projection c (Maybe r))
- on :: MonadQuery m => QueryA m (Projection Flat (Maybe Bool)) ()
- wheres :: MonadRestrict Flat m => QueryA m (Projection Flat (Maybe Bool)) ()
- having :: MonadRestrict Aggregated m => QueryA m (Projection Aggregated (Maybe Bool)) ()
- groupBy :: MonadAggregate m => QueryA m (Projection Flat r) (Projection Aggregated r)
- placeholder :: (PersistableWidth t, SqlProjectable p, Monad m) => QueryA m (QueryA m (p t) a) (PlaceHolders t, a)
- relation :: QuerySimple () (Projection Flat r) -> Relation () r
- relation' :: QuerySimple () (PlaceHolders p, Projection Flat r) -> Relation p r
- aggregateRelation :: QueryAggregate () (Projection Aggregated r) -> Relation () r
- aggregateRelation' :: QueryAggregate () (PlaceHolders p, Projection Aggregated r) -> Relation p r
- uniqueRelation' :: QueryUnique () (PlaceHolders p, Projection c r) -> UniqueRelation p c r
- groupBy' :: MonadAggregate m => QueryA m (AggregateKey (Projection Aggregated r)) (Projection Aggregated r)
- key :: AggregatingSet (Projection Flat r) (Projection Aggregated (Maybe r))
- key' :: AggregatingSet (AggregateKey a) a
- set :: AggregatingSetList (AggregatingSet () a) a
- bkey :: AggregatingPowerSet (Projection Flat r) (Projection Aggregated (Maybe r))
- rollup :: AggregatingPowerSet () a -> AggregateKey a
- cube :: AggregatingPowerSet () a -> AggregateKey a
- groupingSets :: AggregatingSetList () a -> AggregateKey a
- orderBy :: Monad m => Order -> Orderings c m (Projection c t) ()
- asc :: Monad m => Orderings c m (Projection c t) ()
- desc :: Monad m => Orderings c m (Projection c t) ()
- partitionBy :: Window c (Projection c r) ()
- over :: SqlProjectable (Projection c) => Projection OverWindow a -> Window c () () -> Projection c a
- assign :: Monad m => AssignTarget r v -> Assignings r m (Projection Flat v) ()
- derivedUpdate' :: TableDerivable r => Config -> AssignStatement r (PlaceHolders p) -> Update p
- derivedUpdate :: TableDerivable r => AssignStatement r (PlaceHolders p) -> Update p
- derivedDelete' :: TableDerivable r => Config -> RestrictedStatement r (PlaceHolders p) -> Delete p
- derivedDelete :: TableDerivable r => RestrictedStatement r (PlaceHolders p) -> Delete p
- data QueryA m a b
- type QuerySimple = QueryA QuerySimple
- type QueryAggregate = QueryA QueryAggregate
- type QueryUnique = QueryA QueryUnique
- type AggregatingSet = QueryA AggregatingSet
- type AggregatingSetList = QueryA AggregatingSetList
- type AggregatingPowerSet = QueryA AggregatingPowerSet
- type Orderings c m = QueryA (Orderings c m)
- type Window c = QueryA (Window c)
- type Assignings r m = QueryA (Assignings r m)
- type AssignStatement r a = Assignings r Restrict (Projection Flat r) a
- type RestrictedStatement r a = QueryA Restrict (Projection Flat r) a
Documentation
module Database.Relational.Query
query :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> QueryA m () (Projection Flat r) Source #
Same as query
. Arrow version.
The result arrow is not injected by local projections.
queryMaybe :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> QueryA m () (Projection Flat (Maybe r)) Source #
Same as queryMaybe
. Arrow version.
The result arrow is not injected by any local projections.
query' :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation p r -> QueryA m () (PlaceHolders p, Projection Flat r) Source #
Same as query'
. Arrow version.
The result arrow is not injected by any local projections.
queryMaybe' :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation p r -> QueryA m () (PlaceHolders p, Projection Flat (Maybe r)) Source #
Same as queryMaybe'
. Arrow version.
The result arrow is not injected by any local projections.
queryList :: MonadQualify ConfigureQuery m => (Projection c a -> Relation () r) -> QueryA m (Projection c a) (ListProjection (Projection c) r) Source #
Same as queryList
. Arrow version.
The result arrow is designed to be injected by local projections.
queryList' :: MonadQualify ConfigureQuery m => (Projection c a -> Relation p r) -> QueryA m (Projection c a) (PlaceHolders p, ListProjection (Projection c) r) Source #
Same as queryList'
. Arrow version.
The result arrow is designed to be injected by local projections.
queryExists :: MonadQualify ConfigureQuery m => (Projection c a -> Relation () r) -> QueryA m (Projection c a) (ListProjection (Projection Exists) r) Source #
queryExists' :: MonadQualify ConfigureQuery m => (Projection c a -> Relation p r) -> QueryA m (Projection c a) (PlaceHolders p, ListProjection (Projection Exists) r) Source #
Same as queryList'
to pass this result to exists
operator. Arrow version.
The result arrow is designed to be injected by local projections.
queryListU :: MonadQualify ConfigureQuery m => Relation () r -> QueryA m () (ListProjection (Projection c) r) Source #
Same as queryList
. Arrow version.
Useful for no reference cases to local projections.
queryListU' :: MonadQualify ConfigureQuery m => Relation p r -> QueryA m () (PlaceHolders p, ListProjection (Projection c) r) Source #
Same as queryList'
. Arrow version.
Useful for no reference cases to local projections.
queryScalar :: (MonadQualify ConfigureQuery m, ScalarDegree r) => (Projection c a -> UniqueRelation () c r) -> QueryA m (Projection c a) (Projection c (Maybe r)) Source #
Same as queryScalar
. Arrow version.
The result arrow is designed to be injected by any local projection.
queryScalar' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => (Projection c a -> UniqueRelation p c r) -> QueryA m (Projection c a) (PlaceHolders p, Projection c (Maybe r)) Source #
Same as queryScalar'
. Arrow version.
The result arrow is designed to be injected by any local projection.
queryScalarU :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation () c r -> QueryA m () (Projection c (Maybe r)) Source #
Same as queryScalar
. Arrow version.
Useful for no reference cases to local projections.
queryScalarU' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation p c r -> QueryA m () (PlaceHolders p, Projection c (Maybe r)) Source #
Same as queryScalar'
. Arrow version.
Useful for no reference cases to local projections.
uniqueQuery' :: UniqueRelation p c r -> QueryA QueryUnique () (PlaceHolders p, Projection c r) Source #
Same as uniqueQuery'
. Arrow version.
The result arrow is not injected by local projections.
uniqueQueryMaybe' :: UniqueRelation p c r -> QueryA QueryUnique () (PlaceHolders p, Projection c (Maybe r)) Source #
Same as uniqueQueryMaybe'
. Arrow version.
The result arrow is not injected by local projections.
on :: MonadQuery m => QueryA m (Projection Flat (Maybe Bool)) () Source #
Same as on
. Arrow version.
The result arrow is designed to be injected by local conditional flat-projections.
wheres :: MonadRestrict Flat m => QueryA m (Projection Flat (Maybe Bool)) () Source #
Same as wheres
. Arrow version.
The result arrow is designed to be injected by local conditional flat-projections.
having :: MonadRestrict Aggregated m => QueryA m (Projection Aggregated (Maybe Bool)) () Source #
Same as having
. Arrow version.
The result arrow is designed to be injected by local conditional aggregated-projections.
groupBy :: MonadAggregate m => QueryA m (Projection Flat r) (Projection Aggregated r) Source #
Same as groupBy
. Arrow version.
The result arrow is designed to be injected by local flat-projections.
placeholder :: (PersistableWidth t, SqlProjectable p, Monad m) => QueryA m (QueryA m (p t) a) (PlaceHolders t, a) Source #
Same as placeholder
. Arrow version.
The result arrow is designed to be injected by locally built arrow using placeholders.
relation :: QuerySimple () (Projection Flat r) -> Relation () r Source #
Same as relation
.
Finalize query-building arrow instead of query-building monad.
relation' :: QuerySimple () (PlaceHolders p, Projection Flat r) -> Relation p r Source #
Same as relation'
.
Finalize query-building arrow instead of query-building monad.
aggregateRelation :: QueryAggregate () (Projection Aggregated r) -> Relation () r Source #
Same as aggregateRelation
.
Finalize query-building arrow instead of query-building monad.
aggregateRelation' :: QueryAggregate () (PlaceHolders p, Projection Aggregated r) -> Relation p r Source #
Same as aggregateRelation'
.
Finalize query-building arrow instead of query-building monad.
uniqueRelation' :: QueryUnique () (PlaceHolders p, Projection c r) -> UniqueRelation p c r Source #
Same as uniqueRelation'
.
Finalize query-building arrow instead of query-building monad.
groupBy' :: MonadAggregate m => QueryA m (AggregateKey (Projection Aggregated r)) (Projection Aggregated r) Source #
Same as groupBy'
.
This arrow is designed to be injected by local AggregateKey
.
key :: AggregatingSet (Projection Flat r) (Projection Aggregated (Maybe r)) Source #
Same as key
.
This arrow is designed to be injected by local flat-projections.
key' :: AggregatingSet (AggregateKey a) a Source #
Same as key'
.
This arrow is designed to be injected by local AggregteKey
.
set :: AggregatingSetList (AggregatingSet () a) a Source #
Same as set
.
This arrow is designed to be injected by locally built AggregtingSet
arrow.
bkey :: AggregatingPowerSet (Projection Flat r) (Projection Aggregated (Maybe r)) Source #
Same as bkey
.
This arrow is designed to be injected by local flat-projections.
rollup :: AggregatingPowerSet () a -> AggregateKey a Source #
Same as rollup
.
Finalize locally built AggregatingPowerSet
.
cube :: AggregatingPowerSet () a -> AggregateKey a Source #
Same as cube
.
Finalize locally built AggregatingPowerSet
.
groupingSets :: AggregatingSetList () a -> AggregateKey a Source #
Same as groupingSets
.
Finalize locally built AggregatingSetList
.
orderBy :: Monad m => Order -> Orderings c m (Projection c t) () Source #
Same as orderBy
.
The result arrow is designed to be injected by local projections.
asc :: Monad m => Orderings c m (Projection c t) () Source #
Same as asc
.
The result arrow is designed to be injected by local projections.
desc :: Monad m => Orderings c m (Projection c t) () Source #
Same as desc
.
The result arrow is designed to be injected by local projections.
partitionBy :: Window c (Projection c r) () Source #
Same as partitionBy
.
The result arrow is designed to be injected by local projections.
over :: SqlProjectable (Projection c) => Projection OverWindow a -> Window c () () -> Projection c a infix 8 Source #
assign :: Monad m => AssignTarget r v -> Assignings r m (Projection Flat v) () Source #
Make AssignTarget
into arrow which is designed to be
injected by local projection assignees.
derivedUpdate' :: TableDerivable r => Config -> AssignStatement r (PlaceHolders p) -> Update p Source #
Same as derivedUpdate'
.
Make Update
from assigning statement arrow using configuration.
derivedUpdate :: TableDerivable r => AssignStatement r (PlaceHolders p) -> Update p Source #
Same as derivedUpdate
.
Make Update
from assigning statement arrow.
derivedDelete' :: TableDerivable r => Config -> RestrictedStatement r (PlaceHolders p) -> Delete p Source #
Same as derivedDelete'
.
Make Update
from restrict statement arrow using configuration.
derivedDelete :: TableDerivable r => RestrictedStatement r (PlaceHolders p) -> Delete p Source #
Same as derivedDelete
.
Make Update
from restrict statement arrow.
Arrow to build queries.
type QuerySimple = QueryA QuerySimple Source #
Arrow type corresponding to QuerySimple
type QueryAggregate = QueryA QueryAggregate Source #
Arrow type corresponding to QueryAggregate
type QueryUnique = QueryA QueryUnique Source #
Arrow type corresponding to QueryUnique
type AggregatingSet = QueryA AggregatingSet Source #
Arrow type corresponding to AggregatingSet
type AggregatingSetList = QueryA AggregatingSetList Source #
Arrow type corresponding to AggregatingSetList
type AggregatingPowerSet = QueryA AggregatingPowerSet Source #
Arrow type corresponding to AggregatingPowerSet
type Assignings r m = QueryA (Assignings r m) Source #
Arrow type corresponding to Assignings
type AssignStatement r a = Assignings r Restrict (Projection Flat r) a Source #
Arrow type corresponding to AssignStatement
type RestrictedStatement r a = QueryA Restrict (Projection Flat r) a Source #
Arrow type corresponding to RestrictedStatement