{-# LANGUAGE CPP, DeriveDataTypeable #-}
module Database.PostgreSQL.Simple.Copy
( copy
, copy_
, CopyOutResult(..)
, foldCopyData
, getCopyData
, putCopyData
, putCopyEnd
, putCopyError
) where
import Control.Applicative
import Control.Concurrent
import Control.Exception ( throwIO )
import qualified Data.Attoparsec.ByteString.Char8 as P
import Data.Typeable(Typeable)
import Data.Int(Int64)
import qualified Data.ByteString.Char8 as B
import qualified Database.PostgreSQL.LibPQ as PQ
import Database.PostgreSQL.Simple
import Database.PostgreSQL.Simple.Types
import Database.PostgreSQL.Simple.Internal hiding (result, row)
copy :: ( ToRow params ) => Connection -> Query -> params -> IO ()
copy :: forall params.
ToRow params =>
Connection -> Query -> params -> IO ()
copy Connection
conn Query
template params
qs = do
ByteString
q <- forall q. ToRow q => Connection -> Query -> q -> IO ByteString
formatQuery Connection
conn Query
template params
qs
ByteString -> Connection -> Query -> ByteString -> IO ()
doCopy ByteString
"Database.PostgreSQL.Simple.Copy.copy" Connection
conn Query
template ByteString
q
copy_ :: Connection -> Query -> IO ()
copy_ :: Connection -> Query -> IO ()
copy_ Connection
conn (Query ByteString
q) = do
ByteString -> Connection -> Query -> ByteString -> IO ()
doCopy ByteString
"Database.PostgreSQL.Simple.Copy.copy_" Connection
conn (ByteString -> Query
Query ByteString
q) ByteString
q
doCopy :: B.ByteString -> Connection -> Query -> B.ByteString -> IO ()
doCopy :: ByteString -> Connection -> Query -> ByteString -> IO ()
doCopy ByteString
funcName Connection
conn Query
template ByteString
q = do
Result
result <- Connection -> ByteString -> IO Result
exec Connection
conn ByteString
q
ExecStatus
status <- Result -> IO ExecStatus
PQ.resultStatus Result
result
let errMsg :: [Char] -> IO a
errMsg [Char]
msg = forall e a. Exception e => e -> IO a
throwIO forall a b. (a -> b) -> a -> b
$ [Char] -> Query -> QueryError
QueryError
(ByteString -> [Char]
B.unpack ByteString
funcName forall a. [a] -> [a] -> [a]
++ [Char]
" " forall a. [a] -> [a] -> [a]
++ [Char]
msg)
Query
template
let err :: IO a
err = forall {a}. [Char] -> IO a
errMsg forall a b. (a -> b) -> a -> b
$ forall a. Show a => a -> [Char]
show ExecStatus
status
case ExecStatus
status of
ExecStatus
PQ.EmptyQuery -> forall {a}. IO a
err
ExecStatus
PQ.CommandOk -> forall {a}. IO a
err
ExecStatus
PQ.TuplesOk -> forall {a}. IO a
err
ExecStatus
PQ.CopyOut -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
ExecStatus
PQ.CopyIn -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
#if MIN_VERSION_postgresql_libpq(0,9,3)
ExecStatus
PQ.CopyBoth -> forall {a}. [Char] -> IO a
errMsg [Char]
"COPY BOTH is not supported"
#endif
#if MIN_VERSION_postgresql_libpq(0,9,2)
ExecStatus
PQ.SingleTuple -> forall {a}. [Char] -> IO a
errMsg [Char]
"single-row mode is not supported"
#endif
ExecStatus
PQ.BadResponse -> forall a. ByteString -> Result -> ExecStatus -> IO a
throwResultError ByteString
funcName Result
result ExecStatus
status
ExecStatus
PQ.NonfatalError -> forall a. ByteString -> Result -> ExecStatus -> IO a
throwResultError ByteString
funcName Result
result ExecStatus
status
ExecStatus
PQ.FatalError -> forall a. ByteString -> Result -> ExecStatus -> IO a
throwResultError ByteString
funcName Result
result ExecStatus
status
data CopyOutResult
= CopyOutRow !B.ByteString
| CopyOutDone {-# UNPACK #-} !Int64
deriving (CopyOutResult -> CopyOutResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyOutResult -> CopyOutResult -> Bool
$c/= :: CopyOutResult -> CopyOutResult -> Bool
== :: CopyOutResult -> CopyOutResult -> Bool
$c== :: CopyOutResult -> CopyOutResult -> Bool
Eq, Typeable, Int -> CopyOutResult -> ShowS
[CopyOutResult] -> ShowS
CopyOutResult -> [Char]
forall a.
(Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a
showList :: [CopyOutResult] -> ShowS
$cshowList :: [CopyOutResult] -> ShowS
show :: CopyOutResult -> [Char]
$cshow :: CopyOutResult -> [Char]
showsPrec :: Int -> CopyOutResult -> ShowS
$cshowsPrec :: Int -> CopyOutResult -> ShowS
Show)
foldCopyData
:: Connection
-> (a -> B.ByteString -> IO a)
-> (a -> Int64 -> IO b)
-> a
-> IO b
foldCopyData :: forall a b.
Connection
-> (a -> ByteString -> IO a) -> (a -> Int64 -> IO b) -> a -> IO b
foldCopyData Connection
conn a -> ByteString -> IO a
f a -> Int64 -> IO b
g !a
acc = do
CopyOutResult
result <- Connection -> IO CopyOutResult
getCopyData Connection
conn
case CopyOutResult
result of
CopyOutRow ByteString
row -> a -> ByteString -> IO a
f a
acc ByteString
row forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a b.
Connection
-> (a -> ByteString -> IO a) -> (a -> Int64 -> IO b) -> a -> IO b
foldCopyData Connection
conn a -> ByteString -> IO a
f a -> Int64 -> IO b
g
CopyOutDone Int64
count -> a -> Int64 -> IO b
g a
acc Int64
count
getCopyData :: Connection -> IO CopyOutResult
getCopyData :: Connection -> IO CopyOutResult
getCopyData Connection
conn = forall a. Connection -> (Connection -> IO a) -> IO a
withConnection Connection
conn Connection -> IO CopyOutResult
loop
where
funcName :: ByteString
funcName = ByteString
"Database.PostgreSQL.Simple.Copy.getCopyData"
loop :: Connection -> IO CopyOutResult
loop Connection
pqconn = do
#if defined(mingw32_HOST_OS)
row <- PQ.getCopyData pqconn False
#else
CopyOutResult
row <- Connection -> Bool -> IO CopyOutResult
PQ.getCopyData Connection
pqconn Bool
True
#endif
case CopyOutResult
row of
PQ.CopyOutRow ByteString
rowdata -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! ByteString -> CopyOutResult
CopyOutRow ByteString
rowdata
CopyOutResult
PQ.CopyOutDone -> Int64 -> CopyOutResult
CopyOutDone forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Connection -> IO Int64
getCopyCommandTag ByteString
funcName Connection
pqconn
#if defined(mingw32_HOST_OS)
PQ.CopyOutWouldBlock -> do
fail (B.unpack funcName ++ ": the impossible happened")
#else
CopyOutResult
PQ.CopyOutWouldBlock -> do
Maybe Fd
mfd <- Connection -> IO (Maybe Fd)
PQ.socket Connection
pqconn
case Maybe Fd
mfd of
Maybe Fd
Nothing -> forall e a. Exception e => e -> IO a
throwIO (ByteString -> IOError
fdError ByteString
funcName)
Just Fd
fd -> do
Fd -> IO ()
threadWaitRead Fd
fd
Bool
_ <- Connection -> IO Bool
PQ.consumeInput Connection
pqconn
Connection -> IO CopyOutResult
loop Connection
pqconn
#endif
CopyOutResult
PQ.CopyOutError -> do
Maybe ByteString
mmsg <- Connection -> IO (Maybe ByteString)
PQ.errorMessage Connection
pqconn
forall e a. Exception e => e -> IO a
throwIO SqlError {
sqlState :: ByteString
sqlState = ByteString
"",
sqlExecStatus :: ExecStatus
sqlExecStatus = ExecStatus
FatalError,
sqlErrorMsg :: ByteString
sqlErrorMsg = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
"" forall a. a -> a
id Maybe ByteString
mmsg,
sqlErrorDetail :: ByteString
sqlErrorDetail = ByteString
"",
sqlErrorHint :: ByteString
sqlErrorHint = ByteString
funcName
}
putCopyData :: Connection -> B.ByteString -> IO ()
putCopyData :: Connection -> ByteString -> IO ()
putCopyData Connection
conn ByteString
dat = forall a. Connection -> (Connection -> IO a) -> IO a
withConnection Connection
conn forall a b. (a -> b) -> a -> b
$ \Connection
pqconn -> do
ByteString
-> (Connection -> IO CopyInResult) -> Connection -> IO ()
doCopyIn ByteString
funcName (\Connection
c -> Connection -> ByteString -> IO CopyInResult
PQ.putCopyData Connection
c ByteString
dat) Connection
pqconn
where
funcName :: ByteString
funcName = ByteString
"Database.PostgreSQL.Simple.Copy.putCopyData"
putCopyEnd :: Connection -> IO Int64
putCopyEnd :: Connection -> IO Int64
putCopyEnd Connection
conn = forall a. Connection -> (Connection -> IO a) -> IO a
withConnection Connection
conn forall a b. (a -> b) -> a -> b
$ \Connection
pqconn -> do
ByteString
-> (Connection -> IO CopyInResult) -> Connection -> IO ()
doCopyIn ByteString
funcName (\Connection
c -> Connection -> Maybe ByteString -> IO CopyInResult
PQ.putCopyEnd Connection
c forall a. Maybe a
Nothing) Connection
pqconn
ByteString -> Connection -> IO Int64
getCopyCommandTag ByteString
funcName Connection
pqconn
where
funcName :: ByteString
funcName = ByteString
"Database.PostgreSQL.Simple.Copy.putCopyEnd"
putCopyError :: Connection -> B.ByteString -> IO ()
putCopyError :: Connection -> ByteString -> IO ()
putCopyError Connection
conn ByteString
err = forall a. Connection -> (Connection -> IO a) -> IO a
withConnection Connection
conn forall a b. (a -> b) -> a -> b
$ \Connection
pqconn -> do
ByteString
-> (Connection -> IO CopyInResult) -> Connection -> IO ()
doCopyIn ByteString
funcName (\Connection
c -> Connection -> Maybe ByteString -> IO CopyInResult
PQ.putCopyEnd Connection
c (forall a. a -> Maybe a
Just ByteString
err)) Connection
pqconn
Connection -> IO ()
consumeResults Connection
pqconn
where
funcName :: ByteString
funcName = ByteString
"Database.PostgreSQL.Simple.Copy.putCopyError"
doCopyIn :: B.ByteString -> (PQ.Connection -> IO PQ.CopyInResult)
-> PQ.Connection -> IO ()
doCopyIn :: ByteString
-> (Connection -> IO CopyInResult) -> Connection -> IO ()
doCopyIn ByteString
funcName Connection -> IO CopyInResult
action = Connection -> IO ()
loop
where
loop :: Connection -> IO ()
loop Connection
pqconn = do
CopyInResult
stat <- Connection -> IO CopyInResult
action Connection
pqconn
case CopyInResult
stat of
CopyInResult
PQ.CopyInOk -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
CopyInResult
PQ.CopyInError -> do
Maybe ByteString
mmsg <- Connection -> IO (Maybe ByteString)
PQ.errorMessage Connection
pqconn
forall e a. Exception e => e -> IO a
throwIO SqlError {
sqlState :: ByteString
sqlState = ByteString
"",
sqlExecStatus :: ExecStatus
sqlExecStatus = ExecStatus
FatalError,
sqlErrorMsg :: ByteString
sqlErrorMsg = forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
"" forall a. a -> a
id Maybe ByteString
mmsg,
sqlErrorDetail :: ByteString
sqlErrorDetail = ByteString
"",
sqlErrorHint :: ByteString
sqlErrorHint = ByteString
funcName
}
CopyInResult
PQ.CopyInWouldBlock -> do
Maybe Fd
mfd <- Connection -> IO (Maybe Fd)
PQ.socket Connection
pqconn
case Maybe Fd
mfd of
Maybe Fd
Nothing -> forall e a. Exception e => e -> IO a
throwIO (ByteString -> IOError
fdError ByteString
funcName)
Just Fd
fd -> do
Fd -> IO ()
threadWaitWrite Fd
fd
Connection -> IO ()
loop Connection
pqconn
{-# INLINE doCopyIn #-}
getCopyCommandTag :: B.ByteString -> PQ.Connection -> IO Int64
getCopyCommandTag :: ByteString -> Connection -> IO Int64
getCopyCommandTag ByteString
funcName Connection
pqconn = do
Result
result <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
errCmdStatus) forall (m :: * -> *) a. Monad m => a -> m a
return forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Connection -> IO (Maybe Result)
PQ.getResult Connection
pqconn
ByteString
cmdStat <- forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail [Char]
errCmdStatus) forall (m :: * -> *) a. Monad m => a -> m a
return forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Result -> IO (Maybe ByteString)
PQ.cmdStatus Result
result
Connection -> IO ()
consumeResults Connection
pqconn
let rowCount :: Parser ByteString Int64
rowCount = ByteString -> Parser ByteString
P.string ByteString
"COPY " forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> (forall a. Integral a => Parser a
P.decimal forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* forall t. Chunk t => Parser t ()
P.endOfInput)
case forall a. Parser a -> ByteString -> Either [Char] a
P.parseOnly Parser ByteString Int64
rowCount ByteString
cmdStat of
Left [Char]
_ -> do Maybe ByteString
mmsg <- Connection -> IO (Maybe ByteString)
PQ.errorMessage Connection
pqconn
forall (m :: * -> *) a. MonadFail m => [Char] -> m a
fail forall a b. (a -> b) -> a -> b
$ [Char]
errCmdStatusFmt
forall a. [a] -> [a] -> [a]
++ forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Char]
"" (\ByteString
msg -> [Char]
"\nConnection error: "forall a. [a] -> [a] -> [a]
++ByteString -> [Char]
B.unpack ByteString
msg) Maybe ByteString
mmsg
Right Int64
n -> forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! Int64
n
where
errCmdStatus :: [Char]
errCmdStatus = ByteString -> [Char]
B.unpack ByteString
funcName forall a. [a] -> [a] -> [a]
++ [Char]
": failed to fetch command status"
errCmdStatusFmt :: [Char]
errCmdStatusFmt = ByteString -> [Char]
B.unpack ByteString
funcName forall a. [a] -> [a] -> [a]
++ [Char]
": failed to parse command status"
consumeResults :: PQ.Connection -> IO ()
consumeResults :: Connection -> IO ()
consumeResults Connection
pqconn = do
Maybe Result
mres <- Connection -> IO (Maybe Result)
PQ.getResult Connection
pqconn
case Maybe Result
mres of
Maybe Result
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just Result
_ -> Connection -> IO ()
consumeResults Connection
pqconn