relational-record-0.1.0.1: Meta package of Relational Record

Portabilityunknown
Stabilityexperimental
Maintainerex8k.hibino@gmail.com
Safe HaskellNone

Database.Relational.Query.Documentation

Contents

Description

This module is documentation module for relational record.

Synopsis

Concepts

User inferface of Relational Record has main two part of modules.

Database.Relational.Query
Relational Query Building DSL
Database.HDBC.Record
Database Operation Actions

Relational Query Building DSL

Relatoinal Query (Database.Relational.Query) module defines Typed DSL to build complex SQL query.

Monadic Query Context Building

On building query, query structures can be accumulated in monadic context.

Monadic Operators

Some operators are defined to build query structures in monadic context.

query and queryMaybe operators grow query product of monadic context like join operation of SQL. on operator appends a new condition into recent join product condition.

groupBy operator aggregates flat projection value.

wheres and having operators appends a new condition into whole query condition. having only accepts aggregated projection value.

'(<-#)' operator assigns update target column and projection value to build update statement structure.

query :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat r)

Join subquery. Query result is not Maybe.

queryMaybe :: MonadQualify ConfigureQuery m => Relation () r -> m (Projection Flat (Maybe r))

Join subquery. Query result is Maybe.

on :: MonadQuery m => Projection Flat (Maybe Bool) -> m ()

Add restriction to last join. Projection type version.

wheres :: MonadRestrict Flat m => Projection Flat (Maybe Bool) -> m ()

Add restriction to this query. Projection type version.

groupBy

Arguments

:: MonadAggregate m 
=> Projection Flat r

Projection to add into group by

-> m (Projection Aggregated r)

Result context and aggregated projection

Add GROUP BY term into context and get aggregated projection.

having :: MonadRestrict Aggregated m => Projection Aggregated (Maybe Bool) -> m ()

Add restriction to this aggregated query. Aggregated Projection type version.

(<-#) :: Monad m => AssignTarget r v -> Projection Flat v -> Assignings r m ()

Add and assginment.

Direct Join Operators

Not monadic style join is supported by some direct join operators.

inner, left, right, full operators can construct join products directly like SQL. inner operator is INNER JOIN of SQL, left operator is LEFT OUTER JOIN of SQL, and so on. on' operator specifies condition of join product.

inner

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

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

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

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)

Apply restriction for direct join style.

Finalize Context

Several operators are defined to make Relation type with finalizing query monadic context.

relation operator finalizes flat (not aggregated) query monadic context, and aggregateRelation operator finalizes aggregated query monadic context. Both operator convert monadic context into Relation type, and finalized Relation can be reused as joining and sub-quering in another queries.

updateTarget operator finalize monadic context into UpdateTarget type which can be used as update statement.

restriction operator finalize monadic context into Restriction type which can be used as delete statement.

data Relation p r

Relation type with place-holder parameter p and query result type r.

Instances

Show (Relation p r) 

relation :: QuerySimple (Projection Flat r) -> Relation () r

Finalize QuerySimple monad and generate Relation.

data UpdateTarget p r

UpdateTarget type with place-holder parameter p and projection record type r.

updateTarget :: AssignStatement r () -> UpdateTarget () r

Finalize Target monad and generate UpdateTarget.

data Restriction p r

Restriction type with place-holder parameter p and projection record type r.

Instances

TableDerivable r => Show (Restriction p r)

Show where clause.

restriction :: RestrictedStatement r () -> Restriction () r

Finalize Restrict monad and generate Restriction.

Projection

SQL expression can be projected to haskell phantom type in this DSL.

Projection Type

Projection c t is SQL value type projection to haskell type with context type c correspond haskell type t.

Flat is not aggregated query context type, Aggregated is aggregated query context type, OverWindow is window function context type, and so on.

Module Database.Relational.Query.Context contains documentation of other context types.

data Projection c t

Phantom typed projection. Projected into Haskell record type t.

Instances

Projectable Projection Projection

Project from Projection into Projection.

Projectable Projection Expr

Project from Projection into Expr Projection.

SqlProjectable (Projection Flat)

Unsafely make Projection from SQL terms.

SqlProjectable (Projection Aggregated)

Unsafely make Projection from SQL terms.

SqlProjectable (Projection OverWindow)

Unsafely make Projection from SQL terms.

ProjectableShowSql (Projection c)

Unsafely get SQL term from Proejction.

ProjectableMaybe (Projection c)

Control phantom Maybe type in projection type Projection.

ProjectableFunctor (Projection c)

Compose seed of record type Projection.

ProjectableApplicative (Projection c)

Compose record type Projection using applicative style.

data Flat

Type tag for flat (not-aggregated) query

