hscdio-0.1.0.0: Haskell bindings to the libcdio disc-reading library.
Copyright(c) 2018-2021 Sam May
LicenseGPL-3.0-or-later
Maintainerag@eitilt.life
Stabilitystable
Portabilitynon-portable (requires libcdio)
Safe HaskellNone
LanguageHaskell2010

Foreign.Libcdio.Sector

Description

The bulk of this module deals with the sizes of various parts of disc sectors, and so a brief description of each is likely helpful; for more information, see the libcdio user guide, or any of the other various documentation that people have written. Depending on the accuracy required, multiple methods of encoding data onto discs were developed enabling different degrees of error detection and recovery. For ease of implementation, these check regions are spaced evenly throughout the data, effectively dividing it into blocks of sectorSize bytes. The inner structure of each block is thus:

Sector layout

Audio

As audio CDs are intended to be listened to by human ears, often in noisy environments, byte-perfect fidelity was deemed unnecessary; data fills the entire sector without leaving room for checksums or synchronization points. This structure is more technically described as "CD-DA" (Digital Audio).

|- sectorSize -|

Data (Mode 1)

The original structure described in the Yellow Book standard. Mode 1, Form 1 is notably the layout used for CD-ROMs. It would be most correct to describe these as "Mode 1" and "Mode 2" with no reference to form, but the libcdio documentation has adopted the practice below as a parallel to the XA names.

Mode 1, Form 1

|------------------------------------ sectorSize -------------------------------------|
 syncSize + headerSize + dataSize + errorDetectionSize + padSize + errorCorrectionSize
           |------------------------------- syncedSize -------------------------------|
                                   |-------------------- tailSize --------------------|

Mode 1, Form 2

|------------ sectorSize -----------|
 syncSize + headerSize + dataSizeRaw
           |------ syncedSize ------|

XA (Mode 2)

Developed as a later extension to the Mode 1, Form 2 (technically just "Mode 2") standard above to allow different data to be interleaved.

Mode 2, Form 1

|--------------------------------------- sectorSize ----------------------------------------|
 syncSize + headerSize + subheaderSize + dataSize + errorDetectionSize + errorCorrectionSize
|---------- syncHeaderSizeXa ---------|            |-------------- tailSizeXa --------------|
           |------ headerSizeXa ------|
           |---------------------------------- syncedSize ----------------------------------|
                        |--------------------------- dataSizeRaw ---------------------------|

Mode 2, Form 2

|--------------------------- sectorSize --------------------------|
 syncSize + headerSize + subheaderSize + dataSizeRawXa + padSizeXa
|---------- syncHeaderSizeXa ---------|
           |------ headerSizeXa ------|
           |--------------------- syncedSize ---------------------|
                        |-------------- dataSizeRaw --------------|
                        |----- taggedDataSizeRaw -----|

sector.h

Defines

Types

  • cdio_cd_minutes_sectors (removed; most values were simple calculations on CDIO_CD_FRAMES_PER_MIN, which can be done manually)

Symbols

Sound.Libcdio.Read.Data

All size constants (e.g. sectorSize) likewise removed as unnecessary.

Synopsis

Types

data SubchannelData Source #

Types of information stored on disc subchannels.

Instances

Instances details
Bounded SubchannelData Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum SubchannelData Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq SubchannelData Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord SubchannelData Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read SubchannelData Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show SubchannelData Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

type Flags = BitArray Flag Source #

The collection of metadata describing a particular track.

data Flag Source #

Metadata describing the layout or type of data on a track.

Instances

Instances details
Bounded Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

succ :: Flag -> Flag #

pred :: Flag -> Flag #

toEnum :: Int -> Flag #

fromEnum :: Flag -> Int #

enumFrom :: Flag -> [Flag] #

enumFromThen :: Flag -> Flag -> [Flag] #

enumFromTo :: Flag -> Flag -> [Flag] #

enumFromThenTo :: Flag -> Flag -> Flag -> [Flag] #

Eq Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

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

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

Ord Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

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

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Read Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Ix Flag Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

range :: (Flag, Flag) -> [Flag] #

index :: (Flag, Flag) -> Flag -> Int #

unsafeIndex :: (Flag, Flag) -> Flag -> Int #

inRange :: (Flag, Flag) -> Flag -> Bool #

rangeSize :: (Flag, Flag) -> Int #

unsafeRangeSize :: (Flag, Flag) -> Int #

data Lba Source #

The type-safe representation of a Logical Block Address, counting sectors from the very beginning of the write session. See also Lsn.

