docker-0.7.0.1: 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

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

Instances details
Eq ImageID Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show ImageID Source # 
Instance details

Defined in Docker.Client.Types

ToJSON ImageID Source # 
Instance details

Defined in Docker.Client.Types

FromJSON ImageID Source # 
Instance details

Defined in Docker.Client.Types

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 NetworkID Source #

Instances

Instances details
Eq NetworkID Source # 
Instance details

Defined in Docker.Client.Types

Show NetworkID Source # 
Instance details

Defined in Docker.Client.Types

ToJSON NetworkID Source # 
Instance details

Defined in Docker.Client.Types

FromJSON NetworkID Source # 
Instance details

Defined in Docker.Client.Types

fromNetworkID :: NetworkID -> Text Source #

Used for extracting the id of the container from the newtype

toNetworkID :: Text -> Maybe NetworkID Source #

Used for parsing a Text value into a NetworkID.

data Timeout Source #

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

Instances

Instances details
Eq Timeout Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Timeout Source # 
Instance details

Defined in Docker.Client.Types

data Signal Source #

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

Instances

Instances details
Eq Signal Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Signal Source # 
Instance details

Defined in Docker.Client.Types

ToJSON Signal Source # 
Instance details

Defined in Docker.Client.Types

FromJSON Signal Source # 
Instance details

Defined in Docker.Client.Types

data ContainerDetails Source #

Instances

Instances details
Eq ContainerDetails Source # 
Instance details

Defined in Docker.Client.Types

Show ContainerDetails Source # 
Instance details

Defined in Docker.Client.Types

Generic ContainerDetails Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep ContainerDetails :: Type -> Type #

FromJSON ContainerDetails Source # 
Instance details

Defined in Docker.Client.Types

type Rep ContainerDetails Source # 
Instance details

Defined in Docker.Client.Types

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

data DockerClientOpts Source #

Client options used to configure the remote engine we're talking to

Constructors

DockerClientOpts 

Fields

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

Instances

Instances details
Eq ListOpts Source # 
Instance details

Defined in Docker.Client.Types

Show ListOpts Source # 
Instance details

Defined in Docker.Client.Types

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.

Instances

Instances details
Eq DockerVersion Source # 
Instance details

Defined in Docker.Client.Types

Show DockerVersion Source # 
Instance details

Defined in Docker.Client.Types

Generic DockerVersion Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep DockerVersion :: Type -> Type #

ToJSON DockerVersion Source # 
Instance details

Defined in Docker.Client.Types

FromJSON DockerVersion Source # 
Instance details

Defined in Docker.Client.Types

type Rep DockerVersion Source # 
Instance details

Defined in Docker.Client.Types

data ContainerPortInfo Source #

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

data ContainerState Source #

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

Instances

Instances details
Eq ContainerState Source # 
Instance details

Defined in Docker.Client.Types

Show ContainerState Source # 
Instance details

Defined in Docker.Client.Types

Generic ContainerState Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep ContainerState :: Type -> Type #

FromJSON ContainerState Source # 
Instance details

Defined in Docker.Client.Types

type Rep ContainerState Source # 
Instance details

Defined in Docker.Client.Types

data State Source #

Represents the state of the container life cycle.

Instances

Instances details
Eq State Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show State Source # 
Instance details

Defined in Docker.Client.Types

Methods

showsPrec :: Int -> State -> ShowS #

show :: State -> String #

showList :: [State] -> ShowS #

Generic State Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep State :: Type -> Type #

Methods

from :: State -> Rep State x #

to :: Rep State x -> State #

FromJSON State Source # 
Instance details

Defined in Docker.Client.Types

type Rep State Source # 
Instance details

Defined in Docker.Client.Types

type Rep State = D1 ('MetaData "State" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" '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))))

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

Instances details
Eq Label Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Label Source # 
Instance details

Defined in Docker.Client.Types

Methods

showsPrec :: Int -> Label -> ShowS #

show :: Label -> String #

showList :: [Label] -> ShowS #

ToJSON [Label] Source # 
Instance details

Defined in Docker.Client.Types

FromJSON [Label] Source # 
Instance details

Defined in Docker.Client.Types

type Tag = Text Source #

Alias for Tags.

data Image Source #

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

Instances

