| Copyright | © 2015-Present Stack Builders |
|---|---|
| License | MIT |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
System.Hapistrano
Contents
Description
A module for creating reliable deploy processes for Haskell applications.
Synopsis
- runHapistrano :: MonadIO m => Maybe SshOptions -> Shell -> (OutputDest -> String -> IO ()) -> Hapistrano a -> m (Either Int a)
- pushRelease :: Task -> Hapistrano Release
- pushReleaseWithoutVc :: Task -> Hapistrano Release
- activateRelease :: TargetSystem -> Path Abs Dir -> Release -> Hapistrano ()
- linkToShared :: TargetSystem -> Path Abs Dir -> Path Abs Dir -> FilePath -> Maybe Release -> Hapistrano ()
- createHapistranoDeployState :: Path Abs Dir -> Release -> DeployState -> Hapistrano ()
- deploy :: Config -> ReleaseFormat -> Natural -> Bool -> Hapistrano ()
- rollback :: TargetSystem -> Path Abs Dir -> Natural -> Maybe GenericCommand -> Hapistrano ()
- dropOldReleases :: Path Abs Dir -> Natural -> Bool -> Hapistrano ()
- playScript :: Path Abs Dir -> Release -> Maybe (Path Rel Dir) -> [GenericCommand] -> Hapistrano ()
- playScriptLocally :: [GenericCommand] -> Hapistrano ()
- releasePath :: Path Abs Dir -> Release -> Maybe (Path Rel Dir) -> Hapistrano (Path Abs Dir)
- sharedPath :: Path Abs Dir -> Path Abs Dir
- currentSymlinkPath :: Path Abs Dir -> Path Abs File
- tempSymlinkPath :: Path Abs Dir -> Path Abs File
- deployState :: Path Abs Dir -> Maybe (Path Rel Dir) -> Release -> Hapistrano DeployState
Documentation
Arguments
| :: MonadIO m | |
| => Maybe SshOptions | SSH options to use or |
| -> Shell | Shell to run commands |
| -> (OutputDest -> String -> IO ()) | How to print messages |
| -> Hapistrano a | The computation to run |
| -> m (Either Int a) |
Run the Hapistrano monad. The monad hosts exec actions.
pushRelease :: Task -> Hapistrano Release Source #
Perform basic setup for a project, making sure necessary directories exist and pushing a new release directory with the SHA1 or branch specified in the configuration. Return identifier of the pushed release.
pushReleaseWithoutVc :: Task -> Hapistrano Release Source #
Same as pushRelease but doesn't perform any version control
related operations.
Arguments
| :: TargetSystem | |
| -> Path Abs Dir | Deploy path |
| -> Release | Release identifier to activate |
| -> Hapistrano () |
Switch the current symlink to point to the specified release. May be used in deploy or rollback cases.
Arguments
| :: TargetSystem | System to deploy |
| -> Path Abs Dir | Release path |
| -> Path Abs Dir | Deploy path |
| -> FilePath | Thing to link in share |
| -> Maybe Release | Release that was being attempted, if it was defined |
| -> Hapistrano () |
Link something (file or directory) from the {deploy_path}shared directory to a release
createHapistranoDeployState Source #
Arguments
| :: Path Abs Dir | Deploy path |
| -> Release | Release being deployed |
| -> DeployState | Indicates how the deployment went |
| -> Hapistrano () |
Creates the file .hapistrano__state containing
fail or success depending on how the deployment ended.
Arguments
| :: Config | Deploy configuration |
| -> ReleaseFormat | Long or Short format |
| -> Natural | Number of releases to keep |
| -> Bool | Wheter we should keep one failed release or not |
| -> Hapistrano () |
Deploys a new release
Arguments
| :: TargetSystem | |
| -> Path Abs Dir | Deploy path |
| -> Natural | How many releases back to go, 0 re-activates current |
| -> Maybe GenericCommand | Restart command |
| -> Hapistrano () |
Activates one of already deployed releases.
Arguments
| :: Path Abs Dir | Deploy path |
| -> Natural | How many releases to keep |
| -> Bool | Whether the |
| -> Hapistrano () |
Remove older releases to avoid filling up the target host filesystem.
Arguments
| :: Path Abs Dir | Deploy path |
| -> Release | Release identifier |
| -> Maybe (Path Rel Dir) | Working directory |
| -> [GenericCommand] | Commands to execute |
| -> Hapistrano () |
Play the given script switching to directory of given release.
playScriptLocally :: [GenericCommand] -> Hapistrano () Source #
Plays the given script on your machine locally.
Path helpers
Arguments
| :: Path Abs Dir | Deploy path |
| -> Release |
|
| -> Maybe (Path Rel Dir) | Working directory |
| -> Hapistrano (Path Abs Dir) |
Construct path to a particular Release.
Return the full path to the directory containing the shared files/directories.
Get full path to current symlink.
Get full path to temp symlink.