relational-query-0.12.3.0: Typeful, Modular, Relational, algebraic query engine
Copyright2017 Kei Hibino
LicenseBSD3
Maintainerex8k.hibino@gmail.com
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Database.Relational.SqlSyntax

Description

This module is integrated module of sql-syntax.

Synopsis

The SubQuery

Set operations

data Duplication Source #

Result record duplication attribute

Constructors

All 
Distinct 

Instances

Instances details
Show Duplication Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data SetOp Source #

Set operators

Constructors

Union 
Except 
Intersect 

Instances

Instances details
Show SetOp Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> SetOp -> ShowS #

show :: SetOp -> String #

showList :: [SetOp] -> ShowS #

newtype BinOp Source #

Set binary operators

Constructors

BinOp (SetOp, Duplication) 

Instances

Instances details
Show BinOp Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> BinOp -> ShowS #

show :: BinOp -> String #

showList :: [BinOp] -> ShowS #

Qualifiers for nested query

newtype Qualifier Source #

Qualifier type.

Constructors

Qualifier Int 

Instances

Instances details
Show Qualifier Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data Qualified a Source #

Qualified query.

Constructors

Qualified Qualifier a 

Instances

Instances details
Functor Qualified Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

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

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

Foldable Qualified Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

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

foldMap :: Monoid m => (a -> m) -> Qualified a -> 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 # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

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 # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

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

Instances details
Show Order Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

data Nulls Source #

Order of null.

Constructors

NullsFirst 
NullsLast 

Instances

Instances details
Show Nulls Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Nulls -> ShowS #

show :: Nulls -> String #

showList :: [Nulls] -> ShowS #

type OrderColumn = Column Source #

Type for order-by column

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

Type for order-by term

Aggregating types

type AggregateColumnRef = Column Source #

Type for group-by term

newtype AggregateBitKey Source #

Type for group key.

Instances

Instances details
Show AggregateBitKey Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

newtype AggregateSet Source #

Type for grouping set

Constructors

AggregateSet [AggregateElem] 

Instances

Instances details
Show AggregateSet Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data AggregateElem Source #

Type for group-by tree

newtype AggregateKey a Source #

Typeful aggregate element.

Constructors

AggregateKey (a, AggregateElem) 

Product tree type

data NodeAttr Source #

node attribute for product.

Constructors

Just' 
Maybe 

Instances

Instances details
Show NodeAttr Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data ProductTree rs Source #

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

Constructors

Leaf (Bool, Qualified SubQuery) 
Join !(Node rs) !(Node rs) !rs 

Instances

Instances details
Functor ProductTree Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

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

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

Show rs => Show (ProductTree rs) Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data Node rs Source #

Product node. node attribute and product tree.

Constructors

Node !NodeAttr !(ProductTree rs) 

Instances

Instances details
Functor Node Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

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

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

Show rs => Show (Node rs) Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

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 CaseClause Source #

case clause

Instances

Instances details
Show CaseClause Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data WhenClauses Source #

when clauses

Constructors

WhenClauses [(Tuple, Tuple)] Tuple 

Instances

Instances details
Show WhenClauses Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

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

Instances details
Show Column Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Monad m => MonadPartition c (PartitioningSetT c m) Source #

Partition clause instance

Instance details

Defined in Database.Relational.Monad.Trans.Aggregating

Methods

partitionBy :: Record c r -> PartitioningSetT c m () Source #

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

Instances details
(PersistableWidth a, HasProjection l a b) => IsLabel l (PI c a b) Source #

Derive PI label.

Instance details

Defined in Database.Relational.OverloadedProjection

Methods

fromLabel :: PI c a b #

ProductIsoFunctor (Record c) Source #

Map Record which result type is record.

Instance details

Defined in Database.Relational.Record

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> Record c a -> Record c b #

ProductIsoApplicative (Record c) Source #

Compose Record using applicative style.

Instance details

Defined in Database.Relational.Record

Methods

pureP :: ProductConstructor a => a -> Record c a #

(|*|) :: Record c (a -> b) -> Record c a -> Record c b #

ProjectableMaybe (Record c) Source #

Control phantom Maybe type in record type Record.

Instance details

Defined in Database.Relational.Projectable

Methods

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

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

ProductIsoEmpty (Record c) () Source # 
Instance details

Defined in Database.Relational.Record

Methods

pureE :: Record c () #

peRight :: Record c (a, ()) -> Record c a #

peLeft :: Record c ((), a) -> Record c a #

TableDerivable r => Show (Record Flat r -> Assign r (PlaceHolders p)) Source #

Show Set clause and WHERE clause.

Instance details

Defined in Database.Relational.Effect

Methods

showsPrec :: Int -> (Record Flat r -> Assign r (PlaceHolders p)) -> ShowS #

show :: (Record Flat r -> Assign r (PlaceHolders p)) -> String #

showList :: [Record Flat r -> Assign r (PlaceHolders p)] -> ShowS #

TableDerivable r => Show (Record Flat r -> Restrict (PlaceHolders p)) Source #

Show WHERE clause.

Instance details

Defined in Database.Relational.Effect

Show (Record c t) Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

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.

growProduct Source #

Arguments

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

Current tree

-> (NodeAttr, (Bool, 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.

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

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

corrSubQueryTerm Source #

Arguments

:: Bool

if True, add AS keyword. SQLite causes syntax error on UPDATE or DELETE statement.

-> Qualified SubQuery

subquery structure with qualifier

-> StringSQL

result SQL string

Term of qualified table or qualified subquery, used in join-clause of SELECT, correlated UPDATE and DELETE statements. When SubQuery is table, expression will be like TABLE [AS] Tn

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.

Aggregation

composeGroupBy :: [AggregateElem] -> StringSQL Source #

Compose GROUP BY clause from AggregateElem list.

composePartitionBy :: [AggregateColumnRef] -> StringSQL Source #

Compose PARTITION BY clause from AggregateColumnRef list.

Ordering

composeOrderBy :: [OrderingTerm] -> StringSQL Source #

Compose ORDER BY clause from OrderingTerms

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 a row of value expressions.

composeChunkValuesWithColumns Source #

Arguments

:: Int

record count per chunk

-> [Assignment] 
-> StringSQL 

Compose columns row and VALUES clause from a row of value expressions.

composeValuesListWithColumns :: [[Assignment]] -> StringSQL Source #

Compose columns row and VALUES clause from rows list of value expressions.