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

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

Database.Relational.Query.Sub

Contents

Description

This module defines sub-query structure used in query products.

Synopsis

Sub-query

data SubQuery Source #

Sub-query type

fromTable Source #

Arguments

:: Table r

Typed Table metadata

-> SubQuery

Result SubQuery

flatSubQuery :: Config -> UntypedProjection -> Duplication -> JoinProduct -> QueryRestriction Flat -> [OrderingTerm] -> SubQuery Source #

Unsafely generate flat SubQuery from untyped components.

aggregatedSubQuery :: Config -> UntypedProjection -> Duplication -> JoinProduct -> QueryRestriction Flat -> [AggregateElem] -> QueryRestriction Aggregated -> [OrderingTerm] -> SubQuery Source #

Unsafely generate aggregated SubQuery from untyped components.

union :: Duplication -> SubQuery -> SubQuery -> SubQuery Source #

Union binary operator on SubQuery

except :: Duplication -> SubQuery -> SubQuery -> SubQuery Source #

Except binary operator on SubQuery

intersect :: Duplication -> SubQuery -> SubQuery -> SubQuery Source #

Intersect binary operator on SubQuery

showSQL :: SubQuery -> StringSQL Source #

SQL StringSQL for toplevel-SQL.

toSQL :: SubQuery -> String Source #

SQL string for toplevel-SQL.

unitSQL :: SubQuery -> String Source #

SQL string for nested-qeury.

Qualified Sub-query

newtype Qualifier Source #

Qualifier type.

Constructors

Qualifier Int 

data Qualified a Source #

Qualified query.

Instances

Functor Qualified Source # 

Methods

fmap :: (a -> b) -> Qualified a -> Qualified b #

(<$) :: a -> Qualified b -> Qualified a #

Foldable Qualified Source # 

Methods

fold :: Monoid m => Qualified m -> m #

foldMap :: Monoid m => (a -> m) -> Qualified a -> m #

foldr :: (a -> b -> b) -> b -> Qualified a -> b #

foldr' :: (a -> b -> b) -> b -> Qualified a -> b #

foldl :: (b -> a -> b) -> b -> Qualified a -> b #

foldl' :: (b -> a -> b) -> b -> Qualified a -> b #

foldr1 :: (a -> a -> a) -> Qualified a -> a #

foldl1 :: (a -> a -> a) -> Qualified a -> a #

toList :: Qualified a -> [a] #

null :: Qualified a -> Bool #

length :: Qualified a -> Int #

elem :: Eq a => a -> Qualified a -> Bool #

maximum :: Ord a => Qualified a -> a #

minimum :: Ord a => Qualified a -> a #

sum :: Num a => Qualified a -> a #

product :: Num a => Qualified a -> a #

Traversable Qualified Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Qualified a -> f (Qualified b) #

sequenceA :: Applicative f => Qualified (f a) -> f (Qualified a) #

mapM :: Monad m => (a -> m b) -> Qualified a -> m (Qualified b) #

sequence :: Monad m => Qualified (m a) -> m (Qualified a) #

Show a => Show (Qualified a) Source # 

Sub-query columns

column :: Qualified SubQuery -> Int -> StringSQL Source #

Get column SQL string of SubQuery.

Projection

data Projection c t Source #

Phantom typed projection. Projected into Haskell record type t.

Instances

ProjectableMaybe (Projection c) Source #

Control phantom Maybe type in projection type Projection.

ProjectableShowSql (Projection c) Source #

Unsafely get SQL term from Proejction.

SqlProjectable (Projection OverWindow) Source #

Unsafely make Projection from SQL terms.

SqlProjectable (Projection Aggregated) Source #

Unsafely make Projection from SQL terms.

SqlProjectable (Projection Flat) Source #

Unsafely make Projection from SQL terms.

Show (Projection c t) Source # 

Methods

showsPrec :: Int -> Projection c t -> ShowS #

show :: Projection c t -> String #

showList :: [Projection c t] -> ShowS #

data ProjectionUnit Source #

Projection structure unit with single column width

type UntypedProjection = [ProjectionUnit] Source #

Untyped projection. Forgot record type.

untypedProjectionFromJoinedSubQuery :: Qualified SubQuery -> UntypedProjection Source #

Make untyped projection from joined sub-query.

projectionColumns Source #

Arguments

:: Projection c r

Source Projection

-> [StringSQL]

Result SQL string list

Get column SQL string list of projection.

unsafeProjectionStringSql :: Projection c r -> StringSQL Source #

Unsafely get SQL term from Proejction.

Product of sub-queries

type JoinProduct = Maybe QueryProductTree Source #

Type for join product of query.

data NodeAttr Source #

node attribute for product.

Constructors

Just' 
Maybe 

type ProductBuilder = Node QueryRestrictionBuilder Source #

Product noe with join restriction builder.

Query restriction

type QueryRestriction c = [Projection c (Maybe Bool)] Source #

Type for restriction of query.