Instances

MonadQualify ConfigureQuery QueryAggregate

Instance to lift from qualified table forms into QueryAggregate.

MonadRestrict Flat q => MonadRestrict Flat (Restrictings Aggregated q)

Restricted MonadRestrict instance.

MonadQualify ConfigureQuery (Orderings Flat QueryCore)

Instance to lift from qualified table forms into QuerySimple.

SqlProjectable (Projection Flat)

Unsafely make Projection from SQL terms.

data Aggregated

Type tag for aggregated query

Instances

AggregatedContext Aggregated 
MonadQualify ConfigureQuery QueryAggregate

Instance to lift from qualified table forms into QueryAggregate.

MonadRestrict Flat q => MonadRestrict Flat (Restrictings Aggregated q)

Restricted MonadRestrict instance.

SqlProjectable (Projection Aggregated)

Unsafely make Projection from SQL terms.

data Exists

Type tag for exists predicate

data OverWindow

Type tag for window function building

Instances

AggregatedContext OverWindow 
SqlProjectable (Projection OverWindow)

Unsafely make Projection from SQL terms.

Projection Path

! operator is projected value selector using projection path type Pi r0 r1. Pi r0 r1 is projection path type selecting column type r1 from record type r0. <.> operator makes composed projection path from two projection paths.

data Pi r0 r1

Projection path from type r0 into type r1. This type also indicate key object which type is r1 for record type r0.

Instances

ProjectableFunctor (Pi a)

Compose seed of projection path Pi which has record result type.

ProjectableApplicative (Pi a)

Compose projection path Pi which has record result type using applicative style.

(!)

Arguments

:: Projectable Projection p 
=> Projection c a

Source projection

-> Pi a b

Projection path

-> p c b

Narrower projected object

Get narrower projection along with projection path and project into result projection type.

(<.>) :: Pi a b -> Pi b c -> Pi a c

Compose projection path.

Projection Operators

Some operators are defined to caluculate projected values.

For example, value operator projects from Haskell value into Projection corresponding SQL value, values operator projects from Haskell list value into ListProjection, corresponding SQL set value, .=. operator is equal compare operation of projected value correspond to SQL =, .+. operator is plus operation of projected value coresspond to SQL +, and so on.

Module Database.Relational.Query.Projectable contains documentation of other projection operators.

value :: (ShowConstantTermsSQL t, SqlProjectable p) => t -> p t

Generate polymorphic projection of SQL constant values from Haskell value.

values :: (ShowConstantTermsSQL t, SqlProjectable p) => [t] -> ListProjection p t

Polymorphic proejction of SQL set value from Haskell list.

