module Hapistrano
(
Config(..)
, initialState
, runRC
, activateRelease
, runBuild
, defaultSuccessHandler
, defaultErrorHandler
, pushRelease
, restartServerCommand
, rollback
) where
import Control.Lens (makeLenses, use, (^.), (.=))
import Control.Monad (unless)
import Control.Monad.IO.Class (MonadIO(liftIO))
import Control.Monad.Trans.State (StateT, evalStateT, get)
import Control.Monad.Trans.Class (lift)
import Control.Monad.Trans.Either ( EitherT(..)
, left
, right
, runEitherT
, eitherT )
import Data.Char (isNumber)
import Data.List (intercalate, sortBy, sort, isInfixOf)
import Data.Time (getCurrentTime)
import Data.Time.Format (formatTime)
import System.Exit (ExitCode(..))
import System.FilePath.Posix (joinPath, splitPath)
import System.IO (hPutStrLn, stderr)
import System.Locale (defaultTimeLocale)
import System.Process (readProcessWithExitCode)
data Config = Config { _deployPath :: String
, _host :: String
, _repository :: String
, _revision :: String
, _buildScript :: Maybe FilePath
, _restartCommand :: Maybe String
} deriving (Show)
makeLenses ''Config
data HapistranoState = HapistranoState { _config :: Config
, _timestamp :: Maybe String
}
makeLenses ''HapistranoState
type Release = String
type RC a = StateT HapistranoState (EitherT (Int, Maybe String) IO) a
initialState :: Config -> HapistranoState
initialState cfg = HapistranoState { _config = cfg
, _timestamp = Nothing
}
runRC :: ((Int, Maybe String) -> IO a)
-> (a -> IO a)
-> HapistranoState
-> RC a
-> IO a
runRC errorHandler successHandler initState remoteCmd =
eitherT errorHandler
successHandler
(evalStateT remoteCmd initState)
defaultErrorHandler :: (Int, Maybe String) -> IO ()
defaultErrorHandler _ = putStrLn "Deploy failed."
defaultSuccessHandler :: a -> IO ()
defaultSuccessHandler _ = putStrLn "Deploy completed successfully."
setupDirs :: RC (Maybe String)
setupDirs = do
pathName <- use $ config . deployPath
remoteCommand $ "mkdir -p " ++ joinPath [pathName, "releases"]
remoteCommand :: String
-> RC (Maybe String)
remoteCommand command = do
server <- use $ config . host
liftIO $ putStrLn $ "Going to execute " ++ command ++ " on host " ++ server
++ "."
(code, stdout, err) <-
liftIO $ readProcessWithExitCode "ssh" (server : words command) ""
case code of
ExitSuccess -> do
liftIO $ putStrLn $ "Command '" ++ command ++
"' was successful on host '" ++ server ++ "'."
unless (null stdout) (liftIO $ putStrLn $ "Output:\n" ++ stdout)
lift $ right $ maybeString stdout
ExitFailure int -> do
let maybeError = maybeString err
liftIO $ printCommandError server command (int, maybeError)
lift $ left (int, maybeError)
currentTimestamp :: IO String
currentTimestamp = do
curTime <- getCurrentTime
return $ formatTime defaultTimeLocale "%Y%m%d%H%M%S" curTime
echoMessage :: String -> RC (Maybe String)
echoMessage msg = do
liftIO $ putStrLn msg
lift $ right Nothing
printCommandError :: String -> String -> (Int, Maybe String) -> IO ()
printCommandError server cmd (errCode, Nothing) =
hPutStrLn stderr $ "Command " ++ " '" ++ cmd ++ "' failed on host '" ++
server ++ "' with error code " ++ show errCode ++ " and no STDERR output."
printCommandError server cmd (errCode, Just errMsg) =
hPutStrLn stderr $ "Command " ++ " '" ++ cmd ++ "' failed on host '" ++
server ++ "' with error code " ++ show errCode ++ " and message '" ++
errMsg ++ "'."
directoryExists :: FilePath -> RC (Maybe String)
directoryExists path =
remoteCommand $ "ls " ++ path
readCurrentLink :: RC (Maybe FilePath)
readCurrentLink = do
conf <- use config
remoteCommand $ "readlink " ++ currentPath conf
ensureRepositoryPushed :: RC (Maybe String)
ensureRepositoryPushed = do
conf <- use config
res <- directoryExists $ cacheRepoPath conf
case res of
Nothing -> createCacheRepo
Just _ -> lift $ right $ Just "Repo already existed"
maybeString :: String -> Maybe String
maybeString possibleString =
if null possibleString then Nothing else Just possibleString
releasesPath :: Config -> FilePath
releasesPath conf = joinPath [conf ^. deployPath, "releases"]
detectPrevious :: [String] -> RC (Maybe String)
detectPrevious rs = do
let mostRecentRls = biggest rs
case mostRecentRls of
Nothing -> lift $ left (1, Just "No previous releases detected!")
Just rls -> do
timestamp .= mostRecentRls
lift $ right $ Just rls
rollback :: RC (Maybe String)
rollback = previousReleases >>= detectPrevious >> activateRelease
cloneToRelease :: RC (Maybe String)
cloneToRelease = do
conf <- use config
releaseTimestamp <- use timestamp
rls <- case releaseTimestamp of
Nothing -> do
ts <- liftIO currentTimestamp
timestamp .= Just ts
return ts
Just r -> return r
remoteCommand $ "git clone " ++ cacheRepoPath conf ++ " " ++
joinPath [ releasesPath conf, rls ]
cacheRepoPath :: Config -> FilePath
cacheRepoPath conf = joinPath [conf ^. deployPath, "repo"]
currentPath :: Config -> FilePath
currentPath conf = joinPath [conf ^. deployPath, "current"]
pathToRelease :: FilePath -> Release
pathToRelease = last . splitPath
releases :: RC [Release]
releases = do
conf <- use config
res <- remoteCommand $ "find " ++ releasesPath conf ++ " -type d -maxdepth 1"
case res of
Nothing -> lift $ right []
Just s ->
lift $ right $ filter isReleaseString . map pathToRelease
$ lines s
previousReleases :: RC [Release]
previousReleases = do
rls <- releases
currentRelease <- readCurrentLink
case currentRelease of
Nothing -> lift $ left (1, Just "Bad pointer from current link")
Just c -> do
let currentRel = (head . lines . pathToRelease) c
return $ filter (< currentRel) rls
releasePath :: Config -> Release -> FilePath
releasePath conf rls = joinPath [releasesPath conf, rls]
oldReleases :: Config -> [Release] -> [FilePath]
oldReleases conf rs = map mergePath toDelete
where sorted = sortBy (flip compare) rs
toDelete = drop 4 sorted
mergePath = releasePath conf
cleanReleases :: RC (Maybe String)
cleanReleases = do
conf <- use config
allReleases <- releases
case allReleases of
[] -> echoMessage "There are no old releases to prune."
xs -> do
let deletable = oldReleases conf xs
remoteCommand $ "rm -rf -- " ++ foldr (\a b -> a ++ " " ++ b) ""
deletable
isReleaseString :: String -> Bool
isReleaseString s = all isNumber s && length s == 14
createCacheRepo :: RC (Maybe String)
createCacheRepo = do
conf <- use config
remoteCommand $ "git clone --bare " ++ conf ^. repository ++ " " ++
cacheRepoPath conf
currentSymlinkPath :: Config -> FilePath
currentSymlinkPath conf = joinPath [conf ^. deployPath, "current"]
currentTempSymlinkPath :: Config -> FilePath
currentTempSymlinkPath conf = joinPath [conf ^. deployPath, "current_tmp"]
removeCurrentSymlink :: RC (Maybe String)
removeCurrentSymlink = do
conf <- use config
remoteCommand $ "rm -rf " ++ currentSymlinkPath conf
remoteIsLinux :: RC Bool
remoteIsLinux = do
st <- get
res <- remoteCommand "uname"
case res of
Just output -> lift $ right $ "Linux" `isInfixOf` output
_ -> lift $ left (1, Just "Unable to determine remote host type")
restartServerCommand :: RC (Maybe String)
restartServerCommand = do
conf <- use config
case conf ^. restartCommand of
Nothing -> return $ Just "No command given for restart action."
Just cmd -> remoteCommand cmd
runBuild :: RC (Maybe String)
runBuild = do
conf <- use config
case conf ^. buildScript of
Nothing -> do
liftIO $ putStrLn "No build script specified, skipping build step."
return Nothing
Just scr -> do
fl <- liftIO $ readFile scr
let commands = lines fl
buildRelease commands
mvCommand ::
Bool
-> String
mvCommand True = "mv -Tf"
mvCommand False = "mv -f"
symlinkCurrent :: RC (Maybe String)
symlinkCurrent = do
conf <- use config
releaseTimestamp <- use timestamp
case releaseTimestamp of
Nothing -> lift $ left (1, Just "No releases to symlink!")
Just rls -> do
isLnx <- remoteIsLinux
remoteCommand $ "ln -s " ++ rls ++ " " ++
currentTempSymlinkPath conf ++
" && " ++ mvCommand isLnx ++ " " ++
currentTempSymlinkPath conf
++ " " ++ currentSymlinkPath conf
updateCacheRepo :: RC (Maybe String)
updateCacheRepo = do
conf <- use config
remoteCommand $ intercalate " && "
[ "cd " ++ cacheRepoPath conf
, "git fetch origin +refs/heads/*:refs/heads/*" ]
setReleaseRevision :: RC (Maybe String)
setReleaseRevision = do
conf <- use config
releaseTimestamp <- use timestamp
case releaseTimestamp of
Nothing -> lift $ left (1, Just "No releases to symlink!")
Just rls ->
remoteCommand $ intercalate " && "
[ "cd " ++ releasePath conf rls
, "git fetch --all"
, "git reset --hard " ++ conf ^. revision
]
buildRelease :: [String]
-> RC (Maybe String)
buildRelease commands = do
conf <- use config
releaseTimestamp <- use timestamp
case releaseTimestamp of
Nothing -> lift $ left (1, Just "No releases to symlink!")
Just rls -> do
let cdCmd = "cd " ++ releasePath conf rls
remoteCommand $ intercalate " && " $ cdCmd : commands
biggest :: Ord a => [a] -> Maybe a
biggest rls =
case sortBy (flip compare) rls of
[] -> Nothing
r:_ -> Just r
pushRelease :: RC (Maybe String)
pushRelease = setupDirs >> ensureRepositoryPushed >> updateCacheRepo >>
cleanReleases >> cloneToRelease >> setReleaseRevision
activateRelease :: RC (Maybe String)
activateRelease = removeCurrentSymlink >> symlinkCurrent