| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Docker.Client.Types
Synopsis
- data Endpoint
- = VersionEndpoint
- | ListContainersEndpoint ListOpts
- | ListImagesEndpoint ListOpts
- | CreateContainerEndpoint CreateOpts (Maybe ContainerName)
- | StartContainerEndpoint StartOpts ContainerID
- | StopContainerEndpoint Timeout ContainerID
- | WaitContainerEndpoint ContainerID
- | KillContainerEndpoint Signal ContainerID
- | RestartContainerEndpoint Timeout ContainerID
- | PauseContainerEndpoint ContainerID
- | UnpauseContainerEndpoint ContainerID
- | ContainerLogsEndpoint LogOpts Bool ContainerID
- | DeleteContainerEndpoint ContainerDeleteOpts ContainerID
- | InspectContainerEndpoint ContainerID
- | BuildImageEndpoint BuildOpts FilePath
- | CreateImageEndpoint Text Tag (Maybe Text)
- | DeleteImageEndpoint ImageDeleteOpts ImageID
- | CreateNetworkEndpoint CreateNetworkOpts
- | RemoveNetworkEndpoint NetworkID
- type URL = Text
- type ApiVersion = Text
- data ContainerID
- fromContainerID :: ContainerID -> Text
- toContainerID :: Text -> Maybe ContainerID
- data ImageID
- fromImageID :: ImageID -> Text
- toImageID :: Text -> Maybe ImageID
- data NetworkID
- fromNetworkID :: NetworkID -> Text
- toNetworkID :: Text -> Maybe NetworkID
- data Timeout
- data StatusCode = StatusCode Int
- data Signal
- data ContainerDetails = ContainerDetails {
- appArmorProfile :: Text
- args :: [Text]
- containerDetailsConfig :: ContainerConfig
- created :: UTCTime
- driver :: Text
- containerDetailsHostConfig :: HostConfig
- hostnamePath :: FilePath
- hostsPath :: FilePath
- logPath :: FilePath
- containerDetailsId :: ContainerID
- containerDetailsImage :: ImageID
- mountLabel :: Text
- name :: Text
- networkSettings :: NetworkSettings
- path :: FilePath
- processLabel :: Text
- resolveConfPath :: FilePath
- restartCount :: Int
- containerDetailsState :: ContainerState
- mounts :: [Mount]
- data DockerClientOpts = DockerClientOpts {
- apiVer :: ApiVersion
- baseUrl :: URL
- defaultClientOpts :: DockerClientOpts
- data ListOpts = ListOpts {}
- defaultListOpts :: ListOpts
- data DockerVersion = DockerVersion {}
- data ContainerPortInfo = ContainerPortInfo {}
- data Container = Container {
- containerId :: ContainerID
- containerNames :: [Text]
- containerImageName :: Text
- containerImageId :: ImageID
- containerCommand :: Text
- containerCreatedAt :: Int
- containerState :: State
- containerStatus :: Maybe Text
- containerPorts :: [ContainerPortInfo]
- containerLabels :: [Label]
- containerNetworks :: [Network]
- containerMounts :: [Mount]
- data ContainerState = ContainerState {}
- data State
- type Digest = Text
- data Label = Label Name Value
- type Tag = Text
- data Image = DockerImage {
- imageId :: ImageID
- imageCreated :: Integer
- imageParentId :: Maybe ImageID
- imageRepoTags :: [Tag]
- imageRepoDigests :: [Digest]
- imageSize :: Integer
- imageVirtualSize :: Integer
- imageLabels :: [Label]
- data Entrypoint = Entrypoint [Text]
- dropImagePrefix :: [a] -> [a]
- data CreateOpts = CreateOpts {}
- data BuildOpts = BuildOpts {}
- defaultBuildOpts :: Text -> BuildOpts
- defaultCreateOpts :: Text -> CreateOpts
- data DetachKeys
- data StartOpts = StartOpts {}
- defaultStartOpts :: StartOpts
- data ContainerDeleteOpts = ContainerDeleteOpts {
- deleteVolumes :: Bool
- force :: Bool
- defaultContainerDeleteOpts :: ContainerDeleteOpts
- data ImageDeleteOpts = ImageDeleteOpts
- defaultImageDeleteOpts :: ImageDeleteOpts
- type Timestamp = Integer
- data TailLogOpt
- data LogOpts = LogOpts {}
- defaultLogOpts :: LogOpts
- data CreateNetworkOpts = CreateNetworkOpts {}
- defaultCreateNetworkOpts :: Text -> CreateNetworkOpts
- data VolumePermission
- data Bind = Bind {}
- newtype Volume = Volume FilePath
- data Device = Device {}
- type ContainerName = Text
- data VolumeFrom = VolumeFrom ContainerName (Maybe VolumePermission)
- data Link = Link Text (Maybe Text)
- data LogDriverType
- data LogDriverOption = LogDriverOption Name Value
- data LogDriverConfig = LogDriverConfig LogDriverType [LogDriverOption]
- data NetworkMode
- data PortType
- data Network = Network NetworkMode NetworkOptions
- data NetworkSettings = NetworkSettings {
- networkSettingsBridge :: Text
- networkSettingsSandboxId :: Text
- networkSettingsHairpinMode :: Bool
- networkSettingsLinkLocalIPv6Address :: Text
- networkSettingsLinkLocalIPv6PrefixLen :: Int
- networkSettingsPorts :: [PortBinding]
- networkSettingsSandboxKey :: Text
- networkSettingsSecondaryIPAddresses :: Maybe [Text]
- networkSettingsSecondaryIPv6Addresses :: Maybe [Text]
- networkSettingsEndpointID :: Text
- networkSettingsGateway :: Text
- networkSettingsGlobalIPv6Address :: Text
- networkSettingsGlobalIPv6PrefixLen :: Int
- networkSettingsIpAddress :: Text
- networkSettingsIpPrefixLen :: Int
- networkSettingsIpv6Gateway :: Text
- networkSettingsMacAddress :: Text
- networkSettingsNetworks :: [Network]
- data NetworkOptions = NetworkOptions {
- networkOptionsId :: Text
- networkOptionsEndpointId :: Text
- networkOptionsGateway :: Text
- networkOptionsIpAddress :: Text
- networkOptionsIpPrefixLen :: Int
- networkOptionsIpV6Gateway :: Maybe Text
- networkOptionsGlobalIPv6Address :: Maybe Text
- networkOptionsGlobalIPv6PrefixLen :: Maybe Int
- networkOptionsMacAddress :: Text
- data Mount = Mount {}
- data PortBinding = PortBinding {}
- data HostPort = HostPort {}
- type RetryCount = Integer
- data RestartPolicy
- data Isolation
- newtype UTSMode = UTSMode Text
- data HostConfig = HostConfig {
- binds :: [Bind]
- containerIDFile :: Maybe FilePath
- logConfig :: LogDriverConfig
- networkMode :: NetworkMode
- portBindings :: [PortBinding]
- restartPolicy :: RestartPolicy
- volumeDriver :: Maybe Text
- volumesFrom :: [VolumeFrom]
- capAdd :: [Text]
- capDrop :: [Text]
- dns :: [Text]
- dnsOptions :: [Text]
- dnsSearch :: [Text]
- extraHosts :: [Text]
- ipcMode :: Maybe Text
- links :: [Link]
- oomScoreAdj :: Maybe Integer
- privileged :: Bool
- publishAllPorts :: Bool
- readonlyRootfs :: Bool
- securityOpt :: [Text]
- shmSize :: Maybe Integer
- resources :: ContainerResources
- defaultHostConfig :: HostConfig
- newtype NetworkingConfig = NetworkingConfig {
- endpointsConfig :: HashMap EndpointName EndpointConfig
- newtype EndpointConfig = EndpointConfig [Alias]
- data Ulimit = Ulimit {
- ulimitName :: Text
- ulimitSoft :: Integer
- ulimitHard :: Integer
- data ContainerResources = ContainerResources {
- cpuShares :: Maybe Integer
- blkioWeight :: Maybe Integer
- blkioWeightDevice :: Maybe [DeviceWeight]
- blkioDeviceReadBps :: Maybe [DeviceRate]
- blkioDeviceWriteBps :: Maybe [DeviceRate]
- blkioDeviceReadIOps :: Maybe [DeviceRate]
- blkioDeviceWriteIOps :: Maybe [DeviceRate]
- cpuPeriod :: Maybe Integer
- cpusetCpus :: Maybe Text
- cpusetMems :: Maybe Text
- devices :: [Device]
- kernelMemory :: Maybe MemoryConstraint
- memory :: Maybe MemoryConstraint
- memoryReservation :: Maybe MemoryConstraint
- memorySwap :: Maybe MemoryConstraint
- oomKillDisable :: Maybe Bool
- ulimits :: [Ulimit]
- defaultContainerResources :: ContainerResources
- type Port = Integer
- type Name = Text
- type Value = Text
- data EnvVar = EnvVar Name Value
- data ContainerConfig = ContainerConfig {
- hostname :: Maybe Text
- domainname :: Maybe Text
- user :: Maybe Text
- attachStdin :: Bool
- attachStdout :: Bool
- attachStderr :: Bool
- exposedPorts :: [ExposedPort]
- tty :: Bool
- openStdin :: Bool
- stdinOnce :: Bool
- env :: [EnvVar]
- cmd :: [Text]
- image :: Text
- volumes :: [Volume]
- workingDir :: Maybe FilePath
- entrypoint :: Entrypoint
- networkDisabled :: Maybe Bool
- macAddress :: Maybe Text
- labels :: [Label]
- stopSignal :: Signal
- defaultContainerConfig :: Text -> ContainerConfig
- data ExposedPort = ExposedPort Port PortType
- data DeviceWeight = DeviceWeight {}
- data DeviceRate = DeviceRate {}
- addPortBinding :: PortBinding -> CreateOpts -> CreateOpts
- addExposedPort :: ExposedPort -> CreateOpts -> CreateOpts
- addBind :: Bind -> CreateOpts -> CreateOpts
- setCmd :: Text -> CreateOpts -> CreateOpts
- addLink :: Link -> CreateOpts -> CreateOpts
- addVolume :: Volume -> CreateOpts -> CreateOpts
- addVolumeFrom :: VolumeFrom -> CreateOpts -> CreateOpts
- data MemoryConstraint = MemoryConstraint Integer MemoryConstraintSize
- data MemoryConstraintSize
Documentation
List of Docker Engine API endpoints
Constructors
| VersionEndpoint | |
| ListContainersEndpoint ListOpts | |
| ListImagesEndpoint ListOpts | |
| CreateContainerEndpoint CreateOpts (Maybe ContainerName) | |
| StartContainerEndpoint StartOpts ContainerID | |
| StopContainerEndpoint Timeout ContainerID | |
| WaitContainerEndpoint ContainerID | |
| KillContainerEndpoint Signal ContainerID | |
| RestartContainerEndpoint Timeout ContainerID | |
| PauseContainerEndpoint ContainerID | |
| UnpauseContainerEndpoint ContainerID | |
| ContainerLogsEndpoint LogOpts Bool ContainerID | Second argument (Bool) is whether to follow which is currently hardcoded to False.
See note in |
| DeleteContainerEndpoint ContainerDeleteOpts ContainerID | |
| InspectContainerEndpoint ContainerID | |
| BuildImageEndpoint BuildOpts FilePath | |
| CreateImageEndpoint Text Tag (Maybe Text) | Either pull an image from docker hub or imports an image from a tarball (or URL) |
| DeleteImageEndpoint ImageDeleteOpts ImageID | |
| CreateNetworkEndpoint CreateNetworkOpts | |
| RemoveNetworkEndpoint NetworkID |
Instances
type ApiVersion = Text Source #
We should newtype this
data ContainerID Source #
ID of a contianer
Instances
| Eq ContainerID Source # | |
Defined in Docker.Client.Types | |
| Show ContainerID Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> ContainerID -> ShowS # show :: ContainerID -> String # showList :: [ContainerID] -> ShowS # | |
| ToJSON ContainerID Source # | |
Defined in Docker.Client.Types Methods toJSON :: ContainerID -> Value # toEncoding :: ContainerID -> Encoding # toJSONList :: [ContainerID] -> Value # toEncodingList :: [ContainerID] -> Encoding # | |
| FromJSON ContainerID Source # | |
Defined in Docker.Client.Types | |
fromContainerID :: ContainerID -> Text Source #
Used for extracting the id of the container from the newtype
toContainerID :: Text -> Maybe ContainerID Source #
Used for parsing a Text value into a ContainerID. We apply some basic validation here.
fromImageID :: ImageID -> Text Source #
Used for extracting the id of the image from the newtype.
toImageID :: Text -> Maybe ImageID Source #
Helper function used for parsing a Text value into an ImageID. For now just basic validation is used.
fromNetworkID :: NetworkID -> Text Source #
Used for extracting the id of the container from the newtype
Timeout used for stopping a container. DefaultTimeout is 10 seconds.
Constructors
| Timeout Integer | |
| DefaultTimeout |
data StatusCode Source #
Constructors
| StatusCode Int |
Instances
| ToJSON StatusCode Source # | |
Defined in Docker.Client.Types Methods toJSON :: StatusCode -> Value # toEncoding :: StatusCode -> Encoding # toJSONList :: [StatusCode] -> Value # toEncodingList :: [StatusCode] -> Encoding # | |
| FromJSON StatusCode Source # | |
Defined in Docker.Client.Types | |
Signal used for sending to the process running in the container. The default signal is SIGTERM.
data ContainerDetails Source #
Constructors
| ContainerDetails | |
Fields
| |
Instances
data DockerClientOpts Source #
Client options used to configure the remote engine we're talking to
Constructors
| DockerClientOpts | |
Fields
| |
Instances
| Eq DockerClientOpts Source # | |
Defined in Docker.Client.Types Methods (==) :: DockerClientOpts -> DockerClientOpts -> Bool # (/=) :: DockerClientOpts -> DockerClientOpts -> Bool # | |
| Show DockerClientOpts Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> DockerClientOpts -> ShowS # show :: DockerClientOpts -> String # showList :: [DockerClientOpts] -> ShowS # | |
| Monad m => MonadReader (DockerClientOpts, HttpHandler m) (DockerT m) Source # | |
Defined in Docker.Client.Http Methods ask :: DockerT m (DockerClientOpts, HttpHandler m) # local :: ((DockerClientOpts, HttpHandler m) -> (DockerClientOpts, HttpHandler m)) -> DockerT m a -> DockerT m a # reader :: ((DockerClientOpts, HttpHandler m) -> a) -> DockerT m a # | |
defaultClientOpts :: DockerClientOpts Source #
Default DockerClientOpts used for talking to the docker engine.
List options used for filtering the list of container or images.
Instances
defaultListOpts :: ListOpts Source #
Default ListOpts. Doesn't list stopped containers.
data DockerVersion Source #
Data type used for represneting the version of the docker engine remote API.
Constructors
| DockerVersion | |
Instances
data ContainerPortInfo Source #
Data type used for representing the information of various ports that a contianer may expose.
Constructors
| ContainerPortInfo | |
Fields | |
Instances
| Eq ContainerPortInfo Source # | |
Defined in Docker.Client.Types Methods (==) :: ContainerPortInfo -> ContainerPortInfo -> Bool # (/=) :: ContainerPortInfo -> ContainerPortInfo -> Bool # | |
| Show ContainerPortInfo Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> ContainerPortInfo -> ShowS # show :: ContainerPortInfo -> String # showList :: [ContainerPortInfo] -> ShowS # | |
| FromJSON ContainerPortInfo Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser ContainerPortInfo # parseJSONList :: Value -> Parser [ContainerPortInfo] # | |
Data type used for parsing a list of containers.
Constructors
| Container | |
Fields
| |
data ContainerState Source #
Data type used for parsing the container state from a list of containers.
Constructors
| ContainerState | |
Instances
Represents the state of the container life cycle.
Instances
| Eq State Source # | |
| Show State Source # | |
| Generic State Source # | |
| FromJSON State Source # | |
| type Rep State Source # | |
Defined in Docker.Client.Types type Rep State = D1 ('MetaData "State" "Docker.Client.Types" "docker-0.6.0.6-LphaXVRswQk881VhAnye5i" 'False) ((C1 ('MetaCons "Created" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Restarting" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Running" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Paused" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Exited" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Dead" 'PrefixI 'False) (U1 :: Type -> Type)))) | |
Alias for representing a RepoDigest. We could newtype this and add some validation.
Container and Image Labels.
Data type used for parsing information from a list of images.
Constructors
| DockerImage | |
Fields
| |
Instances
data Entrypoint Source #
Constructors
| Entrypoint [Text] |
Instances
| Eq Entrypoint Source # | |
Defined in Docker.Client.Types | |
| Show Entrypoint Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> Entrypoint -> ShowS # show :: Entrypoint -> String # showList :: [Entrypoint] -> ShowS # | |
| Generic Entrypoint Source # | |
Defined in Docker.Client.Types Associated Types type Rep Entrypoint :: Type -> Type # | |
| ToJSON Entrypoint Source # | |
Defined in Docker.Client.Types Methods toJSON :: Entrypoint -> Value # toEncoding :: Entrypoint -> Encoding # toJSONList :: [Entrypoint] -> Value # toEncodingList :: [Entrypoint] -> Encoding # | |
| FromJSON Entrypoint Source # | |
Defined in Docker.Client.Types | |
| type Rep Entrypoint Source # | |
Defined in Docker.Client.Types type Rep Entrypoint = D1 ('MetaData "Entrypoint" "Docker.Client.Types" "docker-0.6.0.6-LphaXVRswQk881VhAnye5i" 'False) (C1 ('MetaCons "Entrypoint" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text]))) | |
dropImagePrefix :: [a] -> [a] Source #
Helper function used for dropping the "image" prefix when serializing the Image data type to and from json.
data CreateOpts Source #
Options used for creating a Container.
Constructors
| CreateOpts | |
Instances
| Eq CreateOpts Source # | |
Defined in Docker.Client.Types | |
| Show CreateOpts Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> CreateOpts -> ShowS # show :: CreateOpts -> String # showList :: [CreateOpts] -> ShowS # | |
| ToJSON CreateOpts Source # | |
Defined in Docker.Client.Types Methods toJSON :: CreateOpts -> Value # toEncoding :: CreateOpts -> Encoding # toJSONList :: [CreateOpts] -> Value # toEncodingList :: [CreateOpts] -> Encoding # | |
Options for when building images from a Dockerfile
Constructors
| BuildOpts | |
Fields
| |
defaultBuildOpts :: Text -> BuildOpts Source #
defaultCreateOpts :: Text -> CreateOpts Source #
Default create options when creating a container. You only need to specify an image name and the rest is all sensible defaults.
data DetachKeys Source #
Override the key sequence for detaching a container. Format is a single character [a-Z] or ctrl-value where value is one of: a-z, @, ^, [, , or _.
Constructors
| WithCtrl Char | |
| WithoutCtrl Char | |
| DefaultDetachKey |
Instances
| Eq DetachKeys Source # | |
Defined in Docker.Client.Types | |
| Show DetachKeys Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> DetachKeys -> ShowS # show :: DetachKeys -> String # showList :: [DetachKeys] -> ShowS # | |
Options for starting a container.
Constructors
| StartOpts | |
Fields | |
defaultStartOpts :: StartOpts Source #
Default options for staring a container.
data ContainerDeleteOpts Source #
Options for deleting a container.
Constructors
| ContainerDeleteOpts | |
Fields
| |
Instances
| Eq ContainerDeleteOpts Source # | |
Defined in Docker.Client.Types Methods (==) :: ContainerDeleteOpts -> ContainerDeleteOpts -> Bool # (/=) :: ContainerDeleteOpts -> ContainerDeleteOpts -> Bool # | |
| Show ContainerDeleteOpts Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> ContainerDeleteOpts -> ShowS # show :: ContainerDeleteOpts -> String # showList :: [ContainerDeleteOpts] -> ShowS # | |
defaultContainerDeleteOpts :: ContainerDeleteOpts Source #
Default options for deleting a container. Most of the time we DON'T want to delete the container's volumes or force delete it if it's running.
data ImageDeleteOpts Source #
Image delete opts
Constructors
| ImageDeleteOpts |
Instances
| Eq ImageDeleteOpts Source # | |
Defined in Docker.Client.Types Methods (==) :: ImageDeleteOpts -> ImageDeleteOpts -> Bool # (/=) :: ImageDeleteOpts -> ImageDeleteOpts -> Bool # | |
| Show ImageDeleteOpts Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> ImageDeleteOpts -> ShowS # show :: ImageDeleteOpts -> String # showList :: [ImageDeleteOpts] -> ShowS # | |
defaultImageDeleteOpts :: ImageDeleteOpts Source #
Sane image deletion defaults
data TailLogOpt Source #
Used for requesting N number of lines when tailing a containers log output.
Instances
| Eq TailLogOpt Source # | |
Defined in Docker.Client.Types | |
| Show TailLogOpt Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> TailLogOpt -> ShowS # show :: TailLogOpt -> String # showList :: [TailLogOpt] -> ShowS # | |
Log options used when requesting the log output from a container.
Constructors
| LogOpts | |
defaultLogOpts :: LogOpts Source #
Sensible default for log options.
data CreateNetworkOpts Source #
Options for creating a network
Constructors
| CreateNetworkOpts | |
Fields
| |
Instances
| Eq CreateNetworkOpts Source # | |
Defined in Docker.Client.Types Methods (==) :: CreateNetworkOpts -> CreateNetworkOpts -> Bool # (/=) :: CreateNetworkOpts -> CreateNetworkOpts -> Bool # | |
| Show CreateNetworkOpts Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> CreateNetworkOpts -> ShowS # show :: CreateNetworkOpts -> String # showList :: [CreateNetworkOpts] -> ShowS # | |
| ToJSON CreateNetworkOpts Source # | |
Defined in Docker.Client.Types Methods toJSON :: CreateNetworkOpts -> Value # toEncoding :: CreateNetworkOpts -> Encoding # toJSONList :: [CreateNetworkOpts] -> Value # toEncodingList :: [CreateNetworkOpts] -> Encoding # | |
defaultCreateNetworkOpts :: Text -> CreateNetworkOpts Source #
Sensible defalut for create network options
data VolumePermission Source #
Set permissions on volumes that you mount in the container.
Instances
Constructors
| Bind | |
Fields | |
Used for marking a directory in the container as "exposed" hence
taking it outside of the COW filesystem and making it mountable
in other containers using VolumesFrom. The volume usually get's
created somewhere in varlibdockervolumes (depending on the volume
driver used).
The CLI example is:
docker run --name app -v /opt/data -it myapp:latest docker run --name app2 --volumes-from app /bin/bash -c "ls -l /opt/data"
Constructors
| Device | |
Fields | |
Instances
| Eq Device Source # | |
| Show Device Source # | |
| Generic Device Source # | |
| ToJSON Device Source # | |
Defined in Docker.Client.Types | |
| FromJSON Device Source # | |
| type Rep Device Source # | |
Defined in Docker.Client.Types type Rep Device = D1 ('MetaData "Device" "Docker.Client.Types" "docker-0.6.0.6-LphaXVRswQk881VhAnye5i" 'False) (C1 ('MetaCons "Device" 'PrefixI 'True) (S1 ('MetaSel ('Just "pathOnHost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "pathInContainer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "cgroupPermissions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))) | |
type ContainerName = Text Source #
data VolumeFrom Source #
Constructors
| VolumeFrom ContainerName (Maybe VolumePermission) |
Instances
| Eq VolumeFrom Source # | |
Defined in Docker.Client.Types | |
| Show VolumeFrom Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> VolumeFrom -> ShowS # show :: VolumeFrom -> String # showList :: [VolumeFrom] -> ShowS # | |
| ToJSON VolumeFrom Source # | |
Defined in Docker.Client.Types Methods toJSON :: VolumeFrom -> Value # toEncoding :: VolumeFrom -> Encoding # toJSONList :: [VolumeFrom] -> Value # toEncodingList :: [VolumeFrom] -> Encoding # | |
| FromJSON VolumeFrom Source # | |
Defined in Docker.Client.Types | |
data LogDriverType Source #
Instances
| Eq LogDriverType Source # | |
Defined in Docker.Client.Types Methods (==) :: LogDriverType -> LogDriverType -> Bool # (/=) :: LogDriverType -> LogDriverType -> Bool # | |
| Show LogDriverType Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> LogDriverType -> ShowS # show :: LogDriverType -> String # showList :: [LogDriverType] -> ShowS # | |
| ToJSON LogDriverType Source # | |
Defined in Docker.Client.Types Methods toJSON :: LogDriverType -> Value # toEncoding :: LogDriverType -> Encoding # toJSONList :: [LogDriverType] -> Value # toEncodingList :: [LogDriverType] -> Encoding # | |
| FromJSON LogDriverType Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser LogDriverType # parseJSONList :: Value -> Parser [LogDriverType] # | |
data LogDriverOption Source #
Constructors
| LogDriverOption Name Value |
Instances
| Eq LogDriverOption Source # | |
Defined in Docker.Client.Types Methods (==) :: LogDriverOption -> LogDriverOption -> Bool # (/=) :: LogDriverOption -> LogDriverOption -> Bool # | |
| Show LogDriverOption Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> LogDriverOption -> ShowS # show :: LogDriverOption -> String # showList :: [LogDriverOption] -> ShowS # | |
| ToJSON [LogDriverOption] Source # | |
Defined in Docker.Client.Types Methods toJSON :: [LogDriverOption] -> Value # toEncoding :: [LogDriverOption] -> Encoding # toJSONList :: [[LogDriverOption]] -> Value # toEncodingList :: [[LogDriverOption]] -> Encoding # | |
| FromJSON [LogDriverOption] Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser [LogDriverOption] # parseJSONList :: Value -> Parser [[LogDriverOption]] # | |
data LogDriverConfig Source #
Constructors
| LogDriverConfig LogDriverType [LogDriverOption] |
Instances
| Eq LogDriverConfig Source # | |
Defined in Docker.Client.Types Methods (==) :: LogDriverConfig -> LogDriverConfig -> Bool # (/=) :: LogDriverConfig -> LogDriverConfig -> Bool # | |
| Show LogDriverConfig Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> LogDriverConfig -> ShowS # show :: LogDriverConfig -> String # showList :: [LogDriverConfig] -> ShowS # | |
| ToJSON LogDriverConfig Source # | |
Defined in Docker.Client.Types Methods toJSON :: LogDriverConfig -> Value # toEncoding :: LogDriverConfig -> Encoding # toJSONList :: [LogDriverConfig] -> Value # toEncodingList :: [LogDriverConfig] -> Encoding # | |
| FromJSON LogDriverConfig Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser LogDriverConfig # parseJSONList :: Value -> Parser [LogDriverConfig] # | |
data NetworkMode Source #
Constructors
| NetworkBridge | |
| NetworkHost | |
| NetworkDisabled | |
| NetworkNamed Text |
Instances
| Eq NetworkMode Source # | |
Defined in Docker.Client.Types | |
| Ord NetworkMode Source # | |
Defined in Docker.Client.Types Methods compare :: NetworkMode -> NetworkMode -> Ordering # (<) :: NetworkMode -> NetworkMode -> Bool # (<=) :: NetworkMode -> NetworkMode -> Bool # (>) :: NetworkMode -> NetworkMode -> Bool # (>=) :: NetworkMode -> NetworkMode -> Bool # max :: NetworkMode -> NetworkMode -> NetworkMode # min :: NetworkMode -> NetworkMode -> NetworkMode # | |
| Show NetworkMode Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> NetworkMode -> ShowS # show :: NetworkMode -> String # showList :: [NetworkMode] -> ShowS # | |
| ToJSON NetworkMode Source # | |
Defined in Docker.Client.Types Methods toJSON :: NetworkMode -> Value # toEncoding :: NetworkMode -> Encoding # toJSONList :: [NetworkMode] -> Value # toEncodingList :: [NetworkMode] -> Encoding # | |
| FromJSON NetworkMode Source # | |
Defined in Docker.Client.Types | |
Constructors
| Network NetworkMode NetworkOptions |
data NetworkSettings Source #
Data type reprsenting the various network settings a container can have.
Constructors
Instances
| Eq NetworkSettings Source # | |
Defined in Docker.Client.Types Methods (==) :: NetworkSettings -> NetworkSettings -> Bool # (/=) :: NetworkSettings -> NetworkSettings -> Bool # | |
| Show NetworkSettings Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> NetworkSettings -> ShowS # show :: NetworkSettings -> String # showList :: [NetworkSettings] -> ShowS # | |
| FromJSON NetworkSettings Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser NetworkSettings # parseJSONList :: Value -> Parser [NetworkSettings] # | |
data NetworkOptions Source #
Data type used for parsing the network information of each container when listing them.
Constructors
Instances
| Eq NetworkOptions Source # | |
Defined in Docker.Client.Types Methods (==) :: NetworkOptions -> NetworkOptions -> Bool # (/=) :: NetworkOptions -> NetworkOptions -> Bool # | |
| Show NetworkOptions Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> NetworkOptions -> ShowS # show :: NetworkOptions -> String # showList :: [NetworkOptions] -> ShowS # | |
| FromJSON NetworkOptions Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser NetworkOptions # parseJSONList :: Value -> Parser [NetworkOptions] # | |
Data type used for parsing the mount information from a container list.
Constructors
| Mount | |
Fields
| |
Instances
| Eq Mount Source # | |
| Show Mount Source # | |
| Generic Mount Source # | |
| FromJSON Mount Source # | |
| type Rep Mount Source # | |
Defined in Docker.Client.Types type Rep Mount = D1 ('MetaData "Mount" "Docker.Client.Types" "docker-0.6.0.6-LphaXVRswQk881VhAnye5i" 'False) (C1 ('MetaCons "Mount" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mountName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "mountSource") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: S1 ('MetaSel ('Just "mountDestination") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath))) :*: (S1 ('MetaSel ('Just "mountDriver") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "mountRW") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "mountPropogation") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))))) | |
data PortBinding Source #
This datastructure models mapping a Port from the container onto the host system s that the service running in the container can be accessed from the outside world. We either map a port onto all interfaces (default) or onto a specific interface like `127.0.0.1`. NOTE: We should disallow duplicate port bindings as the ToJSON instance will only send the last one. { port/protocol: [{ HostPort: "port" }] }
Constructors
| PortBinding | |
Instances
| Eq PortBinding Source # | |
Defined in Docker.Client.Types | |
| Show PortBinding Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> PortBinding -> ShowS # show :: PortBinding -> String # showList :: [PortBinding] -> ShowS # | |
| ToJSON [PortBinding] Source # | |
Defined in Docker.Client.Types Methods toJSON :: [PortBinding] -> Value # toEncoding :: [PortBinding] -> Encoding # toJSONList :: [[PortBinding]] -> Value # toEncodingList :: [[PortBinding]] -> Encoding # | |
| FromJSON [PortBinding] Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser [PortBinding] # parseJSONList :: Value -> Parser [[PortBinding]] # | |
type RetryCount = Integer Source #
data RestartPolicy Source #
Instances
| Eq RestartPolicy Source # | |
Defined in Docker.Client.Types Methods (==) :: RestartPolicy -> RestartPolicy -> Bool # (/=) :: RestartPolicy -> RestartPolicy -> Bool # | |
| Show RestartPolicy Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> RestartPolicy -> ShowS # show :: RestartPolicy -> String # showList :: [RestartPolicy] -> ShowS # | |
| ToJSON RestartPolicy Source # | |
Defined in Docker.Client.Types Methods toJSON :: RestartPolicy -> Value # toEncoding :: RestartPolicy -> Encoding # toJSONList :: [RestartPolicy] -> Value # toEncodingList :: [RestartPolicy] -> Encoding # | |
| FromJSON RestartPolicy Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser RestartPolicy # parseJSONList :: Value -> Parser [RestartPolicy] # | |
data HostConfig Source #
Constructors
| HostConfig | |
Fields
| |
Instances
defaultHostConfig :: HostConfig Source #
Default host confiratuon used for creating a container.
newtype NetworkingConfig Source #
Data type for the NetworkingConfig section of the container settings
Constructors
| NetworkingConfig | |
Fields
| |
Instances
| Eq NetworkingConfig Source # | |
Defined in Docker.Client.Types Methods (==) :: NetworkingConfig -> NetworkingConfig -> Bool # (/=) :: NetworkingConfig -> NetworkingConfig -> Bool # | |
| Show NetworkingConfig Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> NetworkingConfig -> ShowS # show :: NetworkingConfig -> String # showList :: [NetworkingConfig] -> ShowS # | |
| ToJSON NetworkingConfig Source # | |
Defined in Docker.Client.Types Methods toJSON :: NetworkingConfig -> Value # toEncoding :: NetworkingConfig -> Encoding # toJSONList :: [NetworkingConfig] -> Value # toEncodingList :: [NetworkingConfig] -> Encoding # | |
newtype EndpointConfig Source #
EndpointsConfig is container configuration for a specific network
Constructors
| EndpointConfig [Alias] |
Instances
| Eq EndpointConfig Source # | |
Defined in Docker.Client.Types Methods (==) :: EndpointConfig -> EndpointConfig -> Bool # (/=) :: EndpointConfig -> EndpointConfig -> Bool # | |
| Show EndpointConfig Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> EndpointConfig -> ShowS # show :: EndpointConfig -> String # showList :: [EndpointConfig] -> ShowS # | |
| ToJSON EndpointConfig Source # | |
Defined in Docker.Client.Types Methods toJSON :: EndpointConfig -> Value # toEncoding :: EndpointConfig -> Encoding # toJSONList :: [EndpointConfig] -> Value # toEncodingList :: [EndpointConfig] -> Encoding # | |
Constructors
| Ulimit | |
Fields
| |
Instances
| Eq Ulimit Source # | |
| Show Ulimit Source # | |
| Generic Ulimit Source # | |
| ToJSON Ulimit Source # | |
Defined in Docker.Client.Types | |
| FromJSON Ulimit Source # | |
| type Rep Ulimit Source # | |
Defined in Docker.Client.Types type Rep Ulimit = D1 ('MetaData "Ulimit" "Docker.Client.Types" "docker-0.6.0.6-LphaXVRswQk881VhAnye5i" 'False) (C1 ('MetaCons "Ulimit" 'PrefixI 'True) (S1 ('MetaSel ('Just "ulimitName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "ulimitSoft") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Just "ulimitHard") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))) | |
data ContainerResources Source #
Constructors
| ContainerResources | |
Fields
| |
Instances
data ContainerConfig Source #
Constructors
| ContainerConfig | |
Fields
| |
Instances
defaultContainerConfig :: Text -> ContainerConfig Source #
Container configuration used for creating a container with sensible defaults.
data ExposedPort Source #
ExposedPort represents a port (and it's type)
that a container should expose to other containers or the host system.
NOTE: This does not automatically expose the port onto the host
system but rather it just tags it. It's best to be used with
the PublishAllPorts flag. It is also useful for
the daemon to know which Environment variables to
inject into a container linking to our container.
Example linking a Postgres container named db would inject the following
environment variables automatically if we set the corresponding
ExposedPort:
DB_PORT_5432_TCP_PORT="5432" DB_PORT_5432_TCP_PROTO="tcp" DB_PORT_5432_TCP="tcp://172.17.0.1:5432"
Constructors
| ExposedPort Port PortType |
Instances
| Eq ExposedPort Source # | |
Defined in Docker.Client.Types | |
| Show ExposedPort Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> ExposedPort -> ShowS # show :: ExposedPort -> String # showList :: [ExposedPort] -> ShowS # | |
| ToJSON [ExposedPort] Source # | |
Defined in Docker.Client.Types Methods toJSON :: [ExposedPort] -> Value # toEncoding :: [ExposedPort] -> Encoding # toJSONList :: [[ExposedPort]] -> Value # toEncodingList :: [[ExposedPort]] -> Encoding # | |
| FromJSON [ExposedPort] Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser [ExposedPort] # parseJSONList :: Value -> Parser [[ExposedPort]] # | |
data DeviceWeight Source #
Constructors
| DeviceWeight | |
Fields | |
Instances
| Eq DeviceWeight Source # | |
Defined in Docker.Client.Types | |
| Show DeviceWeight Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> DeviceWeight -> ShowS # show :: DeviceWeight -> String # showList :: [DeviceWeight] -> ShowS # | |
| ToJSON DeviceWeight Source # | |
Defined in Docker.Client.Types Methods toJSON :: DeviceWeight -> Value # toEncoding :: DeviceWeight -> Encoding # toJSONList :: [DeviceWeight] -> Value # toEncodingList :: [DeviceWeight] -> Encoding # | |
| FromJSON DeviceWeight Source # | |
Defined in Docker.Client.Types | |
data DeviceRate Source #
Constructors
| DeviceRate | |
Fields | |
Instances
| Eq DeviceRate Source # | |
Defined in Docker.Client.Types | |
| Show DeviceRate Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> DeviceRate -> ShowS # show :: DeviceRate -> String # showList :: [DeviceRate] -> ShowS # | |
| ToJSON DeviceRate Source # | |
Defined in Docker.Client.Types Methods toJSON :: DeviceRate -> Value # toEncoding :: DeviceRate -> Encoding # toJSONList :: [DeviceRate] -> Value # toEncodingList :: [DeviceRate] -> Encoding # | |
| FromJSON DeviceRate Source # | |
Defined in Docker.Client.Types | |
addPortBinding :: PortBinding -> CreateOpts -> CreateOpts Source #
A convenience function that adds PortBindings to and exiting
CreateOpts record. Useful with defaultCreateOpts
Example:
>>>let pb = PortBinding 80 TCP [HostPort "0.0.0.0" 8000]>>>addPortBinding pb $ defaultCreateOpts "nginx:latest"
addExposedPort :: ExposedPort -> CreateOpts -> CreateOpts Source #
Helper function for adding a ExposedPort to and existing CreateOpts record.
addBind :: Bind -> CreateOpts -> CreateOpts Source #
A helper function to more easily add a bind mount to existing CreateOpts records.
setCmd :: Text -> CreateOpts -> CreateOpts Source #
Helper function for adding a Command to and existing CreateOpts record.
addLink :: Link -> CreateOpts -> CreateOpts Source #
Helper function for adding a Link to and existing CreateOpts record.
addVolume :: Volume -> CreateOpts -> CreateOpts Source #
Helper function for adding a Volume to and existing CreateOpts record.
addVolumeFrom :: VolumeFrom -> CreateOpts -> CreateOpts Source #
Helper function for adding a VolumeFrom to and existing CreateOpts record.
data MemoryConstraint Source #
Constructors
| MemoryConstraint Integer MemoryConstraintSize |
Instances
| Eq MemoryConstraint Source # | |
Defined in Docker.Client.Types Methods (==) :: MemoryConstraint -> MemoryConstraint -> Bool # (/=) :: MemoryConstraint -> MemoryConstraint -> Bool # | |
| Show MemoryConstraint Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> MemoryConstraint -> ShowS # show :: MemoryConstraint -> String # showList :: [MemoryConstraint] -> ShowS # | |
| ToJSON MemoryConstraint Source # | |
Defined in Docker.Client.Types Methods toJSON :: MemoryConstraint -> Value # toEncoding :: MemoryConstraint -> Encoding # toJSONList :: [MemoryConstraint] -> Value # toEncodingList :: [MemoryConstraint] -> Encoding # | |
| FromJSON MemoryConstraint Source # | |
Defined in Docker.Client.Types Methods parseJSON :: Value -> Parser MemoryConstraint # parseJSONList :: Value -> Parser [MemoryConstraint] # | |
data MemoryConstraintSize Source #
Instances
| Eq MemoryConstraintSize Source # | |
Defined in Docker.Client.Types Methods (==) :: MemoryConstraintSize -> MemoryConstraintSize -> Bool # (/=) :: MemoryConstraintSize -> MemoryConstraintSize -> Bool # | |
| Show MemoryConstraintSize Source # | |
Defined in Docker.Client.Types Methods showsPrec :: Int -> MemoryConstraintSize -> ShowS # show :: MemoryConstraintSize -> String # showList :: [MemoryConstraintSize] -> ShowS # | |