{-# OPTIONS_HADDOCK prune #-}
module Database.Postgres.Temp.Internal.Core where
import Control.Concurrent
import Control.Concurrent.Async (race_, withAsync)
import Control.Exception
import Control.Monad
import qualified Data.ByteString.Char8 as BSC
import Data.Foldable (for_)
import Data.IORef
import Data.Typeable
import qualified Database.PostgreSQL.Simple as PG
import qualified Database.PostgreSQL.Simple.Options as Client
import System.Directory
import System.Exit (ExitCode(..))
import System.IO
import System.IO.Unsafe (unsafePerformIO)
import System.Posix.Signals (sigINT, sigQUIT, signalProcess)
import System.Process
import System.Process.Internals
import System.Timeout
import Text.PrettyPrint.ANSI.Leijen hiding ((<$>))
data Event
= StartPlan String
| StartPostgres
| WaitForDB
| TryToConnect
deriving (Eq, Ord)
instance Show Event where
show = \case
StartPlan x -> "StartPlan:\n" <> x
StartPostgres -> "StartPostgres"
WaitForDB -> "WaitForDB"
TryToConnect -> "TryToConnect"
data StartError
= StartPostgresFailed ExitCode
| InitDbFailed
{ startErrorStdOut :: String
, startErrorStdErr :: String
, startErrorExitCode :: ExitCode
}
| CreateDbFailed
{ startErrorStdOut :: String
, startErrorStdErr :: String
, startErrorExitCode :: ExitCode
}
| PlanFailed String [String]
| CompleteProcessConfigFailed String [String]
| ConnectionTimedOut
| DeleteDbError PG.SqlError
| EmptyDataDirectory
| CopyCachedInitDbFailed String ExitCode
| FailedToFindDataDirectory String
| SnapshotCopyFailed String ExitCode
deriving (Show, Eq, Typeable)
instance Exception StartError
type Logger = Event -> IO ()
throwIfNotSuccess :: Exception e => (ExitCode -> e) -> ExitCode -> IO ()
throwIfNotSuccess f = \case
ExitSuccess -> pure ()
e -> throwIO $ f e
waitForDB :: Logger -> Client.Options -> IO ()
waitForDB logger options = do
logger TryToConnect
let theConnectionString = Client.toConnectionString options
startAction = PG.connectPostgreSQL theConnectionString
try (bracket startAction PG.close mempty) >>= \case
Left (_ :: IOError) -> threadDelay 1000 >> waitForDB logger options
Right () -> return ()
teeHandle :: Handle -> (Handle -> IO a) -> IO (a, String)
teeHandle orig f =
bracket createPipe (\(x, y) -> hClose x >> hClose y) $ \(readEnd, writeEnd) -> do
outputRef <- newIORef []
let readerLoop = forever $ do
theLine <- hGetLine readEnd
modifyIORef outputRef (<>theLine)
hPutStrLn orig theLine
res <- withAsync readerLoop $ \_ -> f writeEnd
(res,) <$> readIORef outputRef
data CompleteProcessConfig = CompleteProcessConfig
{ completeProcessConfigEnvVars :: [(String, String)]
, completeProcessConfigCmdLine :: [String]
, completeProcessConfigStdIn :: Handle
, completeProcessConfigStdOut :: Handle
, completeProcessConfigStdErr :: Handle
}
prettyHandle :: Handle -> Doc
prettyHandle _ = text "HANDLE"
prettyKeyPair ::(Pretty a, Pretty b) => a -> b -> Doc
prettyKeyPair k v = pretty k <> text ": " <> pretty v
instance Pretty CompleteProcessConfig where
pretty CompleteProcessConfig {..}
= text "completeProcessConfigEnvVars:"
<> softline
<> indent 2 (vsep (map (uncurry prettyKeyPair) completeProcessConfigEnvVars))
<> hardline
<> text "completeProcessConfigCmdLine:"
<> softline
<> text (unwords completeProcessConfigCmdLine)
<> hardline
<> text "completeProcessConfigStdIn:"
<+> prettyHandle completeProcessConfigStdIn
<> hardline
<> text "completeProcessConfigStdOut:"
<+> prettyHandle completeProcessConfigStdOut
<> hardline
<> text "completeProcessConfigStdErr:"
<+> prettyHandle completeProcessConfigStdErr
startProcess
:: String
-> CompleteProcessConfig
-> IO ProcessHandle
startProcess name CompleteProcessConfig {..} = (\(_, _, _, x) -> x) <$>
createProcess_ name (proc name completeProcessConfigCmdLine)
{ std_err = UseHandle completeProcessConfigStdErr
, std_out = UseHandle completeProcessConfigStdOut
, std_in = UseHandle completeProcessConfigStdIn
, env = Just completeProcessConfigEnvVars
}
stopProcess :: ProcessHandle -> IO ExitCode
stopProcess = waitForProcess
executeProcess
:: String
-> CompleteProcessConfig
-> IO ExitCode
executeProcess name conf =
bracket (startProcess name conf) terminateProcess waitForProcess
executeProcessAndTee
:: String
-> CompleteProcessConfig
-> IO (ExitCode, String, String)
executeProcessAndTee name config = fmap (\((x, y), z) -> (x, z, y)) $
teeHandle (completeProcessConfigStdOut config) $ \newOut ->
teeHandle (completeProcessConfigStdErr config) $ \newErr ->
executeProcess name $ config
{ completeProcessConfigStdErr = newErr
, completeProcessConfigStdOut = newOut
}
data CompletePostgresPlan = CompletePostgresPlan
{ completePostgresPlanProcessConfig :: CompleteProcessConfig
, completePostgresPlanClientOptions :: Client.Options
}
instance Pretty CompletePostgresPlan where
pretty CompletePostgresPlan {..}
= text "completePostgresPlanProcessConfig:"
<> softline
<> indent 2 (pretty completePostgresPlanProcessConfig)
<> hardline
<> text "completePostgresPlanClientOptions:"
<+> prettyOptions completePostgresPlanClientOptions
prettyOptions :: Client.Options -> Doc
prettyOptions = text . BSC.unpack . Client.toConnectionString
data PostgresProcess = PostgresProcess
{ postgresProcessClientOptions :: Client.Options
, postgresProcessHandle :: ProcessHandle
}
instance Pretty PostgresProcess where
pretty PostgresProcess {..}
= text "postgresProcessClientOptions:"
<+> prettyOptions postgresProcessClientOptions
stopPostgresProcess :: Bool -> PostgresProcess -> IO ExitCode
stopPostgresProcess graceful PostgresProcess{..} = do
withProcessHandle postgresProcessHandle $ \case
OpenHandle p ->
signalProcess (if graceful then sigINT else sigQUIT) p
OpenExtHandle {} -> pure ()
ClosedHandle _ -> return ()
waitForProcess postgresProcessHandle
startPostgresProcess :: Int -> Logger -> CompletePostgresPlan -> IO PostgresProcess
startPostgresProcess time logger CompletePostgresPlan {..} = do
logger StartPostgres
let startAction = PostgresProcess completePostgresPlanClientOptions
<$> startProcess "postgres" completePostgresPlanProcessConfig
bracketOnError startAction (stopPostgresProcess False) $
\result@PostgresProcess {..} -> do
logger WaitForDB
let options = completePostgresPlanClientOptions
{ Client.dbname = pure "template1"
}
checkForCrash = do
mExitCode <- getProcessExitCode postgresProcessHandle
for_ mExitCode (throwIO . StartPostgresFailed)
timeoutAndThrow = timeout time (waitForDB logger options) >>= \case
Just () -> pure ()
Nothing -> throwIO ConnectionTimedOut
timeoutAndThrow `race_` forever (checkForCrash >> threadDelay 100000)
return result
executeInitDb :: CompleteProcessConfig -> IO ()
executeInitDb config = do
(res, stdOut, stdErr) <- executeProcessAndTee "initdb" config
throwIfNotSuccess (InitDbFailed stdOut stdErr) res
data CompleteCopyDirectoryCommand = CompleteCopyDirectoryCommand
{ copyDirectoryCommandSrc :: FilePath
, copyDirectoryCommandDst :: FilePath
, copyDirectoryCommandCow :: Bool
} deriving (Show, Eq, Ord)
instance Pretty CompleteCopyDirectoryCommand where
pretty CompleteCopyDirectoryCommand {..}
= text "copyDirectoryCommandSrc:"
<> softline
<> indent 2 (text copyDirectoryCommandSrc)
<> hardline
<> text "copyDirectoryCommandDst:"
<> softline
<> indent 2 (text copyDirectoryCommandDst)
<> hardline
<> text "copyDirectoryCommandCow:"
<+> pretty copyDirectoryCommandCow
executeCopyDirectoryCommand :: CompleteCopyDirectoryCommand -> IO ()
executeCopyDirectoryCommand CompleteCopyDirectoryCommand {..} = do
let
#ifdef darwin_HOST_OS
cpFlags = if copyDirectoryCommandCow then "cp -Rc " else "cp -R "
#else
cpFlags = if copyDirectoryCommandCow then "cp -R --reflink=auto " else "cp -R "
#endif
copyCommand = cpFlags <> copyDirectoryCommandSrc <> "/* " <> copyDirectoryCommandDst
throwIfNotSuccess (CopyCachedInitDbFailed copyCommand) =<< system copyCommand
executeCreateDb :: CompleteProcessConfig -> IO ()
executeCreateDb config = do
(res, stdOut, stdErr) <- executeProcessAndTee "createdb" config
throwIfNotSuccess (CreateDbFailed stdOut stdErr) res
data InitDbCachePlan = InitDbCachePlan
{ cachePlanDataDirectory :: FilePath
, cachePlanInitDb :: CompleteProcessConfig
, cachePlanCopy :: CompleteCopyDirectoryCommand
}
instance Pretty InitDbCachePlan where
pretty InitDbCachePlan {..}
= text "cachePlanDataDirectory:"
<> softline
<> indent 2 (pretty cachePlanDataDirectory)
<> hardline
<> text "cachePlanInitDb:"
<> softline
<> indent 2 (pretty cachePlanInitDb)
<> hardline
<> text "cachePlanCopy:"
<> softline
<> indent 2 (pretty cachePlanCopy)
cacheLock :: MVar ()
cacheLock = unsafePerformIO $ newMVar ()
{-# NOINLINE cacheLock #-}
executeInitDbCachePlan :: InitDbCachePlan -> IO ()
executeInitDbCachePlan InitDbCachePlan {..} = do
withMVar cacheLock $ \_ -> do
exists <- doesDirectoryExist cachePlanDataDirectory
unless exists $ executeInitDb cachePlanInitDb
executeCopyDirectoryCommand cachePlanCopy
data Plan = Plan
{ completePlanLogger :: Logger
, completePlanInitDb :: Maybe (Either CompleteProcessConfig InitDbCachePlan)
, completePlanCopy :: Maybe CompleteCopyDirectoryCommand
, completePlanCreateDb :: Maybe CompleteProcessConfig
, completePlanPostgres :: CompletePostgresPlan
, completePlanConfig :: String
, completePlanDataDirectory :: FilePath
, completePlanConnectionTimeout :: Int
}
eitherPretty :: (Pretty a, Pretty b) => Either a b -> Doc
eitherPretty = either pretty pretty
instance Pretty Plan where
pretty Plan {..}
= text "completePlanInitDb:"
<> softline
<> indent 2 (pretty $ fmap eitherPretty completePlanInitDb)
<> hardline
<> text "completePlanCopy:"
<> softline
<> indent 2 (pretty completePlanCopy)
<> hardline
<> text "completePlanCreateDb:"
<> softline
<> indent 2 (pretty completePlanCreateDb)
<> hardline
<> text "completePlanPostgres:"
<> softline
<> indent 2 (pretty completePlanPostgres)
<> hardline
<> text "completePlanConfig:"
<> softline
<> indent 2 (pretty completePlanConfig)
<> hardline
<> text "completePlanDataDirectory:"
<+> pretty completePlanDataDirectory
startPlan :: Plan -> IO PostgresProcess
startPlan plan@Plan {..} = do
completePlanLogger $ StartPlan $ show $ pretty plan
for_ completePlanInitDb $ either executeInitDb executeInitDbCachePlan
for_ completePlanCopy executeCopyDirectoryCommand
versionFileExists <- doesFileExist $ completePlanDataDirectory <> "/PG_VERSION"
unless versionFileExists $ throwIO EmptyDataDirectory
writeFile (completePlanDataDirectory <> "/postgresql.conf") completePlanConfig
let startAction = startPostgresProcess
completePlanConnectionTimeout completePlanLogger completePlanPostgres
bracketOnError startAction (stopPostgresProcess False) $ \result -> do
for_ completePlanCreateDb executeCreateDb
pure result
stopPlan :: PostgresProcess -> IO ExitCode
stopPlan = stopPostgresProcess False