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

Safe HaskellNone
LanguageHaskell2010

Network.LXD.Client.Commands

Contents

Description

This module implements commands to communicate with the LXD daemon over its REST API.

More information about LXD: https://github.com/lxc/lxd

This module implements a high-level interface, and is probably what you need. It uses the lower-level interface implemented in Network.LXD.Client.API, but unless you are a power user, you shouldn't need this module.

Accompanying blog post: https://deliquus.com/posts/2017-10-02-using-servant-to-orchestrate-lxd-containers.html

Synopsis

How to use this library

All commands take place in the HasClient monad. The WithLocalHost and WithRemoteHost monads can be used directly for fast access to an LXD daemon, but you can also make your own monad stack an instance of HasClient.

You can connect to an LXD daemon over a unix-socket on the local host, or over HTTPS. For more information about these connection types see Network.LXD.Client.

An example using these command to conncet to the LXD instance on your local host (should work out of the box).

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Control.Monad.IO.Class (liftIO)
import Network.LXD.Client.Commands

main :: IO ()
main = runWithLocalHost def $ do
    liftIO $ putStrLn "Creating my-container"
    lxcCreate . containerCreateRequest "my-container"
              . ContainerSourceRemote
              $ remoteImage imagesRemote "ubuntu/xenial/amd64"

    liftIO $ putStrLn "Starting my-container"
    lxcStart "my-container"

    liftIO $ putStrLn "Stopping my-container"
    lxcStop "my-container" False

    liftIO $ putStrLn "Deleting my-container"
    lxcDelete "my-container"

Re-exports

def :: Default a => a #

The default value for this type.

Running commands

data Host Source #

A host that can be connected to.

class (MonadIO m, MonadMask m) => HasClient m where Source #

Monad with access to a ClientEnv.

Minimal complete definition

askHost

Methods

askHost :: m Host Source #

Return the LXD remote host to connect to.

askClientEnv :: m ClientEnv Source #

Return the ClientEnv to use when connecting to the LXD host.

Returns defaultClientEnv by default.

API

lxcApi :: HasClient m => m ApiConfig Source #

Get information about the API.

Containers

lxcList :: HasClient m => m [ContainerName] Source #

List all container names.

lxcCreate :: HasClient m => ContainerCreateRequest -> m () Source #

Create a new container.

lxcDelete :: HasClient m => ContainerName -> m () Source #

Delete a container.

lxcInfo :: HasClient m => ContainerName -> m Container Source #

Get information about a container.

lxcStart :: HasClient m => ContainerName -> m () Source #

Start a contianer.

lxcStop :: HasClient m => ContainerName -> Bool -> m () Source #

Stop a container.

The second flag forces the action.

lxcRestart :: HasClient m => ContainerName -> Bool -> m () Source #

Restart a container.

The second flag forces the action.

lxcFreeze :: HasClient m => ContainerName -> m () Source #

Freeze a container.

lxcUnfreeze :: HasClient m => ContainerName -> m () Source #

Unfreeze a container.

Exec

lxcExec Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> String

Command name

-> [String]

Command arguments

-> ByteString

Standard input

-> m ByteString 

Execute a command, catch standard output, print stderr.

lxcExecEnv Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> String

Command name

-> [String]

Command arguments

-> Map String String

Environment variables

-> ByteString

Standard input

-> m ByteString 

Execute a command, provide environment variables, catch standard output, print stderr.

lxcExecRaw Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> String

Command name

-> [String]

Command arguments

-> Map String String

Environment variables

-> MVar (Maybe ByteString)

Stream of standard input, pass Nothing to end the stream.

-> MVar ByteString

Standard output

-> MVar ByteString

Standard error

-> m (Async ()) 

Execute a command, with given environment variables.

Files and directories

Deletion

lxcFileDelete :: HasClient m => ContainerName -> FilePath -> m () Source #

Delete a file or empty directory from an LXD container.

Files

lxcFilePull Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> FilePath

Source path, in the container

-> FilePath

Destination path, in the host

-> m () 

Pull the file contents from an LXD container.

lxcFilePullRaw :: HasClient m => ContainerName -> FilePath -> m ByteString Source #

Pull the file contents from an LXD container, return the lazy bytestring.

lxcFilePush Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> FilePath

Source path, in the host

-> FilePath

Destination path, in the container

-> m () 

Push the file contents to an LXD container.

lxcFilePushAttrs Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> FilePath

Source path, in the host

-> FilePath

Destination path, in the container

-> Maybe Uid 
-> Maybe Gid 
-> m () 

Push the fole contents to an LXD container, with the given attributes.

lxcFilePushRaw :: HasClient m => ContainerName -> FilePath -> ByteString -> m () Source #

