relational-record-0.1.8.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. The project page of relational-record is http://khibino.github.io/haskell-relational-record/ .

Synopsis

Concepts

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

Database.Relational.Query
Relational Query Building DSL
Database.Record and 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) #

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

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

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

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

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

distinct :: MonadQuery m => m () #

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

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

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 :: Relation () a -> Relation () b -> [JoinRestriction a b] -> Relation () (a, b) #

left :: Relation () a -> Relation () b -> [JoinRestriction a (Maybe b)] -> Relation () (a, Maybe b) #

right :: Relation () a -> Relation () b -> [JoinRestriction (Maybe a) b] -> Relation () (Maybe a, b) #

full :: Relation () a -> Relation () b -> [JoinRestriction (Maybe a) (Maybe b)] -> Relation () (Maybe a, Maybe b) #

on' :: ([JoinRestriction a b] -> Relation pc (a, b)) -> [JoinRestriction a b] -> Relation pc (a, b) #

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 :: * -> * -> * #

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 #

aggregateRelation :: QueryAggregate (Projection Aggregated r) -> Relation () r #

data UpdateTarget p r :: * -> * -> * #

Instances

TableDerivable r => Show (UpdateTarget p r) 

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

data Restriction p r :: * -> * -> * #

Instances

TableDerivable r => Show (Restriction p r) 

Methods

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

show :: Restriction p r -> String #

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

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

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 :: * -> * -> * #

Instances

SqlProjectable (Projection OverWindow) 

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Projection OverWindow t

SqlProjectable (Projection Flat) 

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Projection Flat t

SqlProjectable (Projection Aggregated) 

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Projection Aggregated t

ProjectableShowSql (Projection c) 

Methods

unsafeShowSql' :: Projection c a -> StringSQL

ProjectableMaybe (Projection c) 

Methods

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

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

OperatorProjectable (Projection Flat) 
OperatorProjectable (Projection Aggregated) 
Show (Projection c t) 

Methods

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

show :: Projection c t -> String #

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

data Flat :: * #

Instances

SqlProjectable (Projection Flat) 

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Projection Flat t

OperatorProjectable (Projection Flat) 

data Aggregated :: * #

Instances

AggregatedContext Aggregated 
SqlProjectable (Projection Aggregated) 

Methods

unsafeProjectSqlTerms :: [StringSQL] -> Projection Aggregated t

OperatorProjectable (Projection Aggregated) 

data Exists :: * #

data OverWindow :: * #

Instances

AggregatedContext OverWindow 
SqlProjectable (Projection OverWindow) 

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 :: * -> * -> * #

Instances

ProjectableFunctor (Pi a) 

Methods

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

ProjectableApplicative (Pi a) 

Methods

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

Category * Pi 

Methods

id :: cat a a #

(.) :: cat b c -> cat a b -> cat a c #

PersistableWidth r0 => Show (Pi r0 r1) 

Methods

showsPrec :: Int -> Pi r0 r1 -> ShowS #

show :: Pi r0 r1 -> String #

showList :: [Pi r0 r1] -> ShowS #

(!) :: PersistableWidth a => Projection c a -> Pi a b -> Projection c b #

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

Projection Operators

Some operators are defined to calculate projected values.

For example, value operator projects from Haskell value into Projection corresponding SQL row value, which projection is implicitly specified by ShowConstantTermsSQL class. Generic programming with default signature is available to define instances of ShowConstantTermsSQL.

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 #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

casesOrElse :: OperatorProjectable (Projection c) => [(Projection c (Maybe Bool), Projection c a)] -> Projection c a -> Projection c a #

case' :: OperatorProjectable (Projection c) => Projection c a -> [(Projection c a, Projection c b)] -> Projection c b -> Projection c b #

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 #

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

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

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

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

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

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

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

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

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 #

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

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

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

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

(?!) :: PersistableWidth a => Projection c (Maybe a) -> Pi a b -> Projection c (Maybe b) #

