docker-0.4.0.0: An API client for docker written in Haskell

Safe HaskellNone
LanguageHaskell2010

Docker.Client.Types

Synopsis

Documentation

type URL = Text Source #

We should newtype this

type ApiVersion = Text Source #

We should newtype this

data ContainerID Source #

ID of a contianer

Instances

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.

data ImageID Source #

Instances

Eq ImageID Source # 

Methods

(==) :: ImageID -> ImageID -> Bool #

(/=) :: ImageID -> ImageID -> Bool #

Show ImageID Source # 
ToJSON ImageID Source # 

Methods

toJSON :: ImageID -> Value

toEncoding :: ImageID -> Encoding

toJSONList :: [ImageID] -> Value

toEncodingList :: [ImageID] -> Encoding

FromJSON ImageID Source # 

Methods

parseJSON :: Value -> Parser ImageID

parseJSONList :: Value -> Parser [ImageID]

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.

data Timeout Source #

Timeout used for stopping a container. DefaultTimeout is 10 seconds.

data StatusCode Source #

Constructors

StatusCode Int 

Instances

ToJSON StatusCode Source # 

Methods

toJSON :: StatusCode -> Value

toEncoding :: StatusCode -> Encoding

toJSONList :: [StatusCode] -> Value

toEncodingList :: [StatusCode] -> Encoding

FromJSON StatusCode Source # 

Methods

parseJSON :: Value -> Parser StatusCode

parseJSONList :: Value -> Parser [StatusCode]

data Signal Source #

Signal used for sending to the process running in the container. The default signal is SIGTERM.

Instances

Eq Signal Source # 

Methods

(==) :: Signal -> Signal -> Bool #

(/=) :: Signal -> Signal -> Bool #

Show Signal Source # 
ToJSON Signal Source # 

Methods

toJSON :: Signal -> Value

toEncoding :: Signal -> Encoding

toJSONList :: [Signal] -> Value

toEncodingList :: [Signal] -> Encoding

FromJSON Signal Source # 

Methods

parseJSON :: Value -> Parser Signal

parseJSONList :: Value -> Parser [Signal]

data ContainerDetails Source #

Instances

Eq ContainerDetails Source # 
Show ContainerDetails Source # 
Generic ContainerDetails Source # 
FromJSON ContainerDetails Source # 

Methods

parseJSON :: Value -> Parser ContainerDetails

parseJSONList :: Value -> Parser [ContainerDetails]

type Rep ContainerDetails Source # 
type Rep ContainerDetails = D1 (MetaData "ContainerDetails" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) (C1 (MetaCons "ContainerDetails" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "appArmorProfile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "args") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "containerDetailsConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContainerConfig)) ((:*:) (S1 (MetaSel (Just Symbol "created") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 UTCTime)) (S1 (MetaSel (Just Symbol "driver") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "containerDetailsHostConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HostConfig)) (S1 (MetaSel (Just Symbol "hostnamePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))) ((:*:) (S1 (MetaSel (Just Symbol "hostsPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) ((:*:) (S1 (MetaSel (Just Symbol "logPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "containerDetailsId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContainerID)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "containerDetailsImage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageID)) (S1 (MetaSel (Just Symbol "mountLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text))) ((:*:) (S1 (MetaSel (Just Symbol "name") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "networkSettings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NetworkSettings)) (S1 (MetaSel (Just Symbol "path") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "processLabel") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "resolveConfPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))) ((:*:) (S1 (MetaSel (Just Symbol "restartCount") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Just Symbol "state") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContainerState)) (S1 (MetaSel (Just Symbol "mounts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Mount]))))))))

defaultClientOpts :: DockerClientOpts Source #

Default DockerClientOpts used for talking to the docker engine.

data ListOpts Source #

List options used for filtering the list of container or images.

Constructors

ListOpts 

Fields

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 

Fields

Instances

Eq DockerVersion Source # 
Show DockerVersion Source # 
Generic DockerVersion Source # 

Associated Types

type Rep DockerVersion :: * -> * #

ToJSON DockerVersion Source # 

Methods

toJSON :: DockerVersion -> Value

toEncoding :: DockerVersion -> Encoding

toJSONList :: [DockerVersion] -> Value

toEncodingList :: [DockerVersion] -> Encoding

FromJSON DockerVersion Source # 

