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

Database.Relational.Type

Description

This module defines typed SQL.

Synopsis

Typed query statement

newtype Query p a Source #

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

Constructors

Query 

Fields

Instances

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

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.

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

From Relation into untyped SQL query string.

Typed update statement

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

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

unsafeTypedKeyUpdate :: Pi a p -> String -> KeyUpdate p a Source #

Unsafely make typed KeyUpdate from SQL string.

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.

newtype Update p Source #

Update type with place-holder parameter p.

Constructors

Update 

Fields

Instances

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

unsafeTypedUpdate :: String -> Update p Source #

Unsafely make typed Update from SQL string.

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

Make typed Update from Config, 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.

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.

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.

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.

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

Make untyped update SQL string from Table and Assign computation.

Typed insert statement

data Insert a Source #

Insert type to insert record type a.

Constructors

Insert 

Instances

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

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.

unsafeTypedInsert :: String -> Insert a Source #

Unsafely make typed Insert from single 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.

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

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.

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

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.

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.

newtype InsertQuery p Source #

InsertQuery type.

Constructors

InsertQuery 

Instances

Instances details
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

unsafeTypedInsertQuery :: String -> InsertQuery p Source #

Unsafely make typed InsertQuery from SQL string.

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.

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.

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

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

Typed delete statement

newtype Delete p Source #

Delete type with place-holder parameter p.

Constructors

Delete 

Fields

Instances

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

unsafeTypedDelete :: String -> Delete p Source #

Unsafely make typed Delete from SQL string.

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

Make typed Delete from Config, 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.

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.

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

Make untyped delete SQL string from Table and Restrict computation.

Generalized interfaces

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 #

Instances

Instances details
UntypeableNoFetch Delete Source # 
Instance details

Defined in Database.Relational.Type

UntypeableNoFetch InsertQuery Source # 
Instance details

Defined in Database.Relational.Type

UntypeableNoFetch Insert Source # 
Instance details

Defined in Database.Relational.Type

UntypeableNoFetch Update Source # 
Instance details

Defined in Database.Relational.Type

Deprecated

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.

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.

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.

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.

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.

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.

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.

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.

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

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

Deprecated: use updateAllColumn instead of this.

Deprecated. use updateAllColumn.

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

Deprecated: use insert instead of this.

Table type inferred Insert.

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.

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.

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

Deprecated: use insertQuery instead of this.

Table type inferred InsertQuery.

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.

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.