4343{-# LANGUAGE OverloadedStrings #-}
4444{-# LANGUAGE ScopedTypeVariables #-}
4545{-# LANGUAGE BangPatterns #-}
46+ {-# LANGUAGE DerivingStrategies #-}
4647{-# LANGUAGE GeneralizedNewtypeDeriving #-}
47- {-# LANGUAGE DeriveDataTypeable #-}
4848
4949module Database.PostgreSQL.LibPQ
5050 (
@@ -213,23 +213,18 @@ module Database.PostgreSQL.LibPQ
213213 )
214214where
215215
216- import Prelude hiding ( print )
216+ import Control.Exception ( try , IOException , mask_ )
217217import Foreign
218218import Foreign.C.Types
219219import Foreign.C.String
220- #if __GLASGOW_HASKELL__ >= 702
221220import qualified Foreign.ForeignPtr.Unsafe as Unsafe
222- #endif
223221import qualified Foreign.Concurrent as FC
224222import System.Posix.Types ( Fd (.. ) )
225223import System.IO ( IOMode (.. ), SeekMode (.. ) )
226224
227- #if __GLASGOW_HASKELL__ >= 700
228225import GHC.Conc ( closeFdWith ) -- Won't work with GHC 7.0.1
229- #endif
230226import System.Posix.Types ( CPid )
231227
232- import Data.ByteString.Char8 ()
233228import qualified Data.ByteString.Unsafe as B
234229import qualified Data.ByteString.Internal as B ( fromForeignPtr
235230 , c_strlen
@@ -246,14 +241,6 @@ import Database.PostgreSQL.LibPQ.Marshal
246241import Database.PostgreSQL.LibPQ.Notify
247242import Database.PostgreSQL.LibPQ.Oid
248243
249- #if __GLASGOW_HASKELL__ >= 700
250- import Control.Exception (mask_ )
251- #else
252- import qualified Control.Exception
253- mask_ = Control.Exception. block
254- #endif
255-
256- import Control.Exception (try , IOException )
257244
258245#ifndef mingw32_HOST_OS
259246import System.Posix.DynamicLinker
@@ -311,7 +298,6 @@ connectStart connStr =
311298
312299pqfinish :: Ptr PGconn -> MVar NoticeBuffer -> IO ()
313300pqfinish conn noticeBuffer = do
314- #if __GLASGOW_HASKELL__ >= 700
315301-- This covers the case when a connection is closed while other Haskell
316302-- threads are using GHC's IO manager to wait on the descriptor. This is
317303-- commonly the case with asynchronous notifications, for example. Since
@@ -324,9 +310,7 @@ pqfinish conn noticeBuffer = do
324310 -- This case may be worth investigating further
325311 c_PQfinish conn
326312 fd -> closeFdWith (\ _ -> c_PQfinish conn) (Fd fd)
327- #else
328- c_PQfinish conn
329- #endif
313+
330314 nb <- swapMVar noticeBuffer nullPtr
331315 c_free_noticebuffer nb
332316
@@ -350,11 +334,7 @@ newNullConnection = do
350334
351335-- | Test if a connection is the Null Connection.
352336isNullConnection :: Connection -> Bool
353- #if __GLASGOW_HASKELL__ >= 702
354337isNullConnection (Conn x _) = Unsafe. unsafeForeignPtrToPtr x == nullPtr
355- #else
356- isNullConnection (Conn x _) = unsafeForeignPtrToPtr x == nullPtr
357- #endif
358338{-# INLINE isNullConnection #-}
359339
360340-- | If 'connectStart' succeeds, the next stage is to poll libpq so
@@ -1039,8 +1019,12 @@ nfields :: Result
10391019nfields res = withResult res (return . toColumn . c_PQnfields)
10401020
10411021
1042- newtype Column = Col CInt deriving (Eq , Ord , Show , Enum , Num )
1043- newtype Row = Row CInt deriving (Eq , Ord , Show , Enum , Num )
1022+ newtype Column = Col CInt
1023+ deriving stock (Eq , Ord , Show )
1024+ deriving newtype (Enum , Num )
1025+ newtype Row = Row CInt
1026+ deriving stock (Eq , Ord , Show )
1027+ deriving newtype (Enum , Num )
10441028
10451029toColumn :: (Integral a ) => a -> Column
10461030toColumn = Col . fromIntegral
@@ -2173,13 +2157,8 @@ foreign import ccall unsafe "libpq-fe.h PQsocket"
21732157foreign import ccall " libpq-fe.h PQerrorMessage"
21742158 c_PQerrorMessage :: Ptr PGconn -> IO CString
21752159
2176- #if __GLASGOW_HASKELL__ >= 700
21772160foreign import ccall " libpq-fe.h PQfinish"
21782161 c_PQfinish :: Ptr PGconn -> IO ()
2179- #else
2180- foreign import ccall " libpq-fe.h &PQfinish"
2181- p_PQfinish :: FunPtr (Ptr PGconn -> IO () )
2182- #endif
21832162
21842163foreign import ccall " libpq-fe.h PQreset"
21852164 c_PQreset :: Ptr PGconn -> IO ()
0 commit comments