Instances details
Eq Image Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Image Source # 
Instance details

Defined in Docker.Client.Types

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep Image :: Type -> Type #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

FromJSON Image Source # 
Instance details

Defined in Docker.Client.Types

type Rep Image Source # 
Instance details

Defined in Docker.Client.Types

data Entrypoint Source #

Constructors

Entrypoint [Text] 

Instances

Instances details
Eq Entrypoint Source # 
Instance details

Defined in Docker.Client.Types

Show Entrypoint Source # 
Instance details

Defined in Docker.Client.Types

Generic Entrypoint Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep Entrypoint :: Type -> Type #

ToJSON Entrypoint Source # 
Instance details

Defined in Docker.Client.Types

FromJSON Entrypoint Source # 
Instance details

Defined in Docker.Client.Types

type Rep Entrypoint Source # 
Instance details

Defined in Docker.Client.Types

type Rep Entrypoint = D1 ('MetaData "Entrypoint" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" '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.

Instances

Instances details
Eq CreateOpts Source # 
Instance details

Defined in Docker.Client.Types

Show CreateOpts Source # 
Instance details

Defined in Docker.Client.Types

ToJSON CreateOpts Source # 
Instance details

Defined in Docker.Client.Types

data BuildOpts Source #

Options for when building images from a Dockerfile

Constructors

BuildOpts 

Fields

Instances

Instances details
Eq BuildOpts Source # 
Instance details

Defined in Docker.Client.Types

Show BuildOpts Source # 
Instance details

Defined in Docker.Client.Types

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

Instances

Instances details
Eq DetachKeys Source # 
Instance details

Defined in Docker.Client.Types

Show DetachKeys Source # 
Instance details

Defined in Docker.Client.Types

data StartOpts Source #

Options for starting a container.

Constructors

StartOpts 

Instances

Instances details
Eq StartOpts Source # 
Instance details

Defined in Docker.Client.Types

Show StartOpts Source # 
Instance details

Defined in Docker.Client.Types

defaultStartOpts :: StartOpts Source #

Default options for staring a container.

data ContainerDeleteOpts Source #

Options for deleting a container.

Constructors

ContainerDeleteOpts 

Fields

  • deleteVolumes :: Bool

    Automatically cleanup volumes that the container created as well.

  • force :: Bool

    If the container is still running force deletion anyway.

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 

defaultImageDeleteOpts :: ImageDeleteOpts Source #

Sane image deletion defaults

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 

Instances

Instances details
Eq TailLogOpt Source # 
Instance details

Defined in Docker.Client.Types

Show TailLogOpt Source # 
Instance details

Defined in Docker.Client.Types

data LogOpts Source #

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

Constructors

LogOpts 

Instances

Instances details
Eq LogOpts Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show LogOpts Source # 
Instance details

Defined in Docker.Client.Types

defaultLogOpts :: LogOpts Source #

Sensible default for log options.

data CreateNetworkOpts Source #

Options for creating a network

Constructors

CreateNetworkOpts 

Fields

defaultCreateNetworkOpts :: Text -> CreateNetworkOpts Source #

Sensible defalut for create network options

data VolumePermission Source #

Set permissions on volumes that you mount in the container.

Constructors

ReadWrite 
ReadOnly 

Instances

Instances details
Eq VolumePermission Source # 
Instance details

Defined in Docker.Client.Types

Show VolumePermission Source # 
Instance details

Defined in Docker.Client.Types

Generic VolumePermission Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep VolumePermission :: Type -> Type #

ToJSON VolumePermission Source # 
Instance details

Defined in Docker.Client.Types

FromJSON VolumePermission Source # 
Instance details

Defined in Docker.Client.Types

type Rep VolumePermission Source # 
Instance details

Defined in Docker.Client.Types

type Rep VolumePermission = D1 ('MetaData "VolumePermission" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" 'False) (C1 ('MetaCons "ReadWrite" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReadOnly" 'PrefixI 'False) (U1 :: Type -> Type))

data Bind Source #

Instances

Instances details
Eq Bind Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Bind Source # 
Instance details

Defined in Docker.Client.Types

Methods

showsPrec :: Int -> Bind -> ShowS #

show :: Bind -> String #

showList :: [Bind] -> ShowS #

ToJSON Bind Source # 
Instance details

Defined in Docker.Client.Types

FromJSON Bind Source # 
Instance details

Defined in Docker.Client.Types

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

Instances details
Eq Volume Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Volume Source # 
Instance details

Defined in Docker.Client.Types

ToJSON [Volume] Source # 
Instance details

Defined in Docker.Client.Types

FromJSON [Volume] Source # 
Instance details

Defined in Docker.Client.Types

data Device Source #

Instances

Instances details
Eq Device Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Device Source # 
Instance details

Defined in Docker.Client.Types

Generic Device Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep Device :: Type -> Type #

Methods

from :: Device -> Rep Device x #

to :: Rep Device x -> Device #

ToJSON Device Source # 
Instance details

Defined in Docker.Client.Types

FromJSON Device Source # 
Instance details

Defined in Docker.Client.Types

type Rep Device Source # 
Instance details

Defined in Docker.Client.Types

type Rep Device = D1 ('MetaData "Device" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" '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))))