Instances

Instances details
Bounded Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

minBound :: Lba #

maxBound :: Lba #

Enum Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

succ :: Lba -> Lba #

pred :: Lba -> Lba #

toEnum :: Int -> Lba #

fromEnum :: Lba -> Int #

enumFrom :: Lba -> [Lba] #

enumFromThen :: Lba -> Lba -> [Lba] #

enumFromTo :: Lba -> Lba -> [Lba] #

enumFromThenTo :: Lba -> Lba -> Lba -> [Lba] #

Eq Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

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

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

Integral Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

quot :: Lba -> Lba -> Lba #

rem :: Lba -> Lba -> Lba #

div :: Lba -> Lba -> Lba #

mod :: Lba -> Lba -> Lba #

quotRem :: Lba -> Lba -> (Lba, Lba) #

divMod :: Lba -> Lba -> (Lba, Lba) #

toInteger :: Lba -> Integer #

Num Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

(+) :: Lba -> Lba -> Lba #

(-) :: Lba -> Lba -> Lba #

(*) :: Lba -> Lba -> Lba #

negate :: Lba -> Lba #

abs :: Lba -> Lba #

signum :: Lba -> Lba #

fromInteger :: Integer -> Lba #

Ord Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

compare :: Lba -> Lba -> Ordering #

(<) :: Lba -> Lba -> Bool #

(<=) :: Lba -> Lba -> Bool #

(>) :: Lba -> Lba -> Bool #

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

max :: Lba -> Lba -> Lba #

min :: Lba -> Lba -> Lba #

Read Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Real Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

toRational :: Lba -> Rational #

Show Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

showsPrec :: Int -> Lba -> ShowS #

show :: Lba -> String #

showList :: [Lba] -> ShowS #

Ix Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

range :: (Lba, Lba) -> [Lba] #

index :: (Lba, Lba) -> Lba -> Int #

unsafeIndex :: (Lba, Lba) -> Lba -> Int #

inRange :: (Lba, Lba) -> Lba -> Bool #

rangeSize :: (Lba, Lba) -> Int #

unsafeRangeSize :: (Lba, Lba) -> Int #

PrintfArg Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Storable Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

sizeOf :: Lba -> Int #

alignment :: Lba -> Int #

peekElemOff :: Ptr Lba -> Int -> IO Lba #

pokeElemOff :: Ptr Lba -> Int -> Lba -> IO () #

peekByteOff :: Ptr b -> Int -> IO Lba #

pokeByteOff :: Ptr b -> Int -> Lba -> IO () #

peek :: Ptr Lba -> IO Lba #

poke :: Ptr Lba -> Lba -> IO () #

Bits Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

(.&.) :: Lba -> Lba -> Lba #

(.|.) :: Lba -> Lba -> Lba #

xor :: Lba -> Lba -> Lba #

complement :: Lba -> Lba #

shift :: Lba -> Int -> Lba #

rotate :: Lba -> Int -> Lba #

zeroBits :: Lba #

bit :: Int -> Lba #

setBit :: Lba -> Int -> Lba #

clearBit :: Lba -> Int -> Lba #

complementBit :: Lba -> Int -> Lba #

testBit :: Lba -> Int -> Bool #

bitSizeMaybe :: Lba -> Maybe Int #

bitSize :: Lba -> Int #

isSigned :: Lba -> Bool #

shiftL :: Lba -> Int -> Lba #

unsafeShiftL :: Lba -> Int -> Lba #

shiftR :: Lba -> Int -> Lba #

unsafeShiftR :: Lba -> Int -> Lba #

rotateL :: Lba -> Int -> Lba #

rotateR :: Lba -> Int -> Lba #

popCount :: Lba -> Int #

FiniteBits Lba Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

data Lsn Source #

The type-safe representation of a Logical Sector Number, counting sectors from the start of track 1; this notably excludes the blank session lead-in. See also Lba.

Instances

Instances details
Bounded Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

minBound :: Lsn #

maxBound :: Lsn #

Enum Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

succ :: Lsn -> Lsn #

pred :: Lsn -> Lsn #

toEnum :: Int -> Lsn #

fromEnum :: Lsn -> Int #

enumFrom :: Lsn -> [Lsn] #

enumFromThen :: Lsn -> Lsn -> [Lsn] #

enumFromTo :: Lsn -> Lsn -> [Lsn] #

enumFromThenTo :: Lsn -> Lsn -> Lsn -> [Lsn] #

Eq Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

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

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

Integral Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

