b9-0.5.30: A tool and library for building virtual machine images.

Safe HaskellNone
LanguageHaskell2010

B9.DiskImages

Contents

Description

Data types that describe all B9 relevant elements of virtual machine disk images.

Synopsis

Data types for disk image description, e.g. ImageTarget,

data ImageTarget Source #

Build target for disk images; the destination, format and size of the image to generate, as well as how to create or obtain the image before a VmScript is executed with the image mounted at a MountPoint.

Instances

Eq ImageTarget Source # 
Data ImageTarget Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageTarget -> c ImageTarget #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageTarget #

toConstr :: ImageTarget -> Constr #

dataTypeOf :: ImageTarget -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageTarget) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageTarget) #

gmapT :: (forall b. Data b => b -> b) -> ImageTarget -> ImageTarget #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageTarget -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageTarget -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageTarget -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageTarget -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageTarget -> m ImageTarget #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageTarget -> m ImageTarget #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageTarget -> m ImageTarget #

Read ImageTarget Source # 
Show ImageTarget Source # 
Generic ImageTarget Source # 

Associated Types

type Rep ImageTarget :: * -> * #

Arbitrary ImageTarget Source # 
Hashable ImageTarget Source # 
Binary ImageTarget Source # 
NFData ImageTarget Source # 

Methods

rnf :: ImageTarget -> () #

type Rep ImageTarget Source # 

data MountPoint Source #

A mount point or NotMounted

Instances

Eq MountPoint Source # 
Data MountPoint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MountPoint -> c MountPoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MountPoint #

toConstr :: MountPoint -> Constr #

dataTypeOf :: MountPoint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MountPoint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MountPoint) #

gmapT :: (forall b. Data b => b -> b) -> MountPoint -> MountPoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MountPoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MountPoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> MountPoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MountPoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MountPoint -> m MountPoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MountPoint -> m MountPoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MountPoint -> m MountPoint #

Read MountPoint Source # 
Show MountPoint Source # 
Generic MountPoint Source # 

Associated Types

type Rep MountPoint :: * -> * #

Arbitrary MountPoint Source # 
Hashable MountPoint Source # 
Binary MountPoint Source # 
NFData MountPoint Source # 

Methods

rnf :: MountPoint -> () #

type Rep MountPoint Source # 
type Rep MountPoint = D1 (MetaData "MountPoint" "B9.DiskImages" "b9-0.5.30-JIpfhe2WUzZ314Dg9ph204" False) ((:+:) (C1 (MetaCons "MountPoint" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath))) (C1 (MetaCons "NotMounted" PrefixI False) U1))

data ImageDestination Source #

The destination of an image.

Constructors

Share String ImageType ImageResize

Create the image and some meta data so that other builds can use them as ImageSources via From.

LiveInstallerImage String FilePath ImageResize

DEPRECATED Export a raw image that can directly be booted.

LocalFile Image ImageResize

Write an image file to the path in the first argument., possible resizing it,

Transient

Do not export the image. Usefule if the main objective of the b9 build is not an image file, but rather some artifact produced by executing by a containerize build.

Instances

Eq ImageDestination Source # 
Data ImageDestination Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageDestination -> c ImageDestination #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageDestination #

toConstr :: ImageDestination -> Constr #

dataTypeOf :: ImageDestination -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageDestination) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageDestination) #

gmapT :: (forall b. Data b => b -> b) -> ImageDestination -> ImageDestination #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageDestination -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageDestination -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageDestination -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageDestination -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageDestination -> m ImageDestination #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageDestination -> m ImageDestination #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageDestination -> m ImageDestination #

Read ImageDestination Source # 
Show ImageDestination Source # 
Generic ImageDestination Source # 
Arbitrary ImageDestination Source # 
Hashable ImageDestination Source # 
Binary ImageDestination Source # 
NFData ImageDestination Source # 

Methods

rnf :: ImageDestination -> () #

type Rep ImageDestination Source # 

data ImageSource Source #

Specification of how the image to build is obtained.

Constructors

EmptyImage String FileSystem ImageType ImageSize

Create an empty image file having a file system label (first parameter), a file system type (e.g. Ext4) and an ImageSize

CopyOnWrite Image

DEPRECATED

SourceImage Image Partition ImageResize

Clone an existing image file; if the image file contains partitions, select the partition to use, b9 will extract that partition by reading the offset of the partition from the partition table and extract it using dd.

From String ImageResize

Use an image previously shared by via Share.

Instances

Eq ImageSource Source # 
Data ImageSource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageSource -> c ImageSource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageSource #

