opaleye-0.6.7005.0: An SQL-generating DSL targeting PostgreSQL

Safe HaskellNone
LanguageHaskell2010

Opaleye.Manipulation

Contents

Description

Inserts, updates and deletes

Please note that Opaleye currently only supports INSERT or UPDATE with constant values, not the result of SELECTs. That is, you can generate SQL of the form

INSERT INTO thetable (John, 1);

but not

INSERT INTO thetable
   SELECT John,
   (SELECT num FROM thetable ORDER BY num DESC LIMIT 1) + 1;
Synopsis

Documentation

data Delete haskells Source #

Constructors

Delete 

Fields

data Update haskells Source #

Constructors

Update 

Fields

data Insert haskells Source #

Constructors

Insert 

Fields

runInsert_ Source #

Arguments

:: Connection 
-> Insert haskells 
-> IO haskells

Returns a type that depends on the Returning that you provided when creating the Insert.

Run the Insert. To create an Insert use the Insert constructor.

runUpdate_ Source #

Arguments

:: Connection 
-> Update haskells 
-> IO haskells

Returns a type that depends on the Returning that you provided when creating the Update.

Run the Update. To create an Update use the Update constructor.

runDelete_ Source #

Arguments

:: Connection 
-> Delete haskells 
-> IO haskells

Returns a type that depends on the Returning that you provided when creating the Delete.

Run the Delete. To create an Delete use the Delete constructor.

updateEasy Source #

Arguments

:: Default Updater fieldsR fieldsW 
=> (fieldsR -> fieldsR) 
-> fieldsR -> fieldsW 

A convenient wrapper for writing your update function

uUpdateWith = updateEasy (\... -> ...)

rCount :: Returning fieldsR Int64 Source #

Return the number of rows inserted or updated

rReturning Source #

Arguments

:: Default FromFields fields haskells 
=> (fieldsR -> fields) 
-> Returning fieldsR [haskells] 

Return a function of the inserted or updated rows

rReturning's use of the Default FromFields typeclass means that the compiler will have trouble inferring types. It is strongly recommended that you provide full type signatures when using rReturning.

rReturningExplicit Source #

Arguments

:: FromFields fields haskells 
-> (fieldsR -> fields) 
-> Returning fieldsR [haskells] 

Return a function of the inserted or updated rows. Explicit version. You probably just want to use rReturning instead.

runInsert :: Connection -> Table fields fields' -> fields -> IO Int64 Source #

Deprecated: runInsert will be removed in version 0.7. Use runInsertMany instead.

Returns the number of rows inserted

runInsertReturning :: Default QueryRunner fieldsReturned haskells => Connection -> Table fieldsW fieldsR -> fieldsW -> (fieldsR -> fieldsReturned) -> IO [haskells] Source #

Deprecated: runInsertReturning will be removed in version 0.7. Use runInsertManyReturning instead.

runInsertReturning's use of the Default typeclass means that the compiler will have trouble inferring types. It is strongly recommended that you provide full type signatures when using runInsertReturning.

arrangeInsert :: Table columns a -> columns -> SqlInsert Source #

Deprecated: You probably want runInsertMany instead. Will be removed in version 0.7.

arrangeInsertSql :: Table columns a -> columns -> String Source #

Deprecated: You probably want runInsertMany instead. Will be removed in version 0.7.

arrangeInsertMany :: Table columns a -> NonEmpty columns -> SqlInsert Source #

Deprecated: You probably want runInsertMany instead. Will be removed in version 0.7.

arrangeInsertManySql :: Table columns a -> NonEmpty columns -> String Source #

Deprecated: You probably want runInsertMany instead. Will be removed in version 0.7.

arrangeUpdate :: Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> SqlUpdate Source #

Deprecated: You probably want runUpdate instead. Will be removed in version 0.7.

arrangeUpdateSql :: Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> String Source #

Deprecated: You probably want runUpdate instead. Will be removed in version 0.7.

arrangeDelete :: Table a columnsR -> (columnsR -> Column SqlBool) -> SqlDelete Source #

Deprecated: You probably want runDelete instead. Will be removed in version 0.7.

arrangeDeleteSql :: Table a columnsR -> (columnsR -> Column SqlBool) -> String Source #

