module Arion.DockerCompose where
import Protolude
import System.Process
import Prelude ()
data Args = Args
{ Args -> [String]
files :: [FilePath],
Args -> [Text]
otherArgs :: [Text]
}
run :: Args -> IO ()
run :: Args -> IO ()
run Args
args = do
let fileArgs :: [String]
fileArgs = Args
args.files [String] -> (String -> [String]) -> [String]
forall a b. [a] -> (a -> [b]) -> [b]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \String
f -> [String
"--file", String
f]
allArgs :: [String]
allArgs = [String]
fileArgs [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (Text -> String) -> [Text] -> [String]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
map Text -> String
forall a b. ConvertText a b => a -> b
toS Args
args.otherArgs
procSpec :: CreateProcess
procSpec = String -> [String] -> CreateProcess
proc String
"docker-compose" [String]
allArgs
CreateProcess
-> (Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ())
-> IO ()
forall a.
CreateProcess
-> (Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO a)
-> IO a
withCreateProcess CreateProcess
procSpec ((Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ())
-> IO ())
-> (Maybe Handle
-> Maybe Handle -> Maybe Handle -> ProcessHandle -> IO ())
-> IO ()
forall a b. (a -> b) -> a -> b
$ \Maybe Handle
_in Maybe Handle
_out Maybe Handle
_err ProcessHandle
procHandle -> do
ExitCode
exitCode <- ProcessHandle -> IO ExitCode
waitForProcess ProcessHandle
procHandle
case ExitCode
exitCode of
ExitCode
ExitSuccess -> IO ()
forall (f :: * -> *). Applicative f => f ()
pass
ExitFailure Int
1 -> IO ()
forall a. IO a
exitFailure
ExitFailure {} -> do
FatalError -> IO ()
forall (m :: * -> *) e a. (MonadIO m, Exception e) => e -> m a
throwIO (FatalError -> IO ()) -> FatalError -> IO ()
forall a b. (a -> b) -> a -> b
$ Text -> FatalError
FatalError (Text -> FatalError) -> Text -> FatalError
forall a b. (a -> b) -> a -> b
$ Text
"docker-compose failed with " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> ExitCode -> Text
forall a b. (Show a, StringConv String b) => a -> b
show ExitCode
exitCode