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

Safe HaskellNone
LanguageHaskell2010

Database.Postgres.Temp.Internal.Config

Description

This module provides types and functions for combining partial configs into a complete configs to ultimately make a Plan.

This module has two classes of types.

Types like ProcessConfig that could be used by any library that needs to combine process options.

Finally it has types and functions for creating Plans that use temporary resources. This is used to create the default behavior of startConfig and related functions. |

Synopsis

Documentation

data Accum a Source #

Accum is a monoid.

It's <> behavior is analogous to 1 and 0 with *. Think of DontCare as 1 and Zlich as 0.

The behavior of Merge is like Justs.

Since: 1.17.0.0

Constructors

DontCare 
Zlich 
Merge a 
Instances
Functor Accum Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

fmap :: (a -> b) -> Accum a -> Accum b #

(<$) :: a -> Accum b -> Accum a #

Applicative Accum Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

pure :: a -> Accum a #

(<*>) :: Accum (a -> b) -> Accum a -> Accum b #

liftA2 :: (a -> b -> c) -> Accum a -> Accum b -> Accum c #

(*>) :: Accum a -> Accum b -> Accum b #

(<*) :: Accum a -> Accum b -> Accum a #

Eq a => Eq (Accum a) Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

(==) :: Accum a -> Accum a -> Bool #

(/=) :: Accum a -> Accum a -> Bool #

Ord a => Ord (Accum a) Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

compare :: Accum a -> Accum a -> Ordering #

(<) :: Accum a -> Accum a -> Bool #

(<=) :: Accum a -> Accum a -> Bool #

(>) :: Accum a -> Accum a -> Bool #

(>=) :: Accum a -> Accum a -> Bool #

max :: Accum a -> Accum a -> Accum a #

min :: Accum a -> Accum a -> Accum a #

Show a => Show (Accum a) Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

showsPrec :: Int -> Accum a -> ShowS #

show :: Accum a -> String #

showList :: [Accum a] -> ShowS #

Semigroup a => Semigroup (Accum a) Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

(<>) :: Accum a -> Accum a -> Accum a #

sconcat :: NonEmpty (Accum a) -> Accum a #

stimes :: Integral b => b -> Accum a -> Accum a #

Monoid a => Monoid (Accum a) Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

mempty :: Accum a #

mappend :: Accum a -> Accum a -> Accum a #

mconcat :: [Accum a] -> Accum a #

data EnvironmentVariables Source #

The environment variables can be declared to inherit from the running process or they can be specifically added.

Since: 1.12.0.0

Instances
Eq EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Show EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Generic EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Associated Types

type Rep EnvironmentVariables :: Type -> Type #

