{-# LANGUAGE CPP #-}
module Database.PostgreSQL.Simple.Compat
( mask
, (<>)
, unsafeDupablePerformIO
, toByteString
, scientificBuilder
, toPico
, fromPico
) where
import qualified Control.Exception as E
import Data.Monoid
import Data.ByteString (ByteString)
#if MIN_VERSION_bytestring(0,10,0)
import Data.ByteString.Lazy (toStrict)
#else
import qualified Data.ByteString as B
import Data.ByteString.Lazy (toChunks)
#endif
import Data.ByteString.Builder (Builder, toLazyByteString)
#if MIN_VERSION_scientific(0,3,0)
import Data.Text.Lazy.Builder.Scientific (scientificBuilder)
#else
import Data.Scientific (scientificBuilder)
#endif
#if __GLASGOW_HASKELL__ >= 702
import System.IO.Unsafe (unsafeDupablePerformIO)
#elif __GLASGOW_HASKELL__ >= 611
import GHC.IO (unsafeDupablePerformIO)
#else
import GHC.IOBase (unsafeDupablePerformIO)
#endif
import Data.Fixed (Pico)
#if MIN_VERSION_base(4,7,0)
import Data.Fixed (Fixed(MkFixed))
#else
import Unsafe.Coerce (unsafeCoerce)
#endif
mask :: ((IO a -> IO a) -> IO b) -> IO b
#if MIN_VERSION_base(4,3,0)
mask :: forall a b. ((IO a -> IO a) -> IO b) -> IO b
mask (IO a -> IO a) -> IO b
io = forall b. ((forall a. IO a -> IO a) -> IO b) -> IO b
E.mask forall a b. (a -> b) -> a -> b
$ \forall a. IO a -> IO a
restore -> (IO a -> IO a) -> IO b
io forall a. IO a -> IO a
restore
#else
mask io = do
b <- E.blocked
E.block $ io $ \m -> if b then m else E.unblock m
#endif
{-# INLINE mask #-}
#if !MIN_VERSION_base(4,5,0)
infixr 6 <>
(<>) :: Monoid m => m -> m -> m
(<>) = mappend
{-# INLINE (<>) #-}
#endif
toByteString :: Builder -> ByteString
#if MIN_VERSION_bytestring(0,10,0)
toByteString :: Builder -> ByteString
toByteString Builder
x = ByteString -> ByteString
toStrict (Builder -> ByteString
toLazyByteString Builder
x)
#else
toByteString x = B.concat (toChunks (toLazyByteString x))
#endif
#if MIN_VERSION_base(4,7,0)
toPico :: Integer -> Pico
toPico :: Integer -> Pico
toPico = forall k (a :: k). Integer -> Fixed a
MkFixed
fromPico :: Pico -> Integer
fromPico :: Pico -> Integer
fromPico (MkFixed Integer
i) = Integer
i
#else
toPico :: Integer -> Pico
toPico = unsafeCoerce
fromPico :: Pico -> Integer
fromPico = unsafeCoerce
#endif