| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Stack.Docker
Description
Run commands in Docker containers
Synopsis
- cleanup :: HasConfig env => CleanupOpts -> RIO env ()
 - data CleanupOpts = CleanupOpts {
- dcAction :: !CleanupAction
 - dcRemoveKnownImagesLastUsedDaysAgo :: !(Maybe Integer)
 - dcRemoveUnknownImagesCreatedDaysAgo :: !(Maybe Integer)
 - dcRemoveDanglingImagesCreatedDaysAgo :: !(Maybe Integer)
 - dcRemoveStoppedContainersCreatedDaysAgo :: !(Maybe Integer)
 - dcRemoveRunningContainersCreatedDaysAgo :: !(Maybe Integer)
 
 - data CleanupAction
 - dockerCleanupCmdName :: String
 - dockerCmdName :: String
 - dockerHelpOptName :: String
 - dockerPullCmdName :: String
 - entrypoint :: (HasProcessContext env, HasLogFunc env) => Config -> DockerEntrypoint -> RIO env ()
 - preventInContainer :: MonadIO m => m () -> m ()
 - pull :: HasConfig env => RIO env ()
 - reexecWithOptionalContainer :: HasConfig env => Maybe (Path Abs Dir) -> Maybe (RIO env ()) -> IO () -> Maybe (RIO env ()) -> Maybe (RIO env ()) -> RIO env ()
 - reset :: (MonadIO m, MonadReader env m, HasConfig env) => Maybe (Path Abs Dir) -> Bool -> m ()
 - reExecArgName :: String
 - data StackDockerException
- = DockerMustBeEnabledException
 - | OnlyOnHostException
 - | InspectFailedException String
 - | NotPulledException String
 - | InvalidCleanupCommandException String
 - | InvalidImagesOutputException String
 - | InvalidPSOutputException String
 - | InvalidInspectOutputException String
 - | PullFailedException String
 - | DockerTooOldException Version Version
 - | DockerVersionProhibitedException [Version] Version
 - | BadDockerVersionException VersionRange Version
 - | InvalidVersionOutputException
 - | HostStackTooOldException Version (Maybe Version)
 - | ContainerStackTooOldException Version Version
 - | CannotDetermineProjectRootException
 - | DockerNotInstalledException
 - | UnsupportedStackExeHostPlatformException
 - | DockerStackExeParseException String
 
 
Documentation
cleanup :: HasConfig env => CleanupOpts -> RIO env () Source #
Clean-up old docker images and containers.
data CleanupOpts Source #
Options for cleanup.
Constructors
Instances
| Show CleanupOpts Source # | |
Defined in Stack.Docker Methods showsPrec :: Int -> CleanupOpts -> ShowS # show :: CleanupOpts -> String # showList :: [CleanupOpts] -> ShowS #  | |
data CleanupAction Source #
Cleanup action.
Constructors
| CleanupInteractive | |
| CleanupImmediate | |
| CleanupDryRun | 
Instances
| Show CleanupAction Source # | |
Defined in Stack.Docker Methods showsPrec :: Int -> CleanupAction -> ShowS # show :: CleanupAction -> String # showList :: [CleanupAction] -> ShowS #  | |
dockerCleanupCmdName :: String Source #
Command-line argument for docker cleanup.
dockerCmdName :: String Source #
Command-line argument for "docker"
dockerPullCmdName :: String Source #
Command-line argument for docker pull.
entrypoint :: (HasProcessContext env, HasLogFunc env) => Config -> DockerEntrypoint -> RIO env () Source #
The Docker container "entrypoint": special actions performed when first entering a container, such as switching the UID/GID to the "outside-Docker" user's.
preventInContainer :: MonadIO m => m () -> m () Source #
Error if running in a container.
pull :: HasConfig env => RIO env () Source #
Pull latest version of configured Docker image from registry.
reexecWithOptionalContainer :: HasConfig env => Maybe (Path Abs Dir) -> Maybe (RIO env ()) -> IO () -> Maybe (RIO env ()) -> Maybe (RIO env ()) -> RIO env () Source #
If Docker is enabled, re-runs the currently running OS command in a Docker container. Otherwise, runs the inner action.
This takes an optional release action which should be taken IFF control is transferring away from the current process to the intra-container one. The main use for this is releasing a lock. After launching reexecution, the host process becomes nothing but an manager for the call into docker and thus may not hold the lock.
reset :: (MonadIO m, MonadReader env m, HasConfig env) => Maybe (Path Abs Dir) -> Bool -> m () Source #
Remove the project's Docker sandbox.
reExecArgName :: String Source #
Command-line option for --internal-re-exec-version.
data StackDockerException Source #
Exceptions thrown by Stack.Docker.
Constructors
| DockerMustBeEnabledException | Docker must be enabled to use the command.  | 
| OnlyOnHostException | Command must be run on host OS (not in a container).  | 
| InspectFailedException String | 
  | 
| NotPulledException String | Image does not exist.  | 
| InvalidCleanupCommandException String | Input to   | 
| InvalidImagesOutputException String | Invalid output from   | 
| InvalidPSOutputException String | Invalid output from   | 
| InvalidInspectOutputException String | Invalid output from   | 
| PullFailedException String | Could not pull a Docker image.  | 
| DockerTooOldException Version Version | Installed version of   | 
| DockerVersionProhibitedException [Version] Version | Installed version of   | 
| BadDockerVersionException VersionRange Version | Installed version of   | 
| InvalidVersionOutputException | Invalid output from   | 
| HostStackTooOldException Version (Maybe Version) | Version of   | 
| ContainerStackTooOldException Version Version | Version of   | 
| CannotDetermineProjectRootException | Can't determine the project root (where to put docker sandbox).  | 
| DockerNotInstalledException | 
  | 
| UnsupportedStackExeHostPlatformException | Using host stack-exe on unsupported platform.  | 
| DockerStackExeParseException String | 
  | 
Instances
| Show StackDockerException Source # | |
Defined in Stack.Types.Docker Methods showsPrec :: Int -> StackDockerException -> ShowS # show :: StackDockerException -> String # showList :: [StackDockerException] -> ShowS #  | |
| Exception StackDockerException Source # | |
Defined in Stack.Types.Docker Methods toException :: StackDockerException -> SomeException # fromException :: SomeException -> Maybe StackDockerException #  | |