Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- data GenericResponse op a = Response {
- responseType :: ResponseType
- status :: String
- statusCode :: StatusCode
- responseOperation :: op
- errorCode :: Int
- error :: String
- metadata :: a
- type Response a = GenericResponse String a
- type AsyncResponse a = GenericResponse OperationId (BackgroundOperation a)
- data ResponseType
- data StatusCode
- data BackgroundOperation m = BackgroundOperation {
- backgroundOperationId :: String
- backgroundOperationClass :: String
- backgroundOperationCreatedAt :: String
- backgroundOperationUpdatedAt :: String
- backgroundOperationStatus :: String
- backgroundOperationStatusCode :: StatusCode
- backgroundOperationMetadata :: m
- backgroundOperationMayCancel :: Bool
- backgroundOperationeErr :: String
- data ApiConfig = ApiConfig {}
- data ApiStatus
- data AuthStatus
- newtype ApiVersion = ApiVersion String
- data ApiExtension
- newtype CertificateHash = CertificateHash String
- newtype ContainerName = ContainerName String
- data Container = Container {
- containerArchitecture :: String
- containerName :: String
- containerConfig :: Map String String
- containerCreatedAt :: String
- containerDevices :: Map String (Map String String)
- containerEphemeral :: Bool
- containerProfiles :: [String]
- containerStateful :: Bool
- containerExpandedConfig :: Map String String
- containerExpandedDevices :: Map String (Map String String)
- containerStatus :: String
- containerSatusCode :: Int
- containerLastUsedAt :: String
- data ContainerPut = ContainerPut {}
- data ContainerPatch = ContainerPatch {}
- newtype ContainerRename = ContainerRename String
- data MemoryState = MemoryState {}
- data NetworkState = NetworkState {}
- data NetworkAddress = NetworkAddress {}
- data NetworkCounters = NetworkCounters {}
- data ContainerState = ContainerState {}
- data StateAction
- data ContainerPutState = ContainerPutState {}
- containerNewState :: StateAction -> Bool -> ContainerPutState
- data ContainerCreateRequest = ContainerCreateRequest {
- containerCreateRequestName :: String
- containerCreateRequestArchitecture :: String
- containerCreateRequestProfiles :: [String]
- containerCreateRequestEphemeral :: Bool
- containerCreateRequestConfig :: Map String String
- containerCreateRequestDevices :: Map String (Map String String)
- containerCreateRequestInstanceType :: Maybe String
- containerCreateRequestSource :: ContainerSource
- containerCreateRequest :: String -> ContainerSource -> ContainerCreateRequest
- data ContainerSource
- data ContainerDeleteRequest = ContainerDeleteRequest
- data ExecParams
- data ExecRequest params = ExecRequest {}
- type ExecResponseMetadataImmediate = Value
- newtype ExecResponseMetadataWebsocket fdset = ExecResponseMetadataWebsocket {
- execResponseMetadataWebsocketFds :: Fds fdset
- type family ExecResponseMetadata (params :: ExecParams) :: * where ...
- newtype Secret = Secret String
- data FdSet
- data Fds set where
- type family ExecFds (params :: ExecParams) :: FdSet where ...
- newtype Gid = Gid Int
- newtype Uid = Uid Int
- newtype FileMode = FileMode String
- newtype FileType = FileType String
- data RawFileResponse = RawFileResponse MediaType ByteString
- rawFileResponseBody :: RawFileResponse -> ByteString
- fileResponse :: FileType -> ByteString -> Either String FileResponse
- data FileResponse
- = File ByteString
- | Directory (Response [String])
- data PathResponse = PathResponse {}
- newtype LocalContainer = LocalContainer ContainerName
- newtype ImageId = ImageId String
- data Image = Image {
- imageAllAliases :: [ImageAlias]
- imageArchitecture :: String
- imageAutoUpdate :: Bool
- imageCached :: Bool
- imageFingerprint :: String
- imageFilename :: String
- imageProperties :: ImageProperties
- imagePublic :: Bool
- imageSize :: Integer
- imageCreatedAt :: String
- imageExpiresAt :: String
- imageLastUsedAt :: String
- imageUplaodedAt :: String
- data ImageAlias = ImageAlias {}
- defaultImageAlias :: String -> ImageAlias
- data ImageProperties = ImageProperties {}
- newtype ImageAliasName = ImageAliasName String
- data ImageCreateRequest = ImageCreateRequest {}
- imageCreateRequest :: ImageSource -> ImageCreateRequest
- data ImageSource
- data ImageDeleteRequest = ImageDeleteRequest
- newtype LocalImageByAlias = LocalImageByAlias ImageAliasName
- newtype LocalImageByFingerprint = LocalImageByFingerprint ImageId
- data RemoteImage = RemoteImage {}
- remoteImage :: String -> ImageAliasName -> RemoteImage
- remoteImageId :: String -> ImageId -> RemoteImage
- newtype NetworkName = NetworkName String
- data Network = Network {}
- data NetworkCreateRequest = NetworkCreateRequest {}
- newtype NetworkConfigRequest = NetworkConfigRequest {}
- newtype ProfileName = ProfileName String
- data Profile = Profile {}
- data ProfileCreateRequest = ProfileCreateRequest {}
- data ProfileConfigRequest = ProfileConfigRequest {}
- newtype PoolName = PoolName String
- data Pool = Pool {}
- data PoolCreateRequest = PoolCreateRequest {}
- newtype PoolConfigRequest = PoolConfigRequest {}
- type VolumeType = String
- data VolumeName = VolumeName VolumeType String
- data Volume = Volume {}
- data VolumeCreateRequest = VolumeCreateRequest {}
- newtype VolumeConfigRequest = VolumeConfigRequest {}
- newtype OperationId = OperationId String
- type OperationStatus = String
- newtype AllOperations = AllOperations (Map OperationStatus [OperationId])
- data Operation = Operation {}
- newtype OperationProgress = OperationProgress String
- data EventType
- data Event = Event {}
- data EventMetadata
- data JsonOrBinary
Generic responses
data GenericResponse op a Source #
Generic LXD API response object.
Response | |
|
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
data ResponseType Source #
The type of a generic response object.
data StatusCode Source #
Background operations
data BackgroundOperation m Source #
Background operation response object, with metadata of type m
.
FromJSON m => FromJSON (BackgroundOperation m) Source # | |
API
LXD API configuration object.
Returend when querying GET /1.0
. Some objects may not be present if
an untrusted requeset was made.
ApiConfig | |
|
data AuthStatus Source #
newtype ApiVersion Source #
LXD API version string, e.g. 1.0.
data ApiExtension Source #
LXD API extension identifier.
Certificates
newtype CertificateHash Source #
LXD trusted certificate hash.
Containers
Querying information
newtype ContainerName Source #
LXD container name.
LXD container information.
Returned when querying GET /1.0/containers/<name>
.
Configuration
data ContainerPut Source #
Used to set the configuration of an LXD container.
Used when querying PUT /1.0/containers/<name>
.
data ContainerPatch Source #
Used to patch the configuration of an LXD container.
Used when querying PATCH /1.0/containers/<name>
.
newtype ContainerRename Source #
Used to rename a container to the given name.
Used when querying POST /1.0/containers/<name>
.
State
data NetworkState Source #
Network state of an LXD container network device. As used by ContainerState
.
data NetworkAddress Source #
Network address of an LXD container network device. As used by NetworkState
.
data NetworkCounters Source #
Collection of statistics of an LXD container network device. As used by NetworkState
.
data ContainerState Source #
State of an LXD container.
Used when querying GET /1.0/container/<name>/state
.
data StateAction Source #
State change action for an LXD container, as used by ContainerPutState
.
data ContainerPutState Source #
State change request for an LXD container.
Used when querying PUT /1.0/container/<name>/state
.
containerNewState :: StateAction -> Bool -> ContainerPutState Source #
Creating containers
data ContainerCreateRequest Source #
LXD create container request object.
Used when querying POST /1.0/containers
.
containerCreateRequest :: String -> ContainerSource -> ContainerCreateRequest Source #
Create a default ContainerCreateRequest
.
data ContainerSource Source #
Source for creating a container, as used by ContainerCreateRequest
.
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
data ContainerDeleteRequest Source #
LXD delete container request object.
Used when querying DELETE /1.0/containers/<name>
.
Executing commands
data ExecParams Source #
Configuration parameter to ExecRequest
and ExecResponse
.
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 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.
newtype ExecResponseMetadataWebsocket fdset Source #
Metadata of a websocket exec repsonse.
Returned when querying POST /1.0/containers/<name>/exec
with
ExecWebsocketInteractive
or ExecWebsocketNonInteractive
as
configuration.
Paramtrized by a file descriptor set FdSet
, see also the type family
ExecFds
.
type family ExecResponseMetadata (params :: ExecParams) :: * where ... Source #
Type family converting an ExecParams
to the corresponding response type.
Working with file descriptors
A secret used to connect to a websocket.
A set of file descriptors.
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
Group ID of a container file.
User ID of a container file.
Mode of a container file. Encoded in standard octal notation, e.g. 0644
.
Type of a container file. Can be one of directory
, file
or symlink
.
data RawFileResponse Source #
Raw file response, not yet decoded, used because of a bug in Servant.
Use headers to get actual content type.
rawFileResponseBody :: RawFileResponse -> ByteString Source #
Get the body of a RawFileResponse
.
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
newtype LocalContainer Source #
Reference to a local container, as used by ImageSource
.
Images
Querying information
LXD image identifier.
LXD image information.
Returned when querying GET /1.0/images/<fingerprint>
.
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.
newtype ImageAliasName Source #
LXD alias name.
Returned when querying GET /1.0/images/aliases
.
Creating and publishing new images
data ImageCreateRequest Source #
LXD image create request object.
Used when querying POST /1.0/images
.
imageCreateRequest :: ImageSource -> ImageCreateRequest Source #
Construct a new default ImageCreateRequest
.
data ImageSource Source #
A generic image source, used by ImageCreateRequest
.
Deleting images
data ImageDeleteRequest Source #
LXD image delete request object.
Used when querying DELETE /1.0/images/<fingerprint>
.
Referencing images
newtype LocalImageByAlias Source #
Source for a local image, specified by its alias.
newtype LocalImageByFingerprint Source #
Source for a local image, specified by its fingerprint
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
newtype NetworkName Source #
LXD network name.
LXD network.
Returned when querying GET /1.0/networks/<name>
.
Network | |
|
data NetworkCreateRequest Source #
LXD network create request.
Used when querying POST /1.0/networks
.
newtype NetworkConfigRequest Source #
LXD network config update request.
Used when querying PUT/PATCH /1.0/networks/<name>
.
Profiles
newtype ProfileName Source #
LXD profile name.
Returned by GET /1.0/profiles
.
LXD profile.
Returned by GET /1.0/profiles/<name>
.
Profile | |
|
data ProfileCreateRequest Source #
LXD profile create request.
Used when querying POST /1.0/profiles
.
data ProfileConfigRequest Source #
LXD profile config request.
Used when querying PUT/PATCH /1.0/profiles/<name>
.
Storage
LXD storage pool name.
Returned by GET /1.0/storage-pools
.
LXD pool.
Returned by GET /1.0/storage-pools/<name>
.
Pool | |
|
data PoolCreateRequest Source #
LXD pool create request.
Used when querying POST /1.0/storage-pools
.
newtype PoolConfigRequest Source #
LXD pool config request.
Used when querying PUT/PATCH /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
.
LXD volume.
Returend by GET /1.0/storage-pools/<name>/volumes/<type>/<volume>
.
Volume | |
|
data VolumeCreateRequest Source #
LXD volume create request.
Used when querying POST /1.0/storage-pools/<name>/volumes
.
newtype VolumeConfigRequest Source #
LXD volume config request.
Returend by PUT/PATCH /1.0/storage-pools/<name>/volumes/<type>/<volume>
.
Operations
newtype OperationId Source #
LXD operation identifier.
type OperationStatus = String Source #
LXD operation status.
newtype AllOperations Source #
LXD list of all operations.
LXD operation.
Returned when querying GET /1.0/operations/<uuid>
.
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
Type of an LXD event from the /1.0/events
handle.
An event received from /1.0/events
.
data EventMetadata Source #
Metadata of an event.