Deprecated: You probably want runDelete instead. Will be removed in version 0.7.

arrangeInsertManyReturning :: Unpackspec columnsReturned ignored -> Table columnsW columnsR -> NonEmpty columnsW -> (columnsR -> columnsReturned) -> Returning SqlInsert Source #

Deprecated: You probably want runInsertMany instead. Will be removed in version 0.7.

arrangeInsertManyReturningSql :: Unpackspec columnsReturned ignored -> Table columnsW columnsR -> NonEmpty columnsW -> (columnsR -> columnsReturned) -> String Source #

Deprecated: You probably want runInsertManyReturning instead. Will be removed in version 0.7.

arrangeUpdateReturning :: Unpackspec columnsReturned ignored -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> (columnsR -> columnsReturned) -> Returning SqlUpdate Source #

Deprecated: You probably want runUpdateReturning instead. Will be removed in version 0.7.

arrangeUpdateReturningSql :: Unpackspec columnsReturned ignored -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> (columnsR -> columnsReturned) -> String Source #

Deprecated: You probably want runUpdateReturning instead. Will be removed in version 0.7.

runInsertManyOnConflictDoNothing Source #

Arguments

:: Connection 
-> Table columns columns'

Table to insert into

-> [columns]

Rows to insert

-> IO Int64

Number of rows inserted

Deprecated: Use runInsert_. Will be removed in version 0.8.

Insert rows into a table with ON CONFLICT DO NOTHING

runInsertManyReturningOnConflictDoNothing Source #

Arguments

:: Default QueryRunner columnsReturned haskells 
=> Connection 
-> Table columnsW columnsR

Table to insert into

-> [columnsW]

Rows to insert

-> (columnsR -> columnsReturned)

Function f to apply to the inserted rows

-> IO [haskells]

Returned rows after f has been applied

Deprecated: Use runInsert_. Will be removed in version 0.8.

Insert rows into a table with ON CONFLICT DO NOTHING and return a function of the inserted rows

runInsertManyReturningOnConflictDoNothing's use of the Default typeclass means that the compiler will have trouble inferring types. It is strongly recommended that you provide full type signatures when using it.

runInsertMany Source #

Arguments

:: Connection 
-> Table columns columns'

Table to insert into

-> [columns]

Rows to insert

-> IO Int64

Number of rows inserted

Use runInsert_ instead. Will be deprecated in version 0.7.

runInsertManyReturning Source #

Arguments

:: Default QueryRunner columnsReturned haskells 
=> Connection 
-> Table columnsW columnsR

Table to insert into

-> [columnsW]

Rows to insert

-> (columnsR -> columnsReturned)

Function f to apply to the inserted rows

-> IO [haskells]

Returned rows after f has been applied

Use runInsert_ instead. Will be deprecated in version 0.7.

runInsertReturningExplicit :: QueryRunner columnsReturned haskells -> Connection -> Table columnsW columnsR -> columnsW -> (columnsR -> columnsReturned) -> IO [haskells] Source #

Use runInsert_ instead. Will be deprecated in version 0.7.

runInsertManyReturningExplicit :: QueryRunner columnsReturned haskells -> Connection -> Table columnsW columnsR -> [columnsW] -> (columnsR -> columnsReturned) -> IO [haskells] Source #

Use runInsert_ instead. Will be deprecated in version 0.7.

runInsertManyReturningOnConflictDoNothingExplicit :: QueryRunner columnsReturned haskells -> Connection -> Table columnsW columnsR -> [columnsW] -> (columnsR -> columnsReturned) -> IO [haskells] Source #

Use runInsert_ instead. Will be deprecated in version 0.7.

runUpdateEasy Source #

Arguments

:: Default Updater columnsR columnsW 
=> Connection 
-> Table columnsW columnsR

Table to update

-> (columnsR -> columnsR)

Update function to apply to chosen rows

-> (columnsR -> Column SqlBool)

Predicate function f to choose which rows to update. runUpdate will update rows for which f returns TRUE and leave unchanged rows for which f returns FALSE.

-> IO Int64

The number of rows updated

Use runUpdate_ instead. Will be deprecated in version 0.7.

