| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.Postgres.Temp.Internal.Config
Description
This module provides types and functions for combining partial
configs into a complete configs to ultimately make a CompletePlan.
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 CompletePlans that
use temporary resources. This is used to create the default
behavior of startConfig and related
functions.
|
Synopsis
- data EnvironmentVariables = EnvironmentVariables {}
- completeEnvironmentVariables :: [(String, String)] -> EnvironmentVariables -> Either [String] [(String, String)]
- data CommandLineArgs = CommandLineArgs {}
- completeCommandLineArgs :: CommandLineArgs -> [String]
- data ProcessConfig = ProcessConfig {}
- standardProcessConfig :: ProcessConfig
- devNull :: Handle
- silentProcessConfig :: ProcessConfig
- completeProcessConfig :: [(String, String)] -> ProcessConfig -> Either [String] CompleteProcessConfig
- data CompleteDirectoryType
- toFilePath :: CompleteDirectoryType -> FilePath
- data DirectoryType
- setupDirectoryType :: String -> String -> DirectoryType -> IO CompleteDirectoryType
- cleanupDirectoryType :: CompleteDirectoryType -> IO ()
- data CompleteSocketClass
- socketClassToConfig :: CompleteSocketClass -> [String]
- socketClassToHostFlag :: CompleteSocketClass -> [(String, Maybe String)]
- socketClassToHost :: CompleteSocketClass -> String
- data SocketClass
- setupSocketClass :: String -> SocketClass -> IO CompleteSocketClass
- cleanupSocketConfig :: CompleteSocketClass -> IO ()
- data PostgresPlan = PostgresPlan {}
- completePostgresPlan :: [(String, String)] -> PostgresPlan -> Either [String] CompletePostgresPlan
- data Plan = Plan {}
- completePlan :: [(String, String)] -> Plan -> Either [String] CompletePlan
- data Config = Config {}
- toPlan :: Bool -> Bool -> Int -> CompleteSocketClass -> FilePath -> Plan
- setupConfig :: Config -> IO Resources
- cleanupConfig :: Resources -> IO ()
- prettyPrintConfig :: Config -> String
- data Resources = Resources {}
- makeResourcesDataDirPermanent :: Resources -> Resources
- optionsToConfig :: Options -> Config
- type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
- type Lens' s a = Lens s s a a
- inheritL :: Lens' EnvironmentVariables (Last Bool)
- specificL :: Lens' EnvironmentVariables (Map String String)
- commandLineL :: Lens' ProcessConfig CommandLineArgs
- environmentVariablesL :: Lens' ProcessConfig EnvironmentVariables
- stdErrL :: Lens' ProcessConfig (Last Handle)
- stdInL :: Lens' ProcessConfig (Last Handle)
- stdOutL :: Lens' ProcessConfig (Last Handle)
- connectionOptionsL :: Lens' PostgresPlan Options
- postgresConfigL :: Lens' PostgresPlan ProcessConfig
- postgresConfigFileL :: Lens' Plan [String]
- createDbConfigL :: Lens' Plan (Maybe ProcessConfig)
- dataDirectoryStringL :: Lens' Plan (Last String)
- initDbConfigL :: Lens' Plan (Maybe ProcessConfig)
- loggerL :: Lens' Plan (Last Logger)
- postgresPlanL :: Lens' Plan PostgresPlan
- connectionTimeoutL :: Lens' Plan (Last Int)
- resourcesDataDirL :: Lens' Resources CompleteDirectoryType
- resourcesPlanL :: Lens' Resources CompletePlan
- resourcesSocketL :: Lens' Resources CompleteSocketClass
- dataDirectoryL :: Lens' Config DirectoryType
- planL :: Lens' Config Plan
- portL :: Lens' Config (Last (Maybe Int))
- socketClassL :: Lens' Config SocketClass
- temporaryDirectoryL :: Lens' Config (Last FilePath)
- indexBasedL :: Lens' CommandLineArgs (Map Int String)
- keyBasedL :: Lens' CommandLineArgs (Map String (Maybe String))
Documentation
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
completeEnvironmentVariables :: [(String, String)] -> EnvironmentVariables -> Either [String] [(String, String)] Source #
data CommandLineArgs Source #
A type to help combine command line Args.
Since: 1.12.0.0
Constructors
| CommandLineArgs | |
Fields | |
Instances
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
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
silentProcessConfig :: ProcessConfig Source #
silentProcessConfig sets the handles to devnull 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
Constructors
| CPermanent FilePath | |
| CTemporary FilePath |
Instances
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
Arguments
| :: String | Temporary directory configuration |
| -> String | Directory pattern |
| -> DirectoryType | |
| -> IO CompleteDirectoryType |
Either create aCTemporary directory or do nothing to a CPermanent
one.
Since: 1.12.0.0
cleanupDirectoryType :: CompleteDirectoryType -> IO () Source #
Either remove a CTemporary directory or do nothing to a CPermanent
one.
data CompleteSocketClass 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.
Since: 1.12.0.0
Constructors
| CIpSocket String | IP socket type. The |
| CUnixSocket CompleteDirectoryType | UNIX domain socket |
Instances
socketClassToConfig :: CompleteSocketClass -> [String] Source #
Create the extra config lines for listening based on the CompleteSocketClass.
socketClassToHostFlag :: CompleteSocketClass -> [(String, Maybe String)] Source #
Many processes require a "host" flag. We can generate one from the
CompleteSocketClass.
socketClassToHost :: CompleteSocketClass -> String Source #
Get the IP address, host name or UNIX domain socket directory
as a String.
data SocketClass Source #
SocketClass is used to specify how postgres should listen for connections
The two main options are a IpSocket which takes a hostname or IP address.
if not is given the default it "127.0.0.1". Alternatively one can
specify UnixSocket for a UNIX domain socket. If a directory is
specified the socket will live in that folder. Otherwise a
temporary folder will get created for the socket.
Since: 1.12.0.0
Constructors
| IpSocket (Last String) | The monoid for combining IP address configuration. |
| UnixSocket DirectoryType | The monoid for combining UNIX socket configuration. |
Instances
Arguments
| :: String | Temporary directory. |
| -> SocketClass | The type of socket. |
| -> IO CompleteSocketClass |
Turn a SocketClass to a CompleteSocketClass. If the IpSocket is
Nothing default to "127.0.0.1". If the is a UnixSocket
optionally create a temporary directory if configured to do so.
cleanupSocketConfig :: CompleteSocketClass -> IO () Source #
Cleanup the UNIX socket temporary directory if one was created.
data PostgresPlan Source #
postgres process config and corresponding client connection
Options.
Since: 1.12.0.0
Constructors
| PostgresPlan | |
Fields
| |
Instances
completePostgresPlan :: [(String, String)] -> PostgresPlan -> Either [String] CompletePostgresPlan Source #
Turn a PostgresPlan into a CompletePostgresPlan. Fails if any
values are missing.
Describe how to run initdb, createdb and postgres
Since: 1.12.0.0
Constructors
| Plan | |
Fields
| |
Instances
completePlan :: [(String, String)] -> Plan -> Either [String] CompletePlan Source #
Turn a Plan into a CompletePlan. Fails if any values are missing.
The high level options for overriding default behavior.
Since: 1.12.0.0
Constructors
| Config | |
Fields
| |
Instances
| Generic Config Source # | |
| Semigroup Config Source # | |
| Monoid Config Source # | |
| Pretty Config Source # | |
Defined in Database.Postgres.Temp.Internal.Config | |
| type Rep Config Source # | |
Defined in Database.Postgres.Temp.Internal.Config type Rep Config = D1 (MetaData "Config" "Database.Postgres.Temp.Internal.Config" "tmp-postgres-1.12.0.1-FTAVbBlb28U6ckdd2KgA0P" False) (C1 (MetaCons "Config" PrefixI True) ((S1 (MetaSel (Just "plan") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Plan) :*: S1 (MetaSel (Just "socketClass") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 SocketClass)) :*: (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)))))) | |
Arguments
| :: Bool | Make |
| -> Bool | Make |
| -> Int | port |
| -> CompleteSocketClass | Whether to listen on a IP address or UNIX domain socket |
| -> FilePath | The |
| -> Plan |
Create a Plan 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.
cleanupConfig :: Resources -> IO () Source #
Free the temporary resources created by setupConfig.
Resources holds a description of the temporary folders (if there are any)
and includes the final CompletePlan 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
| |
makeResourcesDataDirPermanent :: Resources -> Resources Source #
Make the resourcesDataDir CPermanent so it will not
get cleaned up.
Since: 1.12.0.0
optionsToConfig :: Options -> Config Source #
specificL :: Lens' EnvironmentVariables (Map String String) Source #
Lens for specific.
Since: 1.12.0.0
commandLineL :: Lens' ProcessConfig CommandLineArgs Source #
Lens for commandLine.
Since: 1.12.0.0
environmentVariablesL :: Lens' ProcessConfig EnvironmentVariables Source #
Lens for environmentVariables.
Since: 1.12.0.0
connectionOptionsL :: Lens' PostgresPlan Options Source #
Lens for connectionOptions.
Since: 1.12.0.0
postgresConfigL :: Lens' PostgresPlan ProcessConfig Source #
Lens for postgresConfig.
Since: 1.12.0.0
postgresConfigFileL :: Lens' Plan [String] Source #
Lens for postgresConfigFile.
Since: 1.12.0.0
createDbConfigL :: Lens' Plan (Maybe ProcessConfig) Source #
Lens for createDbConfig.
Since: 1.12.0.0
dataDirectoryStringL :: Lens' Plan (Last String) Source #
Lens for dataDirectoryString.
Since: 1.12.0.0
initDbConfigL :: Lens' Plan (Maybe ProcessConfig) Source #
Lens for initDbConfig.
Since: 1.12.0.0
postgresPlanL :: Lens' Plan PostgresPlan Source #
Lens for postgresPlan.
Since: 1.12.0.0
connectionTimeoutL :: Lens' Plan (Last Int) Source #
Lens for connectionTimeout.
Since: 1.12.0.0
resourcesDataDirL :: Lens' Resources CompleteDirectoryType Source #
Lens for resourcesDataDir.
Since: 1.12.0.0
resourcesPlanL :: Lens' Resources CompletePlan Source #
Lens for resourcesPlan.
Since: 1.12.0.0
resourcesSocketL :: Lens' Resources CompleteSocketClass Source #
Lens for resourcesSocket.
Since: 1.12.0.0
dataDirectoryL :: Lens' Config DirectoryType Source #
Lens for dataDirectory.
Since: 1.12.0.0
socketClassL :: Lens' Config SocketClass Source #
Lens for socketClass.
Since: 1.12.0.0
temporaryDirectoryL :: Lens' Config (Last FilePath) Source #
Lens for socketClass.
Since: 1.12.0.0
indexBasedL :: Lens' CommandLineArgs (Map Int String) Source #
Lens for indexBased.
Since: 1.12.0.0