(?!?) :: PersistableWidth a => Projection c (Maybe a) -> Pi a (Maybe b) -> Projection c (Maybe b) #

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

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

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

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

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

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

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

left' :: Relation pa a -> Relation pb b -> [JoinRestriction a (Maybe b)] -> Relation (pa, pb) (a, Maybe b) #

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

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

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

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

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 #

Minimal complete definition

productConstructor

class ProjectableFunctor p where #

Minimal complete definition

(|$|)

Methods

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

Instances

ProjectableFunctor PlaceHolders 

Methods

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

ProjectableFunctor (Pi a) 

Methods

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

class ProjectableFunctor p => ProjectableApplicative p where #

Minimal complete definition

(|*|)

Methods

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

Instances

ProjectableApplicative PlaceHolders 

Methods

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

ProjectableApplicative (Pi a) 

Methods

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

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

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 #

typedInsert :: PersistableWidth r => Table r -> Pi r r' -> Insert r' #

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

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

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

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

derivedInsert :: (PersistableWidth r, TableDerivable r) => Pi r r' -> Insert r' #

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

derivedUpdate :: TableDerivable r => AssignStatement r (PlaceHolders p) -> Update p #

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

Database Operations

Some HDBC actions are defined for database side effects.

Conversion interfaces to communicate with database

Some record conversion interfaces are defined to communicate with database.

The conversions are implicitly specified by FromSql class and ToSql class. Generic programming with default signature is available to define instances of FromSql and ToSql.

The explicit definitions correnponsing those classes are RecordFromSql and RecordToSql.

class FromSql q a #

Instances

FromSql q () 
(HasColumnConstraint NotNull a, FromSql q a, PersistableType q) => FromSql q (Maybe a) 

class PersistableWidth a => ToSql q a #

Instances

ToSql q () 

Methods

recordToSql :: RecordToSql q ()

(PersistableType q, ToSql q a) => ToSql q (Maybe a) 

Methods

recordToSql :: RecordToSql q (Maybe a)

data RecordFromSql q a :: * -> * -> * #

Instances

Monad (RecordFromSql q) 

Methods

(>>=) :: RecordFromSql q a -> (a -> RecordFromSql q b) -> RecordFromSql q b #

(>>) :: RecordFromSql q a -> RecordFromSql q b -> RecordFromSql q b #

return :: a -> RecordFromSql q a #

fail :: String -> RecordFromSql q a #

Functor (RecordFromSql q) 

Methods

fmap :: (a -> b) -> RecordFromSql q a -> RecordFromSql q b #

(<$) :: a -> RecordFromSql q b -> RecordFromSql q a #

Applicative (RecordFromSql q) 

Methods

pure :: a -> RecordFromSql q a #

(<*>) :: RecordFromSql q (a -> b) -> RecordFromSql q a -> RecordFromSql q b #

(*>) :: RecordFromSql q a -> RecordFromSql q b -> RecordFromSql q b #

(<*) :: RecordFromSql q a -> RecordFromSql q b -> RecordFromSql q a #

data RecordToSql q a :: * -> * -> * #

Generalized Statement

Actions to manage generalized SQL statements.

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

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

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

executeNoFetch :: BoundStatement () -> IO Integer #

Select

Actions to manage SELECT statements.

runQuery function is lazy-read and runQuery' function is strict version, please use carefully.

prepareQuery :: IConnection conn => conn -> Query p a -> IO (PreparedQuery p a) #

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

runQuery :: (IConnection conn, ToSql SqlValue p, FromSql SqlValue a) => conn -> Query p a -> p -> IO [a] #

runQuery' :: (IConnection conn, ToSql SqlValue p, FromSql SqlValue a) => conn -> Query p a -> p -> IO [a] #

Insert Values

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

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

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

Insert Select Results

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

prepareInsertQuery :: IConnection conn => conn -> InsertQuery p -> IO (PreparedInsertQuery p) #

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

Update

Actions to manage UPDATE statements.

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

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

Delete

Actions to manage DELETE statements.

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

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

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

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

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