Copyright | (c) 2021 Red Hat |
---|---|
License | Apache-2.0 |
Maintainer | Tristan de Cacqueray <tdecacqu@redhat.com> |
Safe Haskell | None |
Language | Haskell2010 |
See Podman.Tutorial to learn how to use this library.
Here is the recommended way to import this library:
{-# LANGUAGE OverloadedStrings #-} import Podman
This module re-exports the rest of the library.
Podman.Types provides data types generated from the swagger definitions.
Podman.Internal provides utility function to further decode API response. Internal is exposed for testing purpose and it shouldn't be used.
Synopsis
- data PodmanClient
- withClient :: MonadIO m => Text -> (PodmanClient -> m a) -> m a
- type Result a = Either Error a
- getVersion :: MonadIO m => PodmanClient -> m (Result Version)
- newtype ContainerName = ContainerName Text
- containerExists :: MonadIO m => PodmanClient -> ContainerName -> m (Result Bool)
- containerInspect :: MonadIO m => PodmanClient -> ContainerName -> Bool -> m (Result InspectContainerResponse)
- containerList :: MonadIO m => PodmanClient -> ContainerListQuery -> m (Result [ListContainer])
- containerCreate :: MonadIO m => PodmanClient -> SpecGenerator -> m (Result ContainerCreateResponse)
- data WaitCondition
- containerWait :: MonadIO m => PodmanClient -> ContainerName -> WaitCondition -> m (Either Error Int)
- mkSpecGenerator :: Text -> SpecGenerator
- containerStart :: MonadIO m => PodmanClient -> ContainerName -> Maybe Text -> m (Maybe Error)
- containerDelete :: MonadIO m => PodmanClient -> ContainerName -> Maybe Bool -> Maybe Bool -> m (Maybe Error)
- containerKill :: MonadIO m => PodmanClient -> ContainerName -> Maybe Text -> m (Maybe Error)
- containerMount :: MonadIO m => PodmanClient -> ContainerName -> m (Either Error FilePath)
- containerPause :: MonadIO m => PodmanClient -> ContainerName -> m (Maybe Error)
- containerUnpause :: MonadIO m => PodmanClient -> ContainerName -> m (Maybe Error)
- containerRename :: MonadIO m => PodmanClient -> ContainerName -> ContainerName -> m (Maybe Error)
- containerRestart :: MonadIO m => PodmanClient -> ContainerName -> Maybe Word -> m (Maybe Error)
- containerSendFiles :: MonadIO m => PodmanClient -> ContainerName -> [Entry] -> Text -> Maybe Bool -> m (Maybe Error)
- containerGetFiles :: MonadIO m => PodmanClient -> ContainerName -> Text -> m (Result (Entries FormatError))
- containerAttach :: MonadIO m => PodmanClient -> ContainerName -> AttachQuery -> (ContainerConnection -> IO a) -> m (Result a)
- containerChanges :: MonadIO m => PodmanClient -> ContainerName -> m (Result [ContainerChange])
- containerInitialize :: MonadIO m => PodmanClient -> ContainerName -> m (Maybe Error)
- containerExport :: MonadIO m => PodmanClient -> ContainerName -> m (Result (Entries FormatError))
- containerLogs :: MonadIO m => PodmanClient -> ContainerName -> LogStream -> LogsQuery -> (ContainerOutput -> IO ()) -> m (Maybe Error)
- data LogStream
- data ContainerConnection = ContainerConnection {
- containerRecv :: IO ContainerOutput
- containerSend :: ByteString -> IO ()
- data ContainerOutput
- newtype ExecId = ExecId Text
- execCreate :: MonadIO m => PodmanClient -> ContainerName -> ExecConfig -> m (Result ExecId)
- execInspect :: MonadIO m => PodmanClient -> ExecId -> m (Result ExecInspectResponse)
- execStart :: MonadIO m => PodmanClient -> ExecId -> m (Result [ContainerOutput])
- generateKubeYAML :: MonadIO m => PodmanClient -> [ContainerName] -> Bool -> m (Result Text)
- generateSystemd :: MonadIO m => PodmanClient -> ContainerName -> GenerateSystemdQuery -> m (Result (Map Text Text))
- newtype ImageName = ImageName Text
- imageExists :: MonadIO m => PodmanClient -> ImageName -> m (Result Bool)
- imageList :: MonadIO m => PodmanClient -> ImageListQuery -> m (Result [ImageSummary])
- imageTree :: MonadIO m => PodmanClient -> ImageName -> Maybe Bool -> m (Result ImageTreeResponse)
- imagePull :: MonadIO m => PodmanClient -> ImagePullQuery -> m (Result [ImageName])
- imagePullRaw :: MonadIO m => PodmanClient -> ImagePullQuery -> m (Result ImagesPullResponse)
- newtype NetworkName = NetworkName Text
- networkExists :: MonadIO m => PodmanClient -> NetworkName -> m (Maybe Error)
- networkList :: MonadIO m => PodmanClient -> Maybe Text -> m (Result [NetworkListReport])
- newtype VolumeName = VolumeName Text
- volumeExists :: MonadIO m => PodmanClient -> VolumeName -> m (Maybe Error)
- volumeList :: MonadIO m => PodmanClient -> Maybe Text -> m (Result [Volume])
- newtype SecretName = SecretName Text
- secretList :: MonadIO m => PodmanClient -> m (Result [SecretInfoReport])
- secretCreate :: MonadIO m => PodmanClient -> SecretName -> ByteString -> m (Result SecretCreateResponse)
- secretInspect :: MonadIO m => PodmanClient -> SecretName -> m (Result SecretInfoReport)
- module Podman.Types
- data Text
Client
data PodmanClient #
Use withClient
to create the PodmanClient
:: MonadIO m | |
=> Text | The api url, can be |
-> (PodmanClient -> m a) | The callback |
-> m a | withClient performs the IO |
Server
getVersion :: MonadIO m => PodmanClient -> m (Result Version) #
Returns the Component Version information
Container
newtype ContainerName #
Instances
Eq ContainerName # | |
Defined in Podman.Api (==) :: ContainerName -> ContainerName -> Bool # (/=) :: ContainerName -> ContainerName -> Bool # | |
Show ContainerName # | |
Defined in Podman.Api showsPrec :: Int -> ContainerName -> ShowS # show :: ContainerName -> String # showList :: [ContainerName] -> ShowS # |
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Result Bool) |
Quick way to determine if a container exists by name or ID
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> Bool | Get filesystem usage |
-> m (Result InspectContainerResponse) |
Return low-level information about a container.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerListQuery | The list query, uses |
-> m (Result [ListContainer]) |
Returns a list of containers
containerCreate :: MonadIO m => PodmanClient -> SpecGenerator -> m (Result ContainerCreateResponse) #
Create a container
data WaitCondition #
Instances
Eq WaitCondition # | |
Defined in Podman.Api (==) :: WaitCondition -> WaitCondition -> Bool # (/=) :: WaitCondition -> WaitCondition -> Bool # | |
Show WaitCondition # | |
Defined in Podman.Api showsPrec :: Int -> WaitCondition -> ShowS # show :: WaitCondition -> String # showList :: [WaitCondition] -> ShowS # |
containerWait :: MonadIO m => PodmanClient -> ContainerName -> WaitCondition -> m (Either Error Int) #
Wait on a container to met a given condition
:: Text | image |
-> SpecGenerator |
Creates a SpecGenerator
by setting all the optional attributes to Nothing
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> Maybe Text | Override the key sequence for detaching a container. |
-> m (Maybe Error) |
Start a container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> Maybe Bool | Force delete |
-> Maybe Bool | Delete volumes |
-> m (Maybe Error) |
Delete container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> Maybe Text | Signal to be sent to container, (default TERM) |
-> m (Maybe Error) |
Send a signal to a container, defaults to killing the container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Either Error FilePath) |
Mount a container to the filesystem
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Maybe Error) |
Use the cgroups freezer to suspend all processes in a container.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Maybe Error) |
Unpause Container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> ContainerName | New name for the container |
-> m (Maybe Error) |
Change the name of an existing container.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> Maybe Word | Timeout before sending kill signal to container |
-> m (Maybe Error) |
Restart a container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> [Entry] | List of tar entries |
-> Text | Path to a directory in the container to extract |
-> Maybe Bool | Pause the container while copying (defaults to true) |
-> m (Maybe Error) |
Copy a tar archive of files into a container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> Text | Path to a directory in the container to extract |
-> m (Result (Entries FormatError)) |
Get a tar archive of files from a container
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> AttachQuery | The attach query, use |
-> (ContainerConnection -> IO a) | The callback |
-> m (Result a) |
Hijacks the connection to forward the container's standard streams to the client.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Result [ContainerChange]) |
Report on changes to container's filesystem; adds, deletes or modifications.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Maybe Error) |
Performs all tasks necessary for initializing the container but does not start the container.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> m (Result (Entries FormatError)) |
Export the contents of a container as a tarball.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> LogStream | The log to stream |
-> LogsQuery | The logs query, use |
-> (ContainerOutput -> IO ()) | The callback |
-> m (Maybe Error) |
Get stdout and stderr logs from a container.
data ContainerConnection #
A connection attached to a container. Note that full-duplex communication may require async threads because the http-client doesn't seems to expose aio (e.g. Connection doesn't have a fd, only a recv call)
data ContainerOutput #
A container output
Instances
Eq ContainerOutput # | |
Defined in Podman.Api (==) :: ContainerOutput -> ContainerOutput -> Bool # (/=) :: ContainerOutput -> ContainerOutput -> Bool # | |
Show ContainerOutput # | |
Defined in Podman.Api showsPrec :: Int -> ContainerOutput -> ShowS # show :: ContainerOutput -> String # showList :: [ContainerOutput] -> ShowS # |
Exec
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | The container name |
-> ExecConfig | The exec config |
-> m (Result ExecId) |
Create an exec instance
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ExecId | Exec instance ID |
-> m (Result ExecInspectResponse) |
Inspect an exec instance
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ExecId | Exec instance ID |
-> m (Result [ContainerOutput]) |
Start an exec instance
Pod
:: MonadIO m | |
=> PodmanClient | The client instance |
-> [ContainerName] | List of name or ID of the container or pod. |
-> Bool | Generate YAML for a Kubernetes service object. |
-> m (Result Text) |
Generate a Kubernetes YAML file.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ContainerName | Name or ID of the container or pod. |
-> GenerateSystemdQuery | Systemd configuration. |
-> m (Result (Map Text Text)) |
Generate Systemd Units based on a pod or container.
Image
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ImageName | The image name |
-> m (Result Bool) |
Check if image exists in local store.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ImageListQuery | The list query, use |
-> m (Result [ImageSummary]) |
Returns a list of images on the server.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ImageName | The image name |
-> Maybe Bool | Show all child images and layers of the specified image |
-> m (Result ImageTreeResponse) |
Retrieve the image tree for the provided image name or ID
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ImagePullQuery | The pull query, use |
-> m (Result [ImageName]) |
Pull one or more images from a container registry.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> ImagePullQuery | The pull query, use |
-> m (Result ImagesPullResponse) |
Pull one or more images from a container registry with the full results.
Network
newtype NetworkName #
Instances
Eq NetworkName # | |
Defined in Podman.Api (==) :: NetworkName -> NetworkName -> Bool # (/=) :: NetworkName -> NetworkName -> Bool # | |
Show NetworkName # | |
Defined in Podman.Api showsPrec :: Int -> NetworkName -> ShowS # show :: NetworkName -> String # showList :: [NetworkName] -> ShowS # |
:: MonadIO m | |
=> PodmanClient | The client instance |
-> NetworkName | The network name |
-> m (Maybe Error) | Returns Nothing when the network exists |
Check if network exists in local store.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> Maybe Text | JSON encoded value of the filters (a map[string][]string) to process on the network list. |
-> m (Result [NetworkListReport]) |
Returns a list of networks on the server.
Volume
newtype VolumeName #
Instances
Eq VolumeName # | |
Defined in Podman.Api (==) :: VolumeName -> VolumeName -> Bool # (/=) :: VolumeName -> VolumeName -> Bool # | |
Show VolumeName # | |
Defined in Podman.Api showsPrec :: Int -> VolumeName -> ShowS # show :: VolumeName -> String # showList :: [VolumeName] -> ShowS # |
:: MonadIO m | |
=> PodmanClient | The client instance |
-> VolumeName | The volume name |
-> m (Maybe Error) | Returns Nothing when the volume exists |
Check if volume exists in local store.
:: MonadIO m | |
=> PodmanClient | The client instance |
-> Maybe Text | JSON encoded value of the filters (a map[string][]string) to process on the volume list. |
-> m (Result [Volume]) |
Returns a list of volumes on the server.
Secret
newtype SecretName #
Instances
Eq SecretName # | |
Defined in Podman.Api (==) :: SecretName -> SecretName -> Bool # (/=) :: SecretName -> SecretName -> Bool # | |
Show SecretName # | |
Defined in Podman.Api showsPrec :: Int -> SecretName -> ShowS # show :: SecretName -> String # showList :: [SecretName] -> ShowS # |
:: MonadIO m | |
=> PodmanClient | The client instance |
-> m (Result [SecretInfoReport]) |
Returns a list of secrets
:: MonadIO m | |
=> PodmanClient | The client instance |
-> SecretName | The secret name |
-> ByteString | The secret data |
-> m (Result SecretCreateResponse) |
:: MonadIO m | |
=> PodmanClient | The client instance |
-> SecretName | The secret name |
-> m (Result SecretInfoReport) |
Inspect a secret.
module Podman.Types
re-exports
A space efficient, packed, unboxed Unicode text type.
Instances
Hashable Text | |
Defined in Data.Hashable.Class | |
ToJSON Text | |
Defined in Data.Aeson.Types.ToJSON | |
KeyValue Object | Constructs a singleton |
KeyValue Pair | |
ToJSONKey Text | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Text | |
FromJSONKey Text | |
Defined in Data.Aeson.Types.FromJSON | |
Chunk Text | |
Defined in Data.Attoparsec.Internal.Types | |
FoldCase Text | |
Defined in Data.CaseInsensitive.Internal | |
FromPairs Value (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
v ~ Value => KeyValuePair v (DList Pair) | |
Defined in Data.Aeson.Types.ToJSON | |
type State Text | |
Defined in Data.Attoparsec.Internal.Types | |
type ChunkElem Text | |
Defined in Data.Attoparsec.Internal.Types | |
type Item Text | |