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

Copyright2017 Kei Hibino
LicenseBSD3
Maintainer[email protected]
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Database.Relational.SqlSyntax

Contents

Description

This module is integrated module of sql-syntax.

Synopsis

The SubQuery

Set operations

data Duplication Source #

Result record duplication attribute

Constructors

All 
Distinct 

data SetOp Source #

Set operators

Constructors

Union 
Except 
Intersect 

Instances

newtype BinOp Source #

Set binary operators

Constructors

BinOp (SetOp, Duplication) 

Instances

Qualifiers for nested query

newtype Qualifier Source #

Qualifier type.

Constructors

Qualifier Int 

data Qualified a Source #

Qualified query.

Constructors

Qualified Qualifier a 

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 # 

qualifier :: Qualified a -> Qualifier Source #

Get qualifier

unQualify :: Qualified a -> a Source #

Unqualify.

qualify :: Qualifier -> a -> Qualified a Source #

Add qualifier

Ordering types

data Order Source #

Order direction. Ascendant or Descendant.

Constructors

Asc 
Desc 

Instances

data Nulls Source #

Order of null.

Constructors

NullsFirst 
NullsLast 

Instances

type OrderColumn = StringSQL Source #

Type for order-by column

type OrderingTerm = ((Order, Maybe Nulls), OrderColumn) Source #

Type for order-by term

Aggregating types

type AggregateColumnRef = StringSQL Source #

Type for group-by term

newtype AggregateSet Source #

Type for grouping set

Constructors

AggregateSet [AggregateElem] 

newtype AggregateKey a Source #

Typeful aggregate element.

Constructors

AggregateKey (a, AggregateElem) 

Product tree type

data NodeAttr Source #

node attribute for product.

Constructors

Just' 
Maybe 

data ProductTree rs Source #

Product tree type. Product tree is constructed by left node and right node.

Constructors

Leaf QS 
Join !(Node rs) !(Node rs) !rs 

Instances

Functor ProductTree Source # 

Methods

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

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

Show rs => Show (ProductTree rs) Source # 

data Node rs Source #

Product node. node attribute and product tree.

Constructors

Node !NodeAttr !(ProductTree rs) 

Instances

Functor Node Source # 

Methods

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

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

Show rs => Show (Node rs) Source # 

Methods

showsPrec :: Int -> Node rs -> ShowS #

show :: Node rs -> String #

showList :: [Node rs] -> ShowS #

nodeAttr :: Node rs -> NodeAttr Source #

Get node attribute.

nodeTree :: Node rs -> ProductTree rs Source #

Get tree from node.

type JoinProduct = Maybe (ProductTree [Predicate Flat]) Source #

Type for join product of query.

Case

data WhenClauses Source #

when clauses

Constructors

WhenClauses [(Tuple, Tuple)] Tuple 

Column, Tuple, Record and Projection

data Column Source #

Projected column structure unit with single column width

Constructors

RawColumn StringSQL

used in immediate value or unsafe operations

SubQueryRef (Qualified Int)

normalized sub-query reference Tn with Int index

Scalar SubQuery

scalar sub-query

Case CaseClause Int

nth column of case clause

Instances

type Tuple = [Column] Source #

Untyped projected tuple. Forgot record type.

tupleWidth :: Tuple -> Int Source #

Width of Tuple.

data Record c t Source #

Phantom typed record. Projected into Haskell record type t.

Instances

ProjectableMaybe (Record c) Source #

Control phantom Maybe type in record type Record.

Methods

just :: Record c a -> Record c (Maybe a) Source #

flattenMaybe :: Record c (Maybe (Maybe a)) -> Record c (Maybe a) Source #

ProjectableShowSql (Record c) Source # 
SqlContext c => SqlProjectable (Record c) Source #

Unsafely make Record from SQL terms.

Show (Record c t) Source # 

Methods

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

show :: Record c t -> String #

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

untypeRecord :: Record c t -> Tuple Source #

Discard record type

record :: Tuple -> Record c t Source #

Unsafely type Tuple value to Record type.

type PI c a b = Record c a -> Record c b Source #

Type for projection function.

recordWidth :: Record c r -> Int Source #

Width of Record.

typeFromRawColumns Source #

Arguments

:: [StringSQL]

SQL string list specifies columns

-> Record c r

Result Record

Unsafely generate Record from SQL string list.

