module B9.DiskImages where
import B9.QCUtil
import GHC.Generics (Generic)
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
#endif
import Control.Parallel.Strategies
import Data.Binary
import Data.Data
import Data.Hashable
import Data.Maybe
import Data.Semigroup
import System.FilePath
import Test.QuickCheck
import qualified Text.PrettyPrint.Boxes as Boxes
import Text.Printf
data ImageTarget = ImageTarget
ImageDestination
ImageSource
MountPoint
deriving (Read, Show, Typeable, Data, Eq,Generic)
instance Hashable ImageTarget
instance Binary ImageTarget
instance NFData ImageTarget
data MountPoint = MountPoint FilePath | NotMounted
deriving (Show, Read, Typeable, Data, Eq,Generic)
instance Hashable MountPoint
instance Binary MountPoint
instance NFData MountPoint
data ImageDestination = Share String ImageType ImageResize
| LiveInstallerImage String FilePath ImageResize
| LocalFile Image ImageResize
| Transient
deriving (Read, Show, Typeable, Data,Eq,Generic)
instance Hashable ImageDestination
instance Binary ImageDestination
instance NFData ImageDestination
data ImageSource = EmptyImage String FileSystem ImageType ImageSize
| CopyOnWrite Image
| SourceImage Image Partition ImageResize
| From String ImageResize
deriving (Show,Read,Typeable,Data,Eq,Generic)
instance Hashable ImageSource
instance Binary ImageSource
instance NFData ImageSource
data Partition = NoPT
| Partition Int
deriving (Eq, Show, Read, Typeable, Data,Generic)
instance Hashable Partition
instance Binary Partition
instance NFData Partition
data Image = Image FilePath ImageType FileSystem
deriving (Eq, Show, Read, Typeable, Data,Generic)
instance Hashable Image
instance Binary Image
instance NFData Image
data ImageType = Raw | QCow2 | Vmdk
deriving (Eq,Read,Typeable,Data,Show,Generic)
instance Hashable ImageType
instance Binary ImageType
instance NFData ImageType
data FileSystem = NoFileSystem | Ext4 | ISO9660 | VFAT
deriving (Eq,Show,Read,Typeable,Data,Generic)
instance Hashable FileSystem
instance Binary FileSystem
instance NFData FileSystem
data ImageSize = ImageSize Int SizeUnit
deriving (Eq, Show, Read, Typeable, Data, Generic)
instance Hashable ImageSize
instance Binary ImageSize
instance NFData ImageSize
data SizeUnit = B | KB | MB | GB
deriving (Eq, Show, Read, Ord, Typeable, Data, Generic)
instance Hashable SizeUnit
instance Binary SizeUnit
instance NFData SizeUnit
data ImageResize = ResizeImage ImageSize
| Resize ImageSize
| ShrinkToMinimum
| KeepSize
deriving (Eq, Show, Read, Typeable, Data, Generic)
instance Hashable ImageResize
instance Binary ImageResize
instance NFData ImageResize
type Mounted a = (a, MountPoint)
data SharedImage =
SharedImage SharedImageName
SharedImageDate
SharedImageBuildId
ImageType
FileSystem
deriving (Eq,Read,Show,Typeable,Data,Generic)
instance Hashable SharedImage
instance Binary SharedImage
instance NFData SharedImage
newtype SharedImageName = SharedImageName String deriving (Eq,Ord,Read,Show,Typeable,Data,Hashable,Binary,NFData)
newtype SharedImageDate = SharedImageDate String deriving (Eq,Ord,Read,Show,Typeable,Data,Hashable,Binary,NFData)
newtype SharedImageBuildId = SharedImageBuildId String deriving (Eq,Ord,Read,Show,Typeable,Data,Hashable,Binary,NFData)
instance Ord SharedImage where
compare (SharedImage n d b _ _) (SharedImage n' d' b' _ _) =
compare n n' <> compare d d' <> compare b b'
imageFileName :: Image -> FilePath
imageFileName (Image f _ _) = f
imageImageType :: Image -> ImageType
imageImageType (Image _ t _) = t
getImageDestinationOutputFiles :: ImageTarget -> [FilePath]
getImageDestinationOutputFiles (ImageTarget d _ _) =
case d of
LiveInstallerImage liName liPath _ ->
let path = liPath </> "machines" </> liName </> "disks" </> "raw"
in [path </> "0.raw", path </> "0.size", path </> "VERSION"]
LocalFile (Image lfPath _ _) _ -> [lfPath]
_ -> []
imageDestinationSharedImageName :: ImageDestination -> Maybe SharedImageName
imageDestinationSharedImageName (Share n _ _) = Just (SharedImageName n)
imageDestinationSharedImageName _ = Nothing
imageSourceSharedImageName :: ImageSource -> Maybe SharedImageName
imageSourceSharedImageName (From n _) = Just (SharedImageName n)
imageSourceSharedImageName _ = Nothing
itImageDestination :: ImageTarget -> ImageDestination
itImageDestination (ImageTarget d _ _) = d
itImageSource :: ImageTarget -> ImageSource
itImageSource (ImageTarget _ s _) = s
itImageMountPoint :: ImageTarget -> MountPoint
itImageMountPoint (ImageTarget _ _ m) = m
isPartitioned :: Partition -> Bool
isPartitioned p
| p == NoPT = False
| otherwise = True
getPartition :: Partition -> Int
getPartition (Partition p) = p
getPartition NoPT = error "No partitions!"
imageFileExtension :: ImageType -> String
imageFileExtension Raw = "raw"
imageFileExtension QCow2 = "qcow2"
imageFileExtension Vmdk = "vmdk"
changeImageFormat :: ImageType -> Image -> Image
changeImageFormat fmt' (Image img _ fs) = Image img' fmt' fs
where img' = replaceExtension img (imageFileExtension fmt')
changeImageDirectory :: FilePath -> Image -> Image
changeImageDirectory dir (Image img fmt fs) = Image img' fmt fs
where img' = dir </> takeFileName img
getImageSourceImageType :: ImageSource -> Maybe ImageType
getImageSourceImageType (EmptyImage _ _ t _) = Just t
getImageSourceImageType (CopyOnWrite i) = Just $ imageImageType i
getImageSourceImageType (SourceImage i _ _) = Just $ imageImageType i
getImageSourceImageType (From _ _) = Nothing
siName :: SharedImage -> SharedImageName
siName (SharedImage n _ _ _ _) = n
siDate :: SharedImage -> SharedImageDate
siDate (SharedImage _ n _ _ _) = n
siBuildId :: SharedImage -> SharedImageBuildId
siBuildId (SharedImage _ _ n _ _) = n
prettyPrintSharedImages :: [SharedImage] -> String
prettyPrintSharedImages imgs = Boxes.render table
where
table = Boxes.hsep 1 Boxes.left cols
where
cols = [nameC, dateC, idC]
where
nameC = col "Name" ((\(SharedImageName n) -> n) . siName)
dateC = col "Date" ((\(SharedImageDate n) -> n) . siDate)
idC = col "ID" ((\(SharedImageBuildId n) -> n) . siBuildId)
col title accessor =
(Boxes.text title) Boxes.// (Boxes.vcat Boxes.left cells)
where
cells = Boxes.text <$> accessor <$> imgs
sharedImageImage :: SharedImage -> Image
sharedImageImage (SharedImage (SharedImageName n) _ (SharedImageBuildId bid) sharedImageType sharedImageFileSystem) =
Image
(n ++ "_" ++ bid <.> imageFileExtension sharedImageType)
sharedImageType
sharedImageFileSystem
sharedImageFileName :: SharedImage -> FilePath
sharedImageFileName (SharedImage (SharedImageName n) _ (SharedImageBuildId bid) _ _) =
n ++ "_" ++ bid <.> sharedImageFileExtension
sharedImagesRootDirectory :: FilePath
sharedImagesRootDirectory = "b9_shared_images"
sharedImageFileExtension :: String
sharedImageFileExtension = "b9si"
sharedImageDefaultImageType :: ImageType
sharedImageDefaultImageType = QCow2
transientCOWImage :: FilePath -> FilePath -> ImageTarget
transientCOWImage fileName mountPoint =
ImageTarget
Transient
(CopyOnWrite (Image fileName QCow2 Ext4))
(MountPoint mountPoint)
transientSharedImage :: SharedImageName -> FilePath -> ImageTarget
transientSharedImage (SharedImageName name) mountPoint =
ImageTarget Transient (From name KeepSize) (MountPoint mountPoint)
transientLocalImage :: FilePath -> FilePath -> ImageTarget
transientLocalImage name mountPoint =
ImageTarget Transient (From name KeepSize) (MountPoint mountPoint)
shareCOWImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget
shareCOWImage srcFilename (SharedImageName destName) mountPoint =
ImageTarget
(Share destName QCow2 KeepSize)
(CopyOnWrite (Image srcFilename QCow2 Ext4))
(MountPoint mountPoint)
shareSharedImage :: SharedImageName
-> SharedImageName
-> FilePath
-> ImageTarget
shareSharedImage (SharedImageName srcName) (SharedImageName destName) mountPoint =
ImageTarget
(Share destName QCow2 KeepSize)
(From srcName KeepSize)
(MountPoint mountPoint)
shareLocalImage :: FilePath -> SharedImageName -> FilePath -> ImageTarget
shareLocalImage srcName (SharedImageName destName) mountPoint =
ImageTarget
(Share destName QCow2 KeepSize)
(SourceImage (Image srcName QCow2 Ext4) NoPT KeepSize)
(MountPoint mountPoint)
cowToliveInstallerImage :: String
-> FilePath
-> FilePath
-> FilePath
-> ImageTarget
cowToliveInstallerImage srcName destName outDir mountPoint =
ImageTarget
(LiveInstallerImage destName outDir KeepSize)
(CopyOnWrite (Image srcName QCow2 Ext4))
(MountPoint mountPoint)
cowToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
cowToLocalImage srcName destName mountPoint =
ImageTarget
(LocalFile (Image destName QCow2 Ext4) KeepSize)
(CopyOnWrite (Image srcName QCow2 Ext4))
(MountPoint mountPoint)
localToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
localToLocalImage srcName destName mountPoint =
ImageTarget
(LocalFile (Image destName QCow2 Ext4) KeepSize)
(SourceImage (Image srcName QCow2 Ext4) NoPT KeepSize)
(MountPoint mountPoint)
partition1ToLocalImage :: FilePath -> FilePath -> FilePath -> ImageTarget
partition1ToLocalImage srcName destName mountPoint =
ImageTarget
(LocalFile (Image destName QCow2 Ext4) KeepSize)
(SourceImage (Image srcName QCow2 Ext4) NoPT KeepSize)
(MountPoint mountPoint)
splitToIntermediateSharedImage :: ImageTarget
-> SharedImageName
-> (ImageTarget, ImageTarget)
splitToIntermediateSharedImage (ImageTarget dst src mnt) (SharedImageName intermediateName) =
(imgTargetShared, imgTargetExport)
where
imgTargetShared = ImageTarget intermediateTo src mnt
imgTargetExport = ImageTarget dst intermediateFrom mnt
intermediateTo =
Share
intermediateName
(fromMaybe
sharedImageDefaultImageType
(getImageSourceImageType src))
KeepSize
intermediateFrom = From intermediateName KeepSize
instance Arbitrary ImageTarget where
arbitrary =
ImageTarget <$> smaller arbitrary <*> smaller arbitrary <*>
smaller arbitrary
instance Arbitrary ImageSource where
arbitrary =
oneof
[ EmptyImage "img-label" <$> smaller arbitrary <*>
smaller arbitrary <*>
smaller arbitrary
, CopyOnWrite <$> smaller arbitrary
, SourceImage <$> smaller arbitrary <*> smaller arbitrary <*>
smaller arbitrary
, From <$> arbitrarySharedImageName <*> smaller arbitrary]
instance Arbitrary ImageDestination where
arbitrary =
oneof
[ Share <$> arbitrarySharedImageName <*> smaller arbitrary <*>
smaller arbitrary
, LiveInstallerImage "live-installer" "output-path" <$>
smaller arbitrary
, pure Transient]
instance Arbitrary MountPoint where
arbitrary = elements [MountPoint "/mnt", NotMounted]
instance Arbitrary ImageResize where
arbitrary =
oneof
[ ResizeImage <$> smaller arbitrary
, Resize <$> smaller arbitrary
, pure ShrinkToMinimum
, pure KeepSize]
instance Arbitrary Partition where
arbitrary = oneof [Partition <$> elements [0, 1, 2], pure NoPT]
instance Arbitrary Image where
arbitrary =
Image "img-file-name" <$> smaller arbitrary <*> smaller arbitrary
instance Arbitrary FileSystem where
arbitrary = elements [Ext4]
instance Arbitrary ImageType where
arbitrary = elements [Raw, QCow2, Vmdk]
instance Arbitrary ImageSize where
arbitrary = ImageSize <$> smaller arbitrary <*> smaller arbitrary
instance Arbitrary SizeUnit where
arbitrary = elements [B, KB, MB, GB]
instance Arbitrary SharedImageName where
arbitrary = SharedImageName <$> arbitrarySharedImageName
arbitrarySharedImageName :: Gen String
arbitrarySharedImageName =
elements [printf "arbitrary-shared-img-name-%d" x | x <- [0 :: Int .. 3]]