relational-record-0.1.6.0: Meta package of Relational Record

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

Database.Relational.Query.Documentation

Contents

Description

This module is documentation module for relational record.

Synopsis

Concepts

User interface 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

Relational 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, and can be used only in MonadAggregate context.

wheres and having operators appends a new condition into whole query condition. having only accepts aggregated projection value, and can be used only in MonadRestrict Aggregated context.

distinct operator and all' operator specify SELECT DISTINCT or SELECT ALL, the last specified in monad is used.

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

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

Join sub-query. Query result is not Maybe.

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

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

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 not aggregated query.

groupBy :: MonadAggregate m => forall r. Projection Flat r -> m (Projection Aggregated r) #

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.

distinct :: MonadQuery m => m () #

Specify DISTINCT attribute to query context.

all' :: MonadQuery m => m () #

Specify ALL attribute to query context.

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

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. JoinRestriction is the type of lambda form which expresses condition of join product.

inner infixl 8 #

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 #

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 #

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 #

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 #

Apply restriction for direct join style.

type JoinRestriction a b = Projection Flat a -> Projection Flat b -> Projection Flat (Maybe Bool) #

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
     ...

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-querying 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) 

Methods

showsPrec :: Int -> Relation p r -> ShowS #

show :: Relation p r -> String #

showList :: [Relation p r] -> ShowS #

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.

Instances

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.

Methods

showsPrec :: Int -> Restriction p r -> ShowS #

show :: Restriction p r -> String #

showList :: [Restriction p r] -> ShowS #

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

OperatorProjectable (Projection Flat) 
OperatorProjectable (Projection Aggregated) 
SqlProjectable (Projection Flat)

Unsafely make Projection from SQL terms.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection Flat t #

SqlProjectable (Projection Aggregated)

Unsafely make Projection from SQL terms.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection Aggregated t #

SqlProjectable (Projection OverWindow)

Unsafely make Projection from SQL terms.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection OverWindow t #

ProjectableShowSql (Projection c)

Unsafely get SQL term from Proejction.

Methods

unsafeShowSql' :: Projection c a -> StringSQL #

ProjectableMaybe (Projection c)

Control phantom Maybe type in projection type Projection.

Methods

just :: Projection c a -> Projection c (Maybe a) #

flattenMaybe :: Projection c (Maybe (Maybe a)) -> Projection c (Maybe a) #

ProjectableFunctor (Projection c)

Compose seed of record type Projection.

Methods

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

ProjectableApplicative (Projection c)

Compose record type Projection using applicative style.

Methods

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

Show (Projection c t) 

Methods

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

show :: Projection c t -> String #

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

data Flat :: * #

Type tag for flat (not-aggregated) query

Instances

OperatorProjectable (Projection Flat) 
SqlProjectable (Projection Flat)

Unsafely make Projection from SQL terms.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection Flat t #

data Aggregated :: * #

Type tag for aggregated query

Instances

AggregatedContext Aggregated 
OperatorProjectable (Projection Aggregated) 
SqlProjectable (Projection Aggregated)

Unsafely make Projection from SQL terms.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection Aggregated t #

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.

Methods

unsafeProjectSqlTerms' :: [StringSQL] -> Projection OverWindow t #

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.

Methods

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

ProjectableApplicative (Pi a)

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

Methods

(|*|) :: Pi a (a -> b) -> Pi a a -> Pi a b #

(!) infixl 8 #

Arguments

:: Projection c a

Source projection

-> Pi a b

Projection path

-> Projection c b

Narrower projected object

Get narrower projection along with projection path.

(<.>) :: Pi a b -> Pi b c -> Pi a c infixl 8 #

Compose projection path.

Projection Operators

Some operators are defined to calculate 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 correspond to SQL +, and so on.

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

value :: (ShowConstantTermsSQL t, OperatorProjectable p) => t -> p t #

Generate polymorphic projection of SQL constant values from Haskell value.

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

Polymorphic proejction of SQL set value from Haskell list.