Write the lazy bytestring to a file in an LXD container.

lxcFilePushRawAttrs :: HasClient m => ContainerName -> FilePath -> Maybe Uid -> Maybe Gid -> Maybe FileMode -> FileType -> Maybe WriteMode -> ByteString -> m () Source #

Write the lazy bytestring to a file in an LXD container, with given file attributes.

Directories

lxcFileListDir :: HasClient m => ContainerName -> FilePath -> m [String] Source #

List all entries in a directory, without . or ...

lxcFileMkdir Source #

Arguments

:: HasClient m 
=> ContainerName 
-> String 
-> Bool

Create parent directories

-> m () 

Create a directory.

lxcFileMkdirTemplate Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> FilePath

Source path, in the host

-> FilePath

Destination path, in the container

-> m () 

Create a directory using a host directory as a template.

Note that this function doesn't copy the directory contents. Use lxcFilePushRecursive if you want to copy the directory contents as well.

lxcFileMkdirAttrs Source #

Arguments

:: HasClient m 
=> ContainerName 
-> String 
-> Bool

Create parent directories

-> Maybe Uid 
-> Maybe Gid 
-> Maybe FileMode 
-> m () 

Create a directory, with given attributes.

Recursive

lxcFilePullRecursive Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> FilePath

Source path, in the container

-> FilePath

Destination path, in the host

-> m () 

Recursively pull a directory (or file) from a container.

lxcFilePushRecursive Source #

Arguments

:: HasClient m 
=> ContainerName

Container name

-> FilePath

Source path, in the host

-> FilePath

Destination path, in the container

-> m () 

Recursively push a directory (or file) to a container.

lxcFilePushRecursiveAttrs Source #

Arguments

:: HasClient m 
=> ContainerName 
-> FilePath

Souce path, in the host

-> FilePath

Destination path, in the container

-> Maybe Uid 
-> Maybe Gid 
-> m () 

Recursively push a directory (or file) to a container, with given file attributes.

Images

lxcImageList :: HasClient m => m [ImageId] Source #

List all image IDs.

lxcImageAliases :: HasClient m => m [ImageAliasName] Source #

List al image aliases.

lxcImageInfo :: HasClient m => ImageId -> m Image Source #

Get image information.

lxcImageAlias :: HasClient m => ImageAliasName -> m ImageAlias Source #

Get image alias information.

lxcImageCreate :: HasClient m => ImageCreateRequest -> m () Source #

Create an image.

lxcImageDelete :: HasClient m => ImageId -> m () Source #

Delete an image.

Networks

lxcNetworkList :: HasClient m => m [NetworkName] Source #

List all networks

lxcNetworkCreate :: HasClient m => NetworkCreateRequest -> m () Source #

Create a network.

lxcNetworkInfo :: HasClient m => NetworkName -> m Network Source #

Get network information.

lxcNetworkConfig :: HasClient m => NetworkName -> NetworkConfigRequest -> m () Source #

Configure a network.

lxcNetworkDelete :: HasClient m => NetworkName -> m () Source #

Delete a network

Profiles

lxcProfileList :: HasClient m => m [ProfileName] Source #

List all profiles

lxcProfileCreate :: HasClient m => ProfileCreateRequest -> m () Source #

Create a profile.

lxcProfileInfo :: HasClient m => ProfileName -> m Profile Source #

Get profile information.

lxcProfileConfig :: HasClient m => ProfileName -> ProfileConfigRequest -> m () Source #

Configure a profile.

lxcProfileDelete :: HasClient m => ProfileName -> m () Source #

Delete a profile

Storage

lxcStorageList :: HasClient m => m [PoolName] Source #

List all storage pools

lxcStorageCreate :: HasClient m => PoolCreateRequest -> m () Source #

Create a storage pool.

lxcStorageInfo :: HasClient m => PoolName -> m Pool Source #

Get storage pool information.

lxcStorageConfig :: HasClient m => PoolName -> PoolConfigRequest -> m () Source #

Configure a storage pool.

lxcStorageDelete :: HasClient m => PoolName -> m () Source #

Delete a storage pool

Volume

lxcVolumeList :: HasClient m => PoolName -> m [VolumeName] Source #

List all volumes

lxcVolumeCreate :: HasClient m => PoolName -> VolumeCreateRequest -> m () Source #

Create a volume.

lxcVolumeInfo :: HasClient m => PoolName -> VolumeName -> m Volume Source #

Get volume information.

lxcVolumeConfig :: HasClient m => PoolName -> VolumeName -> VolumeConfigRequest -> m () Source #

Configure a volume.

lxcVolumeDelete :: HasClient m => PoolName -> VolumeName -> m () Source #

Delete a volume