(.=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Compare operator corresponding SQL = .

(.<.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Compare operator corresponding SQL < .

(.<=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Compare operator corresponding SQL <= .

(.>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Compare operator corresponding SQL > .

(.>=.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Compare operator corresponding SQL >= .

(.<>.) :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Compare operator corresponding SQL <> .

casesOrElse

Arguments

:: (SqlProjectable p, ProjectableShowSql p) 
=> [(p (Maybe Bool), p a)]

Each when clauses

-> p a

Else result projection

-> p a

Result projection

Same as caseSearch, but you can write like list casesOrElse clause.

case'

Arguments

:: (SqlProjectable p, ProjectableShowSql p) 
=> p a

Projection value to match

-> [(p a, p b)]

Each when clauses

-> p b

Else result projection

-> p b

Result projection

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

in' :: (SqlProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool)

Binary operator corresponding SQL IN .

and' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Logical operator corresponding SQL AND .

or' :: (SqlProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool)

Logical operator corresponding SQL OR .

isNothing :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)

Operator corresponding SQL IS NULL , and extended against record types.

isJust :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c (Maybe r) -> Projection c (Maybe Bool)

Operator corresponding SQL NOT (... IS NULL) , and extended against record type.

fromMaybe :: (SqlProjectable (Projection c), ProjectableShowSql (Projection c), HasColumnConstraint NotNull r) => Projection c r -> Projection c (Maybe r) -> Projection c r

Operator from maybe type using record extended isNull.

not' :: (SqlProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool)

Logical operator corresponding SQL NOT .

exists :: (SqlProjectable p, ProjectableShowSql p) => ListProjection (Projection Exists) r -> p (Maybe Bool)

Logical operator corresponding SQL EXISTS .

(.||.) :: (SqlProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p a

Concatinate operator corresponding SQL || .

(.+.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a

Number operator corresponding SQL + .

(.-.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a

Number operator corresponding SQL - .

(./.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a

Number operator corresponding SQL / .

(.*.) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a

Number operator corresponding SQL * .

negate' :: (SqlProjectable p, ProjectableShowSql p, Num a) => p a -> p a

Number negate uni-operator corresponding SQL -.

fromIntegral' :: (SqlProjectable p, ProjectableShowSql p, Integral a, Num b) => p a -> p b

Number fromIntegral uni-operator.

showNum :: (SqlProjectable p, ProjectableShowSql p, Num a, IsString b) => p a -> p b

Unsafely show number into string-like type in projections.

Aggregate and Window Functions

Typed aggregate function operators are defined. Aggregated value types is distinguished with Flat value types.

For example, sum' operator is aggregate function of projected flat (not aggregated) value correspond to SQL SUM(...), rank operator is window function of projected value coresspond to SQL RANK(), and so on.

Module Database.Relational.Query.Projectable contains documentation of other aggregate function operators and window function operators.

sum' :: (Num a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)

Aggregation function SUM.

avg :: (Num a, Fractional b, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe b)

Aggregation function AVG.

max' :: (Ord a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)

Aggregation function MAX.

min' :: (Ord a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac (Maybe a)

Aggregation function MIN.

every :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)

Aggregation function EVERY.

any' :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)

Aggregation function ANY.

some' :: (AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe Bool) -> p ac (Maybe Bool)

Aggregation function SOME.

denseRank :: Projection OverWindow Int64

DENSE_RANK() term.

rowNumber :: Projection OverWindow Int64

ROW_NUMBER() term.

percentRank :: Projection OverWindow Double

PERCENT_RANK() term.

cumeDist :: Projection OverWindow Double

CUME_DIST() term.

Set Operators

Several operators are defined to manipulate relation set.

union operator makes union relation set of two relation set correspond to SQL UNION. except operator makes difference relation set of two relation set correspond to SQL EXCEPT. intersect operator makes intersection relation set of two relation set correspond to SQL INTERSECT.

union :: Relation () a -> Relation () a -> Relation () a

Union of two relations.

except :: Relation () a -> Relation () a -> Relation () a

Subtraction of two relations.

intersect :: Relation () a -> Relation () a -> Relation () a

Intersection of two relations.

Maybe Projections

Maybe type flavor of operators against projection path, projection and aggregation are also provided.

For example, ?! operator is maybe flavor of !, <?.> operator is maybe flavor of <.>. ?!? opeartor and <?.?> operator join two Maybe phantom functors.

?+? operator is maybe flavor of .+., nagateMaybe operator is maybe flavor of nagate, sumMaybe operator is maybe flavor of sum'.

Module Database.Relational.Query.Projectable and Database.Relational.Query.ProjectableExtended contain documentation of other Maybe flavor projection operators.

(?!)

Arguments

:: Projectable Projection p 
=> Projection c (Maybe a)

Source Projection. Maybe type

-> Pi a b

Projection path

-> p c (Maybe b)

Narrower projected object. Maybe type result

Get narrower projection along with projection path and project into result projection type. Maybe phantom functor is map-ed.

(?!?)

Arguments

:: Projectable Projection p 
=> Projection c (Maybe a)

Source Projection. Maybe phantom type

-> Pi a (Maybe b)

Projection path. Maybe type leaf

-> p c (Maybe b)

Narrower projected object. Maybe phantom type result

Get narrower projection along with projection path and project into result projection type. Source record Maybe phantom functor and projection path leaf Maybe functor are join-ed.

(<?.>) :: Pi a (Maybe b) -> Pi b c -> Pi a (Maybe c)

Compose projection path. Maybe phantom functor is map-ed.

(<?.?>) :: Pi a (Maybe b) -> Pi b (Maybe c) -> Pi a (Maybe c)

Compose projection path. Maybe phantom functors are join-ed like >=>.

(?+?) :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a)

Number operator corresponding SQL + .

negateMaybe :: (SqlProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a)

Number negate uni-operator corresponding SQL -.

sumMaybe :: (Num a, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat (Maybe a) -> p ac (Maybe a)

Aggregation function SUM.

Placeholders

Placeholder flavor of operators against query operation and set operation are also provided, to realize type safe placeholder.

query', left', relation', updateTarget', restriction', and union' operator are placeholder flavor query, left, relation, updateTarget, restriction and union.

Module Database.Relational.Query.Relation and Database.Relational.Query.Effect contains documentation of other placeholder flavor operators.

query' :: MonadQualify ConfigureQuery m => Relation p r -> m (PlaceHolders p, Projection Flat r)

Join subquery with place-holder parameter p. query result is not Maybe.

left'

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.

relation' :: SimpleQuery p r -> Relation p r

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

updateTarget' :: AssignStatement r (PlaceHolders p) -> UpdateTarget p r

Finalize Target monad and generate UpdateTarget with place-holder parameter p.

restriction' :: RestrictedStatement r (PlaceHolders p) -> Restriction p r

Finalize Restrict monad and generate Restriction with place-holder parameter p

union' :: Relation p a -> Relation q a -> Relation (p, q) a

Union of two relations with place-holder parameters.

Database Statements

Some functions are defined to expand query structure into flat SQL statements to be used by database operation.

relationalQuery function converts Relation type info flat SQL query like SELECT statement.

typedInsert function converts Pi key type info flat SQL INSERT statement.

typedUpdate function converts UpdateTarget type into flat SQL UPDATE statement.

typedDelete function converts Restriction into flat SQL DELETE statement.

typedKeyUpdate function converts Pi key type info flat SQL UPDATE statement.

relationalQuery :: Relation p r -> Query p r

From Relation into typed Query.

typedInsert :: Table r -> Pi r r' -> Insert r'

Make typed Insert from Table and columns selector Pi.

typedUpdate :: Table r -> UpdateTarget p r -> Update p

Make typed Update from Table and Restriction.

typedDelete :: Table r -> Restriction p r -> Delete p

Make typed Delete from Table and Restriction.

typedKeyUpdate :: Table a -> Pi a p -> KeyUpdate p a

Make typed KeyUpdate from Table and key columns selector Pi.

Database Operations

Some HDBC actions are defined for database side effects.

Generalized Statement

Actions to manage generalized SQL statements.

prepareNoFetch :: (UntypeableNoFetch s, IConnection conn) => conn -> s p -> IO (PreparedStatement p ())

Generalized prepare inferred from UntypeableNoFetch instance.

bind :: ToSql SqlValue p => PreparedStatement p a -> p -> BoundStatement a

Typed operation to bind parameters. Infered RecordToSql is used.

execute :: BoundStatement a -> IO (ExecutedStatement a)

Typed execute operation.

executeNoFetch :: BoundStatement () -> IO Integer

Typed execute operation. Only get result.

Select

Actions to manage SELECT statements.

prepareQuery

Arguments

:: IConnection conn 
=> conn

Database connection

-> Query p a

Typed query

-> IO (PreparedQuery p a)

Result typed prepared query with parameter type p and result type a

Same as prepare.

fetch :: FromSql SqlValue a => ExecutedStatement a -> IO (Maybe a)

Fetch a record.

runQuery

Arguments

:: (IConnection conn, ToSql SqlValue p, FromSql SqlValue a) 
=> conn

Database connection

-> Query p a

Query to get record type a requires parameter p

-> p

Parameter type

-> IO [a]

Action to get records

Prepare SQL, bind parameters, execute statement and lazily fetch all records.

Insert Values

Actions to manage INSERT ... VALUES ... statements.

prepareInsert :: IConnection conn => conn -> Insert a -> IO (PreparedInsert a)

Same as prepare.

runInsert :: (IConnection conn, ToSql SqlValue a) => conn -> Insert a -> a -> IO Integer

Prepare insert statement, bind parameters, execute statement and get execution result.

Insert Select Results

Actions to manage INSERT ... SELECT ... statements.

runInsertQuery :: (IConnection conn, ToSql SqlValue p) => conn -> InsertQuery p -> p -> IO Integer

Prepare insert statement, bind parameters, execute statement and get execution result.

Update

Actions to manage UPDATE statements.

prepareUpdate :: IConnection conn => conn -> Update p -> IO (PreparedUpdate p)

Same as prepare.

runUpdate :: (IConnection conn, ToSql SqlValue p) => conn -> Update p -> p -> IO Integer

Prepare update statement, bind parameters, execute statement and get execution result.

Delete

Actions to manage DELETE statements.

prepareDelete :: IConnection conn => conn -> Delete p -> IO (PreparedDelete p)

Same as prepare.

runDelete :: (IConnection conn, ToSql SqlValue p) => conn -> Delete p -> p -> IO Integer

Prepare delete statement, bind parameters, execute statement and get execution result.

Update by Key

Actions to manage UPDATE statements which updates columns other than specified key of the records selected by specified key.

prepareKeyUpdate :: IConnection conn => conn -> KeyUpdate p a -> IO (PreparedKeyUpdate p a)

Same as prepare.

bindKeyUpdate :: ToSql SqlValue a => PreparedKeyUpdate p a -> a -> BoundStatement ()

Typed operation to bind parameters for PreparedKeyUpdate type.

runKeyUpdate :: (IConnection conn, ToSql SqlValue a) => conn -> KeyUpdate p a -> a -> IO Integer

Prepare insert statement, bind parameters, execute statement and get execution result.