hocker-1.0.5: Interact with the docker registry and generate nix build instructions

Copyright(C) 2016 Awake Networks
LicenseApache-2.0
MaintainerAwake Networks <opensource@awakenetworks.com>
Stabilitystable
Safe HaskellNone
LanguageHaskell2010

Hocker.Types

Description

 

Synopsis

Documentation

type RegistryURI = URIRef Absolute #

Docker registry URI.

type Username = Text #

Docker registry username.

type Password = Text #

Docker registry user password.

type Layer = Text #

Docker image layer sha256 hash digest.

type StrippedDigest = Text #

SHA256 hash digest with the hash algorithm identifier prefix, stripped

type Manifest = ByteString #

Docker image manifest JSON.

type ImageConfigJSON = ByteString #

Docker image config JSON.

type RspBS = Response ByteString #

Wreq response type parameterized by the lazy bytestring type.

type Extension = String #

A file extension.

type RepoNamePart = Text #

RepoName is the part before the forward slash in a docker image name, e.g: library in library/debian

type ImageNamePart = Text #

ImageName is the part after the forward slash in a docker image name, e.g: library in library/debian

type ConfigDigest = Base32Digest #

Docker image config JSON file's sha256 hash digest in Nix's base32 encoding.

NB: it's very important to realize there's a significant difference between Nix's base32 encoding and the standard base32 encoding! (i.e, they're not compatible).

data Options w #

Generic top-level optparse-generic CLI args data type and specification.

NOTE: `hocker-layer` does not use this data type because it requires an additional layer sha256 hash digest argument.

Constructors

Options 

Fields

Instances

Show (Options Unwrapped) # 
Generic (Options w) # 

Associated Types

type Rep (Options w) :: * -> * #

Methods

from :: Options w -> Rep (Options w) x #

to :: Rep (Options w) x -> Options w #

ParseRecord (Options Wrapped) # 
type Rep (Options w) # 
type Rep (Options w) = D1 (MetaData "Options" "Hocker.Types" "hocker-1.0.5-79fexLXu3Ts3AzUVy2qF0t" False) (C1 (MetaCons "Options" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "registry") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((:::) w ((<?>) (Maybe RegistryURI) "URI of registry, defaults to the Docker Hub registry")))) (S1 (MetaSel (Just Symbol "credentials") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Credentials)))) ((:*:) (S1 (MetaSel (Just Symbol "out") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ((:::) w ((<?>) (Maybe FilePath) "Write content to location")))) ((:*:) (S1 (MetaSel (Just Symbol "imageName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageName)) (S1 (MetaSel (Just Symbol "imageTag") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageTag))))))

newtype Hocker a #

Hocker ExceptT and ReaderT transformer stack threading a HockerMeta data type.

Instances

Monad Hocker # 

Methods

(>>=) :: Hocker a -> (a -> Hocker b) -> Hocker b #

(>>) :: Hocker a -> Hocker b -> Hocker b #

return :: a -> Hocker a #

fail :: String -> Hocker a #

Functor Hocker # 

Methods

fmap :: (a -> b) -> Hocker a -> Hocker b #

(<$) :: a -> Hocker b -> Hocker a #

Applicative Hocker # 

Methods

pure :: a -> Hocker a #

(<*>) :: Hocker (a -> b) -> Hocker a -> Hocker b #

(*>) :: Hocker a -> Hocker b -> Hocker b #

(<*) :: Hocker a -> Hocker b -> Hocker a #

MonadIO Hocker # 

Methods

liftIO :: IO a -> Hocker a #

MonadReader HockerMeta Hocker # 

Methods

ask :: Hocker HockerMeta #

local :: (HockerMeta -> HockerMeta) -> Hocker a -> Hocker a #

reader :: (HockerMeta -> a) -> Hocker a #

MonadError HockerException Hocker # 

data HockerMeta #

Red wagon record carrying around the environment as we fetch, transform, and assemble docker image artifacts.

newtype Base32Digest #

Newtype base32 encoding of a hash digest.

Please note, this base32 encoding is unique to Nix and not compatible with other base32 encodings.

Constructors

Base32Digest Text 

newtype Base16Digest #

Newtype base16 encoding of a hash digest.

This encoding has no known idiosyncracies specific to Nix, it should be compatible with other tools and library's expectations.

Constructors

Base16Digest Text 

upperFirst :: String -> String #

upperFirst uppercases the first letter of the string.