relational-query-0.8.5.0: Typeful, Modular, Relational, algebraic query engine

Copyright2013-2017 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Database.Relational.Query.Relation

Contents

Description

This module defines re-usable Relation type to compose complex query.

Synopsis

Relation type

table :: Table r -> Relation () r Source #

Simple Relation from Table.

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' :: SimpleQuery p r -> Relation p r Source #

Finalize QuerySimple monad and generate Relation with place-holder parameter p.

aggregateRelation' :: AggregatedQuery p 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.

Query using relation

query :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> m (Projection Flat r) Source #

Join sub-query. Query result is not Maybe.

queryMaybe :: (MonadQualify ConfigureQuery m, MonadQuery m) => Relation () r -> m (Projection Flat (Maybe r)) Source #

Join sub-query. Query result is Maybe. The combinations of query and queryMaybe express inner joins, left outer joins, right outer joins, and full outer joins. Here is an example of a right outer join:

  outerJoin = relation $ do
    e <- queryMaybe employee
    d <- query department
    on $ e ?! E.deptId' .=. just (d ! D.deptId')
    return $ (,) |$| e |*| d

queryList :: MonadQualify ConfigureQuery m => Relation () r -> m (ListProjection (Projection c) r) Source #

List sub-query, for IN and EXIST.

queryList' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, ListProjection (Projection c) r) Source #

List sub-query, for IN and EXIST with place-holder parameter p.

queryScalar :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation () c r -> m (Projection c (Maybe r)) Source #

Scalar sub-query.

queryScalar' :: (MonadQualify ConfigureQuery m, ScalarDegree r) => UniqueRelation p c r -> m (PlaceHolders p, Projection c (Maybe r)) Source #

Scalar sub-query with place-holder parameter p.

uniqueQuery' :: UniqueRelation p c r -> QueryUnique (PlaceHolders p, Projection c r) Source #

Join unique sub-query with place-holder parameter p.

uniqueQueryMaybe' :: UniqueRelation p c r -> QueryUnique (PlaceHolders p, Projection c (Maybe r)) Source #

Join unique sub-query 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 predicate function type for direct style join operator, used on predicates of direct join style as follows.

  do xy <- query $
           relX inner relY on' [ x y -> ... ] -- this lambda form has JoinRestriction type
     ...

inner' infixl 8 Source #

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.

left' infixl 8 Source #

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.

right' infixl 8 Source #

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.

full' infixl 8 Source #

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.

inner infixl 8 Source #

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.

left infixl 8 Source #

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.

right infixl 8 Source #

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.

full infixl 8 Source #

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

union :: Relation () a -> Relation () a -> Relation () a infixl 7 Source #

Union of two relations.

except :: Relation () a -> Relation () a -> Relation () a infixl 7 Source #

Subtraction of two relations.

intersect :: Relation () a -> Relation () a -> Relation () a infixl 8 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 8 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 8 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 8 Source #

Intersection of two relations with place-holder parameters. Not distinct.