{-# OPTIONS_HADDOCK prune #-}
module Database.Postgres.Temp.Internal.Partial where
import Database.Postgres.Temp.Internal.Core
import Control.Applicative.Lift
import Control.Exception
import Control.Monad (join)
import Control.Monad.Trans.Class
import Control.Monad.Trans.Cont
import qualified Data.Map.Strict as Map
import Data.Map.Strict (Map)
import Data.Maybe
import Data.Monoid
import Data.Monoid.Generic
import Data.Typeable
import qualified Database.PostgreSQL.Simple.Options as Client
import GHC.Generics (Generic)
import Network.Socket.Free (getFreePort)
import System.Directory
import System.Environment
import System.IO
import System.IO.Error
import System.IO.Temp (createTempDirectory)
import Text.PrettyPrint.ANSI.Leijen hiding ((<$>))
prettyMap :: (Pretty a, Pretty b) => Map a b -> Doc
prettyMap theMap =
let xs = Map.toList theMap
in vsep $ map (uncurry prettyKeyPair) xs
data PartialEnvVars = PartialEnvVars
{ partialEnvVarsInherit :: Last Bool
, partialEnvVarsSpecific :: Map String String
}
deriving stock (Generic, Show, Eq)
instance Semigroup PartialEnvVars where
x <> y = PartialEnvVars
{ partialEnvVarsInherit =
partialEnvVarsInherit x <> partialEnvVarsInherit y
, partialEnvVarsSpecific =
partialEnvVarsSpecific y <> partialEnvVarsSpecific x
}
instance Monoid PartialEnvVars where
mempty = PartialEnvVars mempty mempty
instance Pretty PartialEnvVars where
pretty PartialEnvVars {..}
= text "partialEnvVarsInherit:"
<+> pretty (getLast partialEnvVarsInherit)
<> hardline
<> text "partialEnvVarsSpecific:"
<> softline
<> indent 2 (prettyMap partialEnvVarsSpecific)
completePartialEnvVars :: [(String, String)] -> PartialEnvVars -> Either [String] [(String, String)]
completePartialEnvVars envs PartialEnvVars {..} = case getLast partialEnvVarsInherit of
Nothing -> Left ["Inherit not specified"]
Just x -> Right $ (if x then envs else [])
<> Map.toList partialEnvVarsSpecific
data PartialCommandLineArgs = PartialCommandLineArgs
{ partialCommandLineArgsKeyBased :: Map String (Maybe String)
, partialCommandLineArgsIndexBased :: Map Int String
}
deriving stock (Generic, Show, Eq)
deriving Monoid via GenericMonoid PartialCommandLineArgs
instance Semigroup PartialCommandLineArgs where
x <> y = PartialCommandLineArgs
{ partialCommandLineArgsKeyBased =
partialCommandLineArgsKeyBased y <> partialCommandLineArgsKeyBased x
, partialCommandLineArgsIndexBased =
partialCommandLineArgsIndexBased y <> partialCommandLineArgsIndexBased x
}
instance Pretty PartialCommandLineArgs where
pretty p@PartialCommandLineArgs {..}
= text "partialCommandLineArgsKeyBased:"
<> softline
<> indent 2 (prettyMap partialCommandLineArgsKeyBased)
<> hardline
<> text "partialCommandLineArgsIndexBased:"
<> softline
<> indent 2 (prettyMap partialCommandLineArgsIndexBased)
<> hardline
<> text "completed:" <+> text (unwords (completeCommandLineArgs p))
takeWhileInSequence :: [(Int, a)] -> [a]
takeWhileInSequence ((0, x):xs) = x : go 0 xs where
go _ [] = []
go prev ((next, a):rest)
| prev + 1 == next = a : go next rest
| otherwise = []
takeWhileInSequence _ = []
completeCommandLineArgs :: PartialCommandLineArgs -> [String]
completeCommandLineArgs PartialCommandLineArgs {..}
= map (\(name, mvalue) -> maybe name (name <>) mvalue)
(Map.toList partialCommandLineArgsKeyBased)
<> takeWhileInSequence (Map.toList partialCommandLineArgsIndexBased)
data PartialProcessConfig = PartialProcessConfig
{ partialProcessConfigEnvVars :: PartialEnvVars
, partialProcessConfigCmdLine :: PartialCommandLineArgs
, partialProcessConfigStdIn :: Last Handle
, partialProcessConfigStdOut :: Last Handle
, partialProcessConfigStdErr :: Last Handle
}
deriving stock (Generic, Eq, Show)
deriving Semigroup via GenericSemigroup PartialProcessConfig
deriving Monoid via GenericMonoid PartialProcessConfig
prettyHandle :: Handle -> Doc
prettyHandle _ = text "[HANDLE]"
instance Pretty PartialProcessConfig where
pretty PartialProcessConfig {..}
= text "partialProcessConfigEnvVars:"
<> softline
<> indent 2 (pretty partialProcessConfigEnvVars)
<> hardline
<> text "partialProcessConfigCmdLine:"
<> softline
<> indent 2 (pretty partialProcessConfigEnvVars)
<> hardline
<> text "partialProcessConfigStdIn:" <+>
pretty (prettyHandle <$> getLast partialProcessConfigStdIn)
<> hardline
<> text "partialProcessConfigStdOut:" <+>
pretty (prettyHandle <$> getLast partialProcessConfigStdOut)
<> hardline
<> text "partialProcessConfigStdErr:" <+>
pretty (prettyHandle <$> getLast partialProcessConfigStdErr)
standardProcessConfig :: PartialProcessConfig
standardProcessConfig = mempty
{ partialProcessConfigEnvVars = mempty
{ partialEnvVarsInherit = pure True
}
, partialProcessConfigStdIn = pure stdin
, partialProcessConfigStdOut = pure stdout
, partialProcessConfigStdErr = pure stderr
}
addErrorContext :: String -> Either [String] a -> Either [String] a
addErrorContext cxt = either (Left . map (cxt <>)) Right
getOption :: String -> Last a -> Errors [String] a
getOption optionName = \case
Last (Just x) -> pure x
Last Nothing -> failure ["Missing " ++ optionName ++ " option"]
completeProcessConfig
:: [(String, String)] -> PartialProcessConfig -> Either [String] ProcessConfig
completeProcessConfig envs PartialProcessConfig {..} = runErrors $ do
let processConfigCmdLine = completeCommandLineArgs partialProcessConfigCmdLine
processConfigEnvVars <- eitherToErrors $
completePartialEnvVars envs partialProcessConfigEnvVars
processConfigStdIn <-
getOption "partialProcessConfigStdIn" partialProcessConfigStdIn
processConfigStdOut <-
getOption "partialProcessConfigStdOut" partialProcessConfigStdOut
processConfigStdErr <-
getOption "partialProcessConfigStdErr" partialProcessConfigStdErr
pure ProcessConfig {..}
data DirectoryType = Permanent FilePath | Temporary FilePath
deriving(Show, Eq, Ord)
toFilePath :: DirectoryType -> FilePath
toFilePath = \case
Permanent x -> x
Temporary x -> x
instance Pretty DirectoryType where
pretty = \case
Permanent x -> text "Permanent" <+> pretty x
Temporary x -> text "Temporary" <+> pretty x
makePermanent :: DirectoryType -> DirectoryType
makePermanent = \case
Temporary x -> Permanent x
x -> x
data PartialDirectoryType
= PPermanent FilePath
| PTemporary
deriving(Show, Eq, Ord)
instance Pretty PartialDirectoryType where
pretty = \case
PPermanent x -> text "Permanent" <+> pretty x
PTemporary -> text "Temporary"
instance Semigroup PartialDirectoryType where
x <> y = case (x, y) of
(a, PTemporary ) -> a
(_, a@PPermanent {}) -> a
instance Monoid PartialDirectoryType where
mempty = PTemporary
setupDirectoryType :: String -> PartialDirectoryType -> IO DirectoryType
setupDirectoryType pattern = \case
PTemporary -> Temporary <$> createTempDirectory "/tmp" pattern
PPermanent x -> pure $ Permanent x
rmDirIgnoreErrors :: FilePath -> IO ()
rmDirIgnoreErrors mainDir = do
let ignoreDirIsMissing e
| isDoesNotExistError e = return ()
| otherwise = throwIO e
removeDirectoryRecursive mainDir `catch` ignoreDirIsMissing
cleanupDirectoryType :: DirectoryType -> IO ()
cleanupDirectoryType = \case
Permanent _ -> pure ()
Temporary filePath -> rmDirIgnoreErrors filePath
data SocketClass
= IpSocket String
| UnixSocket DirectoryType
deriving (Show, Eq, Ord, Generic, Typeable)
instance Pretty SocketClass where
pretty = \case
IpSocket x -> text "IpSocket:" <+> pretty x
UnixSocket x -> text "UnixSocket:" <+> pretty x
socketClassToConfig :: SocketClass -> [String]
socketClassToConfig = \case
IpSocket ip -> ["listen_addresses = '" <> ip <> "'"]
UnixSocket dir ->
[ "listen_addresses = ''"
, "unix_socket_directories = '" <> toFilePath dir <> "'"
]
socketClassToHostFlag :: SocketClass -> [(String, Maybe String)]
socketClassToHostFlag x = [("-h", Just (socketClassToHost x))]
socketClassToHost :: SocketClass -> String
socketClassToHost = \case
IpSocket ip -> ip
UnixSocket dir -> toFilePath dir
data PartialSocketClass
= PIpSocket (Last String)
| PUnixSocket PartialDirectoryType
deriving stock (Show, Eq, Ord, Generic, Typeable)
instance Pretty PartialSocketClass where
pretty = \case
PIpSocket x -> "IpSocket:" <+> pretty (getLast x)
PUnixSocket x -> "UnixSocket" <+> pretty x
instance Semigroup PartialSocketClass where
x <> y = case (x, y) of
(PIpSocket a, PIpSocket b) -> PIpSocket $ a <> b
(a@(PIpSocket _), PUnixSocket _) -> a
(PUnixSocket _, a@(PIpSocket _)) -> a
(PUnixSocket a, PUnixSocket b) -> PUnixSocket $ a <> b
instance Monoid PartialSocketClass where
mempty = PUnixSocket mempty
setupPartialSocketClass :: PartialSocketClass -> IO SocketClass
setupPartialSocketClass theClass = case theClass of
PIpSocket mIp -> pure $ IpSocket $ fromMaybe "127.0.0.1" $
getLast mIp
PUnixSocket mFilePath ->
UnixSocket <$> setupDirectoryType "tmp-postgres-socket" mFilePath
cleanupSocketConfig :: SocketClass -> IO ()
cleanupSocketConfig = \case
IpSocket {} -> pure ()
UnixSocket dir -> cleanupDirectoryType dir
data PartialPostgresPlan = PartialPostgresPlan
{ partialPostgresPlanProcessConfig :: PartialProcessConfig
, partialPostgresPlanClientConfig :: Client.Options
}
deriving stock (Generic)
deriving Semigroup via GenericSemigroup PartialPostgresPlan
deriving Monoid via GenericMonoid PartialPostgresPlan
instance Pretty PartialPostgresPlan where
pretty PartialPostgresPlan {..}
= text "partialPostgresPlanProcessConfig:"
<> softline
<> indent 2 (pretty partialPostgresPlanProcessConfig)
<> hardline
<> text "partialPostgresPlanClientConfig:"
<> softline
<> indent 2 (prettyOptions partialPostgresPlanClientConfig)
completePostgresPlan :: [(String, String)] -> PartialPostgresPlan -> Either [String] PostgresPlan
completePostgresPlan envs PartialPostgresPlan {..} = runErrors $ do
let postgresPlanClientOptions = partialPostgresPlanClientConfig
postgresPlanProcessConfig <-
eitherToErrors $ addErrorContext "partialPostgresPlanProcessConfig: " $
completeProcessConfig envs partialPostgresPlanProcessConfig
pure PostgresPlan {..}
data PartialPlan = PartialPlan
{ partialPlanLogger :: Last Logger
, partialPlanInitDb :: Maybe PartialProcessConfig
, partialPlanCreateDb :: Maybe PartialProcessConfig
, partialPlanPostgres :: PartialPostgresPlan
, partialPlanConfig :: [String]
, partialPlanDataDirectory :: Last String
}
deriving stock (Generic)
deriving Semigroup via GenericSemigroup PartialPlan
deriving Monoid via GenericMonoid PartialPlan
instance Pretty PartialPlan where
pretty PartialPlan {..}
= text "partialPlanInitDb:"
<> softline
<> indent 2 (pretty partialPlanInitDb)
<> hardline
<> text "partialPlanInitDb:"
<> softline
<> indent 2 (pretty partialPlanCreateDb)
<> hardline
<> text "partialPlanPostgres:"
<> softline
<> indent 2 (pretty partialPlanPostgres)
<> hardline
<> text "partialPlanConfig:"
<> softline
<> indent 2 (vsep $ map text partialPlanConfig)
<> hardline
<> text "partialPlanDataDirectory:" <+> pretty (getLast partialPlanDataDirectory)
completePlan :: [(String, String)] -> PartialPlan -> Either [String] Plan
completePlan envs PartialPlan {..} = runErrors $ do
planLogger <- getOption "partialPlanLogger" partialPlanLogger
planInitDb <- eitherToErrors $ addErrorContext "partialPlanInitDb: " $
traverse (completeProcessConfig envs) partialPlanInitDb
planCreateDb <- eitherToErrors $ addErrorContext "partialPlanCreateDb: " $
traverse (completeProcessConfig envs) partialPlanCreateDb
planPostgres <- eitherToErrors $ addErrorContext "partialPlanPostgres: " $
completePostgresPlan envs partialPlanPostgres
let planConfig = unlines partialPlanConfig
planDataDirectory <- getOption "partialPlanDataDirectory"
partialPlanDataDirectory
pure Plan {..}
hasInitDb :: PartialPlan -> Bool
hasInitDb PartialPlan {..} = isJust partialPlanInitDb
hasCreateDb :: PartialPlan -> Bool
hasCreateDb PartialPlan {..} = isJust partialPlanCreateDb
data Resources = Resources
{ resourcesPlan :: Plan
, resourcesSocket :: SocketClass
, resourcesDataDir :: DirectoryType
}
instance Pretty Resources where
pretty Resources {..}
= text "resourcePlan:"
<> softline
<> indent 2 (pretty resourcesPlan)
<> hardline
<> text "resourcesSocket:"
<+> pretty resourcesSocket
<> hardline
<> text "resourcesDataDir:"
<+> pretty resourcesDataDir
makeResourcesDataDirPermanent :: Resources -> Resources
makeResourcesDataDirPermanent r = r
{ resourcesDataDir = makePermanent $ resourcesDataDir r
}
data Config = Config
{ configPlan :: PartialPlan
, configSocket :: PartialSocketClass
, configDataDir :: PartialDirectoryType
, configPort :: Last (Maybe Int)
}
deriving stock (Generic)
deriving Semigroup via GenericSemigroup Config
deriving Monoid via GenericMonoid Config
instance Pretty Config where
pretty Config {..}
= text "configPlan:"
<> softline
<> pretty configPlan
<> hardline
<> text "configSocket:"
<> softline
<> pretty configSocket
<> hardline
<> text "configDataDir:"
<> softline
<> pretty configDataDir
<> hardline
<> text "configPort:" <+> pretty (getLast configPort)
toPlan
:: Bool
-> Bool
-> Int
-> SocketClass
-> FilePath
-> PartialPlan
toPlan makeInitDb makeCreateDb port socketClass dataDirectory = mempty
{ partialPlanConfig = socketClassToConfig socketClass
, partialPlanDataDirectory = pure dataDirectory
, partialPlanPostgres = mempty
{ partialPostgresPlanProcessConfig = mempty
{ partialProcessConfigCmdLine = mempty
{ partialCommandLineArgsKeyBased = Map.fromList
[ ("-p", Just $ show port)
, ("-D", Just dataDirectory)
]
}
}
, partialPostgresPlanClientConfig = mempty
{ Client.host = pure $ socketClassToHost socketClass
, Client.port = pure port
, Client.dbname = pure "postgres"
}
}
, partialPlanCreateDb = if makeCreateDb
then pure $ mempty
{ partialProcessConfigCmdLine = mempty
{ partialCommandLineArgsKeyBased = Map.fromList $
socketClassToHostFlag socketClass <>
[("-p ", Just $ show port)]
}
}
else Nothing
, partialPlanInitDb = if makeInitDb
then pure $ mempty
{ partialProcessConfigCmdLine = mempty
{ partialCommandLineArgsKeyBased = Map.fromList $
[("--pgdata=", Just dataDirectory)]
}
}
else Nothing
}
setupConfig
:: Config
-> IO Resources
setupConfig Config {..} = evalContT $ do
envs <- lift getEnvironment
port <- lift $ maybe getFreePort pure $ join $ getLast configPort
resourcesSocket <- ContT $ bracketOnError
(setupPartialSocketClass configSocket) cleanupSocketConfig
resourcesDataDir <- ContT $ bracketOnError
(setupDirectoryType "tmp-postgres-data" configDataDir) cleanupDirectoryType
let hostAndDirPartial = toPlan
(hasInitDb configPlan)
(hasCreateDb configPlan)
port
resourcesSocket
(toFilePath resourcesDataDir)
finalPlan = hostAndDirPartial <> configPlan
resourcesPlan <- lift $
either (throwIO . CompletePlanFailed (show $ pretty finalPlan)) pure $
completePlan envs finalPlan
pure Resources {..}
cleanupConfig :: Resources -> IO ()
cleanupConfig Resources {..} = do
cleanupSocketConfig resourcesSocket
cleanupDirectoryType resourcesDataDir
optionsToConfig :: Client.Options -> Config
optionsToConfig opts@Client.Options {..}
= ( mempty
{ configPlan = optionsToPlan opts
, configPort = maybe (Last Nothing) (pure . pure) $ getLast port
, configSocket = maybe mempty hostToSocketClass $ getLast host
}
)
optionsToPlan :: Client.Options -> PartialPlan
optionsToPlan opts@Client.Options {..}
= maybe mempty dbnameToPlan (getLast dbname)
<> maybe mempty userToPlan (getLast user)
<> clientOptionsToPlan opts
clientOptionsToPlan :: Client.Options -> PartialPlan
clientOptionsToPlan opts = mempty
{ partialPlanPostgres = mempty
{ partialPostgresPlanClientConfig = opts
}
}
userToPlan :: String -> PartialPlan
userToPlan user = mempty
{ partialPlanCreateDb = pure $ mempty
{ partialProcessConfigCmdLine = mempty
{ partialCommandLineArgsKeyBased = Map.singleton "--username=" $ Just user
}
}
, partialPlanInitDb = pure $ mempty
{ partialProcessConfigCmdLine = mempty
{ partialCommandLineArgsKeyBased = Map.singleton "--username=" $ Just user
}
}
}
dbnameToPlan :: String -> PartialPlan
dbnameToPlan dbName = mempty
{ partialPlanCreateDb = pure $ mempty
{ partialProcessConfigCmdLine = mempty
{ partialCommandLineArgsIndexBased = Map.singleton 0 dbName
}
}
}
hostToSocketClass :: String -> PartialSocketClass
hostToSocketClass hostOrSocketPath = case hostOrSocketPath of
'/' : _ -> PUnixSocket $ PPermanent hostOrSocketPath
_ -> PIpSocket $ pure hostOrSocketPath
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
partialEnvVarsInheritL :: Lens' PartialEnvVars (Last Bool)
partialEnvVarsInheritL f_aj5e (PartialEnvVars x_aj5f x_aj5g)
= (fmap (\ y_aj5h -> (PartialEnvVars y_aj5h) x_aj5g))
(f_aj5e x_aj5f)
{-# INLINE partialEnvVarsInheritL #-}
partialEnvVarsSpecificL :: Lens' PartialEnvVars (Map String String)
partialEnvVarsSpecificL f_aj5i (PartialEnvVars x_aj5j x_aj5k)
= (fmap (\ y_aj5l -> (PartialEnvVars x_aj5j) y_aj5l))
(f_aj5i x_aj5k)
{-# INLINE partialEnvVarsSpecificL #-}
partialProcessConfigCmdLineL ::
Lens' PartialProcessConfig PartialCommandLineArgs
partialProcessConfigCmdLineL
f_allv
(PartialProcessConfig x_allw x_allx x_ally x_allz x_allA)
= (fmap
(\ y_allB
-> ((((PartialProcessConfig x_allw) y_allB) x_ally) x_allz)
x_allA))
(f_allv x_allx)
{-# INLINE partialProcessConfigCmdLineL #-}
partialProcessConfigEnvVarsL ::
Lens' PartialProcessConfig PartialEnvVars
partialProcessConfigEnvVarsL
f_allC
(PartialProcessConfig x_allD x_allE x_allF x_allG x_allH)
= (fmap
(\ y_allI
-> ((((PartialProcessConfig y_allI) x_allE) x_allF) x_allG)
x_allH))
(f_allC x_allD)
{-# INLINE partialProcessConfigEnvVarsL #-}
partialProcessConfigStdErrL ::
Lens' PartialProcessConfig (Last Handle)
partialProcessConfigStdErrL
f_allJ
(PartialProcessConfig x_allK x_allL x_allM x_allN x_allO)
= (fmap
(\ y_allP
-> ((((PartialProcessConfig x_allK) x_allL) x_allM) x_allN)
y_allP))
(f_allJ x_allO)
{-# INLINE partialProcessConfigStdErrL #-}
partialProcessConfigStdInL ::
Lens' PartialProcessConfig (Last Handle)
partialProcessConfigStdInL
f_allQ
(PartialProcessConfig x_allR x_allS x_allT x_allU x_allV)
= (fmap
(\ y_allW
-> ((((PartialProcessConfig x_allR) x_allS) y_allW) x_allU)
x_allV))
(f_allQ x_allT)
{-# INLINE partialProcessConfigStdInL #-}
partialProcessConfigStdOutL ::
Lens' PartialProcessConfig (Last Handle)
partialProcessConfigStdOutL
f_allX
(PartialProcessConfig x_allY x_allZ x_alm0 x_alm1 x_alm2)
= (fmap
(\ y_alm3
-> ((((PartialProcessConfig x_allY) x_allZ) x_alm0) y_alm3)
x_alm2))
(f_allX x_alm1)
{-# INLINE partialProcessConfigStdOutL #-}
partialPostgresPlanClientConfigL ::
Lens' PartialPostgresPlan Client.Options
partialPostgresPlanClientConfigL
f_am1y
(PartialPostgresPlan x_am1z x_am1A)
= (fmap (\ y_am1B -> (PartialPostgresPlan x_am1z) y_am1B))
(f_am1y x_am1A)
{-# INLINE partialPostgresPlanClientConfigL #-}
partialPostgresPlanProcessConfigL ::
Lens' PartialPostgresPlan PartialProcessConfig
partialPostgresPlanProcessConfigL
f_am1C
(PartialPostgresPlan x_am1D x_am1E)
= (fmap (\ y_am1F -> (PartialPostgresPlan y_am1F) x_am1E))
(f_am1C x_am1D)
{-# INLINE partialPostgresPlanProcessConfigL #-}
partialPlanConfigL :: Lens' PartialPlan [String]
partialPlanConfigL
f_amcw
(PartialPlan x_amcx x_amcy x_amcz x_amcA x_amcB x_amcC)
= (fmap
(\ y_amcD
-> (((((PartialPlan x_amcx) x_amcy) x_amcz) x_amcA) y_amcD)
x_amcC))
(f_amcw x_amcB)
{-# INLINE partialPlanConfigL #-}
partialPlanCreateDbL ::
Lens' PartialPlan (Maybe PartialProcessConfig)
partialPlanCreateDbL
f_amcE
(PartialPlan x_amcF x_amcG x_amcH x_amcI x_amcJ x_amcK)
= (fmap
(\ y_amcL
-> (((((PartialPlan x_amcF) x_amcG) y_amcL) x_amcI) x_amcJ)
x_amcK))
(f_amcE x_amcH)
{-# INLINE partialPlanCreateDbL #-}
partialPlanDataDirectoryL :: Lens' PartialPlan (Last String)
partialPlanDataDirectoryL
f_amcM
(PartialPlan x_amcN x_amcO x_amcP x_amcQ x_amcR x_amcS)
= (fmap
(\ y_amcT
-> (((((PartialPlan x_amcN) x_amcO) x_amcP) x_amcQ) x_amcR)
y_amcT))
(f_amcM x_amcS)
{-# INLINE partialPlanDataDirectoryL #-}
partialPlanInitDbL ::
Lens' PartialPlan (Maybe PartialProcessConfig)
partialPlanInitDbL
f_amcU
(PartialPlan x_amcV x_amcW x_amcX x_amcY x_amcZ x_amd0)
= (fmap
(\ y_amd1
-> (((((PartialPlan x_amcV) y_amd1) x_amcX) x_amcY) x_amcZ)
x_amd0))
(f_amcU x_amcW)
{-# INLINE partialPlanInitDbL #-}
partialPlanLoggerL :: Lens' PartialPlan (Last Logger)
partialPlanLoggerL
f_amd2
(PartialPlan x_amd3 x_amd4 x_amd5 x_amd6 x_amd7 x_amd8)
= (fmap
(\ y_amd9
-> (((((PartialPlan y_amd9) x_amd4) x_amd5) x_amd6) x_amd7)
x_amd8))
(f_amd2 x_amd3)
{-# INLINE partialPlanLoggerL #-}
partialPlanPostgresL :: Lens' PartialPlan PartialPostgresPlan
partialPlanPostgresL
f_amda
(PartialPlan x_amdb x_amdc x_amdd x_amde x_amdf x_amdg)
= (fmap
(\ y_amdh
-> (((((PartialPlan x_amdb) x_amdc) x_amdd) y_amdh) x_amdf)
x_amdg))
(f_amda x_amde)
{-# INLINE partialPlanPostgresL #-}
resourcesDataDirL :: Lens' Resources DirectoryType
resourcesDataDirL f_ampd (Resources x_ampe x_ampf x_ampg)
= (fmap (\ y_amph -> ((Resources x_ampe) x_ampf) y_amph))
(f_ampd x_ampg)
{-# INLINE resourcesDataDirL #-}
resourcesPlanL :: Lens' Resources Plan
resourcesPlanL f_ampi (Resources x_ampj x_ampk x_ampl)
= (fmap (\ y_ampm -> ((Resources y_ampm) x_ampk) x_ampl))
(f_ampi x_ampj)
{-# INLINE resourcesPlanL #-}
resourcesSocketL :: Lens' Resources SocketClass
resourcesSocketL f_ampn (Resources x_ampo x_ampp x_ampq)
= (fmap (\ y_ampr -> ((Resources x_ampo) y_ampr) x_ampq))
(f_ampn x_ampp)
{-# INLINE resourcesSocketL #-}
configDataDirL :: Lens' Config PartialDirectoryType
configDataDirL f_amyD (Config x_amyE x_amyF x_amyG x_amyH)
= (fmap (\ y_amyI -> (((Config x_amyE) x_amyF) y_amyI) x_amyH))
(f_amyD x_amyG)
{-# INLINE configDataDirL #-}
configPlanL :: Lens' Config PartialPlan
configPlanL f_amyJ (Config x_amyK x_amyL x_amyM x_amyN)
= (fmap (\ y_amyO -> (((Config y_amyO) x_amyL) x_amyM) x_amyN))
(f_amyJ x_amyK)
{-# INLINE configPlanL #-}
configPortL :: Lens' Config (Last (Maybe Int))
configPortL f_amyP (Config x_amyQ x_amyR x_amyS x_amyT)
= (fmap (\ y_amyU -> (((Config x_amyQ) x_amyR) x_amyS) y_amyU))
(f_amyP x_amyT)
{-# INLINE configPortL #-}
configSocketL :: Lens' Config PartialSocketClass
configSocketL f_amyV (Config x_amyW x_amyX x_amyY x_amyZ)
= (fmap (\ y_amz0 -> (((Config x_amyW) y_amz0) x_amyY) x_amyZ))
(f_amyV x_amyX)
{-# INLINE configSocketL #-}
partialCommandLineArgsIndexBasedL ::
Lens' PartialCommandLineArgs (Map Int String)
partialCommandLineArgsIndexBasedL
f_amNr
(PartialCommandLineArgs x_amNs x_amNt)
= (fmap (\ y_amNu -> (PartialCommandLineArgs x_amNs) y_amNu))
(f_amNr x_amNt)
{-# INLINE partialCommandLineArgsIndexBasedL #-}
partialCommandLineArgsKeyBasedL ::
Lens' PartialCommandLineArgs (Map String (Maybe String))
partialCommandLineArgsKeyBasedL
f_amNv
(PartialCommandLineArgs x_amNw x_amNx)
= (fmap (\ y_amNy -> (PartialCommandLineArgs y_amNy) x_amNx))
(f_amNv x_amNw)
{-# INLINE partialCommandLineArgsKeyBasedL #-}