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

Safe HaskellNone
LanguageHaskell2010

Database.Postgres.Temp.Internal.Partial

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 PartialProcessConfig 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 PartialEnvVars Source #

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

Instances
Eq PartialEnvVars Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Show PartialEnvVars Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Generic PartialEnvVars Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Associated Types

type Rep PartialEnvVars :: Type -> Type #

Semigroup PartialEnvVars Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Monoid PartialEnvVars Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialEnvVars Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialEnvVars = D1 (MetaData "PartialEnvVars" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "PartialEnvVars" PrefixI True) (S1 (MetaSel (Just "partialEnvVarsInherit") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Bool)) :*: S1 (MetaSel (Just "partialEnvVarsSpecific") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String String))))

completePartialEnvVars :: [(String, String)] -> PartialEnvVars -> Either [String] [(String, String)] Source #

Combine the current environment (if indicated by partialEnvVarsInherit) with partialEnvVarsSpecific

data PartialCommandLineArgs Source #

A type to help combine command line arguments.

Constructors

PartialCommandLineArgs 

Fields

Instances
Eq PartialCommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Show PartialCommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Generic PartialCommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Associated Types

type Rep PartialCommandLineArgs :: Type -> Type #

Semigroup PartialCommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Monoid PartialCommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialCommandLineArgs Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialCommandLineArgs = D1 (MetaData "PartialCommandLineArgs" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "PartialCommandLineArgs" PrefixI True) (S1 (MetaSel (Just "partialCommandLineArgsKeyBased") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map String (Maybe String))) :*: S1 (MetaSel (Just "partialCommandLineArgsIndexBased") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map Int String))))

takeWhileInSequence :: [(Int, a)] -> [a] Source #

Take values as long as the index is the successor of the last index.

data PartialProcessConfig Source #

The monoidial version of ProcessConfig. Used to combine overrides with defaults when creating a ProcessConfig.

Constructors

PartialProcessConfig 

Fields

Instances
Eq PartialProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Show PartialProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Generic PartialProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Associated Types

type Rep PartialProcessConfig :: Type -> Type #

Semigroup PartialProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Monoid PartialProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialProcessConfig Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialProcessConfig = D1 (MetaData "PartialProcessConfig" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "PartialProcessConfig" PrefixI True) ((S1 (MetaSel (Just "partialProcessConfigEnvVars") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialEnvVars) :*: S1 (MetaSel (Just "partialProcessConfigCmdLine") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialCommandLineArgs)) :*: (S1 (MetaSel (Just "partialProcessConfigStdIn") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Handle)) :*: (S1 (MetaSel (Just "partialProcessConfigStdOut") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Handle)) :*: S1 (MetaSel (Just "partialProcessConfigStdErr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Handle))))))

standardProcessConfig :: PartialProcessConfig Source #

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

addErrorContext :: String -> Either [String] a -> Either [String] a Source #

A helper to add more info to all the error messages.

getOption :: String -> Last a -> Validation [String] a Source #

A helper for creating an error if a Last is not defined.

toFilePath :: DirectoryType -> FilePath Source #

Get the file path of a DirectoryType, regardless if it is a Permanent or Temporary type.

data PartialDirectoryType Source #

The monoidial version of DirectoryType. Used to combine overrides with defaults when creating a DirectoryType. The monoid instance treats PTemporary as mempty and takes the last PPermanent value.

Constructors

PPermanent FilePath

A permanent file that should not be generated.

PTemporary

A temporary file that needs to generated.

Instances
Eq PartialDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Ord PartialDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Show PartialDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Semigroup PartialDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Monoid PartialDirectoryType Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

initDirectoryType :: String -> PartialDirectoryType -> IO DirectoryType Source #

Either create aTemporary directory or do nothing to a Permanent one.

rmDirIgnoreErrors :: FilePath -> IO () Source #

Either create a temporary directory or do nothing

shutdownDirectoryType :: DirectoryType -> IO () Source #

Either remove a Temporary directory or do nothing to a Permanent one.

data SocketClass Source #

A type for configuring the listening address of the postgres process. postgres can listen on several types of sockets simulatanously but we don't support that behavior. One can either listen on a IP based socket or a UNIX domain socket.

Constructors

IpSocket String

IP socket type. The String is either an IP address or a host that will resolve to an IP address.

UnixSocket DirectoryType

UNIX domain socket

Instances
Eq SocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Ord SocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Show SocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Generic SocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Associated Types

type Rep SocketClass :: Type -> Type #

type Rep SocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep SocketClass = D1 (MetaData "SocketClass" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "IpSocket" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "UnixSocket" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 DirectoryType)))

socketClassToConfig :: SocketClass -> [String] Source #

Create the extra config lines for listening based on the SocketClass

socketClassToHostFlag :: SocketClass -> [(String, Maybe String)] Source #

Many processes require a "host" flag. We can generate one from the SocketClass.

socketClassToHost :: SocketClass -> String Source #

Get the IP address, host name or UNIX domain socket directory as a String

data PartialSocketClass Source #

The monoidial version of SocketClass. Used to combine overrides with defaults when creating a SocketClass. The monoid instance treats 'PUnixSocket mempty' as mempty and combines the

Constructors

PIpSocket (Last String)

The monoid for combining IP address configuration

PUnixSocket PartialDirectoryType

The monoid for combining UNIX socket configuration

Instances
Eq PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Ord PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Show PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Generic PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Associated Types

type Rep PartialSocketClass :: Type -> Type #

Semigroup PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Monoid PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialSocketClass Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialSocketClass = D1 (MetaData "PartialSocketClass" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "PIpSocket" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last String))) :+: C1 (MetaCons "PUnixSocket" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialDirectoryType)))