quot :: Lsn -> Lsn -> Lsn #

rem :: Lsn -> Lsn -> Lsn #

div :: Lsn -> Lsn -> Lsn #

mod :: Lsn -> Lsn -> Lsn #

quotRem :: Lsn -> Lsn -> (Lsn, Lsn) #

divMod :: Lsn -> Lsn -> (Lsn, Lsn) #

toInteger :: Lsn -> Integer #

Num Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

(+) :: Lsn -> Lsn -> Lsn #

(-) :: Lsn -> Lsn -> Lsn #

(*) :: Lsn -> Lsn -> Lsn #

negate :: Lsn -> Lsn #

abs :: Lsn -> Lsn #

signum :: Lsn -> Lsn #

fromInteger :: Integer -> Lsn #

Ord Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

compare :: Lsn -> Lsn -> Ordering #

(<) :: Lsn -> Lsn -> Bool #

(<=) :: Lsn -> Lsn -> Bool #

(>) :: Lsn -> Lsn -> Bool #

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

max :: Lsn -> Lsn -> Lsn #

min :: Lsn -> Lsn -> Lsn #

Read Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Real Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

toRational :: Lsn -> Rational #

Show Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

showsPrec :: Int -> Lsn -> ShowS #

show :: Lsn -> String #

showList :: [Lsn] -> ShowS #

Ix Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

range :: (Lsn, Lsn) -> [Lsn] #

index :: (Lsn, Lsn) -> Lsn -> Int #

unsafeIndex :: (Lsn, Lsn) -> Lsn -> Int #

inRange :: (Lsn, Lsn) -> Lsn -> Bool #

rangeSize :: (Lsn, Lsn) -> Int #

unsafeRangeSize :: (Lsn, Lsn) -> Int #

PrintfArg Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Storable Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

sizeOf :: Lsn -> Int #

alignment :: Lsn -> Int #

peekElemOff :: Ptr Lsn -> Int -> IO Lsn #

pokeElemOff :: Ptr Lsn -> Int -> Lsn -> IO () #

peekByteOff :: Ptr b -> Int -> IO Lsn #

pokeByteOff :: Ptr b -> Int -> Lsn -> IO () #

peek :: Ptr Lsn -> IO Lsn #

poke :: Ptr Lsn -> Lsn -> IO () #

Bits Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

(.&.) :: Lsn -> Lsn -> Lsn #

(.|.) :: Lsn -> Lsn -> Lsn #

xor :: Lsn -> Lsn -> Lsn #

complement :: Lsn -> Lsn #

shift :: Lsn -> Int -> Lsn #

rotate :: Lsn -> Int -> Lsn #

zeroBits :: Lsn #

bit :: Int -> Lsn #

setBit :: Lsn -> Int -> Lsn #

clearBit :: Lsn -> Int -> Lsn #

complementBit :: Lsn -> Int -> Lsn #

testBit :: Lsn -> Int -> Bool #

bitSizeMaybe :: Lsn -> Maybe Int #

bitSize :: Lsn -> Int #

isSigned :: Lsn -> Bool #

shiftL :: Lsn -> Int -> Lsn #

unsafeShiftL :: Lsn -> Int -> Lsn #

shiftR :: Lsn -> Int -> Lsn #

unsafeShiftR :: Lsn -> Int -> Lsn #

rotateL :: Lsn -> Int -> Lsn #

rotateR :: Lsn -> Int -> Lsn #

popCount :: Lsn -> Int #

FiniteBits Lsn Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

data Msf Source #

Minute/second/frame structure for addresses. Generally only makes sense for audio discs.

Instances

Instances details
Bounded Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Methods

minBound :: Msf #

maxBound :: Msf #

Enum Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Methods

succ :: Msf -> Msf #

pred :: Msf -> Msf #

toEnum :: Int -> Msf #

fromEnum :: Msf -> Int #

enumFrom :: Msf -> [Msf] #

enumFromThen :: Msf -> Msf -> [Msf] #

enumFromTo :: Msf -> Msf -> [Msf] #

enumFromThenTo :: Msf -> Msf -> Msf -> [Msf] #

Eq Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Methods

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

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

Ord Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Methods

compare :: Msf -> Msf -> Ordering #

(<) :: Msf -> Msf -> Bool #

(<=) :: Msf -> Msf -> Bool #

(>) :: Msf -> Msf -> Bool #

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

max :: Msf -> Msf -> Msf #

min :: Msf -> Msf -> Msf #

Read Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Show Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Methods

showsPrec :: Int -> Msf -> ShowS #

