3737--
3838-----------------------------------------------------------------------------
3939
40+ {-# LANGUAGE CPP #-}
4041{-# LANGUAGE ForeignFunctionInterface #-}
4142{-# LANGUAGE EmptyDataDecls #-}
4243{-# LANGUAGE OverloadedStrings #-}
@@ -212,10 +213,6 @@ module Database.PostgreSQL.LibPQ
212213 )
213214where
214215
215- #include <libpq-fe.h>
216- #include <libpq/libpq-fs.h>
217- #include "noticehandlers.h"
218-
219216import Prelude hiding ( print )
220217import Foreign
221218import Foreign.C.Types
@@ -242,12 +239,12 @@ import qualified Data.ByteString as B
242239
243240import Control.Concurrent.MVar
244241
245- import Data.Typeable
246-
247242import Database.PostgreSQL.LibPQ.Compat
248243import Database.PostgreSQL.LibPQ.Enums
249244import Database.PostgreSQL.LibPQ.Internal
250245import Database.PostgreSQL.LibPQ.Marshal
246+ import Database.PostgreSQL.LibPQ.Notify
247+ import Database.PostgreSQL.LibPQ.Oid
251248
252249#if __GLASGOW_HASKELL__ >= 700
253250import Control.Exception (mask_ )
@@ -699,12 +696,6 @@ connectionUsedPassword connection =
699696newtype Result = Result (ForeignPtr PGresult ) deriving (Eq , Show )
700697data PGresult
701698
702-
703- newtype Oid = Oid CUInt deriving (Eq , Ord , Read , Show , Storable , Typeable )
704-
705- invalidOid :: Oid
706- invalidOid = Oid (# const InvalidOid )
707-
708699-- | Convert a list of parameters to the format expected by libpq FFI calls.
709700withParams :: [Maybe (Oid , B. ByteString , Format )]
710701 -> (CInt -> Ptr Oid -> Ptr CString -> Ptr CInt -> Ptr CInt -> IO a )
@@ -1739,35 +1730,7 @@ cancel (Cancel fp) =
17391730-- ordinary SQL commands. The arrival of NOTIFY messages can
17401731-- subsequently be detected by calling 'notifies'.
17411732
1742- data Notify = Notify {
1743- notifyRelname :: {-# UNPACK #-} ! B. ByteString -- ^ notification channel name
1744- , notifyBePid :: {-# UNPACK #-} ! CPid -- ^ process ID of notifying server process
1745- , notifyExtra :: {-# UNPACK #-} ! B. ByteString -- ^ notification payload string
1746- } deriving Show
17471733
1748- #if __GLASGOW_HASKELL__ < 800
1749- #let alignment t = "%lu", (unsigned long)offsetof(struct {char x__; t (y__); }, y__)
1750- #endif
1751- instance Storable Notify where
1752- sizeOf _ = # {size PGnotify }
1753-
1754- alignment _ = # {alignment PGnotify }
1755-
1756- peek ptr = do
1757- relname <- B. packCString =<< # {peek PGnotify , relname} ptr
1758- extra <- B. packCString =<< # {peek PGnotify , extra} ptr
1759- be_pid <- fmap f $ # {peek PGnotify , be_pid} ptr
1760- return $! Notify relname be_pid extra
1761- where
1762- f :: CInt -> CPid
1763- f = fromIntegral
1764-
1765- poke ptr (Notify a b c) =
1766- B. useAsCString a $ \ a' ->
1767- B. useAsCString c $ \ c' ->
1768- do # {poke PGnotify , relname} ptr a'
1769- # {poke PGnotify , be_pid} ptr (fromIntegral b :: CInt )
1770- # {poke PGnotify , extra} ptr c'
17711734
17721735
17731736-- | Returns the next notification from a list of unhandled
@@ -1915,8 +1878,6 @@ maybeBsFromForeignPtr fp f =
19151878
19161879type NoticeReceiver = NoticeBuffer -> Ptr PGresult -> IO ()
19171880
1918- data PGnotice
1919-
19201881-- | Upon connection initialization, any notices received from the server are
19211882-- normally written to the console. Notices are akin to warnings, and
19221883-- are distinct from notifications. This function suppresses notices.
@@ -1954,8 +1915,8 @@ getNotice (Conn _ nbRef) =
19541915 then return Nothing
19551916 else do
19561917 fp <- newForeignPtr finalizerFree (castPtr np)
1957- len <- # {peek PGnotice , len} np
1958- return $! Just $! mkPS fp ( # offset PGnotice , str) len
1918+ len <- pgNoticePeekLen np
1919+ return $! Just $! mkPS fp pgNoticeOffsetStr ( fromIntegral len)
19591920
19601921-- $largeobjects
19611922
0 commit comments