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

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

Database.Relational

Description

This module is integrated module of Query.

Synopsis

Documentation

class PersistableWidth r => TableDerivable r where Source #

Inference rule of Table existence.

data Table r Source #

Phantom typed table type

Instances
Show (Table r) Source # 
Instance details

Defined in Database.Relational.Table

Methods

showsPrec :: Int -> Table r -> ShowS #

show :: Table r -> String #

showList :: [Table r] -> ShowS #

type QuerySuffix = [Keyword] Source #

Type for query suffix words

updateOtherThanKeySQL Source #

Arguments

:: Table r

Table metadata

-> Pi r p

Key columns

-> String

Result SQL

Generate update SQL specified by single key.

data Unique #

Constraint type. Unique key.

data NotNull #

Constraint type. Not-null key.

Instances
HasColumnConstraint NotNull a => HasColumnConstraint NotNull (a, b)

Inference rule of ColumnConstraint NotNull for tuple (,) type.

Instance details

Defined in Database.Record.KeyConstraint

data Primary #

Constraint type. Primary key.

class PersistableWidth ct => HasConstraintKey c r ct where Source #

Constraint Key inference interface.

Methods

constraintKey :: Key c r ct Source #

Infer constraint key.

data Key c r ct Source #

Constraint Key proof object. Constraint type c, record type r and columns type ct.

tableConstraint :: Key c r ct -> KeyConstraint c r Source #

Get table constraint KeyConstraint proof object from constraint Key.

projectionKey :: Key c r ct -> Pi r ct Source #

Get projection path proof object from constraint Key.

uniqueKey :: PersistableWidth ct => Key Primary r ct -> Key Unique r ct Source #

Derive Unique constraint Key from Primary constraint Key

derivedUniqueKey :: HasConstraintKey Primary r ct => Key Unique r ct Source #

Inferred Unique constraint Key. Record type r has unique key which type is ct derived from primay key.

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

Type for projection function.

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

Type for predicate to restrict of query result.

data Record c t Source #

Phantom typed record. Projected into Haskell record type t.