initPartialSocketClass :: PartialSocketClass -> IO SocketClass Source #

Turn a PartialSocketClass to a SocketClass. If the PIpSocket is Nothing default to "127.0.0.1". If the is a PUnixSocket optionally create a temporary directory if configured to do so.

shutdownSocketConfig :: SocketClass -> IO () Source #

Cleanup the UNIX socket temporary directory if one was created.

data PartialPostgresPlan Source #

PartialPostgresPlan

Constructors

PartialPostgresPlan 

Fields

data PartialPlan Source #

The monoidial version of Plan. Used to combine overrides with defaults when creating a plan.

Instances
Generic PartialPlan Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Associated Types

type Rep PartialPlan :: Type -> Type #

Semigroup PartialPlan Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

Monoid PartialPlan Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialPlan Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep PartialPlan = D1 (MetaData "PartialPlan" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "PartialPlan" PrefixI True) ((S1 (MetaSel (Just "partialPlanLogger") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last Logger)) :*: (S1 (MetaSel (Just "partialPlanInitDb") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PartialProcessConfig)) :*: S1 (MetaSel (Just "partialPlanCreateDb") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PartialProcessConfig)))) :*: (S1 (MetaSel (Just "partialPlanPostgres") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialPostgresPlan) :*: (S1 (MetaSel (Just "partialPlanConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "partialPlanDataDirectory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last String))))))

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

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

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 initPlan. See initConfig for an example of how to create a Resources.

Constructors

Resources 

Fields

data Config Source #

The high level options for overriding default behavior.

Constructors

Config 

Fields

Instances
Generic Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

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.Partial

Monoid Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep Config Source # 
Instance details

Defined in Database.Postgres.Temp.Internal.Partial

type Rep Config = D1 (MetaData "Config" "Database.Postgres.Temp.Internal.Partial" "tmp-postgres-1.5.0.0-FwUuhmxVHIG7HToJRSqgBA" False) (C1 (MetaCons "Config" PrefixI True) ((S1 (MetaSel (Just "configPlan") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialPlan) :*: S1 (MetaSel (Just "configSocket") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialSocketClass)) :*: (S1 (MetaSel (Just "configDataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PartialDirectoryType) :*: S1 (MetaSel (Just "configPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last (Maybe Int))))))

toPlan Source #

Arguments

:: Bool

Make initdb options

-> Bool

Make createdb options

-> Int

port

-> SocketClass

Whether to listen on a IP address or UNIX domain socket

-> FilePath

The postgres data directory

-> PartialPlan 

Create a PartialPlan that sets the command line options of all processes (initdb, postgres and createdb) using a

initConfig Source #

Arguments

:: Config

extraConfig to mappend after the default config

-> IO Resources 

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

shutdownResources :: Resources -> IO () Source #

Free the temporary resources created by initConfig

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.

optionsToPlan :: Options -> PartialPlan Source #

Convert the Options to a PartialPlan that can be connected to with the Options.

userToPlan :: String -> PartialPlan Source #

Create a PartialPlan given a user

dbnameToPlan :: String -> PartialPlan Source #

Adds a createdb PartialProcessPlan with the argument as the database name.

hostToSocketClass :: String -> PartialSocketClass Source #

Parse a host string as either an UNIX domain socket directory or a domain or IP.