toConstr :: ImageSource -> Constr #

dataTypeOf :: ImageSource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageSource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageSource) #

gmapT :: (forall b. Data b => b -> b) -> ImageSource -> ImageSource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageSource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageSource -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageSource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageSource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageSource -> m ImageSource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageSource -> m ImageSource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageSource -> m ImageSource #

Read ImageSource Source # 
Show ImageSource Source # 
Generic ImageSource Source # 

Associated Types

type Rep ImageSource :: * -> * #

Arbitrary ImageSource Source # 
Hashable ImageSource Source # 
Binary ImageSource Source # 
NFData ImageSource Source # 

Methods

rnf :: ImageSource -> () #

type Rep ImageSource Source # 

data Partition Source #

The partition to extract.

Constructors

NoPT

There is no partition table on the image

Partition Int

Extract partition n n must be in 0..3

Instances

Eq Partition Source # 
Data Partition Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Partition -> c Partition #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Partition #

toConstr :: Partition -> Constr #

dataTypeOf :: Partition -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Partition) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Partition) #

gmapT :: (forall b. Data b => b -> b) -> Partition -> Partition #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Partition -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Partition -> r #

gmapQ :: (forall d. Data d => d -> u) -> Partition -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Partition -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Partition -> m Partition #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Partition -> m Partition #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Partition -> m Partition #

Read Partition Source # 
Show Partition Source # 
Generic Partition Source # 

Associated Types

type Rep Partition :: * -> * #

Arbitrary Partition Source # 
Hashable Partition Source # 
Binary Partition Source # 
NFData Partition Source # 

Methods

rnf :: Partition -> () #

type Rep Partition Source # 
type Rep Partition = D1 (MetaData "Partition" "B9.DiskImages" "b9-0.5.30-JIpfhe2WUzZ314Dg9ph204" False) ((:+:) (C1 (MetaCons "NoPT" PrefixI False) U1) (C1 (MetaCons "Partition" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))))

data Image Source #

A vm disk image file consisting of a path to the image file, and the type and file system.

Instances

Eq Image Source # 

Methods

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

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

Data Image Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Image -> c Image #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Image #

toConstr :: Image -> Constr #

dataTypeOf :: Image -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Image) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Image) #

gmapT :: (forall b. Data b => b -> b) -> Image -> Image #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Image -> r #

gmapQ :: (forall d. Data d => d -> u) -> Image -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Image -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Image -> m Image #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Image -> m Image #

Read Image Source # 
Show Image Source # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

Arbitrary Image Source # 

Methods

arbitrary :: Gen Image #

shrink :: Image -> [Image] #

Hashable Image Source # 

Methods

hashWithSalt :: Int -> Image -> Int #

hash :: Image -> Int #

Binary Image Source # 

Methods

put :: Image -> Put #

get :: Get Image #

putList :: [Image] -> Put #

NFData Image Source # 

Methods

rnf :: Image -> () #

type Rep Image Source # 

data ImageType Source #

An image type defines the actual file format of a file containing file systems. These are like virtual harddrives

Constructors

Raw 
QCow2 
Vmdk 

Instances

Eq ImageType Source # 
Data ImageType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageType -> c ImageType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageType #

toConstr :: ImageType -> Constr #

dataTypeOf :: ImageType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageType) #

gmapT :: (forall b. Data b => b -> b) -> ImageType -> ImageType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageType -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageType -> m ImageType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageType -> m ImageType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageType -> m ImageType #

Read ImageType Source # 
Show ImageType Source # 
Generic ImageType Source # 

Associated Types

type Rep ImageType :: * -> * #

Arbitrary ImageType Source # 
Hashable ImageType Source # 
Binary ImageType Source # 
NFData ImageType Source # 

Methods

rnf :: ImageType -> () #

type Rep ImageType Source # 
type Rep ImageType = D1 (MetaData "ImageType" "B9.DiskImages" "b9-0.5.30-JIpfhe2WUzZ314Dg9ph204" False) ((:+:) (C1 (MetaCons "Raw" PrefixI False) U1) ((:+:) (C1 (MetaCons "QCow2" PrefixI False) U1) (C1 (MetaCons "Vmdk" PrefixI False) U1)))

data FileSystem Source #

The file systems that b9 can use and convert.

Constructors

NoFileSystem 
Ext4 
ISO9660 
VFAT 

Instances

Eq FileSystem Source # 
Data FileSystem Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileSystem -> c FileSystem #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileSystem #

toConstr :: FileSystem -> Constr #

dataTypeOf :: FileSystem -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileSystem) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileSystem) #