(.=.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 #

Compare operator corresponding SQL = .

(.<.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 #

Compare operator corresponding SQL < .

(.<=.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 #

Compare operator corresponding SQL <= .

(.>.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 #

Compare operator corresponding SQL > .

(.>=.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 #

Compare operator corresponding SQL >= .

(.<>.) :: (OperatorProjectable p, ProjectableShowSql p) => p ft -> p ft -> p (Maybe Bool) infix 4 #

Compare operator corresponding SQL <> .

and' :: (OperatorProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool) -> p (Maybe Bool) infixr 3 #

Logical operator corresponding SQL AND .

or' :: (OperatorProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool) -> p (Maybe Bool) infixr 2 #

Logical operator corresponding SQL OR .

in' :: (OperatorProjectable p, ProjectableShowSql p) => p t -> ListProjection p t -> p (Maybe Bool) infix 4 #

Binary operator corresponding SQL IN .

(.||.) :: (OperatorProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p a infixl 5 #

Concatinate operator corresponding SQL || .

like :: (OperatorProjectable p, ProjectableShowSql p, IsString a, ShowConstantTermsSQL a) => p a -> a -> p (Maybe Bool) infix 4 #

String-compare operator corresponding SQL LIKE .

like' :: (OperatorProjectable p, ProjectableShowSql p, IsString a) => p a -> p a -> p (Maybe Bool) infix 4 #

String-compare operator corresponding SQL LIKE .

(.+.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 6 #

Number operator corresponding SQL + .

(.-.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 6 #

Number operator corresponding SQL - .

(.*.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 7 #

Number operator corresponding SQL * .

(./.) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p a -> p a -> p a infixl 7 #

Number operator corresponding SQL /// .

isNothing :: (OperatorProjectable (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 :: (OperatorProjectable (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 :: (OperatorProjectable (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' :: (OperatorProjectable p, ProjectableShowSql p) => p (Maybe Bool) -> p (Maybe Bool) #

Logical operator corresponding SQL NOT .

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

Logical operator corresponding SQL EXISTS .

negate' :: (OperatorProjectable 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.

casesOrElse #

Arguments

:: (OperatorProjectable 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

:: (OperatorProjectable 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

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 correspond to SQL RANK(), and so on.

To convert window function result into normal projection, use the over operator with built Window monad.

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

count :: (Integral b, AggregatedContext ac, SqlProjectable (p ac)) => Projection Flat a -> p ac b #

Aggregation function COUNT.

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.

over :: SqlProjectable (Projection c) => Projection OverWindow a -> Window c () -> Projection c a infix 8 #

Operator to make window function result projection using built Window monad.

rank :: Integral a => Projection OverWindow a #

RANK() term.

denseRank :: Integral a => Projection OverWindow a #

DENSE_RANK() term.

rowNumber :: Integral a => Projection OverWindow a #

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 infixl 7 #

Union of two relations.

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

Subtraction of two relations.

intersect :: Relation () a -> Relation () a -> Relation () a infixl 8 #

Intersection of two relations.

Maybe Projections

Some operators are provided to manage projections with Maybe phantom type.

just operator creates Maybe typed projection, flattenMaybe operator joins nested Maybe typed projection.

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 <.>. ?!? operator and <?.?> operator join two Maybe phantom functors.

?+? operator is maybe flavor of .+., negateMaybe operator is maybe flavor of negate', 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.

just :: ProjectableMaybe p => forall a. p a -> p (Maybe a) #

Cast projection phantom type into Maybe.

flattenMaybe :: ProjectableMaybe p => forall a. p (Maybe (Maybe a)) -> p (Maybe a) #

Compose nested Maybe phantom type on projection.

(?!) infixl 8 #

Arguments

:: Projection c (Maybe a)

Source Projection. Maybe type

-> Pi a b

Projection path

-> Projection c (Maybe b)

Narrower projected object. Maybe type result

Get narrower projection along with projection path Maybe phantom functor is map-ed.

(?!?) infixl 8 #

Arguments

:: Projection c (Maybe a)

Source Projection. Maybe phantom type

-> Pi a (Maybe b)

Projection path. Maybe type leaf

-> Projection 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) infixl 8 #

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

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

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

(?+?) :: (OperatorProjectable p, ProjectableShowSql p, Num a) => p (Maybe a) -> p (Maybe a) -> p (Maybe a) infixl 6 #

Number operator corresponding SQL + .

negateMaybe :: (OperatorProjectable 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

placeholders operator takes a lambda-form which argument is Projection typed placeholders and its scope is restricted by that lambda-form and then creates dummy value with Placeholders typed which propagate placeholder type information into Relation layer.

Placeholders' flavor of operators against query operation and set operation are also provided, to realize type safe placeholders.

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

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

placeholder :: (PersistableWidth t, SqlProjectable p, Monad m) => (p t -> m a) -> m (PlaceHolders t, a) #

Provide scoped placeholder and return its parameter object. Monadic version.

query' :: MonadQuery m => forall p r. Relation p r -> m (PlaceHolders p, Projection Flat r) #

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

left' infixl 8 #

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 infixl 7 #

Union of two relations with place-holder parameters.

Record Mapping

Applicative style record mapping is supported, for Projection, Pi and PlaceHolders. |$| operator can be used on ProjectableFunctor context, and |*| operator can be used on ProjectableApplicative context with ProductConstructor, like Foo |$| projection1 |*| projection2 |*| projection3 , Foo |$| placeholders1 |*| placeholders2 |*| placeholders3, and so on.

>< operator constructs pair result. x >< y is the same as (,) |$| x |*| y.

class ProductConstructor r #

Specify tuple like record constructors which are allowed to define ProjectableFunctor.

Minimal complete definition

productConstructor

Instances

ProductConstructor (a -> b -> (a, b))

ProductConstructor instance of pair.

Methods

productConstructor :: a -> b -> (a, b) #

class ProjectableFunctor p where #

Weaken functor on projections.

Minimal complete definition

(|$|)

Methods

(|$|) :: ProductConstructor (a -> b) => (a -> b) -> p a -> p b infixl 4 #

Method like fmap.

Instances

ProjectableFunctor PlaceHolders

Compose seed of record type PlaceHolders.

Methods

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

ProjectableFunctor (Projection c)

Compose seed of record type Projection.

Methods

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

ProjectableFunctor (Pi a)

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

Methods

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

class ProjectableFunctor p => ProjectableApplicative p where #

Weaken applicative functor on projections.

Minimal complete definition

(|*|)

Methods

(|*|) :: p (a -> b) -> p a -> p b infixl 4 #

Method like <*>.

Instances

ProjectableApplicative PlaceHolders

Compose record type PlaceHolders using applicative style.

Methods

(|*|) :: PlaceHolders (a -> b) -> PlaceHolders a -> PlaceHolders b #

ProjectableApplicative (Projection c)

Compose record type Projection using applicative style.

Methods

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

ProjectableApplicative (Pi a)

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

Methods

(|*|) :: Pi a (a -> b) -> Pi a a -> Pi a b #

(><) :: ProjectableApplicative p => p a -> p b -> p (a, b) infixl 1 #

Binary operator the same as projectZip.

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.

typedInsertQuery function converts Pi key type and Relation type info flat SQL INSERT ... SELECT ... 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.

Some handy table type inferred functions are provided, derivedInsert, derivedInsertQuery, derivedUpdate and derivedDelete.

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.

typedInsertQuery :: Table r -> Pi r r' -> Relation p r' -> InsertQuery p #

Make typed InsertQuery from columns selector Table, Pi and Relation.

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.

derivedInsert :: TableDerivable r => Pi r r' -> Insert r' #

Table type inferred Insert.

derivedInsertQuery :: TableDerivable r => Pi r r' -> Relation p r' -> InsertQuery p #

Table type inferred InsertQuery.

derivedDelete :: TableDerivable r => RestrictedStatement r (PlaceHolders p) -> Delete p #

Make typed Delete from defaultConfig, derived table and RestrictContext

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.