Skip to content
Open
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
32 changes: 24 additions & 8 deletions gargoyle-postgresql-connect/src/Gargoyle/PostgreSQL/Connect.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,11 @@
module Gargoyle.PostgreSQL.Connect (withDb, openDb) where
{-# LANGUAGE LambdaCase #-}
module Gargoyle.PostgreSQL.Connect
( openDb
, withDb
, withDbConnString
) where

import Control.Monad ((>=>))
import Control.Monad ((<=<))
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Data.Pool (Pool, createPool)
Expand All @@ -18,15 +23,26 @@ import System.Directory (doesFileExist)
-- order to open and start the database. Otherwise, it will create the
-- database for you if it doesn't exist.
withDb :: String -> (Pool Connection -> IO a) -> IO a
withDb dbPath a = do
withDb dbPath k = do
dbExists <- doesFileExist dbPath
if dbExists
flip withDbConnString k =<< if dbExists
-- use the file contents as the uri for an existing server
then C8.readFile dbPath >>= openDb . head . C8.lines >>= a
then Left . head . C8.lines <$> C8.readFile dbPath
-- otherwise assume it's a folder for a local database
else do
g <- postgresNix
withGargoyle g dbPath $ openDb >=> a
else pure $ Right dbPath

-- | Either connects to a database at the given connection string in the Left
-- case, or uses gargoyle at the filepath specified in the Right case. Allows
-- to keep the connection string at a different place from the gargoyle
-- cluster.
withDbConnString :: Either ByteString FilePath -> (Pool Connection -> IO a) -> IO a
withDbConnString = \case
-- use the file contents as the uri for an existing server
Left connStr -> (>>=) (openDb connStr)
-- otherwise assume it's a folder for a local database
Right gargoylePath -> \k -> do
g <- postgresNix
withGargoyle g gargoylePath $ k <=< openDb

openDb :: ByteString -> IO (Pool Connection)
openDb dbUri = createPool (connectPostgreSQL dbUri) close 1 5 20