gmapT :: (forall b. Data b => b -> b) -> FileSystem -> FileSystem #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileSystem -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileSystem -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileSystem -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileSystem -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileSystem -> m FileSystem #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileSystem -> m FileSystem #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileSystem -> m FileSystem #

Read FileSystem Source # 
Show FileSystem Source # 
Generic FileSystem Source # 

Associated Types

type Rep FileSystem :: * -> * #

Arbitrary FileSystem Source # 
Hashable FileSystem Source # 
Binary FileSystem Source # 
NFData FileSystem Source # 

Methods

rnf :: FileSystem -> () #

type Rep FileSystem Source # 
type Rep FileSystem = D1 (MetaData "FileSystem" "B9.DiskImages" "b9-0.5.30-JIpfhe2WUzZ314Dg9ph204" False) ((:+:) ((:+:) (C1 (MetaCons "NoFileSystem" PrefixI False) U1) (C1 (MetaCons "Ext4" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ISO9660" PrefixI False) U1) (C1 (MetaCons "VFAT" PrefixI False) U1)))

data ImageSize Source #

A data type for image file or file system size; instead of passing Ints around this also captures a size unit so that the Int can be kept small

Constructors

ImageSize Int SizeUnit 

Instances

Eq ImageSize Source # 
Data ImageSize Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageSize -> c ImageSize #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageSize #

toConstr :: ImageSize -> Constr #

dataTypeOf :: ImageSize -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageSize) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageSize) #

gmapT :: (forall b. Data b => b -> b) -> ImageSize -> ImageSize #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageSize -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageSize -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageSize -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageSize -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageSize -> m ImageSize #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageSize -> m ImageSize #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageSize -> m ImageSize #

Read ImageSize Source # 
Show ImageSize Source # 
Generic ImageSize Source # 

Associated Types

type Rep ImageSize :: * -> * #

Arbitrary ImageSize Source # 
Hashable ImageSize Source # 
Binary ImageSize Source # 
NFData ImageSize Source # 

Methods

rnf :: ImageSize -> () #

type Rep ImageSize Source # 

data SizeUnit Source #

Enumeration of size multipliers. The exact semantics may vary depending on what external tools look at these. E.g. the size unit is convert to a size parameter of the qemu-img command line tool.

Constructors

B 
KB 
MB 
GB 

Instances

Eq SizeUnit Source # 
Data SizeUnit Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SizeUnit -> c SizeUnit #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SizeUnit #

toConstr :: SizeUnit -> Constr #

dataTypeOf :: SizeUnit -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SizeUnit) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SizeUnit) #

gmapT :: (forall b. Data b => b -> b) -> SizeUnit -> SizeUnit #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SizeUnit -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SizeUnit -> r #

gmapQ :: (forall d. Data d => d -> u) -> SizeUnit -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SizeUnit -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SizeUnit -> m SizeUnit #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SizeUnit -> m SizeUnit #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SizeUnit -> m SizeUnit #

Ord SizeUnit Source # 
Read SizeUnit Source # 
Show SizeUnit Source # 
Generic SizeUnit Source # 

Associated Types

type Rep SizeUnit :: * -> * #

Methods

from :: SizeUnit -> Rep SizeUnit x #

to :: Rep SizeUnit x -> SizeUnit #

Arbitrary SizeUnit Source # 
Hashable SizeUnit Source # 

Methods

hashWithSalt :: Int -> SizeUnit -> Int #

hash :: SizeUnit -> Int #

Binary SizeUnit Source # 

Methods

put :: SizeUnit -> Put #

get :: Get SizeUnit #

putList :: [SizeUnit] -> Put #

NFData SizeUnit Source # 

Methods

rnf :: SizeUnit -> () #