typeFromScalarSubQuery :: SubQuery -> Record c t Source #

Unsafely generate Record from scalar sub-query.

Predicate to restrict Query result

type Predicate c = Record c (Maybe Bool) Source #

Type for predicate to restrict of query result.

Interfaces to manipulate ProductTree type

growProduct Source #

Arguments

:: Maybe (Node (DList (Predicate Flat)))

Current tree

-> (NodeAttr, Qualified SubQuery)

New leaf to push into right

-> Node (DList (Predicate Flat))

Result node

Push new leaf node into product right term.

restrictProduct Source #

Arguments

:: Node (DList (Predicate Flat))

Target node which has product to restrict

-> Predicate Flat

Restriction to add

-> Node (DList (Predicate Flat))

Result node

Add restriction into top product of product tree node.

aggregateColumnRef :: AggregateColumnRef -> AggregateElem Source #

Single term aggregation element.

aggregatePowerKey :: [AggregateColumnRef] -> AggregateBitKey Source #

Key of aggregation power set.

aggregateRollup :: [AggregateBitKey] -> AggregateElem Source #

Rollup aggregation element.

aggregateCube :: [AggregateBitKey] -> AggregateElem Source #

Cube aggregation element.

aggregateSets :: [AggregateSet] -> AggregateElem Source #

Grouping sets aggregation.

composeGroupBy :: [AggregateElem] -> StringSQL Source #

Compose GROUP BY clause from AggregateElem list.

composePartitionBy :: [AggregateColumnRef] -> StringSQL Source #

Compose PARTITION BY clause from AggregateColumnRef list.

aggregateKeyRecord :: AggregateKey a -> a Source #

Extract typed record from AggregateKey.

unsafeAggregateKey :: (a, AggregateElem) -> AggregateKey a Source #

Unsafely bind typed-record and untyped-term into AggregateKey.

flatSubQuery :: Config -> Tuple -> Duplication -> JoinProduct -> [Predicate Flat] -> [OrderingTerm] -> SubQuery Source #

Unsafely generate flat SubQuery from untyped components.

aggregatedSubQuery :: Config -> Tuple -> Duplication -> JoinProduct -> [Predicate Flat] -> [AggregateElem] -> [Predicate 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

caseSearch Source #

Arguments

:: [(Predicate c, Record c a)]

Each when clauses

-> Record c a

Else result record

-> Record c a

Result record

Search case operator correnponding SQL search CASE. Like, CASE WHEN p0 THEN a WHEN p1 THEN b ... ELSE c END

case' Source #

Arguments

:: Record c a

Record value to match

-> [(Record c a, Record c b)]

Each when clauses

-> Record c b

Else result record

-> Record c b

Result record

Simple case operator correnponding SQL simple CASE. Like, CASE x WHEN v THEN a WHEN w THEN b ... ELSE c END

composeOrderBy :: [OrderingTerm] -> StringSQL Source #

Compose ORDER BY clause from OrderingTerms

Sub-query

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

Sub-query columns

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

Get column SQL string of Qualified SubQuery.

Tuple and Record

tupleFromJoinedSubQuery :: Qualified SubQuery -> Tuple Source #

Make untyped tuple (qualified column list) from joined sub-query (Qualified SubQuery).

recordRawColumns Source #

Arguments

:: Record c r

Source Record

-> [StringSQL]

Result SQL string list

Get column SQL string list of record.

Query restriction

composeWhere :: [Predicate Flat] -> StringSQL Source #

Compose WHERE clause from QueryRestriction.

composeHaving :: [Predicate Aggregated] -> StringSQL Source #

Compose HAVING clause from QueryRestriction.

Update and Insert assignments

type AssignColumn = StringSQL Source #

Column SQL String of assignment

type AssignTerm = StringSQL Source #

Value SQL String of assignment

type Assignment = (AssignColumn, AssignTerm) Source #

Assignment pair

composeSets :: [Assignment] -> StringSQL Source #

Compose SET clause from [Assignment].

composeChunkValues Source #

Arguments

:: Int

record count per chunk

-> [AssignTerm]

value expression list

-> Keyword 

Compose VALUES clause from value expression list.

composeChunkValuesWithColumns Source #

Arguments

:: Int

record count per chunk

-> [Assignment] 
-> StringSQL 

Compose VALUES clause from value expression list.