tmp-postgres-1.27.0.4: Start and stop a temporary postgres

Safe HaskellNone
LanguageHaskell2010

Database.Postgres.Temp.Internal

Description

This module provides the high level functions that are re-exported by Database.Postgres.Temp. Additionally it includes some identifiers that are used for testing but are not exported.

Synopsis

Documentation

data DB Source #

Handle for holding temporary resources, the postgres process handle and postgres connection information. The DB also includes the final plan used to start initdb, createdb and postgres.

Since: 1.12.0.0

Constructors

DB 

Fields

Instances
Pretty DB Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

Methods

pretty :: DB -> Doc #

prettyList :: [DB] -> Doc #

toConnectionString :: DB -> ByteString Source #

Convert a DB to a connection string. Alternatively one can access the Options using toConnectionOptions.

Since: 1.12.0.0

toConnectionOptions :: DB -> Options Source #

Convert a DB to a connection Options type.

Since: 1.12.0.0

toDataDirectory :: DB -> FilePath Source #

Access the data directory. This was either generated or specified explicitly when creating the Config

Since: 1.12.0.0

makeDataDirectoryPermanent :: DB -> DB Source #

Make the data directory permanent. Useful for debugging. If you are using with or withConfig this function will not modify the DB that is passed for cleanup. You will need to setup your own bracket like

bracket (fmap makeDataDirectoryPermanent start) (either mempty stop)

Since: 1.24.0.0

toTemporaryDirectory :: DB -> FilePath Source #

Get the directory that is used to create other temporary directories

Since: 1.12.0.0

toPostgresqlConfigFile :: DB -> String Source #

Get the final postgresql.conf

Since: 1.25.0.0

fastPostgresConfig :: [(String, String)] Source #

The fastest config we can make.

shared_buffers = 12MB
fsync = off
synchronous_commit = off
full_page_writes = off
log_min_messages = PANIC
log_min_error_statement = PANIC
log_statement = none
client_min_messages = ERROR

Since: 1.21.0.0

defaultConfig :: Config Source #