type Rep SizeUnit Source # 
type Rep SizeUnit = D1 (MetaData "SizeUnit" "B9.DiskImages" "b9-0.5.30-JIpfhe2WUzZ314Dg9ph204" False) ((:+:) ((:+:) (C1 (MetaCons "B" PrefixI False) U1) (C1 (MetaCons "KB" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MB" PrefixI False) U1) (C1 (MetaCons "GB" PrefixI False) U1)))

data ImageResize Source #

How to resize an image file.

Constructors

ResizeImage ImageSize

Resize the image but not the file system. Note that a file system contained in the image file might be corrupted by this operation. To not only resize the image file but also the fil system contained in it, use Resize.

Resize ImageSize

Resize an image and the contained file system.

ShrinkToMinimum

Resize an image and the contained file system to the smallest size to fit the contents of the file system.

KeepSize

Do not change the image size.

Instances

Eq ImageResize Source # 
Data ImageResize Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ImageResize -> c ImageResize #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ImageResize #

toConstr :: ImageResize -> Constr #

dataTypeOf :: ImageResize -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ImageResize) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ImageResize) #

gmapT :: (forall b. Data b => b -> b) -> ImageResize -> ImageResize #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ImageResize -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ImageResize -> r #

gmapQ :: (forall d. Data d => d -> u) -> ImageResize -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ImageResize -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ImageResize -> m ImageResize #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageResize -> m ImageResize #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ImageResize -> m ImageResize #

Read ImageResize Source # 
Show ImageResize Source # 
Generic ImageResize Source # 

Associated Types

type Rep ImageResize :: * -> * #

Arbitrary ImageResize Source # 
Hashable ImageResize Source # 
Binary ImageResize Source # 
NFData ImageResize Source # 

Methods

rnf :: ImageResize -> () #

type Rep ImageResize Source # 
type Rep ImageResize = D1 (MetaData "ImageResize" "B9.DiskImages" "b9-0.5.30-JIpfhe2WUzZ314Dg9ph204" False) ((:+:) ((:+:) (C1 (MetaCons "ResizeImage" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageSize))) (C1 (MetaCons "Resize" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageSize)))) ((:+:) (C1 (MetaCons "ShrinkToMinimum" PrefixI False) U1) (C1 (MetaCons "KeepSize" PrefixI False) U1)))

type Mounted a = (a, MountPoint) Source #

A type alias that indicates that something of type a is mount at a MountPoint

Shared Images

data SharedImage Source #

SharedImage holds all data necessary to describe an instance of a shared image identified by a SharedImageName. Shared images are stored in Repositorys.

Instances

Eq SharedImage Source # 
Data SharedImage Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SharedImage -> c SharedImage #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SharedImage #

toConstr :: SharedImage -> Constr #

dataTypeOf :: SharedImage -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SharedImage) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SharedImage) #

gmapT :: (forall b. Data b => b -> b) -> SharedImage -> SharedImage #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SharedImage -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SharedImage -> r #

gmapQ :: (forall d. Data d => d -> u) -> SharedImage -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SharedImage -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SharedImage -> m SharedImage #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImage -> m SharedImage #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImage -> m SharedImage #

Ord SharedImage Source #

Shared images are orderd by name, build date and build id

Read SharedImage Source # 
Show SharedImage Source # 
Generic SharedImage Source # 

Associated Types

type Rep SharedImage :: * -> * #

Hashable SharedImage Source # 
Binary SharedImage Source # 
NFData SharedImage Source # 

Methods

rnf :: SharedImage -> () #

type Rep SharedImage Source # 

newtype SharedImageName Source #

The name of the image is the de-facto identifier for push, pull, From and Share. B9 always selects the newest version the shared image identified by that name when using a shared image as an ImageSource. This is a wrapper around a string that identifies a SharedImage

Constructors

SharedImageName String 

Instances

Eq SharedImageName Source # 
Data SharedImageName Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SharedImageName -> c SharedImageName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SharedImageName #

toConstr :: SharedImageName -> Constr #

dataTypeOf :: SharedImageName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SharedImageName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SharedImageName) #

gmapT :: (forall b. Data b => b -> b) -> SharedImageName -> SharedImageName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SharedImageName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SharedImageName -> r #

gmapQ :: (forall d. Data d => d -> u) -> SharedImageName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SharedImageName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SharedImageName -> m SharedImageName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImageName -> m SharedImageName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImageName -> m SharedImageName #

Ord SharedImageName Source # 
Read SharedImageName Source # 
Show SharedImageName Source # 
Arbitrary SharedImageName Source # 
Hashable SharedImageName Source # 
Binary SharedImageName Source # 
NFData SharedImageName Source # 

Methods

rnf :: SharedImageName -> () #

newtype SharedImageDate Source #

The exact time that build job started. This is a wrapper around a string contains the build date of a SharedImage; this is purely additional convenience and typesafety

Constructors

SharedImageDate String 

Instances

Eq SharedImageDate Source # 
Data SharedImageDate Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SharedImageDate -> c SharedImageDate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SharedImageDate #

toConstr :: SharedImageDate -> Constr #

dataTypeOf :: SharedImageDate -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SharedImageDate) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SharedImageDate) #

gmapT :: (forall b. Data b => b -> b) -> SharedImageDate -> SharedImageDate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SharedImageDate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SharedImageDate -> r #

