lxd-client-0.1.0.5: LXD client written in Haskell.

Safe HaskellNone
LanguageHaskell2010

Network.LXD.Client.Types

Contents

Description

This module implements all types used to communicate with the LXD daemon REST end-point.

These types are e.g. used in the Network.LXD.Client.Commands module.

Synopsis

Generic responses

data GenericResponse op a Source #

Generic LXD API response object.

type Response a = GenericResponse String a Source #

LXD API synchronous repsonse object, without resulting operation.

type AsyncResponse a = GenericResponse OperationId (BackgroundOperation a) Source #

LXD API asynchronous response object, with resulting operation

Background operations

API

data ApiConfig Source #

LXD API configuration object.

Returend when querying GET /1.0. Some objects may not be present if an untrusted requeset was made.

Certificates

Containers

Querying information

Configuration

newtype ContainerRename Source #

Used to rename a container to the given name.

Used when querying POST /1.0/containers/<name>.

Constructors

ContainerRename String 

State

Creating containers

data ContainerSource Source #

Source for creating a container, as used by ContainerCreateRequest.

Constructors

ContainerSourceLocalByAlias LocalImageByAlias

Container based on a local image with a certain alias.

ContainerSourceLocalByFingerprint LocalImageByFingerprint

Container based on a local image with a certain alias.

ContainerSourceNone

Container without a pre-populated rootfs.

ContainerSourceRemote RemoteImage

Continer based on a public remote image.

Deleting containers

Executing commands

data ExecParams Source #

Configuration parameter to ExecRequest and ExecResponse.

Constructors

ExecImmediate

Don't wait for a websocket connection before executing.

ExecWebsocketInteractive

Wait for websocket, allocate PTY.

ExecWebsocketNonInteractive

Wait for websocket, don't allocate PTY.

data ExecRequest (params :: ExecParams) Source #

LXD container exec request, configured using ExecParams as type parameter.

Request body when querying POST /1.0/containers/<name>/exec.

type ExecResponseMetadataImmediate = Value Source #

Metadata of an immediate exec response.

Returned when querying POST /1.0/containers/<name>/exec with ExecImmediate as configuration.

Working with file descriptors

newtype Secret Source #

A secret used to connect to a websocket.

Constructors

Secret String 

data FdSet Source #

A set of selected file descriptors.

Constructors

FdAll 
FdPty 

Instances

data Fds set where Source #

A set of file descriptors.

Constructors

FdsAll :: {..} -> Fds FdAll 
FdsPty :: {..} -> Fds FdPty 

type family ExecFds (params :: ExecParams) :: FdSet where ... Source #

Type family converting an ExecParams to an FdSet.

Working with files

newtype Gid Source #

Group ID of a container file.

Constructors

Gid Int 

Instances

Bounded Gid Source # 

Methods

minBound :: Gid #

maxBound :: Gid #

Enum Gid Source # 

Methods

succ :: Gid -> Gid #

pred :: Gid -> Gid #

toEnum :: Int -> Gid #

fromEnum :: Gid -> Int #

enumFrom :: Gid -> [Gid] #

enumFromThen :: Gid -> Gid -> [Gid] #

enumFromTo :: Gid -> Gid -> [Gid] #

enumFromThenTo :: Gid -> Gid -> Gid -> [Gid] #

Eq Gid Source # 

Methods

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

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

Integral Gid Source # 

Methods

quot :: Gid -> Gid -> Gid #

rem :: Gid -> Gid -> Gid #

div :: Gid -> Gid -> Gid #

mod :: Gid -> Gid -> Gid #

quotRem :: Gid -> Gid -> (Gid, Gid) #

divMod :: Gid -> Gid -> (Gid, Gid) #

toInteger :: Gid -> Integer #

Num Gid Source # 

Methods

(+) :: Gid -> Gid -> Gid #

(-) :: Gid -> Gid -> Gid #

(*) :: Gid -> Gid -> Gid #

negate :: Gid -> Gid #

abs :: Gid -> Gid #

signum :: Gid -> Gid #

fromInteger :: Integer -> Gid #

Ord Gid Source # 

Methods

compare :: Gid -> Gid -> Ordering #

(<) :: Gid -> Gid -> Bool #

(<=) :: Gid -> Gid -> Bool #

(>) :: Gid -> Gid -> Bool #

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

max :: Gid -> Gid -> Gid #

min :: Gid -> Gid -> Gid #

Read Gid Source # 
Real Gid Source # 