Methods

parseJSON :: Value -> Parser DockerVersion

parseJSONList :: Value -> Parser [DockerVersion]

type Rep DockerVersion Source # 

data ContainerPortInfo Source #

Data type used for representing the information of various ports that a contianer may expose.

data Container Source #

Data type used for parsing a list of containers.

Instances

Eq Container Source # 
Show Container Source # 
FromJSON Container Source # 

Methods

parseJSON :: Value -> Parser Container

parseJSONList :: Value -> Parser [Container]

data ContainerState Source #

Data type used for parsing the container state from a list of containers.

Instances

Eq ContainerState Source # 
Show ContainerState Source # 
Generic ContainerState Source # 

Associated Types

type Rep ContainerState :: * -> * #

FromJSON ContainerState Source # 

Methods

parseJSON :: Value -> Parser ContainerState

parseJSONList :: Value -> Parser [ContainerState]

type Rep ContainerState Source # 

data Status Source #

Represents the status of the container life cycle.

Instances

Eq Status Source # 

Methods

(==) :: Status -> Status -> Bool #

(/=) :: Status -> Status -> Bool #

Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

FromJSON Status Source # 

Methods

parseJSON :: Value -> Parser Status

parseJSONList :: Value -> Parser [Status]

type Rep Status Source # 
type Rep Status = D1 (MetaData "Status" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) ((:+:) ((:+:) (C1 (MetaCons "Created" PrefixI False) U1) ((:+:) (C1 (MetaCons "Restarting" PrefixI False) U1) (C1 (MetaCons "Running" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Paused" PrefixI False) U1) ((:+:) (C1 (MetaCons "Exited" PrefixI False) U1) (C1 (MetaCons "Dead" PrefixI False) U1))))

type Digest = Text Source #

Alias for representing a RepoDigest. We could newtype this and add some validation.

data Label Source #

Container and Image Labels.

Constructors

Label Name Value 

Instances

Eq Label Source # 

Methods

(==) :: Label -> Label -> Bool #

(/=) :: Label -> Label -> Bool #

Show Label Source # 

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

ToJSON [Label] Source # 

Methods

toJSON :: [Label] -> Value

toEncoding :: [Label] -> Encoding

toJSONList :: [[Label]] -> Value

toEncodingList :: [[Label]] -> Encoding

FromJSON [Label] Source # 

Methods

parseJSON :: Value -> Parser [Label]

parseJSONList :: Value -> Parser [[Label]]

type Tag = Text Source #

Alias for Tags.

data Image Source #

Data type used for parsing information from a list of images.

Instances

Eq Image Source # 

Methods

(==) :: Image -> Image -> Bool #

(/=) :: Image -> Image -> Bool #

Show Image Source # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

FromJSON Image Source # 

Methods

parseJSON :: Value -> Parser Image

parseJSONList :: Value -> Parser [Image]

type Rep Image Source # 

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.

data BuildOpts Source #

Options for when building images from a Dockerfile

Constructors

BuildOpts 

Fields

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 _.

data StartOpts Source #

Options for starting a container.

Constructors

StartOpts 

defaultStartOpts :: StartOpts Source #

Default options for staring a container.

data DeleteOpts Source #

Options for deleting a container.

Constructors

DeleteOpts 

Fields

  • deleteVolumes :: Bool

    Automatically cleanup volumes that the container created as well.

  • force :: Bool

    If the container is still running force deletion anyway.

defaultDeleteOpts :: DeleteOpts 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.

type Timestamp = Integer Source #

Timestamp alias.

data TailLogOpt Source #

Used for requesting N number of lines when tailing a containers log output.

Constructors

Tail Integer 
All 

data LogOpts Source #

Log options used when requesting the log output from a container.

Constructors

LogOpts 

defaultLogOpts :: LogOpts Source #

Sensible default for log options.

data VolumePermission Source #

Set permissions on volumes that you mount in the container.

Constructors

ReadWrite 
ReadOnly 

data Bind Source #

Constructors

Bind 

Instances

Eq Bind Source # 

Methods

(==) :: Bind -> Bind -> Bool #

(/=) :: Bind -> Bind -> Bool #

Show Bind Source # 

Methods

showsPrec :: Int -> Bind -> ShowS #

show :: Bind -> String #

showList :: [Bind] -> ShowS #

ToJSON Bind Source # 

Methods

toJSON :: Bind -> Value

toEncoding :: Bind -> Encoding

toJSONList :: [Bind] -> Value

toEncodingList :: [Bind] -> Encoding

FromJSON Bind Source # 

Methods

parseJSON :: Value -> Parser Bind

parseJSONList :: Value -> Parser [Bind]

newtype Volume Source #

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

Volume FilePath 

Instances

Eq Volume Source # 

Methods

(==) :: Volume -> Volume -> Bool #

(/=) :: Volume -> Volume -> Bool #

Show Volume Source # 
ToJSON [Volume] Source # 

Methods

toJSON :: [Volume] -> Value

toEncoding :: [Volume] -> Encoding

toJSONList :: [[Volume]] -> Value

toEncodingList :: [[Volume]] -> Encoding

FromJSON [Volume] Source # 

Methods

parseJSON :: Value -> Parser [Volume]

parseJSONList :: Value -> Parser [[Volume]]

data Device Source #

Instances

Eq Device Source # 

Methods

(==) :: Device -> Device -> Bool #

(/=) :: Device -> Device -> Bool #

Show Device Source # 
Generic Device Source # 

Associated Types

type Rep Device :: * -> * #

Methods

from :: Device -> Rep Device x #

to :: Rep Device x -> Device #

ToJSON Device Source # 

Methods

toJSON :: Device -> Value

toEncoding :: Device -> Encoding

toJSONList :: [Device] -> Value

toEncodingList :: [Device] -> Encoding

FromJSON Device Source # 

Methods

parseJSON :: Value -> Parser Device

parseJSONList :: Value -> Parser [Device]

type Rep Device Source # 
type Rep Device = D1 (MetaData "Device" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) (C1 (MetaCons "Device" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "pathOnHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) ((:*:) (S1 (MetaSel (Just Symbol "pathInContainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "cgroupPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))))

type ContainerName = Text Source #

data VolumeFrom Source #

Instances

Eq VolumeFrom Source # 
Show VolumeFrom Source # 
ToJSON VolumeFrom Source # 

Methods

toJSON :: VolumeFrom -> Value

toEncoding :: VolumeFrom -> Encoding

toJSONList :: [VolumeFrom] -> Value

toEncodingList :: [VolumeFrom] -> Encoding

FromJSON VolumeFrom Source # 

Methods

parseJSON :: Value -> Parser VolumeFrom

parseJSONList :: Value -> Parser [VolumeFrom]

data Link Source #

Constructors

Link Text (Maybe Text) 

data PortType Source #

Constructors

TCP 
UDP 

Instances

Eq PortType Source # 
Ord PortType Source # 
Read PortType Source # 
Show PortType Source # 
Generic PortType Source # 

Associated Types

type Rep PortType :: * -> * #

Methods

from :: PortType -> Rep PortType x #

to :: Rep PortType x -> PortType #

ToJSON PortType Source # 

Methods

toJSON :: PortType -> Value

toEncoding :: PortType -> Encoding

toJSONList :: [PortType] -> Value

toEncodingList :: [PortType] -> Encoding

FromJSON PortType Source # 

Methods

parseJSON :: Value -> Parser PortType

parseJSONList :: Value -> Parser [PortType]

type Rep PortType Source # 
type Rep PortType = D1 (MetaData "PortType" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) ((:+:) (C1 (MetaCons "TCP" PrefixI False) U1) (C1 (MetaCons "UDP" PrefixI False) U1))

data Network Source #

Instances

Eq Network Source # 

Methods

(==) :: Network -> Network -> Bool #

(/=) :: Network -> Network -> Bool #

Show Network Source # 
FromJSON [Network] Source # 

Methods

parseJSON :: Value -> Parser [Network]

parseJSONList :: Value -> Parser [[Network]]

data Mount Source #

Data type used for parsing the mount information from a container list.

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" }] }

Instances

Eq PortBinding Source # 
Show PortBinding Source # 
ToJSON [PortBinding] Source # 

Methods

toJSON :: [PortBinding] -> Value

toEncoding :: [PortBinding] -> Encoding

toJSONList :: [[PortBinding]] -> Value

toEncodingList :: [[PortBinding]] -> Encoding

FromJSON [PortBinding] Source # 

Methods

parseJSON :: Value -> Parser [PortBinding]

parseJSONList :: Value -> Parser [[PortBinding]]

data HostPort Source #

Constructors

HostPort 

Fields

Instances

Eq HostPort Source # 
Show HostPort Source # 
ToJSON HostPort Source # 

Methods

toJSON :: HostPort -> Value

toEncoding :: HostPort -> Encoding

toJSONList :: [HostPort] -> Value

toEncodingList :: [HostPort] -> Encoding

FromJSON HostPort Source # 

Methods

parseJSON :: Value -> Parser HostPort

parseJSONList :: Value -> Parser [HostPort]

newtype UTSMode Source #

Constructors

UTSMode Text 

data HostConfig Source #

Instances

Eq HostConfig Source # 
Show HostConfig Source # 
Generic HostConfig Source # 

Associated Types

type Rep HostConfig :: * -> * #

ToJSON HostConfig Source # 

Methods

toJSON :: HostConfig -> Value

toEncoding :: HostConfig -> Encoding

toJSONList :: [HostConfig] -> Value

toEncodingList :: [HostConfig] -> Encoding

FromJSON HostConfig Source # 

Methods

parseJSON :: Value -> Parser HostConfig

parseJSONList :: Value -> Parser [HostConfig]

type Rep HostConfig Source # 
type Rep HostConfig = D1 (MetaData "HostConfig" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) (C1 (MetaCons "HostConfig" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "binds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Bind])) (S1 (MetaSel (Just Symbol "containerIDFile") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath)))) ((:*:) (S1 (MetaSel (Just Symbol "logConfig") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LogDriverConfig)) ((:*:) (S1 (MetaSel (Just Symbol "networkMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 NetworkMode)) (S1 (MetaSel (Just Symbol "portBindings") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PortBinding]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "restartPolicy") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RestartPolicy)) ((:*:) (S1 (MetaSel (Just Symbol "volumeDriver") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "volumesFrom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [VolumeFrom])))) ((:*:) (S1 (MetaSel (Just Symbol "capAdd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) ((:*:) (S1 (MetaSel (Just Symbol "capDrop") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) (S1 (MetaSel (Just Symbol "dns") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "dnsOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) ((:*:) (S1 (MetaSel (Just Symbol "dnsSearch") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) (S1 (MetaSel (Just Symbol "extraHosts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])))) ((:*:) (S1 (MetaSel (Just Symbol "ipcMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "links") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Link])) (S1 (MetaSel (Just Symbol "oomScoreAdj") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "privileged") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "publishAllPorts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "readonlyRootfs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "securityOpt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text])) ((:*:) (S1 (MetaSel (Just Symbol "shmSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "resources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ContainerResources))))))))

defaultHostConfig :: HostConfig Source #

Default host confiratuon used for creating a container.

data Ulimit Source #

Constructors

Ulimit 

Instances

Eq Ulimit Source # 

Methods

(==) :: Ulimit -> Ulimit -> Bool #

(/=) :: Ulimit -> Ulimit -> Bool #

Show Ulimit Source # 
Generic Ulimit Source # 

Associated Types

type Rep Ulimit :: * -> * #

Methods

from :: Ulimit -> Rep Ulimit x #

to :: Rep Ulimit x -> Ulimit #

ToJSON Ulimit Source # 

Methods

toJSON :: Ulimit -> Value

toEncoding :: Ulimit -> Encoding

toJSONList :: [Ulimit] -> Value

toEncodingList :: [Ulimit] -> Encoding

FromJSON Ulimit Source # 

Methods

parseJSON :: Value -> Parser Ulimit

parseJSONList :: Value -> Parser [Ulimit]

type Rep Ulimit Source # 

data ContainerResources Source #

Instances

Eq ContainerResources Source # 
Show ContainerResources Source # 
Generic ContainerResources Source # 
FromJSON ContainerResources Source # 

Methods

parseJSON :: Value -> Parser ContainerResources

parseJSONList :: Value -> Parser [ContainerResources]

type Rep ContainerResources Source # 
type Rep ContainerResources = D1 (MetaData "ContainerResources" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) (C1 (MetaCons "ContainerResources" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "cpuShares") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer))) (S1 (MetaSel (Just Symbol "blkioWeight") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))) ((:*:) (S1 (MetaSel (Just Symbol "blkioWeightDevice") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [DeviceWeight]))) (S1 (MetaSel (Just Symbol "blkioDeviceReadBps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [DeviceRate]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "blkioDeviceWriteBps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [DeviceRate]))) (S1 (MetaSel (Just Symbol "blkioDeviceReadIOps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [DeviceRate])))) ((:*:) (S1 (MetaSel (Just Symbol "blkioDeviceWriteIOps") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [DeviceRate]))) (S1 (MetaSel (Just Symbol "cpuPeriod") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Integer)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "cpusetCpus") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "cpusetMems") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "devices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Device])) (S1 (MetaSel (Just Symbol "kernelMemory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MemoryConstraint))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "memory") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MemoryConstraint))) (S1 (MetaSel (Just Symbol "memoryReservation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MemoryConstraint)))) ((:*:) (S1 (MetaSel (Just Symbol "memorySwap") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe MemoryConstraint))) ((:*:) (S1 (MetaSel (Just Symbol "oomKillDisable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "ulimits") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Ulimit]))))))))

type Name = Text Source #

type Value = Text Source #

data EnvVar Source #

Constructors

EnvVar Name Value 

Instances

Eq EnvVar Source # 

Methods

(==) :: EnvVar -> EnvVar -> Bool #

(/=) :: EnvVar -> EnvVar -> Bool #

Show EnvVar Source # 
ToJSON EnvVar Source # 

Methods

toJSON :: EnvVar -> Value

toEncoding :: EnvVar -> Encoding

toJSONList :: [EnvVar] -> Value

toEncodingList :: [EnvVar] -> Encoding

FromJSON EnvVar Source # 

Methods

parseJSON :: Value -> Parser EnvVar

parseJSONList :: Value -> Parser [EnvVar]

data ContainerConfig Source #

Instances

Eq ContainerConfig Source # 
Show ContainerConfig Source # 
Generic ContainerConfig Source # 
ToJSON ContainerConfig Source # 

Methods

toJSON :: ContainerConfig -> Value

toEncoding :: ContainerConfig -> Encoding

toJSONList :: [ContainerConfig] -> Value

toEncodingList :: [ContainerConfig] -> Encoding

FromJSON ContainerConfig Source # 

Methods

parseJSON :: Value -> Parser ContainerConfig

parseJSONList :: Value -> Parser [ContainerConfig]

type Rep ContainerConfig Source # 
type Rep ContainerConfig = D1 (MetaData "ContainerConfig" "Docker.Client.Types" "docker-0.4.0.0-inplace" False) (C1 (MetaCons "ContainerConfig" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "hostname") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "domainname") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "user") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "attachStdin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "attachStdout") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "attachStderr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "exposedPorts") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ExposedPort]))) ((:*:) (S1 (MetaSel (Just Symbol "tty") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "openStdin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "stdinOnce") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "env") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [EnvVar])) (S1 (MetaSel (Just Symbol "cmd") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Text]))) ((:*:) (S1 (MetaSel (Just Symbol "image") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "volumes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Volume])) (S1 (MetaSel (Just Symbol "workingDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe FilePath)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "entrypoint") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "networkDisabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "macAddress") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "labels") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Label])) (S1 (MetaSel (Just Symbol "stopSignal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Signal))))))))

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 # 
Show ExposedPort Source # 
ToJSON [ExposedPort] Source # 

Methods

toJSON :: [ExposedPort] -> Value

toEncoding :: [ExposedPort] -> Encoding

toJSONList :: [[ExposedPort]] -> Value

toEncodingList :: [[ExposedPort]] -> Encoding

FromJSON [ExposedPort] Source # 

Methods

parseJSON :: Value -> Parser [ExposedPort]

parseJSONList :: Value -> Parser [[ExposedPort]]

data DeviceRate Source #

Constructors

DeviceRate 

Instances

Eq DeviceRate Source # 
Show DeviceRate Source # 
ToJSON DeviceRate Source # 

Methods

toJSON :: DeviceRate -> Value

toEncoding :: DeviceRate -> Encoding

toJSONList :: [DeviceRate] -> Value

toEncodingList :: [DeviceRate] -> Encoding

FromJSON DeviceRate Source # 

Methods

parseJSON :: Value -> Parser DeviceRate

parseJSONList :: Value -> Parser [DeviceRate]

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.