Skip to content

Commit

Permalink
Fix deprecation warning
Browse files Browse the repository at this point in the history
  • Loading branch information
alexfmpe committed May 4, 2024
1 parent 5954006 commit 1829078
Showing 1 changed file with 3 additions and 2 deletions.
Original file line number Diff line number Diff line change
@@ -1,9 +1,10 @@
{-# LANGUAGE TypeApplications #-}
module Gargoyle.PostgreSQL.Connect (withDb, withDb', openDb) where

import Control.Monad ((>=>))
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Data.Pool (Pool, createPool)
import Data.Pool (Pool, defaultPoolConfig, newPool, setNumStripes)
import Database.PostgreSQL.Simple (Connection, close, connectPostgreSQL)
import Gargoyle (withGargoyle)
import Gargoyle.PostgreSQL.Nix (postgresNix)
Expand All @@ -17,7 +18,7 @@ withDb dbPath f = either error pure =<< withDb' dbPath (openDb >=> f)

-- | Convert a connection string into a connection 'Pool'.
openDb :: ByteString -> IO (Pool Connection)
openDb dbUri = createPool (connectPostgreSQL dbUri) close 1 5 20
openDb dbUri = newPool $ setNumStripes (Just 1) $ defaultPoolConfig (connectPostgreSQL dbUri) close (realToFrac @Int 5) 20

-- | Connects to a database using information at the given filepath.
-- The given filepath can be either a folder (for a local db)
Expand Down

0 comments on commit 1829078

Please # to comment.