gmapQ :: (forall d. Data d => d -> u) -> SharedImageDate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SharedImageDate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SharedImageDate -> m SharedImageDate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImageDate -> m SharedImageDate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImageDate -> m SharedImageDate #

Ord SharedImageDate Source # 
Read SharedImageDate Source # 
Show SharedImageDate Source # 
Hashable SharedImageDate Source # 
Binary SharedImageDate Source # 
NFData SharedImageDate Source # 

Methods

rnf :: SharedImageDate -> () #

newtype SharedImageBuildId Source #

Every B9 build running in a B9Monad contains a random unique id that is generated once per build (no matter how many artifacts are created in that build) This field contains the build id of the build that created the shared image instance. This is A wrapper around a string contains the build id of a SharedImage; this is purely additional convenience and typesafety

Instances

Eq SharedImageBuildId Source # 
Data SharedImageBuildId Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SharedImageBuildId -> c SharedImageBuildId #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SharedImageBuildId #

toConstr :: SharedImageBuildId -> Constr #

dataTypeOf :: SharedImageBuildId -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SharedImageBuildId) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SharedImageBuildId) #

gmapT :: (forall b. Data b => b -> b) -> SharedImageBuildId -> SharedImageBuildId #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SharedImageBuildId -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SharedImageBuildId -> r #

gmapQ :: (forall d. Data d => d -> u) -> SharedImageBuildId -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SharedImageBuildId -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SharedImageBuildId -> m SharedImageBuildId #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImageBuildId -> m SharedImageBuildId #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SharedImageBuildId -> m SharedImageBuildId #

Ord SharedImageBuildId Source # 
Read SharedImageBuildId Source # 
Show SharedImageBuildId Source # 
Hashable SharedImageBuildId Source # 
Binary SharedImageBuildId Source # 
NFData SharedImageBuildId Source # 

Methods

rnf :: SharedImageBuildId -> () #

Constroctor and accessors for Image ImageTarget ImageSource

imageFileName :: Image -> FilePath Source #

Return the name of the file corresponding to an Image

getImageDestinationOutputFiles :: ImageTarget -> [FilePath] Source #

Return the files generated for a LocalFile or a LiveInstallerImage; SharedImage and Transient are treated like they have no ouput files because the output files are manged by B9.

imageDestinationSharedImageName :: ImageDestination -> Maybe SharedImageName Source #

Return the name of a shared image, if the ImageDestination is a Share destination

imageSourceSharedImageName :: ImageSource -> Maybe SharedImageName Source #

Return the name of a shared source image, if the ImageSource is a From source

isPartitioned :: Partition -> Bool Source #

Return true if a Partition parameter is actually refering to a partition, false if it is NoPT

getPartition :: Partition -> Int Source #

Return the Partition index or throw a runtime error if aplied to NoPT

imageFileExtension :: ImageType -> String Source #

Return the file name extension of an image file with a specific image format.

changeImageFormat :: ImageType -> Image -> Image Source #

Change the image file format and also rename the image file name to have the appropriate file name extension. See imageFileExtension and replaceExtension

Constructors and accessors for ImageSources

Constructors and accessors for SharedImages

siName :: SharedImage -> SharedImageName Source #

Return the name of a shared image.

siDate :: SharedImage -> SharedImageDate Source #

Return the date of a shared image.

siBuildId :: SharedImage -> SharedImageBuildId Source #

Return the build id of a shared image.

prettyPrintSharedImages :: [SharedImage] -> String Source #

Print the contents of the shared image in one line

sharedImageImage :: SharedImage -> Image Source #

Return the disk image of an sharedImage

sharedImageFileName :: SharedImage -> FilePath Source #

Calculate the path to the text file holding the serialized SharedImage relative to the directory of shared images in a repository.

sharedImageDefaultImageType :: ImageType Source #

The internal image type to use as best guess when dealing with a From value.

Constructors for ImageTargets

transientCOWImage :: FilePath -> FilePath -> ImageTarget Source #

Use a QCow2 image with an Ext4 file system

shareSharedImage :: SharedImageName -> SharedImageName -> FilePath -> ImageTarget Source #

Share an image based on a shared image

cowToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #

Export a QCow2 image file with Ext4 fs as a local file

localToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #

Export a QCow2 image file with Ext4 fs as a local file

partition1ToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #

Create a local image file from the contents of the first partition of a local QCow2 image.

ImageTarget Transformations

splitToIntermediateSharedImage :: ImageTarget -> SharedImageName -> (ImageTarget, ImageTarget) Source #

Split any image target into two image targets, one for creating an intermediate shared image and one from the intermediate shared image to the output image.

Arbitrary instances for quickcheck