runUpdate Source #

Arguments

:: Connection 
-> Table columnsW columnsR

Table to update

-> (columnsR -> columnsW)

Update function to apply to chosen rows

-> (columnsR -> Column SqlBool)

Predicate function f to choose which rows to update. runUpdate will update rows for which f returns TRUE and leave unchanged rows for which f returns FALSE.

-> IO Int64

The number of rows updated

Use runUpdate_ instead. Will be deprecated in version 0.7.

runUpdateReturning Source #

Arguments

:: Default QueryRunner columnsReturned haskells 
=> Connection 
-> Table columnsW columnsR

Table to update

-> (columnsR -> columnsW)

Update function to apply to chosen rows

-> (columnsR -> Column SqlBool)

Predicate function f to choose which rows to update. runUpdate will update rows for which f returns TRUE and leave unchanged rows for which f returns FALSE.

-> (columnsR -> columnsReturned)

Functon g to apply to the updated rows

-> IO [haskells]

Returned rows after g has been applied

Use runUpdate_ instead. Will be deprecated in version 0.7.

runUpdateReturningExplicit :: QueryRunner columnsReturned haskells -> Connection -> Table columnsW columnsR -> (columnsR -> columnsW) -> (columnsR -> Column SqlBool) -> (columnsR -> columnsReturned) -> IO [haskells] Source #

Use runUpdate_ instead. Will be deprecated in version 0.7.

runDelete Source #

Arguments

:: Connection 
-> Table a columnsR

Table to delete rows from

-> (columnsR -> Column SqlBool)

Predicate function f to choose which rows to delete. runDelete will delete rows for which f returns TRUE and leave unchanged rows for which f returns FALSE.

-> IO Int64

The number of rows deleted

Use runDelete_ instead. Will be deprecated in 0.7.

Other

Do not use the export of Unpackspec. It will not be exported in version 0.7.

data Unpackspec columns columns' Source #

Instances
Profunctor Unpackspec Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

dimap :: (a -> b) -> (c -> d) -> Unpackspec b c -> Unpackspec a d #

lmap :: (a -> b) -> Unpackspec b c -> Unpackspec a c #

rmap :: (b -> c) -> Unpackspec a b -> Unpackspec a c #

(#.) :: Coercible c b => q b c -> Unpackspec a b -> Unpackspec a c #

(.#) :: Coercible b a => Unpackspec b c -> q a b -> Unpackspec a c #

ProductProfunctor Unpackspec Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

purePP :: b -> Unpackspec a b #

(****) :: Unpackspec a (b -> c) -> Unpackspec a b -> Unpackspec a c #

empty :: Unpackspec () () #

(***!) :: Unpackspec a b -> Unpackspec a' b' -> Unpackspec (a, a') (b, b') #

SumProfunctor Unpackspec Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

(+++!) :: Unpackspec a b -> Unpackspec a' b' -> Unpackspec (Either a a') (Either b b') #

Default Unpackspec (Column a) (Column a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

def :: Unpackspec (Column a) (Column a) #

Default Unpackspec a b => Default Unpackspec (MaybeFields a) (MaybeFields b) Source # 
Instance details

Defined in Opaleye.Internal.MaybeFields

Functor (Unpackspec a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

fmap :: (a0 -> b) -> Unpackspec a a0 -> Unpackspec a b #

(<$) :: a0 -> Unpackspec a b -> Unpackspec a a0 #

Applicative (Unpackspec a) Source # 
Instance details

Defined in Opaleye.Internal.Unpackspec

Methods

pure :: a0 -> Unpackspec a a0 #

(<*>) :: Unpackspec a (a0 -> b) -> Unpackspec a a0 -> Unpackspec a b #

liftA2 :: (a0 -> b -> c) -> Unpackspec a a0 -> Unpackspec a b -> Unpackspec a c #

(*>) :: Unpackspec a a0 -> Unpackspec a b -> Unpackspec a b #

(<*) :: Unpackspec a a0 -> Unpackspec a b -> Unpackspec a a0 #

Currently DoNothing is the only conflict action supported by Opaleye.

data OnConflict Source #

Constructors

DoNothing
ON CONFLICT DO NOTHING