Semigroup EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Monoid EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Pretty EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep EnvironmentVariables Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep EnvironmentVariables = D1 (MetaData "EnvironmentVariables" "Database.Postgres.Temp.Internal.Config" "tmp-postgres-1.31.0.0-KpuWfN3uOoI2mcaLVKswt" False) (C1 (MetaCons "EnvironmentVariables" PrefixI True) (S1 (MetaSel (Just "inherit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Bool)) :*: S1 (MetaSel (Just "specific") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String String))))

completeEnvironmentVariables :: [(String, String)] -> EnvironmentVariables -> Either [String] [(String, String)] Source #

Combine the current environment (if indicated by inherit) with specific.

Since: 1.12.0.0

data CommandLineArgs Source #

A type to help combine command line Args.

Since: 1.12.0.0

Constructors

CommandLineArgs 

Fields

  • keyBased :: Map String (Maybe String)

    Args of the form -h foo, --host=foo and --switch. The key is mappended with value so the key should include the space or equals (as shown in the first two examples respectively). The Dual monoid is used so the last key wins.

  • indexBased :: Map Int String

    Args that appear at the end of the key based Args. The Dual monoid is used so the last key wins.

Instances
Eq CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Show CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Generic CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Associated Types

type Rep CommandLineArgs :: Type -> Type #

Semigroup CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Monoid CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Pretty CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep CommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep CommandLineArgs = D1 (MetaData "CommandLineArgs" "Database.Postgres.Temp.Internal.Config" "tmp-postgres-1.31.0.0-KpuWfN3uOoI2mcaLVKswt" False) (C1 (MetaCons "CommandLineArgs" PrefixI True) (S1 (MetaSel (Just "keyBased") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String (Maybe String))) :*: S1 (MetaSel (Just "indexBased") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int String))))

completeCommandLineArgs :: CommandLineArgs -> [String] Source #

This convert the CommandLineArgs to '[String]'.

Since: 1.12.0.0

data ProcessConfig Source #

Process configuration

Since: 1.12.0.0

Constructors

ProcessConfig 

Fields

Instances
Eq ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Show ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Generic ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Associated Types

type Rep ProcessConfig :: Type -> Type #

Semigroup ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Monoid ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Pretty ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep ProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

standardProcessConfig :: ProcessConfig Source #

The standardProcessConfig sets the handles to stdin, stdout and stderr and inherits the environment variables from the calling process.

Since: 1.12.0.0

devNull :: Handle Source #

A global reference to /dev/null Handle.

Since: 1.12.0.0

silentProcessConfig :: ProcessConfig Source #

silentProcessConfig sets the handles to /dev/null and inherits the environment variables from the calling process.

Since: 1.12.0.0

completeProcessConfig :: [(String, String)] -> ProcessConfig -> Either [String] CompleteProcessConfig Source #

Turn a ProcessConfig into a ProcessConfig. Fails if any values are missing.

Since: 1.12.0.0

data CompleteDirectoryType Source #

A type to track whether a file is temporary and needs to be cleaned up.

Since: 1.12.0.0

Instances
Eq CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Ord CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Show CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Generic CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Associated Types

type Rep CompleteDirectoryType :: Type -> Type #

Pretty CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

NFData CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

rnf :: CompleteDirectoryType -> () #

type Rep CompleteDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep CompleteDirectoryType = D1 (MetaData "CompleteDirectoryType" "Database.Postgres.Temp.Internal.Config" "tmp-postgres-1.31.0.0-KpuWfN3uOoI2mcaLVKswt" False) (C1 (MetaCons "CPermanent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) :+: C1 (MetaCons "CTemporary" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))

toFilePath :: CompleteDirectoryType -> FilePath Source #

Get the file path of a CompleteDirectoryType, regardless if it is a CPermanent or CTemporary type.

Since: 1.12.0.0

data DirectoryType Source #

Used to specify a Temporary folder that is automatically cleaned up or a Permanent folder which is not automatically cleaned up.

Since: 1.12.0.0

Constructors

Permanent FilePath

A permanent file that should not be generated.

Temporary

A temporary file that needs to generated.

Instances
Eq DirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Ord DirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Show DirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Semigroup DirectoryType Source #

Takes the last Permanent value.

Instance details

Defined in Database.Postgres.Temp.Internal.Config

Monoid DirectoryType Source #

Temporary as mempty

Instance details

Defined in Database.Postgres.Temp.Internal.Config

Pretty DirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

setupDirectoryType Source #

Arguments

:: String

Temporary directory configuration

-> String

Directory pattern

-> DirectoryType 
-> IO CompleteDirectoryType 

Either create aCTemporary directory or do create the directory if it does not exist to a CPermanent one.

Since: 1.29.0.0

cleanupDirectoryType :: CompleteDirectoryType -> IO () Source #

Either remove a CTemporary directory or do nothing to a CPermanent one.

completePostgresPlan :: [(String, String)] -> Config -> Either [String] CompletePostgresPlan Source #

Turn a Config into a CompletePostgresPlan. Fails if any values are missing.

completePlan :: [(String, String)] -> String -> Config -> Either [String] Plan Source #

Turn a Config into a Plan. Fails if any values are missing.

data Config Source #

The high level options for overriding default behavior.

Since: 1.22.0.0

Constructors

Config 

Fields

Instances
Generic Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

Semigroup Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Monoid Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Pretty Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

Methods

pretty :: Config -> Doc #

prettyList :: [Config] -> Doc #

type Rep Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

type Rep Config = D1 (MetaData "Config" "Database.Postgres.Temp.Internal.Config" "tmp-postgres-1.31.0.0-KpuWfN3uOoI2mcaLVKswt" False) (C1 (MetaCons "Config" PrefixI True) (((S1 (MetaSel (Just "logger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Logger)) :*: (S1 (MetaSel (Just "initDbConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Accum ProcessConfig)) :*: S1 (MetaSel (Just "copyConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last (Maybe CopyDirectoryCommand))))) :*: (S1 (MetaSel (Just "createDbConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Accum ProcessConfig)) :*: (S1 (MetaSel (Just "postgresConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ProcessConfig) :*: S1 (MetaSel (Just "connectionOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Options)))) :*: ((S1 (MetaSel (Just "postgresConfigFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)]) :*: (S1 (MetaSel (Just "connectionTimeout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Int)) :*: S1 (MetaSel (Just "socketDirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DirectoryType))) :*: ((S1 (MetaSel (Just "dataDirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DirectoryType) :*: S1 (MetaSel (Just "port") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last (Maybe Int)))) :*: (S1 (MetaSel (Just "temporaryDirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last FilePath)) :*: S1 (MetaSel (Just "initDbCache") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last (Maybe (Bool, FilePath)))))))))

data CopyDirectoryCommand Source #

Copy command used to create a data directory. If initdb used to create the data directory directly this is not needed.

If destinationDirectory is Nothing then the dataDirectory (which might be generated) is used.

Since: 1.16.0.0

toPlan Source #

Arguments

:: Bool

Make initdb options.

-> Bool

Make createdb options.

-> Int

The port.

-> FilePath

Socket directory.

-> FilePath

The postgres data directory.

-> Config 

Create a Config that sets the command line options of all processes (initdb, postgres and createdb). This the generated plan that is combined with the extra plan from startConfig.

setupConfig Source #

Arguments

:: Config

extra Config to mappend after the generated Config.

-> IO Resources 

Create all the temporary resources from a Config. This also combines the Config from toPlan with the extra Config passed in.

cleanupConfig :: Resources -> IO () Source #

Free the temporary resources created by setupConfig.

prettyPrintConfig :: Config -> String Source #

Display a Config.

Since: 1.12.0.0

data Resources Source #

Resources holds a description of the temporary folders (if there are any) and includes the final Plan that can be used with startPlan. See setupConfig for an example of how to create a Resources.

Since: 1.12.0.0

Constructors

Resources 

Fields

Instances
Pretty Resources Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Config

makeResourcesDataDirPermanent :: Resources -> Resources Source #

Make the resourcesDataDir CPermanent so it will not get cleaned up.

Since: 1.12.0.0

optionsToConfig :: Options -> Config Source #

Attempt to create a config from a Options. This is useful if want to create a database owned by a specific user you will also log in as among other use cases. It is possible some Options are not supported so don't hesitate to open an issue on github if you find one.