data Link Source #

Constructors

Link Text (Maybe Text) 

Instances

data PortType Source #

Constructors

TCP 
UDP 

Instances

Instances details
Eq PortType Source # 
Instance details

Defined in Docker.Client.Types

Ord PortType Source # 
Instance details

Defined in Docker.Client.Types

Read PortType Source # 
Instance details

Defined in Docker.Client.Types

Show PortType Source # 
Instance details

Defined in Docker.Client.Types

Generic PortType Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep PortType :: Type -> Type #

Methods

from :: PortType -> Rep PortType x #

to :: Rep PortType x -> PortType #

ToJSON PortType Source # 
Instance details

Defined in Docker.Client.Types

FromJSON PortType Source # 
Instance details

Defined in Docker.Client.Types

type Rep PortType Source # 
Instance details

Defined in Docker.Client.Types

type Rep PortType = D1 ('MetaData "PortType" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" 'False) (C1 ('MetaCons "TCP" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "UDP" 'PrefixI 'False) (U1 :: Type -> Type))

data Network Source #

Instances

Instances details
Eq Network Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Network Source # 
Instance details

Defined in Docker.Client.Types

FromJSON [Network] Source # 
Instance details

Defined in Docker.Client.Types

data Mount Source #

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

Instances

Instances details
Eq Mount Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Mount Source # 
Instance details

Defined in Docker.Client.Types

Methods

showsPrec :: Int -> Mount -> ShowS #

show :: Mount -> String #

showList :: [Mount] -> ShowS #

Generic Mount Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep Mount :: Type -> Type #

Methods

from :: Mount -> Rep Mount x #

to :: Rep Mount x -> Mount #

FromJSON Mount Source # 
Instance details

Defined in Docker.Client.Types

type Rep Mount Source # 
Instance details

Defined in Docker.Client.Types

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

Instances details
Eq PortBinding Source # 
Instance details

Defined in Docker.Client.Types

Show PortBinding Source # 
Instance details

Defined in Docker.Client.Types

ToJSON [PortBinding] Source # 
Instance details

Defined in Docker.Client.Types

FromJSON [PortBinding] Source # 
Instance details

Defined in Docker.Client.Types

data HostPort Source #

Constructors

HostPort 

Fields

Instances

Instances details
Eq HostPort Source # 
Instance details

Defined in Docker.Client.Types

Show HostPort Source # 
Instance details

Defined in Docker.Client.Types

ToJSON HostPort Source # 
Instance details

Defined in Docker.Client.Types

FromJSON HostPort Source # 
Instance details

Defined in Docker.Client.Types

data Isolation Source #

Constructors

Default 
Process 
Hyperv 

Instances

Instances details
Eq Isolation Source # 
Instance details

Defined in Docker.Client.Types

Show Isolation Source # 
Instance details

Defined in Docker.Client.Types

newtype UTSMode Source #

Constructors

UTSMode Text 

Instances

Instances details
Eq UTSMode Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show UTSMode Source # 
Instance details

Defined in Docker.Client.Types

data HostConfig Source #

Instances

Instances details
Eq HostConfig Source # 
Instance details

Defined in Docker.Client.Types

Show HostConfig Source # 
Instance details

Defined in Docker.Client.Types

Generic HostConfig Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep HostConfig :: Type -> Type #

ToJSON HostConfig Source # 
Instance details

Defined in Docker.Client.Types

FromJSON HostConfig Source # 
Instance details

Defined in Docker.Client.Types

type Rep HostConfig Source # 
Instance details

Defined in Docker.Client.Types

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

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

newtype EndpointConfig Source #

EndpointsConfig is container configuration for a specific network

Constructors

EndpointConfig [Alias] 

data Ulimit Source #

Constructors

Ulimit 

Instances

Instances details
Eq Ulimit Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show Ulimit Source # 
Instance details

Defined in Docker.Client.Types

Generic Ulimit Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep Ulimit :: Type -> Type #

Methods

from :: Ulimit -> Rep Ulimit x #

to :: Rep Ulimit x -> Ulimit #

ToJSON Ulimit Source # 
Instance details

Defined in Docker.Client.Types

FromJSON Ulimit Source # 
Instance details

Defined in Docker.Client.Types

type Rep Ulimit Source # 
Instance details

Defined in Docker.Client.Types

type Rep Ulimit = D1 ('MetaData "Ulimit" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" '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 #

Instances

Instances details
Eq ContainerResources Source # 
Instance details

Defined in Docker.Client.Types

Show ContainerResources Source # 
Instance details

Defined in Docker.Client.Types

Generic ContainerResources Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep ContainerResources :: Type -> Type #

FromJSON ContainerResources Source # 
Instance details

Defined in Docker.Client.Types

type Rep ContainerResources Source # 
Instance details

Defined in Docker.Client.Types

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

type Name = Text Source #

data EnvVar Source #

Constructors

EnvVar Name Value 

Instances

Instances details
Eq EnvVar Source # 
Instance details

Defined in Docker.Client.Types

Methods

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

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

Show EnvVar Source # 
Instance details

Defined in Docker.Client.Types

ToJSON EnvVar Source # 
Instance details

Defined in Docker.Client.Types

FromJSON EnvVar Source # 
Instance details

Defined in Docker.Client.Types

data ContainerConfig Source #

Instances

Instances details
Eq ContainerConfig Source # 
Instance details

Defined in Docker.Client.Types

Show ContainerConfig Source # 
Instance details

Defined in Docker.Client.Types

Generic ContainerConfig Source # 
Instance details

Defined in Docker.Client.Types

Associated Types

type Rep ContainerConfig :: Type -> Type #

ToJSON ContainerConfig Source # 
Instance details

Defined in Docker.Client.Types

FromJSON ContainerConfig Source # 
Instance details

Defined in Docker.Client.Types

type Rep ContainerConfig Source # 
Instance details

Defined in Docker.Client.Types

type Rep ContainerConfig = D1 ('MetaData "ContainerConfig" "Docker.Client.Types" "docker-0.7.0.1-F3bKiQrSTY07wiEXH0kWTW" 'False) (C1 ('MetaCons "ContainerConfig" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "hostname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "domainname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))) :*: (S1 ('MetaSel ('Just "user") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "attachStdin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "attachStdout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "attachStderr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "exposedPorts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ExposedPort])) :*: (S1 ('MetaSel ('Just "tty") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "openStdin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "stdinOnce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) :*: (((S1 ('MetaSel ('Just "env") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [EnvVar]) :*: S1 ('MetaSel ('Just "cmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])) :*: (S1 ('MetaSel ('Just "image") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: (S1 ('MetaSel ('Just "volumes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Volume]) :*: S1 ('MetaSel ('Just "workingDir") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FilePath))))) :*: ((S1 ('MetaSel ('Just "entrypoint") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Entrypoint) :*: S1 ('MetaSel ('Just "networkDisabled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Bool))) :*: (S1 ('MetaSel ('Just "macAddress") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: (S1 ('MetaSel ('Just "labels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Label]) :*: S1 ('MetaSel ('Just "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

Instances details
Eq ExposedPort Source # 
Instance details

Defined in Docker.Client.Types

Show ExposedPort Source # 
Instance details

Defined in Docker.Client.Types

ToJSON [ExposedPort] Source # 
Instance details

Defined in Docker.Client.Types

FromJSON [ExposedPort] Source # 
Instance details

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.