{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
module Snap.Snaplet.PostgresqlSimple (
Postgres(..)
, HasPostgres(..)
, PGSConfig(..)
, pgsDefaultConfig
, mkPGSConfig
, pgsInit
, pgsInit'
, getConnectionString
, withPG
, P.Connection
, liftPG
, liftPG'
, query
, query_
, fold
, foldWithOptions
, fold_
, foldWithOptions_
, forEach
, forEach_
, execute
, execute_
, executeMany
, returning
, withTransaction
, withTransactionLevel
, withTransactionMode
, withTransactionEither
, withTransactionModeEither
, formatMany
, formatQuery
, P.Query
, P.In(..)
, P.Binary(..)
, P.Only(..)
, P.SqlError(..)
, P.FormatError(..)
, P.QueryError(..)
, P.ResultError(..)
, P.TransactionMode(..)
, P.IsolationLevel(..)
, P.ReadWriteMode(..)
, P.begin
, P.beginLevel
, P.beginMode
, P.rollback
, P.commit
, (P.:.)(..)
, ToRow(..)
, FromRow(..)
, P.defaultConnectInfo
, P.defaultTransactionMode
, P.defaultIsolationLevel
, P.defaultReadWriteMode
, field
) where
import qualified Control.Exception as E
import Control.Lens (set, (^#))
import Control.Monad (liftM)
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Reader (ReaderT, ask, asks,
local)
import Control.Monad.State (get)
import Control.Monad.Trans.Control (MonadBaseControl,
liftBaseWith, restoreM)
import Data.ByteString (ByteString)
import qualified Data.Configurator as C
import qualified Data.Configurator.Types as C
import Data.Int (Int64)
import Data.Monoid (Monoid (..), (<>))
import Data.Pool (createPool)
import Data.Ratio (denominator, numerator)
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Builder as TB
import qualified Data.Text.Lazy.Builder.Int as TB
import qualified Data.Text.Lazy.Builder.RealFloat as TB
import qualified Database.PostgreSQL.Simple as P
import Database.PostgreSQL.Simple.FromRow
import Database.PostgreSQL.Simple.ToRow
import qualified Database.PostgreSQL.Simple.Transaction as P
import Paths_snaplet_postgresql_simple
import Prelude hiding ((++))
import qualified Snap as Snap
import Snap.Snaplet.PostgresqlSimple.Internal
instance HasPostgres (Snap.Handler b Postgres) where
getPostgresState = get
setLocalPostgresState s = local (const s)
instance {-# OVERLAPPING #-} (MonadIO m, MonadBaseControl IO m)
=> HasPostgres (ReaderT (Snap.Snaplet Postgres) m) where
getPostgresState = asks (^# Snap.snapletValue)
setLocalPostgresState s = local (set Snap.snapletValue s)
instance {-# OVERLAPPING #-} (MonadIO m, MonadBaseControl IO m)
=> HasPostgres (ReaderT Postgres m) where
getPostgresState = ask
setLocalPostgresState s = local (const s)
getConnectionString :: C.Config -> IO ByteString
getConnectionString config = do
let params =
[ ["host"]
, ["hostaddr"]
, ["port"]
, ["dbname","db"]
, ["user"]
, ["password","pass"]
, ["connection_timeout"]
, ["client_encoding"]
, ["options"]
, ["application_name"]
, ["fallback_application_name"]
, ["keepalives"]
, ["keepalives_idle"]
, ["keepalives_interval"]
, ["keepalives_count"]
, ["sslmode"]
, ["sslcompression"]
, ["sslcert"]
, ["sslkey"]
, ["sslrootcert"]
, ["sslcrl"]
, ["requirepeer"]
, ["krbsrvname"]
, ["gsslib"]
, ["service"]
]
connstr <- fmap mconcat $ mapM showParam params
extra <- fmap TB.fromText $ C.lookupDefault "" config "connectionString"
return $! T.encodeUtf8 (TL.toStrict (TB.toLazyText (connstr <> extra)))
where
qt = TB.singleton '\''
bs = TB.singleton '\\'
sp = TB.singleton ' '
eq = TB.singleton '='
lookupConfig = foldr (\name names -> do
mval <- C.lookup config name
case mval of
Nothing -> names
Just _ -> return mval)
(return Nothing)
showParam [] = undefined
showParam names@(name:_) = do
mval :: Maybe C.Value <- lookupConfig names
let key = TB.fromText name <> eq
case mval of
Nothing -> return mempty
Just (C.Bool x) -> return (key <> showBool x <> sp)
Just (C.String x) -> return (key <> showText x <> sp)
Just (C.Number x) -> return (key <> showNum x <> sp)
Just (C.List _) -> return mempty
showBool x = TB.decimal (fromEnum x)
nd ratio = (numerator ratio, denominator ratio)
showNum (nd -> (n,1)) = TB.decimal n
showNum x = TB.formatRealFloat TB.Fixed Nothing
( fromIntegral (numerator x)
/ fromIntegral (denominator x) :: Double )
showText x = qt <> loop x
where
loop (T.break escapeNeeded -> (a,b))
= TB.fromText a <>
case T.uncons b of
Nothing -> qt
Just (c,b') -> escapeChar c <> loop b'
escapeNeeded c = c == '\'' || c == '\\'
escapeChar c = case c of
'\'' -> bs <> qt
'\\' -> bs <> bs
_ -> TB.singleton c
description :: T.Text
description = "PostgreSQL abstraction"
datadir :: Maybe (IO FilePath)
datadir = Just $ liftM (<>"/resources/db") getDataDir
pgsInit :: Snap.SnapletInit b Postgres
pgsInit = Snap.makeSnaplet "postgresql-simple" description datadir $ do
config <- mkPGSConfig =<< Snap.getSnapletUserConfig
initHelper config
pgsInit' :: PGSConfig -> Snap.SnapletInit b Postgres
pgsInit' config = Snap.makeSnaplet "postgresql-simple" description Nothing $
initHelper config
mkPGSConfig :: MonadIO m => C.Config -> m PGSConfig
mkPGSConfig config = liftIO $ do
connstr <- getConnectionString config
stripes <- C.lookupDefault 1 config "numStripes"
idle <- C.lookupDefault 5 config "idleTime"
resources <- C.lookupDefault 20 config "maxResourcesPerStripe"
return $ PGSConfig connstr stripes idle resources
initHelper :: MonadIO m => PGSConfig -> m Postgres
initHelper PGSConfig{..} = do
pool <- liftIO $ createPool (P.connectPostgreSQL pgsConnStr) P.close
pgsNumStripes (realToFrac pgsIdleTime)
pgsResources
return $ PostgresPool pool
query :: (HasPostgres m, ToRow q, FromRow r)
=> P.Query -> q -> m [r]
query q params = liftPG' (\c -> P.query c q params)
query_ :: (HasPostgres m, FromRow r) => P.Query -> m [r]
query_ q = liftPG' (`P.query_` q)
returning :: (HasPostgres m, ToRow q, FromRow r)
=> P.Query -> [q] -> m [r]
returning q params = liftPG' (\c -> P.returning c q params)
fold :: (HasPostgres m,
FromRow row,
ToRow params)
=> P.Query -> params -> b -> (b -> row -> IO b) -> m b
fold template qs a f = liftPG' (\c -> P.fold c template qs a f)
foldWithOptions :: (HasPostgres m,
FromRow row,
ToRow params)
=> P.FoldOptions
-> P.Query
-> params
-> b
-> (b -> row -> IO b)
-> m b
foldWithOptions opts template qs a f =
liftPG' (\c -> P.foldWithOptions opts c template qs a f)
fold_ :: (HasPostgres m,
FromRow row)
=> P.Query -> b -> (b -> row -> IO b) -> m b
fold_ template a f = liftPG' (\c -> P.fold_ c template a f)
foldWithOptions_ :: (HasPostgres m,
FromRow row)
=> P.FoldOptions
-> P.Query
-> b
-> (b -> row -> IO b)
-> m b
foldWithOptions_ opts template a f =
liftPG' (\c -> P.foldWithOptions_ opts c template a f)
forEach :: (HasPostgres m,
FromRow r,
ToRow q)
=> P.Query -> q -> (r -> IO ()) -> m ()
forEach template qs f = liftPG' (\c -> P.forEach c template qs f)
forEach_ :: (HasPostgres m,
FromRow r)
=> P.Query -> (r -> IO ()) -> m ()
forEach_ template f = liftPG' (\c -> P.forEach_ c template f)
execute :: (HasPostgres m, ToRow q)
=> P.Query -> q -> m Int64
execute template qs = liftPG' (\c -> P.execute c template qs)
execute_ :: (HasPostgres m)
=> P.Query -> m Int64
execute_ template = liftPG' (`P.execute_` template)
executeMany :: (HasPostgres m, ToRow q)
=> P.Query -> [q] -> m Int64
executeMany template qs = liftPG' (\c -> P.executeMany c template qs)
withTransaction :: (HasPostgres m)
=> m a -> m a
withTransaction = withTransactionMode P.defaultTransactionMode
withTransactionLevel :: (HasPostgres m)
=> P.IsolationLevel -> m a -> m a
withTransactionLevel lvl =
withTransactionMode P.defaultTransactionMode { P.isolationLevel = lvl }
withTransactionMode :: (HasPostgres m)
=> P.TransactionMode -> m a -> m a
withTransactionMode mode act = withPG $ do
pg <- getPostgresState
r <- liftBaseWith $ \run -> E.mask
$ \unmask -> withConnection pg
$ \con -> do
P.beginMode mode con
r <- unmask (run act) `E.onException` P.rollback con
P.commit con
return r
restoreM r
withTransactionEither :: (HasPostgres m)
=> m (Either a b) -> m (Either a b)
withTransactionEither = withTransactionModeEither P.defaultTransactionMode
withTransactionModeEither :: (HasPostgres m)
=> P.TransactionMode -> m (Either a b) -> m (Either a b)
withTransactionModeEither mode act = withPG $ do
pg <- getPostgresState
r <- liftBaseWith $ \run -> E.mask
$ \unmask -> withConnection pg
$ \con -> do
P.beginMode mode con
r <- unmask (run act) `E.onException` P.rollback con
either (const $ P.rollback con) (const $ P.commit con) $ restoreM r
return r
restoreM r
formatMany :: (ToRow q, HasPostgres m)
=> P.Query -> [q] -> m ByteString
formatMany q qs = liftPG' (\c -> P.formatMany c q qs)
formatQuery :: (ToRow q, HasPostgres m)
=> P.Query -> q -> m ByteString
formatQuery q qs = liftPG' (\c -> P.formatQuery c q qs)