The default configuration. This will create a database called "postgres" via initdb (it's default behavior). It will create a temporary directory for the data and a temporary directory for a unix socket and listen on 127.0.0.1 and ::1 on a random port. Additionally it will use the following "postgresql.conf" which is optimized for performance.

shared_buffers = 12MB
fsync = off
synchronous_commit = off
full_page_writes = off
log_min_messages = PANIC
log_min_error_statement = PANIC
log_statement = none
client_min_messages = ERROR

defaultConfig also passes the --no-sync flag to initdb.

If you would like to customize this behavior you can start with the defaultConfig and overwrite fields or combine a defaultConfig with another Config using <> (mappend).

Alternatively you can eschew defaultConfig altogether, however your postgres might start and run faster if you use defaultConfig.

The defaultConfig redirects all output to /dev/null. See verboseConfig for a version that logs more output.

To append additional lines to "postgresql.conf" file create a custom Config like the following.

custom = defaultConfig <> mempty
  { postgresConfigFile =
      [ ("wal_level, "replica")
      , ("archive_mode", on")
      , ("max_wal_senders", "2")
      , ("fsync", "on")
      , ("synchronous_commit", "on")
      ]
  }

This is common enough there is defaultPostgresConf which is a helper to do this.

As an alternative to using defaultConfig one could create a config from connections parameters using optionsToDefaultConfig.

Since: 1.21.0.0

defaultConfig_9_3_10 :: Config Source #

Default configuration for PostgreSQL versions 9.3 and greater but less than 10.

If you get an error that "--no-sync" is an invalid parameter then you should use this config.

Since: 1.21.1.0

defaultPostgresConf :: [(String, String)] -> Config Source #

mappend the defaultConfig with a Config that provides additional "postgresql.conf" lines. Equivalent to:

defaultPostgresConf extra = defaultConfig <> mempty
  { postgresConfigFile = extra
  }

Since: 1.21.0.0

verbosePostgresConfig :: [(String, String)] Source #

Default postgres options

Since: 1.21.0.0

verboseConfig :: Config Source #

This is similar to defaultConfig but it logs as much as possible..

Since: 1.21.0.0

startConfig Source #

Arguments

:: Config

extra configuration that is mappended last to the generated Config. generated <> extra.

-> IO (Either StartError DB) 

Create zero or more temporary resources and use them to make a Config.

The passed in config is inspected and a generated config is created. The final config is built by

generated <> extra

Based on the value of socketDirectory a "postgresql.conf" is created with:

listen_addresses = '127.0.0.1, ::1'
unix_socket_directories = 'SOCKET_DIRECTORY'

Additionally the generated Config also:

All of these values can be overrided by the extra config.

The returned DB requires cleanup. startConfig should be used with a bracket and stop, e.g.

withConfig :: Config -> (DB -> IO a) -> IO (Either StartError a)
withConfig plan f = bracket (startConfig plan) (either mempty stop) $
  either (pure . Left) (fmap Right . f)

or just use withConfig. If you are calling startConfig you probably want withConfig anyway.

Since: 1.15.0.0

start :: IO (Either StartError DB) Source #

Default start behavior. Equivalent to calling startConfig with the defaultConfig.

Since: 1.21.0.0

stop :: DB -> IO () Source #

Stop the postgres process and cleanup any temporary resources that might have been created.

Since: 1.12.0.0

stopPostgres :: DB -> IO ExitCode Source #

Only stop the postgres process but leave any temporary resources. Useful for testing backup strategies when used in conjunction with restart or withRestart.

Since: 1.12.0.0

stopPostgresGracefully :: DB -> IO ExitCode Source #

Only stop the postgres process but leave any temporary resources. In contrast to stopPostgres this function makes sure postgres has time to properly write files to the data directory.

Since: 1.16.1.0

restart :: DB -> IO (Either StartError DB) Source #

Restart the postgres from DB using the prior Config. This will also start an instance previously stoppped with stopPostgres.

Since: 1.12.0.0

withConfig Source #

Arguments

:: Config

The extra Config combined with the generated Config. See startConfig for more info.

-> (DB -> IO a)

action continuation.

-> IO (Either StartError a) 

Exception safe database create with options. See startConfig for more details. Calls stop even in the face of exceptions.

Since: 1.21.0.0

with Source #

Arguments

:: (DB -> IO a)

action continuation.

-> IO (Either StartError a) 

Default expectation safe interface. Equivalent to

with = withConfig defaultConfig

Since: 1.21.0.0

withRestart :: DB -> (DB -> IO a) -> IO (Either StartError a) Source #

Exception safe version of restart.

Since: 1.12.0.0

optionsToDefaultConfig :: Options -> Config Source #

Attempt to create a Config from a Options. Useful if you want to create a database owned by a specific user you will also login with among other use cases.

Since: 1.21.0.0

prettyPrintDB :: DB -> String Source #

Display a DB.

Since: 1.12.0.0

data CacheConfig Source #

Configuration for the initdb data directory cache.

Since: 1.25.0.0

Constructors

CacheConfig 

Fields

data Cache Source #

A handle to cache temporary resources and configuration.

Since: 1.25.0.0

Instances
Generic Cache Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

Associated Types

type Rep Cache :: Type -> Type #

Methods

from :: Cache -> Rep Cache x #

to :: Rep Cache x -> Cache #

NFData Cache Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

Methods

rnf :: Cache -> () #

type Rep Cache Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

type Rep Cache = D1 (MetaData "Cache" "Database.Postgres.Temp.Internal" "tmp-postgres-1.27.0.4-88cnYaWuFsFIvymLfesLnG" False) (C1 (MetaCons "Cache" PrefixI True) (S1 (MetaSel (Just "cacheResourcesCow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "cacheResourcesDirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompleteDirectoryType)))

cowCheck :: Bool Source #

A bool that is True if the cp on the path supports "copy on write" flags.

defaultCacheConfig :: CacheConfig Source #

defaultCacheConfig attempts to determine if the cp on the path supports "copy on write" flags and if it does, sets cacheUseCopyOnWrite to True.

It sets cacheDirectoryType to Permanent ~/.tmp-postgres and cacheTemporaryDirectory to /tmp (but this is not used when Permanent is set).

Since: 1.25.0.0

setupInitDbCache :: CacheConfig -> IO Cache Source #

Setup the initdb cache folder.

Since: 1.25.0.0

cleanupInitDbCache :: Cache -> IO () Source #

Cleanup the cache directory if it was Temporary.

Since: 1.25.0.0

withDbCacheConfig Source #

Arguments

:: CacheConfig

Configuration

-> (Cache -> IO a)

action for which caching is enabled

-> IO a 

Enable initdb data directory caching. This can lead to a 4x speedup.

Exception safe version of setupInitDbCache. Equivalent to

withDbCacheConfig = bracket (setupInitDbCache config) cleanupInitDbCache

Since: 1.25.0.0

withDbCache :: (Cache -> IO a) -> IO a Source #

Equivalent to withDbCacheConfig with the CacheConfig defaultCacheConfig makes.

Here is an example using caching:

withDbCache $ \cache -> do
  withCache (cacheConfig cache) $ \db -> ...
  withCache (cacheConfig cache) $ \db -> ...

Since: 1.25.0.0

cacheConfig :: Cache -> Config Source #

Helper to make a Config out of caching info.

Since: 1.25.0.0

newtype Snapshot Source #

A type to track a possibly temporary snapshot directory

Since: 1.20.0.0

Constructors

Snapshot 
Instances
Generic Snapshot Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

Associated Types

type Rep Snapshot :: Type -> Type #

Methods

from :: Snapshot -> Rep Snapshot x #

to :: Rep Snapshot x -> Snapshot #

NFData Snapshot Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

Methods

rnf :: Snapshot -> () #

type Rep Snapshot Source # 
Instance details

Defined in Database.Postgres.Temp.Internal

type Rep Snapshot = D1 (MetaData "Snapshot" "Database.Postgres.Temp.Internal" "tmp-postgres-1.27.0.4-88cnYaWuFsFIvymLfesLnG" True) (C1 (MetaCons "Snapshot" PrefixI True) (S1 (MetaSel (Just "unSnapshot") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompleteDirectoryType)))

takeSnapshot Source #

Arguments

:: DirectoryType

Either a Temporary or preexisting Permanent directory.

-> DB

The handle. The postgres is shutdown and the data directory is copied.

-> IO (Either StartError Snapshot) 

Shutdown the database and copy the directory to a folder.

Since: 1.20.0.0

cleanupSnapshot :: Snapshot -> IO () Source #

Cleanup any temporary resources used for the snapshot.

Since: 1.20.0.0

withSnapshot :: DirectoryType -> DB -> (Snapshot -> IO a) -> IO (Either StartError a) Source #

Exception safe method for taking a file system level copy of the database cluster.

Snapshots are useful if you would like to start every test from a migrated database and the migration process is more time consuming then copying the additional data.

Here is an example with caching and snapshots:

withDbCache $ \cache -> withConfig (cacheConfig cache) $ \db ->
  migrate db
  withSnapshot Temporary db $ \snapshot -> do
    withConfig (snapshotConfig db) $ \migratedDb -> ...
    withConfig (snapshotConfig db) $ \migratedDb -> ...
    withConfig (snapshotConfig db) $ \migratedDb -> ...

Since: 1.20.0.0

snapshotConfig :: Snapshot -> Config Source #

Convert a snapshot into a Config that includes a copyConfig for copying the snapshot directory to a temporary directory.

Since: 1.20.0.0