| Copyright | 2013 Kei Hibino | 
|---|---|
| License | BSD3 | 
| Maintainer | ex8k.hibino@gmail.com | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Database.Relational.Query.Relation
Description
This module defines re-usable Relation type to compose complex query.
- data Relation p r
- table :: Table r -> Relation () r
- derivedRelation :: TableDerivable r => Relation () r
- tableOf :: TableDerivable r => Relation () r -> Table r
- 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
- data UniqueRelation p c r
- unsafeUnique :: Relation p r -> UniqueRelation p c r
- unUnique :: UniqueRelation p c r -> Relation p r
- uniqueRelation' :: QueryUnique (PlaceHolders p, Projection c r) -> UniqueRelation p c r
- aggregatedUnique :: Relation ph r -> Pi r a -> (Projection Flat a -> Projection Aggregated b) -> UniqueRelation ph Flat b
- dump :: Relation p r -> String
- sqlFromRelationWith :: Relation p r -> Config -> StringSQL
- sqlFromRelation :: Relation p r -> StringSQL
- query :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat r)
- query' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat r)
- queryMaybe :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat (Maybe r))
- queryMaybe' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat (Maybe r))
- queryList :: MonadQualify ConfigureQuery m => Relation () r -> m (ListProjection (Projection c) r)
- queryList' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, ListProjection (Projection c) r)
- queryScalar :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation () c r -> m (Projection c r)
- queryScalar' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation p c r -> m (PlaceHolders p, Projection c r)
- uniqueQuery' :: MonadQualifyUnique ConfigureQuery m => UniqueRelation p c r -> m (PlaceHolders p, Projection c r)
- uniqueQueryMaybe' :: MonadQualifyUnique ConfigureQuery m => UniqueRelation p c r -> m (PlaceHolders p, Projection c (Maybe r))
- type JoinRestriction a b = Projection Flat a -> Projection Flat b -> Projection Flat (Maybe Bool)
- rightPh :: Relation ((), p) r -> Relation p r
- leftPh :: Relation (p, ()) r -> Relation p r
- inner' :: Relation pa a -> Relation pb b -> [JoinRestriction a b] -> Relation (pa, pb) (a, b)
- left' :: Relation pa a -> Relation pb b -> [JoinRestriction a (Maybe b)] -> Relation (pa, pb) (a, Maybe b)
- right' :: Relation pa a -> Relation pb b -> [JoinRestriction (Maybe a) b] -> Relation (pa, pb) (Maybe a, b)
- full' :: Relation pa a -> Relation pb b -> [JoinRestriction (Maybe a) (Maybe b)] -> Relation (pa, pb) (Maybe a, Maybe b)
- 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)
- union :: Relation () a -> Relation () a -> Relation () a
- except :: Relation () a -> Relation () a -> Relation () a
- intersect :: Relation () a -> Relation () a -> Relation () a
- unionAll :: Relation () a -> Relation () a -> Relation () a
- exceptAll :: Relation () a -> Relation () a -> Relation () a
- intersectAll :: Relation () a -> Relation () a -> Relation () a
- union' :: Relation p a -> Relation q a -> Relation (p, q) a
- except' :: Relation p a -> Relation q a -> Relation (p, q) a
- intersect' :: Relation p a -> Relation q a -> Relation (p, q) a
- unionAll' :: Relation p a -> Relation q a -> Relation (p, q) a
- exceptAll' :: Relation p a -> Relation q a -> Relation (p, q) a
- intersectAll' :: Relation p a -> Relation q a -> Relation (p, q) a
Relation type
Relation type with place-holder parameter p and query result type r.
derivedRelation :: TableDerivable r => Relation () r Source
Infered Relation.
tableOf :: TableDerivable r => Relation () r -> Table r Source
Interface to derive Table type object.
relation :: QuerySimple (Projection Flat r) -> Relation () r Source
Finalize QuerySimple monad and generate Relation.
relation' :: QuerySimple (PlaceHolders p, Projection Flat r) -> Relation p r Source
Finalize QuerySimple monad and generate Relation with place-holder parameter p.
aggregateRelation :: QueryAggregate (Projection Aggregated r) -> Relation () r Source
Finalize QueryAggregate monad and geneate Relation.
aggregateRelation' :: QueryAggregate (PlaceHolders p, Projection Aggregated r) -> Relation p r Source
Finalize QueryAggregate monad and geneate Relation with place-holder parameter p.
data UniqueRelation p c r Source
Unique relation type to compose scalar queries.
unsafeUnique :: Relation p r -> UniqueRelation p c r Source
Unsafely specify unique relation.
unUnique :: UniqueRelation p c r -> Relation p r Source
Discard unique attribute.
uniqueRelation' :: QueryUnique (PlaceHolders p, Projection c r) -> UniqueRelation p c r Source
Finalize QueryUnique monad and generate UniqueRelation.
aggregatedUnique :: Relation ph r -> Pi r a -> (Projection Flat a -> Projection Aggregated b) -> UniqueRelation ph Flat b Source
Aggregated UniqueRelation.
sqlFromRelationWith :: Relation p r -> Config -> StringSQL Source
Generate SQL string from Relation with configuration.
sqlFromRelation :: Relation p r -> StringSQL Source
SQL string from Relation.
Query using relation
query :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat r) Source
Join subquery. Query result is not Maybe.
query' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat r) Source
Join subquery with place-holder parameter p. query result is not Maybe.
queryMaybe :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat (Maybe r)) Source
Join subquery. Query result is Maybe.
queryMaybe' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat (Maybe r)) Source
Join subquery with place-holder parameter p. Query result is Maybe.
queryList :: MonadQualify ConfigureQuery m => Relation () r -> m (ListProjection (Projection c) r) Source
List subQuery, for IN and EXIST.
queryList' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, ListProjection (Projection c) r) Source
List subQuery, for IN and EXIST with place-holder parameter p.
queryScalar :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation () c r -> m (Projection c r) Source
Scalar subQuery.
queryScalar' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation p c r -> m (PlaceHolders p, Projection c r) Source
Scalar subQuery with place-holder parameter p.
uniqueQuery' :: MonadQualifyUnique ConfigureQuery m => UniqueRelation p c r -> m (PlaceHolders p, Projection c r) Source
Join unique subquery with place-holder parameter p.
uniqueQueryMaybe' :: MonadQualifyUnique ConfigureQuery m => UniqueRelation p c r -> m (PlaceHolders p, Projection c (Maybe r)) Source
Join unique subquery with place-holder parameter p. Query result is Maybe.
Direct style join
type JoinRestriction a b = Projection Flat a -> Projection Flat b -> Projection Flat (Maybe Bool) Source
Restriction function type for direct style join operator.
rightPh :: Relation ((), p) r -> Relation p r Source
Simplify placeholder type applying left identity element.
leftPh :: Relation (p, ()) r -> Relation p r Source
Simplify placeholder type applying right identity element.
Arguments
| :: Relation pa a | Left query to join | 
| -> Relation pb b | Right query to join | 
| -> [JoinRestriction a b] | Join restrictions | 
| -> Relation (pa, pb) (a, b) | Result joined relation | 
Direct inner join with place-holder parameters.
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.
Arguments
| :: Relation pa a | Left query to join | 
| -> Relation pb b | Right query to join | 
| -> [JoinRestriction (Maybe a) b] | Join restrictions | 
| -> Relation (pa, pb) (Maybe a, b) | Result joined relation | 
Direct right outer join with place-holder parameters.
Arguments
| :: Relation pa a | Left query to join | 
| -> Relation pb b | Right query to join | 
| -> [JoinRestriction (Maybe a) (Maybe b)] | Join restrictions | 
| -> Relation (pa, pb) (Maybe a, Maybe b) | Result joined relation | 
Direct full outer join with place-holder parameters.
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) infixl 8 Source
Apply restriction for direct join style.
Relation append
except :: Relation () a -> Relation () a -> Relation () a infixl 7 Source
Subtraction of two relations.
intersect :: Relation () a -> Relation () a -> Relation () a infixl 7 Source
Intersection of two relations.
unionAll :: Relation () a -> Relation () a -> Relation () a infixl 7 Source
Union of two relations. Not distinct.
exceptAll :: Relation () a -> Relation () a -> Relation () a infixl 7 Source
Subtraction of two relations. Not distinct.
intersectAll :: Relation () a -> Relation () a -> Relation () a infixl 7 Source
Intersection of two relations. Not distinct.
union' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source
Union of two relations with place-holder parameters.
except' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source
Subtraction of two relations with place-holder parameters.
intersect' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source
Intersection of two relations with place-holder parameters.
unionAll' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source
Union of two relations with place-holder parameters. Not distinct.
exceptAll' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source
Subtraction of two relations with place-holder parameters. Not distinct.
intersectAll' :: Relation p a -> Relation q a -> Relation (p, q) a infixl 7 Source
Intersection of two relations with place-holder parameters. Not distinct.