Methods

toRational :: Gid -> Rational #

Show Gid Source # 

Methods

showsPrec :: Int -> Gid -> ShowS #

show :: Gid -> String #

showList :: [Gid] -> ShowS #

ToHttpApiData Gid Source # 
FromHttpApiData Gid Source # 

newtype Uid Source #

User ID of a container file.

Constructors

Uid Int 

Instances

Bounded Uid Source # 

Methods

minBound :: Uid #

maxBound :: Uid #

Enum Uid Source # 

Methods

succ :: Uid -> Uid #

pred :: Uid -> Uid #

toEnum :: Int -> Uid #

fromEnum :: Uid -> Int #

enumFrom :: Uid -> [Uid] #

enumFromThen :: Uid -> Uid -> [Uid] #

enumFromTo :: Uid -> Uid -> [Uid] #

enumFromThenTo :: Uid -> Uid -> Uid -> [Uid] #

Eq Uid Source # 

Methods

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

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

Integral Uid Source # 

Methods

quot :: Uid -> Uid -> Uid #

rem :: Uid -> Uid -> Uid #

div :: Uid -> Uid -> Uid #

mod :: Uid -> Uid -> Uid #

quotRem :: Uid -> Uid -> (Uid, Uid) #

divMod :: Uid -> Uid -> (Uid, Uid) #

toInteger :: Uid -> Integer #

Num Uid Source # 

Methods

(+) :: Uid -> Uid -> Uid #

(-) :: Uid -> Uid -> Uid #

(*) :: Uid -> Uid -> Uid #

negate :: Uid -> Uid #

abs :: Uid -> Uid #

signum :: Uid -> Uid #

fromInteger :: Integer -> Uid #

Ord Uid Source # 

Methods

compare :: Uid -> Uid -> Ordering #

(<) :: Uid -> Uid -> Bool #

(<=) :: Uid -> Uid -> Bool #

(>) :: Uid -> Uid -> Bool #

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

max :: Uid -> Uid -> Uid #

min :: Uid -> Uid -> Uid #

Read Uid Source # 
Real Uid Source # 

Methods

toRational :: Uid -> Rational #

Show Uid Source # 

Methods

showsPrec :: Int -> Uid -> ShowS #

show :: Uid -> String #

showList :: [Uid] -> ShowS #

ToHttpApiData Uid Source # 
FromHttpApiData Uid Source # 

fileResponse :: FileType -> ByteString -> Either String FileResponse Source #

Construct a file response from a type and a ByteString.

data FileResponse Source #

LXD file response object, representing either a file or a directory.

Used by the GET /1.0/containers/<name>/files/<filename> endpoints.

data PathResponse Source #

LXD path response object, which is a file and metadata.

Used by the /1.0/containers/<name>/files/... endpoints.

Referencing containers

Images

Querying information

data ImageAlias Source #

Alias of an image.

Returned when querying GET /1.0/images/aliases/<name>, and as a part of GET /1.0/images/<fingerprint>.

defaultImageAlias :: String -> ImageAlias Source #

Create a default ImageAlias, with empty description and target.

Creating and publishing new images

Deleting images

data ImageDeleteRequest Source #

LXD image delete request object.

Used when querying DELETE /1.0/images/<fingerprint>.

Constructors

ImageDeleteRequest 

Referencing images

remoteImage :: String -> ImageAliasName -> RemoteImage Source #

Create a remote image reference form a public remote.

remoteImageId :: String -> ImageId -> RemoteImage Source #

Create a remote image reference form a public remote, using an image ID.

Networks

data Network Source #

LXD network.

Returned when querying GET /1.0/networks/<name>.

Profiles

Storage

data Pool Source #

LXD pool.

Returned by GET /1.0/storage-pools/<name>.

Volumes

type VolumeType = String Source #

Type of a volume.

data VolumeName Source #

LXD volume name, and its type.

Returned by GET /1.0/storage-pools/<name>/volumes.

data Volume Source #

LXD volume.

Returend by GET /1.0/storage-pools/<name>/volumes/<type>/<volume>.

Operations

type OperationStatus = String Source #

LXD operation status.

newtype OperationProgress Source #

Progress of an LXD operation.

You can try to decode operationMetadata if the operationStatusCode is SRunning to see of the operation contains progress information.

The embedded String value is in the format 87% (12.04 MB/s).

Events

data Event Source #

An event received from /1.0/events.

Servant Helpers