Safe Haskell | None |
---|
- create :: FilePath -> CreateParameters -> IO ()
- data CreateParameters = CreateParameters {
- createBlockSize :: BlockSize
- createDiskType :: DiskType
- createParentTimeStamp :: Maybe VhdDiffTime
- createParentUnicodeName :: Maybe ParentUnicodeName
- createParentUniqueId :: Maybe UniqueId
- createTimeStamp :: Maybe VhdDiffTime
- createUuid :: Maybe UniqueId
- createUseBatmap :: Bool
- createVirtualSize :: VirtualByteCount
- defaultCreateParameters :: CreateParameters
- getInfo :: FilePath -> IO (Either String (Header, Footer))
- snapshot :: Vhd -> FilePath -> IO ()
- readData :: Vhd -> IO ByteString
- readDataRange :: Vhd -> Word64 -> Word64 -> IO ByteString
- writeDataRange :: Vhd -> Word64 -> ByteString -> IO ()
- withVhd :: FilePath -> (Vhd -> IO a) -> IO a
- class Sized a where
- newtype BlockSize = BlockSize Word32
- newtype BlockByteAddress = BlockByteAddress Word32
- newtype BlockSectorAddress = BlockSectorAddress Word32
- newtype VirtualBlockAddress = VirtualBlockAddress Word32
- newtype VirtualByteAddress = VirtualByteAddress Word64
- type DiskGeometryCylinders = Word16
- type DiskGeometryHeads = Word8
- type DiskGeometrySectorsPerTrack = Word8
- type PhysicalByteAddress = Word64
- type PhysicalByteCount = Word64
- type PhysicalSectorAddress = Word32
- type PhysicalSectorCount = Word32
- type VirtualBlockCount = Word32
- type VirtualByteCount = Word64
- type VirtualSectorAddress = Word32
- type VirtualSectorCount = Word32
- vaddrPlus :: VirtualByteAddress -> Word64 -> VirtualByteAddress
- vaddrToBlock :: VirtualByteAddress -> BlockSize -> (VirtualBlockAddress, BlockByteAddress, Word32)
- vaddrNextBlock :: VirtualByteAddress -> BlockSize -> VirtualByteAddress
- addrToSector :: Word64 -> PhysicalSectorAddress
- data Version = Version VersionMajor VersionMinor
- type VersionMajor = Word16
- type VersionMinor = Word16
- data CreatorHostOs
- data DiskGeometry = DiskGeometry DiskGeometryCylinders DiskGeometryHeads DiskGeometrySectorsPerTrack
- data DiskType
- newtype Cookie = Cookie ByteString
- newtype CreatorApplication = CreatorApplication ByteString
- data ParentLocatorEntry = ParentLocatorEntry {}
- nullParentLocatorEntry :: ParentLocatorEntry
- newtype ParentUnicodeName = ParentUnicodeName String
- newtype ParentLocatorEntries = ParentLocatorEntries [ParentLocatorEntry]
- cookie :: ByteString -> Cookie
- creatorApplication :: ByteString -> CreatorApplication
- parentLocatorEntries :: [ParentLocatorEntry] -> ParentLocatorEntries
- parentUnicodeName :: [Char] -> ParentUnicodeName
- data Header = Header {
- headerCookie :: Cookie
- headerDataOffset :: PhysicalByteAddress
- headerTableOffset :: PhysicalByteAddress
- headerVersion :: Version
- headerMaxTableEntries :: VirtualBlockCount
- headerBlockSize :: BlockSize
- headerChecksum :: Checksum
- headerParentUniqueId :: UniqueId
- headerParentTimeStamp :: VhdDiffTime
- headerReserved1 :: ByteString
- headerParentUnicodeName :: ParentUnicodeName
- headerParentLocatorEntries :: ParentLocatorEntries
- newtype Checksum = Checksum Word32
- class Serialize a => CheckSumable a where
- calculateChecksum :: a -> Checksum
- getChecksum :: a -> Checksum
- setChecksum :: Checksum -> a -> a
- checksumCalculate :: ByteString -> Checksum
- verifyChecksum :: CheckSumable a => a -> Bool
- adjustChecksum :: CheckSumable a => a -> a
- data Footer = Footer {
- footerCookie :: Cookie
- footerIsTemporaryDisk :: Bool
- footerFormatVersion :: Version
- footerDataOffset :: PhysicalByteAddress
- footerTimeStamp :: VhdDiffTime
- footerCreatorApplication :: CreatorApplication
- footerCreatorVersion :: Version
- footerCreatorHostOs :: CreatorHostOs
- footerOriginalSize :: VirtualByteCount
- footerCurrentSize :: VirtualByteCount
- footerDiskGeometry :: DiskGeometry
- footerDiskType :: DiskType
- footerChecksum :: Checksum
- footerUniqueId :: UniqueId
- footerIsSavedState :: Bool
- data UniqueId
- uniqueId :: ByteString -> UniqueId
- randomUniqueId :: IO UniqueId
Documentation
create :: FilePath -> CreateParameters -> IO ()Source
Creates an empty VHD file with the specified parameters.
data CreateParameters Source
getInfo :: FilePath -> IO (Either String (Header, Footer))Source
Retrieves the header and footer from a VHD file.
readData :: Vhd -> IO ByteStringSource
Reads data from the whole virtual address space of the given VHD.
:: Vhd | Vhd chain to read from |
-> Word64 | offset address in the VHD |
-> Word64 | number of byte to read |
-> IO ByteString |
Reads data from the given virtual address range of the given VHD.
TODO: modify this function to read sub-blocks where appropriate.
:: Vhd | Vhd chain to write to |
-> Word64 | offset address in the VHD |
-> ByteString | the data to write in the VHD |
-> IO () |
Writes data to the given virtual address of the given VHD.
block size
newtype BlockByteAddress Source
The offset from the beginning of a block in bytes
newtype BlockSectorAddress Source
The offset from the beginning of a block in sectors
newtype VirtualBlockAddress Source
The absolute number of the block
newtype VirtualByteAddress Source
An absolute address in byte in the vhd content space
type DiskGeometryHeads = Word8Source
type PhysicalByteAddress = Word64Source
type PhysicalByteCount = Word64Source
type PhysicalSectorCount = Word32Source
type VirtualBlockCount = Word32Source
type VirtualByteCount = Word64Source
type VirtualSectorAddress = Word32Source
type VirtualSectorCount = Word32Source
vaddrToBlock :: VirtualByteAddress -> BlockSize -> (VirtualBlockAddress, BlockByteAddress, Word32)Source
vaddrNextBlock :: VirtualByteAddress -> BlockSize -> VirtualByteAddressSource
increment the virtual address to align to the next block
type VersionMajor = Word16Source
type VersionMinor = Word16Source
data CreatorHostOs Source
data DiskGeometry Source
newtype CreatorApplication Source
newtype ParentUnicodeName Source
newtype ParentLocatorEntries Source
cookie :: ByteString -> CookieSource
smart constructor for Cookie
creatorApplication :: ByteString -> CreatorApplicationSource
smart constructor for CreatorApplication
parentLocatorEntries :: [ParentLocatorEntry] -> ParentLocatorEntriesSource
smart constructor for ParentLocatorEntries
class Serialize a => CheckSumable a whereSource
calculateChecksum :: a -> ChecksumSource
getChecksum :: a -> ChecksumSource
setChecksum :: Checksum -> a -> aSource
verifyChecksum :: CheckSumable a => a -> BoolSource
adjustChecksum :: CheckSumable a => a -> aSource
uniqueId :: ByteString -> UniqueIdSource
smart constructor for uniqueId