show :: Msf -> String #

showList :: [Msf] -> ShowS #

Storable Msf Source # 
Instance details

Defined in Foreign.Libcdio.Sector

Methods

sizeOf :: Msf -> Int #

alignment :: Msf -> Int #

peekElemOff :: Ptr Msf -> Int -> IO Msf #

pokeElemOff :: Ptr Msf -> Int -> Msf -> IO () #

peekByteOff :: Ptr b -> Int -> IO Msf #

pokeByteOff :: Ptr b -> Int -> Msf -> IO () #

peek :: Ptr Msf -> IO Msf #

poke :: Ptr Msf -> Msf -> IO () #

Conversions

lbaToLsn :: Lba -> Lsn Source #

Convert an LBA address into the corresponding LSN.

lsnToLba :: Lsn -> Lba Source #

Convert an LSN address into the corresponding LBA.

lbaToMsf :: Lba -> Msf Source #

Convert an LBA address into the corresponding timestamp, assuming audio data.

msfToLba :: Msf -> Lba Source #

Convert a timestamp into the corresponding LBA address, assuming audio data.

lsnToMsf :: Lsn -> Msf Source #

Convert an LSN address into the corresponding timestamp, assuming audio data.

msfToLsn :: Msf -> Lsn Source #

Convert a timestamp into the corresponding LSN address, assuming audio data.

lbaToMsfStr :: Lba -> String Source #

Print a logical address as the corresponding timestamp, assuming audio data.

msfToStr :: Msf -> String Source #

Print a disc timestamp in the standard "MM:SS:FF" format.

Basic counts

chunkSize :: Word Source #

The size of the smallest meaningful segment of data, in bytes.

minSessionNo :: Word Source #

The smallest session number on a disc.

maxSessions :: Word Source #

How many sessions are allowed on a disc.

pregapSectors :: Word Source #

The number of sectors spanned by a track pre-gap by default.

postgapSectors :: Word Source #

The number of sectors spanned by a track post-gap by default.

maxSectors :: Word Source #

The maximum number of sectors allowed to be stored on a disc.

framesizeSub :: Word Source #

The size of a segment of data in the subchannel, in bytes.

Units of time

chunksPerSector :: Word Source #

The number of data chunks comprising a disc sector.

framesPerSec :: Word Source #

The number of disc sectors comprising a second of audio data.

secsPerMin :: Word Source #

The number of seconds in a minute.

framesPerMin :: Word Source #

A shortcut for calculating framesPerSec * secsPerMin

cdMins :: Word Source #

The typical maximum length of a disc, though it's not a strict limit.

Sector blocks

sectorSize :: Word Source #

The size of an entire disc sector, in bytes.

syncedSize :: Word Source #

The size of a disc sector in bytes, ignoring the sync header.

sectorSizeMax :: Word Source #

The maximum number of bytes that may be returned from a single call.

Headers

sectorSyncHeader :: ByteString Source #

The byte sequence used to mark the start of a disc sector, to allow correcting drift while reading.

syncSize :: Word Source #

The number of bytes in a disc sector's sync header.

headerSize :: Word Source #

The size of the address of a data sector, in bytes.

subheaderSize :: Word Source #

The size of the subheader of an XA sector, in bytes.

headerSizeXa :: Word Source #

The total size of the meaningful XA sector headers, in bytes.

syncHeaderSizeXa :: Word Source #

The total size of all headers in an XA sector, including the sync marker.

Data

dataSize :: Word Source #

The amount of data which may be contained in a disc sector with error correction, in bytes.

dataSizeRaw :: Word Source #

The amount of data which may be contained in a disc sector without error correction, in bytes.

dataSizeRawXa :: Word Source #

The amount of data contained in an XA sector without error correction, in bytes.

taggedDataSizeRaw :: Word Source #

The size of tagged data (counting the subheader) contained in an XA sector without error correction, in bytes.

Error correction

errorDetectionSize :: Word Source #

The size of the EDC error correction segment, in bytes.

errorCorrectionSize :: Word Source #

The size of the ECC error correction segment, in bytes.

padSize :: Word Source #

The amount of padding between the EDC and ECC segments in a Mode 1 sector, in bytes.

padSizeXa :: Word Source #

The amount of padding at the end of an XA sector without error correction, in bytes.

tailSize :: Word Source #

The total size of all data sector error correction segments, in bytes.

tailSizeXa :: Word Source #

The total size of all XA sector error correction segments, in bytes.