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

Foreign.Libcdio.Types

Description

The original header defined a rather heterogeneous collection of typedefs, enums, and preprocessor macros, none of which provide much utility when separated from their associated functions. Instead of following that design decision (which only makes sense under the C #include model), this module instead exports every type used by the interface without any constructors or associated functions, for any type signatures which may expose an object only in passing it along.

types.h

Defines

Types

Sound.Libcdio.Types

The exact collection of exported types has been changed to reflect those used by the higher-level interface, but the modules are otherwise very similar; many types are shared between the two.

Synopsis

Disc

data Cdio Source #

A particular disc reading/writing device, along with the data contained on the loaded disc. Note well that this is always a mutable object, and is not thread-safe; moreover, any function this is passed to may wind up silently modifying the data.

data Whence Source #

Which location an offset passed to seek should be based on.

Instances

Instances details
Bounded Whence Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum Whence Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq Whence Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

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

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

Ord Whence Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read Whence Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show Whence Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

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 () #

data Bcd Source #

A bitwise encoding where the lower four bits encode a number modulo 10, and the upper encode the same divided by 10.

Instances

Instances details
Bounded Bcd Source #
>>> map fromBcd8 [minBound, maxBound]
[0, 159]
Instance details

Defined in Foreign.Libcdio.Util

Methods

minBound :: Bcd #

maxBound :: Bcd #

Enum Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

succ :: Bcd -> Bcd #

pred :: Bcd -> Bcd #

toEnum :: Int -> Bcd #

fromEnum :: Bcd -> Int #

enumFrom :: Bcd -> [Bcd] #

enumFromThen :: Bcd -> Bcd -> [Bcd] #

enumFromTo :: Bcd -> Bcd -> [Bcd] #

enumFromThenTo :: Bcd -> Bcd -> Bcd -> [Bcd] #

Eq Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

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

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

Integral Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

quot :: Bcd -> Bcd -> Bcd #

rem :: Bcd -> Bcd -> Bcd #

div :: Bcd -> Bcd -> Bcd #

mod :: Bcd -> Bcd -> Bcd #

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

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

toInteger :: Bcd -> Integer #

Num Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

(+) :: Bcd -> Bcd -> Bcd #

(-) :: Bcd -> Bcd -> Bcd #

(*) :: Bcd -> Bcd -> Bcd #

negate :: Bcd -> Bcd #

abs :: Bcd -> Bcd #

signum :: Bcd -> Bcd #

fromInteger :: Integer -> Bcd #

Ord Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

compare :: Bcd -> Bcd -> Ordering #

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

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

(>) :: Bcd -> Bcd -> Bool #

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

max :: Bcd -> Bcd -> Bcd #

min :: Bcd -> Bcd -> Bcd #

Read Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Real Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

toRational :: Bcd -> Rational #

Show Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

showsPrec :: Int -> Bcd -> ShowS #

show :: Bcd -> String #

showList :: [Bcd] -> ShowS #

Ix Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

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

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

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

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

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

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

PrintfArg Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Storable Bcd Source # 
Instance details

Defined in Foreign.Libcdio.Util

Methods

sizeOf :: Bcd -> Int #

alignment :: Bcd -> Int #

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

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

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

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

peek :: Ptr Bcd -> IO Bcd #

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

data Track Source #

An index into the segmentation within a write session on a disc.

Instances

Instances details
Bounded Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Enum Track Source #

Note that fromEnum DiscLeadout uses a value (== 100) chosen to be contiguous to the rest of the datatype rather than that used internally (== 0xAA). toEnum accepts both values.

Instance details

Defined in Foreign.Libcdio.Types.Internal

Eq Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

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

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

Num Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Ord Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

compare :: Track -> Track -> Ordering #

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

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

(>) :: Track -> Track -> Bool #

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

max :: Track -> Track -> Track #

min :: Track -> Track -> Track #

Read Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Show Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

showsPrec :: Int -> Track -> ShowS #

show :: Track -> String #

showList :: [Track] -> ShowS #

Ix Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

PrintfArg Track Source # 
Instance details

Defined in Foreign.Libcdio.Types.Internal

Storable Track Source #

Note that poke uses the official representation of DiscLeadout (CDIO_CDROM_LEADOUT_TRACK == 0xAA, as used by libcdio) rather than the hscdio fromEnum DiscLeadout (== 100), as the latter was chosen for proximity to the other constructors.

Instance details

Defined in Foreign.Libcdio.Types.Internal

Methods

sizeOf :: Track -> Int #

alignment :: Track -> Int #

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

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

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

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

peek :: Ptr Track -> IO Track #

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

data TrackNum Source #

Opaque newtype representing the numeric index of a Track, while enforcing the invariants inherant to the specification. Of very limited utility outside that context.

data TrackFormat Source #

The structure in which data is stored on a segment of a disc. The exact representation of these values is discussed in Foreign.Libcdio.Sector.

Instances

Instances details
Bounded TrackFormat Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum TrackFormat Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq TrackFormat Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord TrackFormat Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read TrackFormat Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show TrackFormat Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

data ReadMode Source #

How data is laid out on a disc.

data SessionArg Source #

Metadata about the session in the form of (often freeform) text, providing a type-safe index to getArg. Note that not every driver type supports every item.

The key "access-mode" is handled separately by getAccessMode, to better reflect its restricted outputs.

Instances

Instances details
Bounded SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Enum SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Eq SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Ord SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Read SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Show SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

Storable SessionArg Source # 
Instance details

Defined in Foreign.Libcdio.Device

CdText

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

data Field Source #

Instances

Instances details
Bounded Field Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum Field Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq Field Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

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

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

Ord Field Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

compare :: Field -> Field -> Ordering #

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

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

(>) :: Field -> Field -> Bool #

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

max :: Field -> Field -> Field #

min :: Field -> Field -> Field #

Read Field Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show Field Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

data Genre Source #

Genres recognized in the CD Text standard.

Instances

Instances details
Bounded Genre Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum Genre Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq Genre Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

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

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

Ord Genre Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

compare :: Genre -> Genre -> Ordering #

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

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

(>) :: Genre -> Genre -> Bool #

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

max :: Genre -> Genre -> Genre #

min :: Genre -> Genre -> Genre #

Read Genre Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show Genre Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Methods

showsPrec :: Int -> Genre -> ShowS #

show :: Genre -> String #

showList :: [Genre] -> ShowS #

data Language Source #

Written languages recognized in the CD Text standard.

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 #

type Flags = BitArray Flag Source #

The collection of metadata describing a particular track.

Hardware

data DriverId Source #

Devices or file types supported by the library.

data DriverReturnCode Source #

Descriptions of various error states which may be returned by driver functions.

Instances

Instances details
Bounded DriverReturnCode Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum DriverReturnCode Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq DriverReturnCode Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord DriverReturnCode Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read DriverReturnCode Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show DriverReturnCode Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

data DriveCapabilityRead Source #

Instances

Instances details
Bounded DriveCapabilityRead Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum DriveCapabilityRead Source #

Write-related properties a device can have, mostly describing what formats it can burn, which are collected in DriveWriteCaps.

Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq DriveCapabilityRead Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord DriveCapabilityRead Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read DriveCapabilityRead Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show DriveCapabilityRead Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ix DriveCapabilityRead Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

type DriveReadCaps = BitArray DriveCapabilityRead Source #

The collection of features for reading discs a device provides.

data DriveCapabilityWrite Source #

Instances

Instances details
Bounded DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ix DriveCapabilityWrite Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

type DriveWriteCaps = BitArray DriveCapabilityWrite Source #

The collection of features for writing discs a device provides.

data DriveCapabilityMisc Source #

Miscellaneous properties a device can have, typically describing hardware features, which are collected in DriveMiscCaps.

Instances

Instances details
Bounded DriveCapabilityMisc Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum DriveCapabilityMisc Source #

Read-related properties a device can have, mostly describing what formats it understands, which are collected in DriveReadCaps.

The difference between ReadAnalogAudio and ReadDigitalAudio is poorly documented in libcdio; they have been named here according to their assumed meanings (see https://www.cdrfaq.org/faq02.html#S2-4-3), but that pattern may not be completely accurate.

Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq DriveCapabilityMisc Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord DriveCapabilityMisc Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read DriveCapabilityMisc Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show DriveCapabilityMisc Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ix DriveCapabilityMisc Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

type DriveMiscCaps = BitArray DriveCapabilityMisc Source #

The collection of hardware features a device was built with.

type DriveCaps = (DriveReadCaps, DriveWriteCaps, DriveMiscCaps) Source #

The three types are usually passed around together, so we can simplify the type signatures using them.

data DiscMode Source #

Different types of disc. Modes are combined from several sources, along with some libcdio-specific additions:

  • MMC-5 6.33.3.13 (Send CUESHEET)
  • MMC-5 Table 400 "DVD Book"
  • GNU/Linux /usr/include/linux/cdrom.h

As C2HS and Haddock don't yet interact well enough to document Enum fields, some of the less obvious mappings include:

Data

data Filesystem Source #

Types of filesystem which may be read from a disc.

Instances

Instances details
Bounded Filesystem Source # 
Instance details

Defined in Foreign.Libcdio.CdTypes

Enum Filesystem Source # 
Instance details

Defined in Foreign.Libcdio.CdTypes

Eq Filesystem Source # 
Instance details

Defined in Foreign.Libcdio.CdTypes

Ord Filesystem Source # 
Instance details

Defined in Foreign.Libcdio.CdTypes

Read Filesystem Source # 
Instance details

Defined in Foreign.Libcdio.CdTypes

Show Filesystem Source # 
Instance details

Defined in Foreign.Libcdio.CdTypes

data FilesystemClass Source #

Higher-level descriptions of discs/filesystems.

Instances

Instances details
Bounded FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Enum FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Eq FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ord FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Read FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Show FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

Ix FilesystemClass Source # 
Instance details

Defined in Foreign.Libcdio.Types.Enums

type FilesystemClasses = BitArray FilesystemClass Source #

A collection of disc/filesystem descriptions.

data IsoAnalysis Source #

A collection of data describing a disc using the ISO 9660 standard.

Logging

data LogEntry Source #

An unstructured message emitted from the library to let the user know what's going on behind the scenes.

data LogLevel Source #

How much detail should be recorded in the logs.