Instances
(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 #

data SubQuery Source #

Sub-query type

Instances
Show SubQuery Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

data AggregateKey a Source #

Typeful aggregate element.

data Nulls Source #

Order of null.

Constructors

NullsFirst 
NullsLast 
Instances
Show Nulls Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Nulls -> ShowS #

show :: Nulls -> String #

showList :: [Nulls] -> ShowS #

data Order Source #

Order direction. Ascendant or Descendant.

Constructors

Asc 
Desc 
Instances
Show Order Source # 
Instance details

Defined in Database.Relational.SqlSyntax.Types

Methods

showsPrec :: Int -> Order -> ShowS #

show :: Order -> String #

showList :: [Order] -> ShowS #

unitSQL :: SubQuery -> String Source #

SQL string for nested-qeury.

data RecordList p t Source #

Projected record list type for row list.

list :: [p t] -> RecordList p t Source #

Make projected record list from Record list.

class Monad m => MonadPartition c m where Source #

Window specification building interface.

Methods

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

Add PARTITION BY term into context.

Instances
MonadPartition c m => MonadPartition c (Orderings c m) Source #

MonadPartition with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

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

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 #

class MonadQuery m => MonadAggregate m where Source #

Aggregated query building interface extends MonadQuery.

Methods

groupBy Source #

Arguments

:: Record Flat r

Record to add into group by

-> m (Record Aggregated r)

Result context and aggregated record | Add GROUP BY term into context and get aggregated record. Non-traditional group-by version.

Add GROUP BY term into context and get aggregated record.

groupBy' Source #

Arguments

:: AggregateKey (Record Aggregated r)

Key to aggretate for non-traditional group-by interface

-> m (Record Aggregated r)

Result context and aggregated record

class (Functor q, Monad q, Functor m, Monad m) => MonadQualify q m Source #

Lift interface from base qualify monad.

Minimal complete definition

liftQualify

Instances
(Functor q, Monad q) => MonadQualify q q Source # 
Instance details

Defined in Database.Relational.Monad.Class

Methods

liftQualify :: q a -> q a Source #

MonadQualify ConfigureQuery QueryUnique Source # 
Instance details

Defined in Database.Relational.Monad.Unique

MonadQualify q m => MonadQualify q (QueryJoin m) Source # 
Instance details

Defined in Database.Relational.Monad.Trans.Join

Methods

liftQualify :: q a -> QueryJoin m a Source #

MonadQualify q m => MonadQualify q (AggregatingSetT m) Source #

Aggregated MonadQualify.

Instance details

Defined in Database.Relational.Monad.Trans.Aggregating

Methods

liftQualify :: q a -> AggregatingSetT m a Source #

MonadQualify q m => MonadQualify q (Restrictings c m) Source #

Restricted MonadQualify instance.

Instance details

Defined in Database.Relational.Monad.Trans.Restricting

Methods

liftQualify :: q a -> Restrictings c m a Source #

MonadQualify q m => MonadQualify q (Orderings c m) Source #

MonadQualify with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

liftQualify :: q a -> Orderings c m a Source #

MonadQualify q m => MonadQualify q (Assignings r m) Source #

MonadQualify with assigning.

Instance details

Defined in Database.Relational.Monad.Trans.Assigning

Methods

liftQualify :: q a -> Assignings r m a Source #

class (Functor m, Monad m, MonadQualify ConfigureQuery m) => MonadQuery m where Source #

Query building interface.

Minimal complete definition

setDuplication, restrictJoin, query', queryMaybe'

Methods

query' :: Relation p r -> m (PlaceHolders p, Record Flat r) Source #

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

queryMaybe' :: Relation p r -> m (PlaceHolders p, Record Flat (Maybe r)) Source #

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

Instances
MonadQuery QueryUnique Source # 
Instance details

Defined in Database.Relational.Monad.Unique

MonadQuery (QueryJoin ConfigureQuery) Source #

Joinable query instance.

Instance details

Defined in Database.Relational.Monad.Trans.Join

MonadQuery m => MonadQuery (AggregatingSetT m) Source #

Aggregated MonadQuery.

Instance details

Defined in Database.Relational.Monad.Trans.Aggregating

MonadQuery q => MonadQuery (Restrictings c q) Source #

Restricted MonadQuery instance.

Instance details

Defined in Database.Relational.Monad.Trans.Restricting

MonadQuery m => MonadQuery (Orderings c m) Source #

MonadQuery with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

class (Functor m, Monad m) => MonadRestrict c m where Source #

Restrict context interface

Methods

restrict Source #

Arguments

:: Predicate c

Record which represent restriction

-> m ()

Restricted query context

Add restriction to this context.

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

Specify ALL attribute to query context.

distinct :: MonadQuery m => m () Source #

Specify DISTINCT attribute to query context.

on :: MonadQuery m => Predicate Flat -> m () Source #

Add restriction to last join. Record type version.

wheres :: MonadRestrict Flat m => Predicate Flat -> m () Source #

Add restriction to this not aggregated query.

having :: MonadRestrict Aggregated m => Predicate Aggregated -> m () Source #

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

data Orderings c m a Source #

Type to accumulate ordering context. Type c is ordering term record context type.

Instances
MonadPartition c m => MonadPartition c (Orderings c m) Source #

MonadPartition with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

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

MonadQualify q m => MonadQualify q (Orderings c m) Source #

MonadQualify with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

liftQualify :: q a -> Orderings c m a Source #

MonadRestrict rc m => MonadRestrict rc (Orderings c m) Source #

MonadRestrict with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

restrict :: Predicate rc -> Orderings c m () Source #

MonadTrans (Orderings c) Source # 
Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

lift :: Monad m => m a -> Orderings c m a #

Monad m => Monad (Orderings c m) Source # 
Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

(>>=) :: Orderings c m a -> (a -> Orderings c m b) -> Orderings c m b #

(>>) :: Orderings c m a -> Orderings c m b -> Orderings c m b #

return :: a -> Orderings c m a #

fail :: String -> Orderings c m a #

Functor m => Functor (Orderings c m) Source # 
Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

fmap :: (a -> b) -> Orderings c m a -> Orderings c m b #

(<$) :: a -> Orderings c m b -> Orderings c m a #

Applicative m => Applicative (Orderings c m) Source # 
Instance details

Defined in Database.Relational.Monad.Trans.Ordering

Methods

pure :: a -> Orderings c m a #

(<*>) :: Orderings c m (a -> b) -> Orderings c m a -> Orderings c m b #

liftA2 :: (a -> b -> c0) -> Orderings c m a -> Orderings c m b -> Orderings c m c0 #

(*>) :: Orderings c m a -> Orderings c m b -> Orderings c m b #

(<*) :: Orderings c m a -> Orderings c m b -> Orderings c m a #

MonadAggregate m => MonadAggregate (Orderings c m) Source #

MonadAggregate with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

MonadQuery m => MonadQuery (Orderings c m) Source #

MonadQuery with ordering.

Instance details

Defined in Database.Relational.Monad.Trans.Ordering

orderBy' Source #

Arguments

:: Monad m 
=> Record c t

Ordering terms to add

-> Order

Order direction

-> Nulls

Order of null

-> Orderings c m ()

Result context with ordering

Add ordering terms with null ordering.

orderBy Source #

Arguments

:: Monad m 
=> Record c t

Ordering terms to add

-> Order

Order direction

-> Orderings c m ()

Result context with ordering

Add ordering terms.

asc Source #

Arguments

:: Monad m 
=> Record c t

Ordering terms to add

-> Orderings c m ()

Result context with ordering

Add ascendant ordering term.

desc Source #

Arguments

:: Monad m 
=> Record c t

Ordering terms to add

-> Orderings c m ()

Result context with ordering

Add descendant ordering term.

key :: Record Flat r -> AggregatingSet (Record Aggregated (Maybe r)) Source #

Specify key of single grouping set from Record.

key' :: AggregateKey a -> AggregatingSet a Source #

Specify key of single grouping set.

set :: AggregatingSet a -> AggregatingSetList a Source #

Finalize and specify single grouping set.

bkey :: Record Flat r -> AggregatingPowerSet (Record Aggregated (Maybe r)) Source #

Specify key of rollup and cube power set.

rollup :: AggregatingPowerSet a -> AggregateKey a Source #

Finalize grouping power set as rollup power set.

cube :: AggregatingPowerSet a -> AggregateKey a Source #

Finalize grouping power set as cube power set.

groupingSets :: AggregatingSetList a -> AggregateKey a Source #

Finalize grouping set list.

assignTo :: Monad m => Record Flat v -> AssignTarget r v -> Assignings r m () Source #

Add an assignment.

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

Add and assginment.

type SimpleQuery p r = OrderedQuery Flat QueryCore p r Source #

Simple (not-aggregated) query type. SimpleQuery' p r == QuerySimple (PlaceHolders p, Record r).

type QuerySimple = Orderings Flat QueryCore Source #

Simple (not-aggregated) query monad type.

type Window c = Orderings c (PartitioningSet c) Source #

Partition monad type for partition-by clause.

over :: SqlContext c => Record OverWindow a -> Window c () -> Record c a infix 8 Source #

Operator to make record of window function result using built Window monad.

type Restrict = Restrictings Flat ConfigureQuery Source #

Restrict only monad type used from update statement and delete statement.

type Assign r = Assignings r Restrict Source #

Target update monad type used from update statement and merge statement.

type Register r = Assignings r ConfigureQuery Source #

Target register monad type used from insert statement.

class PersistableWidth ct => ScalarDegree ct Source #

Constraint which represents scalar degree.

Instances
ScalarDegree ct => ScalarDegree (Maybe ct) Source # 
Instance details

Defined in Database.Relational.Scalar

class UntypeableNoFetch s where Source #

Untype interface for typed no-result type statments with single type parameter which represents place-holder parameter p.

Methods

untypeNoFetch :: s p -> String Source #

newtype Delete p Source #

Delete type with place-holder parameter p.

Constructors

Delete 

Fields

Instances
UntypeableNoFetch Delete Source # 
Instance details

Defined in Database.Relational.Type

Show (Delete p) Source #

Show delete SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Delete p -> ShowS #

show :: Delete p -> String #

showList :: [Delete p] -> ShowS #

newtype InsertQuery p Source #

InsertQuery type.

Constructors

InsertQuery 
Instances
UntypeableNoFetch InsertQuery Source # 
Instance details

Defined in Database.Relational.Type

Show (InsertQuery p) Source #

Show insert SQL string.

Instance details

Defined in Database.Relational.Type

data Insert a Source #

Insert type to insert record type a.

Constructors

Insert 
Instances
UntypeableNoFetch Insert Source # 
Instance details

Defined in Database.Relational.Type

Show (Insert a) Source #

Show insert SQL string.

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Insert a -> ShowS #

show :: Insert a -> String #

showList :: [Insert a] -> ShowS #

newtype Update p Source #

Update type with place-holder parameter p.

Constructors

Update 

Fields

Instances
UntypeableNoFetch Update Source # 
Instance details

Defined in Database.Relational.Type

Show (Update p) Source #

Show update SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Update p -> ShowS #

show :: Update p -> String #

showList :: [Update p] -> ShowS #

data KeyUpdate p a Source #

Update type with key type p and update record type a. Columns to update are record columns other than key columns, So place-holder parameter type is the same as record type a.

Constructors

KeyUpdate 

Fields

Instances
Show (KeyUpdate p a) Source #

Show update SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> KeyUpdate p a -> ShowS #

show :: KeyUpdate p a -> String #

showList :: [KeyUpdate p a] -> ShowS #

newtype Query p a Source #

Query type with place-holder parameter p and query result type a.

Constructors

Query 

Fields

Instances
Show (Query p a) Source #

Show query SQL string

Instance details

Defined in Database.Relational.Type

Methods

showsPrec :: Int -> Query p a -> ShowS #

show :: Query p a -> String #

showList :: [Query p a] -> ShowS #

unsafeTypedQuery Source #

Arguments

:: String

Query SQL to type

-> Query p a

Typed result

Unsafely make typed Query from SQL string.

relationalQuerySQL :: Config -> Relation p r -> QuerySuffix -> String Source #

From Relation into untyped SQL query string.

relationalQuery_ :: Config -> Relation p r -> QuerySuffix -> Query p r Source #

From Relation into typed Query with suffix SQL words.

relationalQuery' :: Relation p r -> QuerySuffix -> Query p r Source #

From Relation into typed Query with suffix SQL words.

relationalQuery :: Relation p r -> Query p r Source #

From Relation into typed Query.

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

Make typed KeyUpdate from Table and key columns selector Pi.

typedKeyUpdateTable :: TableDerivable r => Relation () r -> Pi r p -> KeyUpdate p r Source #

Make typed KeyUpdate object using derived info specified by Relation type.

keyUpdate :: TableDerivable r => Pi r p -> KeyUpdate p r Source #

Make typed KeyUpdate from derived table and key columns selector Pi.

derivedKeyUpdate :: TableDerivable r => Pi r p -> KeyUpdate p r Source #

Deprecated: use keyUpdate instead of this.

Make typed KeyUpdate from derived table and key columns selector Pi.

unsafeTypedUpdate :: String -> Update p Source #

Unsafely make typed Update from SQL string.

updateSQL :: Config -> Table r -> (Record Flat r -> Assign r (PlaceHolders p)) -> String Source #

Make untyped update SQL string from Table and Assign computation.

typedUpdate' :: Config -> Table r -> (Record Flat r -> Assign r (PlaceHolders p)) -> Update p Source #

Make typed Update from Config, Table and Assign computation.

typedUpdate :: Table r -> (Record Flat r -> Assign r (PlaceHolders p)) -> Update p Source #

Deprecated: use typedUpdate defaultConfig` instead of this.

Make typed Update using defaultConfig, Table and Assign computation.

update' :: TableDerivable r => Config -> (Record Flat r -> Assign r (PlaceHolders p)) -> Update p Source #

Make typed Update from Config, derived table and Assign computation.

derivedUpdate' :: TableDerivable r => Config -> (Record Flat r -> Assign r (PlaceHolders p)) -> Update p Source #

Deprecated: use update' instead of this.

Make typed Update from Config, derived table and Assign computation.

update :: TableDerivable r => (Record Flat r -> Assign r (PlaceHolders p)) -> Update p Source #

Make typed Update from defaultConfig, derived table and Assign computation.

updateNoPH :: TableDerivable r => (Record Flat r -> Assign r ()) -> Update () Source #

Make typed Update from defaultConfig, derived table and Assign computation with no(unit) placeholder.

derivedUpdate :: TableDerivable r => (Record Flat r -> Assign r (PlaceHolders p)) -> Update p Source #

Deprecated: use update instead of this.

Make typed Update from defaultConfig, derived table and Assign computation.

typedUpdateAllColumn :: PersistableWidth r => Table r -> (Record Flat r -> Restrict (PlaceHolders p)) -> Update (r, p) Source #

Make typed Update from Table and Restrict computation. Update target is all column.

updateAllColumn' :: (PersistableWidth r, TableDerivable r) => Config -> (Record Flat r -> Restrict (PlaceHolders p)) -> Update (r, p) Source #

Make typed Update from Config, derived table and Restrict computation. Update target is all column.

derivedUpdateAllColumn' :: (PersistableWidth r, TableDerivable r) => Config -> (Record Flat r -> Restrict (PlaceHolders p)) -> Update (r, p) Source #

Deprecated: use updateAllColumn' instead of this.

Deprecated. use updateAllColumn'.

updateAllColumn :: (PersistableWidth r, TableDerivable r) => (Record Flat r -> Restrict (PlaceHolders p)) -> Update (r, p) Source #

Make typed Update from defaultConfig, derived table and Restrict computation. Update target is all column.

updateAllColumnNoPH :: (PersistableWidth r, TableDerivable r) => (Record Flat r -> Restrict ()) -> Update r Source #

Make typed Update from defaultConfig, derived table and Restrict computation without placeholder other than target table columns. Update target is all column.

derivedUpdateAllColumn :: (PersistableWidth r, TableDerivable r) => (Record Flat r -> Restrict (PlaceHolders p)) -> Update (r, p) Source #

Deprecated: use updateAllColumn instead of this.

Deprecated. use updateAllColumn.

untypeChunkInsert :: Insert a -> String Source #

Statement to use chunked insert

chunkSizeOfInsert :: Insert a -> Int Source #

Size to use chunked insert

unsafeTypedInsert' :: String -> String -> Int -> Insert a Source #

Unsafely make typed Insert from single insert and chunked insert SQL.

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

Make typed Insert from Table and columns selector Pi with configuration parameter.

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

Deprecated: use typedInsert defaultConfig` instead of this.

Make typed Insert from Table and columns selector Pi.

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

Table type inferred Insert.

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

Deprecated: use insert instead of this.

Table type inferred Insert.

typedInsertValue' :: Config -> Table r -> InsertTarget p r -> Insert p Source #

Make typed Insert from Config, Table and monadic builded InsertTarget object.

typedInsertValue :: Table r -> InsertTarget p r -> Insert p Source #

Deprecated: use typedInsertValue defaultConfig` instead of this.

Make typed Insert from Table and monadic builded InsertTarget object.

insertValue' :: TableDerivable r => Config -> Register r (PlaceHolders p) -> Insert p Source #

Make typed Insert from Config, derived table and monadic builded Register object.

derivedInsertValue' :: TableDerivable r => Config -> Register r (PlaceHolders p) -> Insert p Source #

Deprecated: use insertValue' instead of this.

Make typed Insert from Config, derived table and monadic builded Register object.

insertValue :: TableDerivable r => Register r (PlaceHolders p) -> Insert p Source #

Make typed Insert from defaultConfig, derived table and monadic builded Register object.

insertValueNoPH :: TableDerivable r => Register r () -> Insert () Source #

Make typed Insert from defaultConfig, derived table and monadic builded Register object with no(unit) placeholder.

derivedInsertValue :: TableDerivable r => Register r (PlaceHolders p) -> Insert p Source #

Deprecated: use insertValue instead of this.

Make typed Insert from defaultConfig, derived table and monadic builded Register object.

insertValueList' :: (TableDerivable r, LiteralSQL r') => Config -> Pi r r' -> [r'] -> [Insert ()] Source #

Make typed Insert list from Config and records list.

insertValueList :: (TableDerivable r, LiteralSQL r') => Pi r r' -> [r'] -> [Insert ()] Source #

Make typed Insert list from records list.

insertQuerySQL :: Config -> Table r -> Pi r r' -> Relation p r' -> String Source #

Make untyped insert select SQL string from Table, Pi and Relation.

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

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

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

Deprecated: use typedInsertQuery defaultConfig` instead of this.

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

insertQuery' :: TableDerivable r => Config -> Pi r r' -> Relation p r' -> InsertQuery p Source #

Table type inferred InsertQuery.

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

Table type inferred InsertQuery with defaultConfig.

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

Deprecated: use insertQuery instead of this.

Table type inferred InsertQuery.

deleteSQL :: Config -> Table r -> (Record Flat r -> Restrict (PlaceHolders p)) -> String Source #

Make untyped delete SQL string from Table and Restrict computation.

typedDelete' :: Config -> Table r -> (Record Flat r -> Restrict (PlaceHolders p)) -> Delete p Source #

Make typed Delete from Config, Table and Restrict computation.

typedDelete :: Table r -> (Record Flat r -> Restrict (PlaceHolders p)) -> Delete p Source #

Deprecated: use typedDelete defaultConfig` instead of this.

Make typed Delete from Table and Restrict computation.

delete' :: TableDerivable r => Config -> (Record Flat r -> Restrict (PlaceHolders p)) -> Delete p Source #

Make typed Delete from Config, derived table and Restrict computation.

derivedDelete' :: TableDerivable r => Config -> (Record Flat r -> Restrict (PlaceHolders p)) -> Delete p Source #

Deprecated: use delete' instead of this.

Make typed Delete from Config, derived table and Restrict computation.

delete :: TableDerivable r => (Record Flat r -> Restrict (PlaceHolders p)) -> Delete p Source #

Make typed Delete from defaultConfig, derived table and Restrict computation.

deleteNoPH :: TableDerivable r => (Record Flat r -> Restrict ()) -> Delete () Source #

Make typed Delete from defaultConfig, derived table and Restrict computation with no(unit) placeholder.

derivedDelete :: TableDerivable r => (Record Flat r -> Restrict (PlaceHolders p)) -> Delete p Source #

Deprecated: use delete instead of this.

Make typed Delete from defaultConfig, derived table and Restrict computation.

data InsertTarget p r Source #

InsertTarget type with place-holder parameter p and projected record type r.

type UpdateTarget p r = Record Flat r -> Assign r (PlaceHolders p) Source #

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

type Restriction p r = Record Flat r -> Restrict (PlaceHolders p) Source #

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

restriction :: (Record Flat r -> Restrict ()) -> Restriction () r Source #

Deprecated: same as ((>> return unitPH) .)

Deprecated.

restriction' :: (Record Flat r -> Restrict (PlaceHolders p)) -> Restriction p r Source #

Deprecated: same as id

Deprecated.

sqlWhereFromRestriction :: Config -> Table r -> (Record Flat r -> Restrict (PlaceHolders p)) -> StringSQL Source #

Deprecated: low-level API, this API will be expired.

SQL WHERE clause StringSQL string from Restrict computation.

updateTarget :: (Record Flat r -> Assign r ()) -> UpdateTarget () r Source #

Deprecated: old-style API. Use new-style Database.Relational.updateNoPH.

Deprecated.

updateTarget' :: (Record Flat r -> Assign r (PlaceHolders p)) -> UpdateTarget p r Source #

Deprecated: same as id

Deprecated.

liftTargetAllColumn :: PersistableWidth r => (Record Flat r -> Restrict (PlaceHolders ())) -> Record Flat r -> Assign r (PlaceHolders r) Source #

Deprecated: old-style API. use Database.Relational.updateAllColumnNoPH instead of this.

Lift Restrict computation to Assign computation. Assign target columns are all.

liftTargetAllColumn' :: PersistableWidth r => (Record Flat r -> Restrict (PlaceHolders p)) -> Record Flat r -> Assign r (PlaceHolders (r, p)) Source #

Lift Restrict computation to Assign computation. Assign target columns are all. With placefolder type p.

updateTargetAllColumn :: PersistableWidth r => (Record Flat r -> Restrict ()) -> Record Flat r -> Assign r (PlaceHolders r) Source #

Deprecated: Use Database.Relational.updateAllColumnNoPH instead of this.

Deprecated.

updateTargetAllColumn' :: PersistableWidth r => (Record Flat r -> Restrict (PlaceHolders p)) -> Record Flat r -> Assign r (PlaceHolders (r, p)) Source #

Deprecated: Use Database.Relational.updateAllColumn instead of this.

Deprecated.

sqlFromUpdateTarget :: Config -> Table r -> (Record Flat r -> Assign r (PlaceHolders p)) -> StringSQL Source #

Deprecated: low-level API, this API will be expired.

SQL SET clause and WHERE clause StringSQL string from Assign computation.

insertTarget :: Register r () -> InsertTarget () r Source #

Deprecated: old-style API. Use new-style Database.Relational.insertValueNoPH .

Finalize Register monad and generate InsertTarget.

insertTarget' :: Register r (PlaceHolders p) -> InsertTarget p r Source #

Finalize Register monad and generate InsertTarget with place-holder parameter p.

piRegister :: PersistableWidth r => Pi r r' -> Register r (PlaceHolders r') Source #

parametalized Register monad from Pi

sqlChunkFromInsertTarget :: Config -> Table r -> InsertTarget p r -> (StringSQL, Int) Source #

Make StringSQL string of SQL INSERT record chunk statement from InsertTarget

sqlFromInsertTarget :: Config -> Table r -> InsertTarget p r -> StringSQL Source #

Make StringSQL string of SQL INSERT statement from InsertTarget

sqlChunksFromRecordList :: LiteralSQL r' => Config -> Table r -> Pi r r' -> [r'] -> [StringSQL] Source #

Make StringSQL strings of SQL INSERT strings from records list