{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE FlexibleContexts          #-}
{-# LANGUAGE FlexibleInstances         #-}
{-# LANGUAGE GADTs                     #-}
{-# LANGUAGE MultiParamTypeClasses     #-}

-- | 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;
-- @

module Opaleye.Manipulation (-- * Insert
                             runInsert,
                             Insert(..),
                             -- * Update
                             runUpdate,
                             Update(..),
                             updateEasy,
                             -- * Delete
                             runDelete,
                             Delete(..),
                             -- * Returning
                             MI.Returning,
                             rCount,
                             rReturning,
                             rReturningI,
                             rReturningExplicit,
                             -- * On conflict
                             -- | Currently 'doNothing' is the
                             -- only conflict action supported by
                             -- Opaleye.
                             HSql.OnConflict,
                             doNothing,
                             -- * Deprecated
                             runInsert_,
                             runUpdate_,
                             runDelete_,
                             -- ** @DoNothing@
                             -- | Use 'doNothing' instead.
                             -- @DoNothing@ will be deprecated in
                             -- version 0.9.
                             HSql.OnConflict(HSql.DoNothing),
                             ) where

import qualified Opaleye.Field        as F
import qualified Opaleye.RunSelect as RS
import qualified Opaleye.Internal.RunQuery as IRQ
import qualified Opaleye.Table as T
import qualified Opaleye.Internal.Table as TI
import           Opaleye.Internal.Column (Column)
import           Opaleye.Internal.Helpers ((.:), (.:.))
import           Opaleye.Internal.Inferrable (Inferrable, runInferrable)
import           Opaleye.Internal.Manipulation (Updater(Updater))
import qualified Opaleye.Internal.Manipulation as MI
import           Opaleye.SqlTypes (SqlBool)

import qualified Opaleye.Internal.HaskellDB.Sql as HSql

import qualified Database.PostgreSQL.Simple as PGS

import qualified Data.Profunctor.Product.Default as D

import           Data.Int (Int64)
import           Data.String (fromString)
import qualified Data.List.NonEmpty as NEL

-- * Run a manipulation

-- | Run the 'Insert'.  To create an 'Insert' use the 'Insert'
-- constructor.
runInsert  :: PGS.Connection
           -- ^
           -> Insert haskells
           -- ^
           -> IO haskells
           -- ^ Returns a type that depends on the 'MI.Returning' that
           -- you provided when creating the 'Insert'.
runInsert :: Connection -> Insert haskells -> IO haskells
runInsert Connection
conn Insert haskells
i = case Insert haskells
i of
  Insert Table fieldsW fieldsR
table_ [fieldsW]
rows_ Returning fieldsR haskells
returning_ Maybe OnConflict
onConflict_ ->
    let insert :: Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
insert = case (Returning fieldsR haskells
returning_, Maybe OnConflict
onConflict_) of
          (Returning fieldsR haskells
MI.Count, Maybe OnConflict
Nothing) ->
            Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
forall columns columns'.
Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertMany
          (Returning fieldsR haskells
MI.Count, Just OnConflict
HSql.DoNothing) ->
            Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
forall columns columns'.
Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertManyOnConflictDoNothing
          (MI.ReturningExplicit FromFields b c
qr fieldsR -> b
f, Maybe OnConflict
oc) ->
            \Connection
c Table fieldsW fieldsR
t [fieldsW]
r -> FromFields b c
-> Connection
-> Table fieldsW fieldsR
-> [fieldsW]
-> (fieldsR -> b)
-> Maybe OnConflict
-> IO [c]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> [columnsW]
-> (columnsR -> columnsReturned)
-> Maybe OnConflict
-> IO [haskells]
MI.runInsertManyReturningExplicit FromFields b c
qr Connection
c Table fieldsW fieldsR
t [fieldsW]
r fieldsR -> b
f Maybe OnConflict
oc
    in Connection -> Table fieldsW fieldsR -> [fieldsW] -> IO haskells
insert Connection
conn Table fieldsW fieldsR
table_ [fieldsW]
rows_

-- | Use 'runInsert' instead.  Will be deprecated in 0.9.
runInsert_ :: PGS.Connection
           -> Insert haskells
           -> IO haskells
runInsert_ :: Connection -> Insert haskells -> IO haskells
runInsert_ = Connection -> Insert haskells -> IO haskells
forall haskells. Connection -> Insert haskells -> IO haskells
runInsert

-- | Run the 'Update'.  To create an 'Update' use the 'Update'
-- constructor.
runUpdate  :: PGS.Connection
           -- ^
           -> Update haskells
           -- ^
           -> IO haskells
           -- ^ Returns a type that depends on the 'MI.Returning' that
           -- you provided when creating the 'Update'.
runUpdate :: Connection -> Update haskells -> IO haskells
runUpdate  Connection
conn Update haskells
i = case Update haskells
i of
  Update Table fieldsW fieldsR
table_ fieldsR -> fieldsW
updateWith_ fieldsR -> Field SqlBool
where_ Returning fieldsR haskells
returning_ -> case Returning fieldsR haskells
returning_ of
          Returning fieldsR haskells
MI.Count ->
            Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (String -> Query
forall a. IsString a => String -> a
fromString (Table fieldsW fieldsR
-> (fieldsR -> fieldsW) -> (fieldsR -> Field SqlBool) -> String
forall columnsW columnsR.
Table columnsW columnsR
-> (columnsR -> columnsW) -> (columnsR -> Field SqlBool) -> String
MI.arrangeUpdateSql Table fieldsW fieldsR
table_ fieldsR -> fieldsW
updateWith_ fieldsR -> Field SqlBool
where_))
          MI.ReturningExplicit FromFields b c
qr fieldsR -> b
f ->
            FromFields b c
-> Connection
-> Table fieldsW fieldsR
-> (fieldsR -> fieldsW)
-> (fieldsR -> Column SqlBool)
-> (fieldsR -> b)
-> IO [c]
forall columnsReturned haskells columnsW columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturningExplicit FromFields b c
qr Connection
conn Table fieldsW fieldsR
table_ fieldsR -> fieldsW
updateWith_ fieldsR -> Column SqlBool
fieldsR -> Field SqlBool
where_ fieldsR -> b
f

-- | Use 'runUpdate' instead.  Will be deprecated in 0.9.
runUpdate_ :: PGS.Connection
           -> Update haskells
           -> IO haskells
runUpdate_ :: Connection -> Update haskells -> IO haskells
runUpdate_ = Connection -> Update haskells -> IO haskells
forall haskells. Connection -> Update haskells -> IO haskells
runUpdate

-- | Run the 'Delete'.  To create an 'Delete' use the 'Delete'
-- constructor.
runDelete  :: PGS.Connection
           -- ^
           -> Delete haskells
           -> IO haskells
           -- ^ Returns a type that depends on the 'MI.Returning' that
           -- you provided when creating the 'Delete'.
runDelete :: Connection -> Delete haskells -> IO haskells
runDelete Connection
conn Delete haskells
i = case Delete haskells
i of
  Delete Table fieldsW fieldsR
table_ fieldsR -> Field SqlBool
where_ Returning fieldsR haskells
returning_ -> case Returning fieldsR haskells
returning_ of
          Returning fieldsR haskells
MI.Count ->
            Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (String -> Query
forall a. IsString a => String -> a
fromString (Table fieldsW fieldsR -> (fieldsR -> Field SqlBool) -> String
forall a columnsR.
Table a columnsR -> (columnsR -> Field SqlBool) -> String
MI.arrangeDeleteSql Table fieldsW fieldsR
table_ fieldsR -> Field SqlBool
where_))
          MI.ReturningExplicit FromFields b c
qr fieldsR -> b
f ->
            FromFields b c
-> Connection
-> Table fieldsW fieldsR
-> (fieldsR -> Field SqlBool)
-> (fieldsR -> b)
-> IO [c]
forall columnsReturned haskells a columnsR.
FromFields columnsReturned haskells
-> Connection
-> Table a columnsR
-> (columnsR -> Field SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
MI.runDeleteReturningExplicit FromFields b c
qr Connection
conn Table fieldsW fieldsR
table_ fieldsR -> Field SqlBool
where_ fieldsR -> b
f

-- | Use 'runDelete' instead.  Will be deprecated in 0.9.
runDelete_ :: PGS.Connection
           -> Delete haskells
           -> IO haskells
runDelete_ :: Connection -> Delete haskells -> IO haskells
runDelete_ = Connection -> Delete haskells -> IO haskells
forall haskells. Connection -> Delete haskells -> IO haskells
runDelete

-- * Create a manipulation

data Insert haskells = forall fieldsW fieldsR. Insert
   { ()
iTable      :: T.Table fieldsW fieldsR
   , ()
iRows       :: [fieldsW]
   , ()
iReturning  :: MI.Returning fieldsR haskells
   , Insert haskells -> Maybe OnConflict
iOnConflict :: Maybe HSql.OnConflict
   -- ^ NB There is a clash of terminology between Haskell and
   -- Postgres.
   --
   --     * 'iOnConflict' @=@ 'Nothing' means omit @ON CONFLICT@ statement
   --
   --     * 'iOnConflict' @=@ 'Just' 'HSql.DoNothing' means @ON CONFLICT DO
   --        NOTHING@
   }

data Update haskells = forall fieldsW fieldsR. Update
   { ()
uTable      :: T.Table fieldsW fieldsR
   , ()
uUpdateWith :: fieldsR -> fieldsW
   -- ^ Be careful: providing 'Nothing' to a field created by
   -- 'Opaleye.Table.optionalTableFields' updates the field to its default
   -- value.  Many users have been confused by this because they
   -- assume it means that the field is to be left unchanged.  For an
   -- easier time wrap your update function in 'updateEasy'.
   , ()
uWhere      :: fieldsR -> F.Field SqlBool
   , ()
uReturning  :: MI.Returning fieldsR haskells
   }

-- | A convenient wrapper for writing your update function
--
-- @uUpdateWith = updateEasy (\\... -> ...)@
updateEasy :: D.Default Updater fieldsR fieldsW
           => (fieldsR -> fieldsR)
           -- ^
           -> (fieldsR -> fieldsW)
updateEasy :: (fieldsR -> fieldsR) -> fieldsR -> fieldsW
updateEasy fieldsR -> fieldsR
u = fieldsR -> fieldsW
u' (fieldsR -> fieldsW) -> (fieldsR -> fieldsR) -> fieldsR -> fieldsW
forall b c a. (b -> c) -> (a -> b) -> a -> c
. fieldsR -> fieldsR
u
  where Updater fieldsR -> fieldsW
u' = Updater fieldsR fieldsW
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def

data Delete haskells = forall fieldsW fieldsR. Delete
  { ()
dTable     :: T.Table fieldsW fieldsR
  , ()
dWhere     :: fieldsR -> F.Field SqlBool
  , ()
dReturning :: MI.Returning fieldsR haskells
  }

-- ** Returning

-- | Return the number of rows inserted or updated
rCount :: MI.Returning fieldsR Int64
rCount :: Returning fieldsR Int64
rCount = Returning fieldsR Int64
forall a. Returning a Int64
MI.Count

-- | Return a function of the inserted or updated rows
--
-- 'rReturning''s use of the @'D.Default' 'Opaleye.RunSelect.FromFields'@
-- typeclass means that the
-- compiler will have trouble inferring types.  It is strongly
-- recommended that you provide full type signatures when using
-- 'rReturning'.
rReturning :: D.Default RS.FromFields fields haskells
           => (fieldsR -> fields)
           -- ^
           -> MI.Returning fieldsR [haskells]
rReturning :: (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturning = FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
forall fields haskells fieldsR.
FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningExplicit FromFields fields haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def

-- | Like 'rReturning' but with better inference properties.  On the
-- other hand the mapping from SQL fields to Haskell types is less
-- flexible.
rReturningI :: D.Default (Inferrable RS.FromFields) fields haskells
            => (fieldsR -> fields)
            -- ^
            -> MI.Returning fieldsR [haskells]
rReturningI :: (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningI = FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
forall fields haskells fieldsR.
FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningExplicit (Inferrable FromFields fields haskells -> FromFields fields haskells
forall (p :: * -> * -> *) a b. Inferrable p a b -> p a b
runInferrable Inferrable FromFields fields haskells
forall (p :: * -> * -> *) a b. Default p a b => p a b
D.def)

-- | Return a function of the inserted or updated rows.  Explicit
-- version.  You probably just want to use 'rReturning' instead.
rReturningExplicit :: RS.FromFields fields haskells
                   -- ^
                   -> (fieldsR -> fields)
                   -- ^
                   -> MI.Returning fieldsR [haskells]
rReturningExplicit :: FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
rReturningExplicit = FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
forall fields haskells fieldsR.
FromFields fields haskells
-> (fieldsR -> fields) -> Returning fieldsR [haskells]
MI.ReturningExplicit

-- * Deprecated versions

-- | Insert rows into a table with @ON CONFLICT DO NOTHING@
runInsertManyOnConflictDoNothing :: PGS.Connection
                                 -- ^
                                 -> T.Table columns columns'
                                 -- ^ Table to insert into
                                 -> [columns]
                                 -- ^ Rows to insert
                                 -> IO Int64
                                 -- ^ Number of rows inserted
runInsertManyOnConflictDoNothing :: Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertManyOnConflictDoNothing Connection
conn Table columns columns'
table_ [columns]
columns =
  case [columns] -> Maybe (NonEmpty columns)
forall a. [a] -> Maybe (NonEmpty a)
NEL.nonEmpty [columns]
columns of
    -- Inserting the empty list is just the same as returning 0
    Maybe (NonEmpty columns)
Nothing       -> Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
0
    Just NonEmpty columns
columns' -> (Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (Query -> IO Int64) -> (String -> Query) -> String -> IO Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Query
forall a. IsString a => String -> a
fromString (String -> IO Int64)
-> (Table columns columns'
    -> NonEmpty columns -> Maybe OnConflict -> String)
-> Table columns columns'
-> NonEmpty columns
-> Maybe OnConflict
-> IO Int64
forall r z a b c.
(r -> z) -> (a -> b -> c -> r) -> a -> b -> c -> z
.:. Table columns columns'
-> NonEmpty columns -> Maybe OnConflict -> String
forall columnsW columnsR.
Table columnsW columnsR
-> NonEmpty columnsW -> Maybe OnConflict -> String
MI.arrangeInsertManySql)
                         Table columns columns'
table_ NonEmpty columns
columns' (OnConflict -> Maybe OnConflict
forall a. a -> Maybe a
Just OnConflict
HSql.DoNothing)

runInsertMany :: PGS.Connection
              -- ^
              -> T.Table columns columns'
              -- ^ Table to insert into
              -> [columns]
              -- ^ Rows to insert
              -> IO Int64
              -- ^ Number of rows inserted
runInsertMany :: Connection -> Table columns columns' -> [columns] -> IO Int64
runInsertMany Connection
conn Table columns columns'
t [columns]
columns = case [columns] -> Maybe (NonEmpty columns)
forall a. [a] -> Maybe (NonEmpty a)
NEL.nonEmpty [columns]
columns of
  -- Inserting the empty list is just the same as returning 0
  Maybe (NonEmpty columns)
Nothing       -> Int64 -> IO Int64
forall (m :: * -> *) a. Monad m => a -> m a
return Int64
0
  Just NonEmpty columns
columns' -> (Connection -> Query -> IO Int64
PGS.execute_ Connection
conn (Query -> IO Int64) -> (String -> Query) -> String -> IO Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Query
forall a. IsString a => String -> a
fromString (String -> IO Int64)
-> (Table columns columns' -> NonEmpty columns -> String)
-> Table columns columns'
-> NonEmpty columns
-> IO Int64
forall r z a b. (r -> z) -> (a -> b -> r) -> a -> b -> z
.: Table columns columns' -> NonEmpty columns -> String
forall columns a. Table columns a -> NonEmpty columns -> String
MI.arrangeInsertManySqlI) Table columns columns'
t NonEmpty columns
columns'

runUpdateReturningExplicit :: RS.FromFields columnsReturned haskells
                           -> PGS.Connection
                           -> T.Table columnsW columnsR
                           -> (columnsR -> columnsW)
                           -> (columnsR -> Column SqlBool)
                           -> (columnsR -> columnsReturned)
                           -> IO [haskells]
runUpdateReturningExplicit :: FromFields columnsReturned haskells
-> Connection
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Column SqlBool)
-> (columnsR -> columnsReturned)
-> IO [haskells]
runUpdateReturningExplicit FromFields columnsReturned haskells
qr Connection
conn Table columnsW columnsR
t columnsR -> columnsW
update columnsR -> Column SqlBool
cond columnsR -> columnsReturned
r =
  RowParser haskells -> Connection -> Query -> IO [haskells]
forall r. RowParser r -> Connection -> Query -> IO [r]
PGS.queryWith_ RowParser haskells
parser Connection
conn
                 (String -> Query
forall a. IsString a => String -> a
fromString (Unpackspec columnsReturned ()
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Field SqlBool)
-> (columnsR -> columnsReturned)
-> String
forall columnsReturned ignored columnsW columnsR.
Unpackspec columnsReturned ignored
-> Table columnsW columnsR
-> (columnsR -> columnsW)
-> (columnsR -> Field SqlBool)
-> (columnsR -> columnsReturned)
-> String
MI.arrangeUpdateReturningSql Unpackspec columnsReturned ()
u Table columnsW columnsR
t columnsR -> columnsW
update columnsR -> Column SqlBool
columnsR -> Field SqlBool
cond columnsR -> columnsReturned
r))
  where IRQ.FromFields Unpackspec columnsReturned ()
u columnsReturned -> RowParser haskells
_ columnsReturned -> Int
_ = FromFields columnsReturned haskells
qr
        parser :: RowParser haskells
parser = FromFields columnsReturned haskells
-> columnsReturned -> RowParser haskells
forall columns haskells.
FromFields columns haskells -> columns -> RowParser haskells
IRQ.prepareRowParser FromFields columnsReturned haskells
qr (columnsR -> columnsReturned
r columnsR
v)
        TI.View columnsR
v = TableFields columnsW columnsR -> View columnsR
forall writeColumns viewColumns.
TableFields writeColumns viewColumns -> View viewColumns
TI.tableColumnsView (Table columnsW columnsR -> TableFields columnsW columnsR
forall writeColumns viewColumns.
Table writeColumns viewColumns
-> TableFields writeColumns viewColumns
TI.tableColumns Table columnsW columnsR
t)

doNothing :: HSql.OnConflict
doNothing :: OnConflict
doNothing = OnConflict
HSql.DoNothing