Safe Haskell | None |
---|---|
Language | Haskell2010 |
- Data types for disk image description, e.g.
ImageTarget
, - Shared Images
- Constructor and accessors for
Image
ImageTarget
ImageSource
- Constructors and accessors for
ImageSource
s - Constructors and accessors for
SharedImage
s - Constructors for
ImageTarget
s ImageTarget
TransformationsArbitrary
instances for quickcheck
Data types that describe all B9 relevant elements of virtual machine disk images.
Synopsis
- data ImageTarget = ImageTarget ImageDestination ImageSource MountPoint
- data MountPoint
- data ImageDestination
- data ImageSource
- data Partition
- data Image = Image FilePath ImageType FileSystem
- data ImageType
- data FileSystem
- = NoFileSystem
- | Ext4
- | Ext4_64
- | ISO9660
- | VFAT
- data ImageSize = ImageSize Int SizeUnit
- bytesToKiloBytes :: Int -> ImageSize
- imageSizeToKiB :: ImageSize -> Int
- sizeUnitKiB :: SizeUnit -> Int
- normalizeSize :: ImageSize -> ImageSize
- addImageSize :: ImageSize -> ImageSize -> ImageSize
- data SizeUnit
- data ImageResize
- type Mounted a = (a, MountPoint)
- data SharedImage = SharedImage SharedImageName SharedImageDate SharedImageBuildId ImageType FileSystem
- newtype SharedImageName = SharedImageName String
- fromSharedImageName :: SharedImageName -> String
- newtype SharedImageDate = SharedImageDate String
- newtype SharedImageBuildId = SharedImageBuildId String
- fromSharedImageBuildId :: SharedImageBuildId -> String
- sharedImagesToMap :: [SharedImage] -> Map SharedImageName (Set SharedImage)
- takeLatestSharedImage :: [SharedImage] -> Maybe SharedImage
- imageFileName :: Image -> FilePath
- imageImageType :: Image -> ImageType
- getImageDestinationOutputFiles :: ImageTarget -> [FilePath]
- imageDestinationSharedImageName :: ImageDestination -> Maybe SharedImageName
- imageSourceSharedImageName :: ImageSource -> Maybe SharedImageName
- itImageDestination :: ImageTarget -> ImageDestination
- itImageSource :: ImageTarget -> ImageSource
- itImageMountPoint :: ImageTarget -> MountPoint
- isPartitioned :: Partition -> Bool
- getPartition :: Partition -> Int
- imageFileExtension :: ImageType -> String
- changeImageFormat :: ImageType -> Image -> Image
- changeImageDirectory :: FilePath -> Image -> Image
- getImageSourceImageType :: ImageSource -> Maybe ImageType
- sharedImageName :: SharedImage -> SharedImageName
- sharedImageDate :: SharedImage -> SharedImageDate
- sharedImageBuildId :: SharedImage -> SharedImageBuildId
- prettyPrintSharedImages :: Set SharedImage -> String
- sharedImageImage :: SharedImage -> Image
- sharedImageFileName :: SharedImage -> FilePath
- sharedImagesRootDirectory :: FilePath
- sharedImageFileExtension :: String
- sharedImageDefaultImageType :: ImageType
- transientCOWImage :: FilePath -> FilePath -> ImageTarget
- transientSharedImage :: SharedImageName -> FilePath -> ImageTarget
- transientLocalImage :: FilePath -> FilePath -> ImageTarget
- shareCOWImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget
- shareSharedImage :: SharedImageName -> SharedImageName -> FilePath -> ImageTarget
- shareLocalImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget
- cowToliveInstallerImage :: String -> FilePath -> FilePath -> FilePath -> ImageTarget
- cowToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
- localToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
- partition1ToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
- splitToIntermediateSharedImage :: ImageTarget -> SharedImageName -> (ImageTarget, ImageTarget)
- arbitrarySharedImageName :: Gen String
- unitTests :: Spec
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
data MountPoint Source #
A mount point or NotMounted
Instances
data ImageDestination Source #
The destination of an image.
Share String ImageType ImageResize | Create the image and some meta data so that other
builds can use them as |
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
data ImageSource Source #
Specification of how the image to build is obtained.
EmptyImage String FileSystem ImageType ImageSize | Create an empty image file having a file system label
(first parameter), a file system type (e.g. |
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 |
From String ImageResize | Use an image previously shared by via |
Instances
The partition to extract.
Instances
Eq Partition Source # | |
Data Partition Source # | |
Defined in B9.DiskImages 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 # | |
Arbitrary Partition Source # | |
Hashable Partition Source # | |
Defined in B9.DiskImages | |
Binary Partition Source # | |
NFData Partition Source # | |
Defined in B9.DiskImages | |
type Rep Partition Source # | |
Defined in B9.DiskImages type Rep Partition = D1 (MetaData "Partition" "B9.DiskImages" "b9-2.1.0-RZRDTT94jm9r60J5nt33" False) (C1 (MetaCons "NoPT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Partition" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) |
A vm disk image file consisting of a path to the image file, and the type and file system.
Instances
Eq Image Source # | |
Data Image Source # | |
Defined in B9.DiskImages 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 # 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 # | |
Generic Image Source # | |
Arbitrary Image Source # | |
Hashable Image Source # | |
Defined in B9.DiskImages | |
Binary Image Source # | |
NFData Image Source # | |
Defined in B9.DiskImages | |
type Rep Image Source # | |
Defined in B9.DiskImages type Rep Image = D1 (MetaData "Image" "B9.DiskImages" "b9-2.1.0-RZRDTT94jm9r60J5nt33" False) (C1 (MetaCons "Image" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ImageType) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FileSystem)))) |
An image type defines the actual file format of a file containing file systems. These are like virtual harddrives
Instances
Eq ImageType Source # | |
Data ImageType Source # | |
Defined in B9.DiskImages 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 # | |
Function ImageType Source # | |
Arbitrary ImageType Source # | |
CoArbitrary ImageType Source # | |
Defined in B9.DiskImages coarbitrary :: ImageType -> Gen b -> Gen b # | |
Hashable ImageType Source # | |
Defined in B9.DiskImages | |
Binary ImageType Source # | |
NFData ImageType Source # | |
Defined in B9.DiskImages | |
type Rep ImageType Source # | |
Defined in B9.DiskImages |
data FileSystem Source #
The file systems that b9 can use and convert.
Instances
A data type for image file or file system size; instead of passing Int
s
around this also captures a size unit so that the Int
can be kept small
Instances
sizeUnitKiB :: SizeUnit -> Int Source #
Convert a SizeUnit
to the number of kibi bytes one element represents.
normalizeSize :: ImageSize -> ImageSize Source #
Choose the greatest unit possible to exactly represent an ImageSize
.
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.
Instances
Bounded SizeUnit Source # | |
Enum SizeUnit Source # | |
Eq SizeUnit Source # | |
Data SizeUnit Source # | |
Defined in B9.DiskImages 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 # | |
Defined in B9.DiskImages | |
Read SizeUnit Source # | |
Show SizeUnit Source # | |
Generic SizeUnit Source # | |
Arbitrary SizeUnit Source # | |
Hashable SizeUnit Source # | |
Defined in B9.DiskImages | |
Binary SizeUnit Source # | |
NFData SizeUnit Source # | |
Defined in B9.DiskImages | |
type Rep SizeUnit Source # | |
data ImageResize Source #
How to resize an image file.
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 ImageSize | Resize an image and the contained file system. |
ShrinkToMinimumAndIncrease ImageSize | Shrink to minimum size needed and increase by the amount given. |
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
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
Repository
s.
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
fromSharedImageName :: SharedImageName -> String Source #
Get the String representation of a 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
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
fromSharedImageBuildId :: SharedImageBuildId -> String Source #
Get the String representation of a SharedImageBuildId
.
sharedImagesToMap :: [SharedImage] -> Map SharedImageName (Set SharedImage) Source #
Transform a list of SharedImage
values into a Map
that associates
each SharedImageName
with a Set
of the actual images with that name.
The Set
contains values of type
.SharedImage
The Ord
instance of SharedImage
sorts by name first and then by
sharedImageDate
, since the values in a Set
share the same sharedImageName
,
they are effectively orderd by build date, which is useful the shared image cleanup.
Since: 1.1.0
takeLatestSharedImage :: [SharedImage] -> Maybe SharedImage Source #
Return the SharedImage
with the highest sharedImageDate
.
Since: 1.1.0
Constructor and accessors for Image
ImageTarget
ImageSource
getImageDestinationOutputFiles :: ImageTarget -> [FilePath] Source #
Return the files generated for a LocalFile
or a LiveInstallerImage
; SharedImage
and Transient
are treated like they have no output 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
itImageDestination :: ImageTarget -> ImageDestination Source #
Get the ImageDestination
of an ImageTarget
itImageSource :: ImageTarget -> ImageSource Source #
Get the ImageSource
of an ImageTarget
itImageMountPoint :: ImageTarget -> MountPoint Source #
Get the MountPoint
of an ImageTarget
isPartitioned :: Partition -> Bool Source #
getPartition :: Partition -> Int Source #
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 ImageSource
s
Constructors and accessors for SharedImage
s
sharedImageName :: SharedImage -> SharedImageName Source #
Return the name of a shared image.
sharedImageDate :: SharedImage -> SharedImageDate Source #
Return the build date of a shared image.
sharedImageBuildId :: SharedImage -> SharedImageBuildId Source #
Return the build id of a shared image.
prettyPrintSharedImages :: Set 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 ImageTarget
s
transientCOWImage :: FilePath -> FilePath -> ImageTarget Source #
transientSharedImage :: SharedImageName -> FilePath -> ImageTarget Source #
Use a shared image
transientLocalImage :: FilePath -> FilePath -> ImageTarget Source #
Use a shared image
shareCOWImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget Source #
shareSharedImage :: SharedImageName -> SharedImageName -> FilePath -> ImageTarget Source #
Share an image based on a shared image
shareLocalImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget Source #
cowToliveInstallerImage :: String -> FilePath -> FilePath -> FilePath -> ImageTarget Source #
cowToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #
localToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget Source #
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.