module Database.PostgreSQL.Simple.LargeObjects
( loCreat
, loCreate
, loImport
, loImportWithOid
, loExport
, loOpen
, loWrite
, loRead
, loSeek
, loTell
, loTruncate
, loClose
, loUnlink
, Oid(..)
, LoFd
, IOMode(..)
, SeekMode(..)
) where
import Control.Applicative ((<$>))
import Control.Exception (throwIO)
import qualified Data.ByteString as B
import Database.PostgreSQL.LibPQ (Oid(..),LoFd(..))
import qualified Database.PostgreSQL.LibPQ as PQ
import Database.PostgreSQL.Simple.Internal
import System.IO (IOMode(..),SeekMode(..))
liftPQ :: B.ByteString -> Connection -> (PQ.Connection -> IO (Maybe a)) -> IO a
liftPQ :: ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
str Connection
conn Connection -> IO (Maybe a)
m = Connection -> (Connection -> IO a) -> IO a
forall a. Connection -> (Connection -> IO a) -> IO a
withConnection Connection
conn ((Connection -> IO a) -> IO a) -> (Connection -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Connection
c -> do
Maybe a
res <- Connection -> IO (Maybe a)
m Connection
c
case Maybe a
res of
Maybe a
Nothing -> do
ByteString
msg <- ByteString
-> (ByteString -> ByteString) -> Maybe ByteString -> ByteString
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ByteString
str ByteString -> ByteString
forall a. a -> a
id (Maybe ByteString -> ByteString)
-> IO (Maybe ByteString) -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Connection -> IO (Maybe ByteString)
PQ.errorMessage Connection
c
SqlError -> IO a
forall e a. Exception e => e -> IO a
throwIO (SqlError -> IO a) -> SqlError -> IO a
forall a b. (a -> b) -> a -> b
$ ByteString -> SqlError
fatalError ByteString
msg
Just a
x -> a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
x
loCreat :: Connection -> IO Oid
loCreat :: Connection -> IO Oid
loCreat Connection
conn = ByteString
-> Connection -> (Connection -> IO (Maybe Oid)) -> IO Oid
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loCreat" Connection
conn (\Connection
c -> Connection -> IO (Maybe Oid)
PQ.loCreat Connection
c)
loCreate :: Connection -> Oid -> IO Oid
loCreate :: Connection -> Oid -> IO Oid
loCreate Connection
conn Oid
oid = ByteString
-> Connection -> (Connection -> IO (Maybe Oid)) -> IO Oid
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loCreate" Connection
conn (\Connection
c -> Connection -> Oid -> IO (Maybe Oid)
PQ.loCreate Connection
c Oid
oid)
loImport :: Connection -> FilePath -> IO Oid
loImport :: Connection -> FilePath -> IO Oid
loImport Connection
conn FilePath
path = ByteString
-> Connection -> (Connection -> IO (Maybe Oid)) -> IO Oid
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loImport" Connection
conn (\Connection
c -> Connection -> FilePath -> IO (Maybe Oid)
PQ.loImport Connection
c FilePath
path)
loImportWithOid :: Connection -> FilePath -> Oid -> IO Oid
loImportWithOid :: Connection -> FilePath -> Oid -> IO Oid
loImportWithOid Connection
conn FilePath
path Oid
oid = ByteString
-> Connection -> (Connection -> IO (Maybe Oid)) -> IO Oid
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loImportWithOid" Connection
conn (\Connection
c -> Connection -> FilePath -> Oid -> IO (Maybe Oid)
PQ.loImportWithOid Connection
c FilePath
path Oid
oid)
loExport :: Connection -> Oid -> FilePath -> IO ()
loExport :: Connection -> Oid -> FilePath -> IO ()
loExport Connection
conn Oid
oid FilePath
path = ByteString -> Connection -> (Connection -> IO (Maybe ())) -> IO ()
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loExport" Connection
conn (\Connection
c -> Connection -> Oid -> FilePath -> IO (Maybe ())
PQ.loExport Connection
c Oid
oid FilePath
path)
loOpen :: Connection -> Oid -> IOMode -> IO LoFd
loOpen :: Connection -> Oid -> IOMode -> IO LoFd
loOpen Connection
conn Oid
oid IOMode
mode = ByteString
-> Connection -> (Connection -> IO (Maybe LoFd)) -> IO LoFd
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loOpen" Connection
conn (\Connection
c -> Connection -> Oid -> IOMode -> IO (Maybe LoFd)
PQ.loOpen Connection
c Oid
oid IOMode
mode )
loWrite :: Connection -> LoFd -> B.ByteString -> IO Int
loWrite :: Connection -> LoFd -> ByteString -> IO Int
loWrite Connection
conn LoFd
fd ByteString
dat = ByteString
-> Connection -> (Connection -> IO (Maybe Int)) -> IO Int
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loWrite" Connection
conn (\Connection
c -> Connection -> LoFd -> ByteString -> IO (Maybe Int)
PQ.loWrite Connection
c LoFd
fd ByteString
dat)
loRead :: Connection -> LoFd -> Int -> IO B.ByteString
loRead :: Connection -> LoFd -> Int -> IO ByteString
loRead Connection
conn LoFd
fd Int
maxlen = ByteString
-> Connection
-> (Connection -> IO (Maybe ByteString))
-> IO ByteString
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loRead" Connection
conn (\Connection
c -> Connection -> LoFd -> Int -> IO (Maybe ByteString)
PQ.loRead Connection
c LoFd
fd Int
maxlen)
loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO Int
loSeek :: Connection -> LoFd -> SeekMode -> Int -> IO Int
loSeek Connection
conn LoFd
fd SeekMode
seekmode Int
offset = ByteString
-> Connection -> (Connection -> IO (Maybe Int)) -> IO Int
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loSeek" Connection
conn (\Connection
c -> Connection -> LoFd -> SeekMode -> Int -> IO (Maybe Int)
PQ.loSeek Connection
c LoFd
fd SeekMode
seekmode Int
offset)
loTell :: Connection -> LoFd -> IO Int
loTell :: Connection -> LoFd -> IO Int
loTell Connection
conn LoFd
fd = ByteString
-> Connection -> (Connection -> IO (Maybe Int)) -> IO Int
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loTell" Connection
conn (\Connection
c -> Connection -> LoFd -> IO (Maybe Int)
PQ.loTell Connection
c LoFd
fd)
loTruncate :: Connection -> LoFd -> Int -> IO ()
loTruncate :: Connection -> LoFd -> Int -> IO ()
loTruncate Connection
conn LoFd
fd Int
len = ByteString -> Connection -> (Connection -> IO (Maybe ())) -> IO ()
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loTruncate" Connection
conn (\Connection
c -> Connection -> LoFd -> Int -> IO (Maybe ())
PQ.loTruncate Connection
c LoFd
fd Int
len)
loClose :: Connection -> LoFd -> IO ()
loClose :: Connection -> LoFd -> IO ()
loClose Connection
conn LoFd
fd = ByteString -> Connection -> (Connection -> IO (Maybe ())) -> IO ()
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loClose" Connection
conn (\Connection
c -> Connection -> LoFd -> IO (Maybe ())
PQ.loClose Connection
c LoFd
fd)
loUnlink :: Connection -> Oid -> IO ()
loUnlink :: Connection -> Oid -> IO ()
loUnlink Connection
conn Oid
oid = ByteString -> Connection -> (Connection -> IO (Maybe ())) -> IO ()
forall a.
ByteString -> Connection -> (Connection -> IO (Maybe a)) -> IO a
liftPQ ByteString
"loUnlink" Connection
conn (\Connection
c -> Connection -> Oid -> IO (Maybe ())
PQ.loUnlink Connection
c Oid
oid)