module System.Hapistrano.Core
( runHapistrano
, failWith
, exec
, scpFile
, scpDir )
where
import Control.Monad
import Control.Monad.Except
import Control.Monad.Reader
import Data.Proxy
import Path
import System.Exit
import System.Hapistrano.Commands
import System.Hapistrano.Types
import System.Process
runHapistrano :: MonadIO m
=> Maybe SshOptions
-> (OutputDest -> String -> IO ())
-> Hapistrano a
-> m (Either Int a)
runHapistrano sshOptions printFnc m = liftIO $ do
let config = Config
{ configSshOptions = sshOptions
, configPrint = printFnc }
r <- runReaderT (runExceptT m) config
case r of
Left (Failure n msg) -> do
forM_ msg (printFnc StderrDest)
return (Left n)
Right x -> return (Right x)
failWith :: Int -> Maybe String -> Hapistrano a
failWith n msg = throwError (Failure n msg)
exec :: forall a. Command a => a -> Hapistrano (Result a)
exec typedCmd = do
Config {..} <- ask
let (prog, args) =
case configSshOptions of
Nothing ->
("bash", ["-c", cmd])
Just SshOptions {..} ->
("ssh", [sshHost, "-p", show sshPort, cmd])
cmd = renderCommand typedCmd
parseResult (Proxy :: Proxy a) <$> exec' prog args cmd
scpFile
:: Path Abs File
-> Path Abs File
-> Hapistrano ()
scpFile src dest =
scp' (fromAbsFile src) (fromAbsFile dest) ["-q"]
scpDir
:: Path Abs Dir
-> Path Abs Dir
-> Hapistrano ()
scpDir src dest =
scp' (fromAbsDir src) (fromAbsDir dest) ["-qr"]
scp'
:: FilePath
-> FilePath
-> [String]
-> Hapistrano ()
scp' src dest extraArgs = do
Config {..} <- ask
let prog = "scp"
portArg =
case sshPort <$> configSshOptions of
Nothing -> []
Just x -> ["-P", show x]
hostPrefix =
case sshHost <$> configSshOptions of
Nothing -> ""
Just x -> x ++ ":"
args = extraArgs ++ portArg ++ [src, hostPrefix ++ dest]
void (exec' prog args (prog ++ " " ++ unwords args))
exec'
:: String
-> [String]
-> String
-> Hapistrano String
exec' prog args cmd = do
Config {..} <- ask
let hostLabel =
case configSshOptions of
Nothing -> "localhost"
Just SshOptions {..} -> sshHost ++ ":" ++ show sshPort
liftIO $ configPrint StdoutDest (putLine hostLabel ++ "$ " ++ cmd ++ "\n")
(exitCode, stdout', stderr') <- liftIO
(readProcessWithExitCode prog args "")
unless (null stdout') . liftIO $
configPrint StdoutDest stdout'
unless (null stderr') . liftIO $
configPrint StderrDest stderr'
case exitCode of
ExitSuccess ->
return stdout'
ExitFailure n ->
failWith n Nothing
putLine :: String -> String
putLine str = "*** " ++ str ++ padding ++ "\n"
where
padding = ' ' : replicate (75 length str) '*'