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

Sound.Libcdio.Read.Data

Description

This module is likely what most usage of the library revolves around: retrieving the data stored on a CD. For more discussion of the layout, see Foreign.Libcdio.Sector.

Synopsis

Types

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 Whence Source #

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

Constructors

SeekStart 
SeekCurrent 
SeekEnd 

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 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:

isCdRom :: DiscMode -> Bool Source #

Return true if a DiscMode refers to some sort of CD.

isDvd :: DiscMode -> Bool Source #

Return true if a DiscMode refers to some sort of DVD.

Info

discMode :: Cdio (Maybe DiscMode) Source #

Determine which type of disc is being accessed.

discJolietLevel :: Cdio (Maybe Word) Source #

The original ISO 9660 (data) filesystem specification was rather restrictive in what files could be named; the Joliet extensions allow such exciting features as lowercase letters, not to mention full Unicode support.

lastAddress :: Cdio (Maybe Lsn) Source #

Get the size of a disc in blocks, or equivalently the address of the end of the readable data.

lastSessionAddress :: Cdio (Either DriverReturnCode Lsn) Source #

Get the starting address of the last write session of a disc.

audioTimestamp :: Lsn -> Text Source #

Print a disc timestamp in the standard "MM:SS:FF" format, assuming the address refers to audio data.

catalogue :: Cdio (Maybe Text) Source #

Get the media catalog number from a disc. This may also be retrieved by code $ info Nothing, though that references a different source and thus may not have the same return value.

isrc :: Track -> Cdio (Maybe Text) Source #

The International Standard Recording Code the given track. This may also be retrieved by code . info $ Just t, though that references a different source and thus may not have the same return value.

Read

For now, the library isn't able to automatically determine which read* function should be used; refer to format, and switch on its return value. For more info on the various data layouts, see the intro to Foreign.Libcdio.Sector.

Compared to the C and Foreign interfaces, all read functions have been tweaked for better internal consistency. Where a cdio_read or readBytes call would ask for the number of bytes to read, here it asks for the number of sectors. On the other hand, the formerly sector-oriented commands operate from the current seek position rather than, effectively, hiding a seek behind the scenes.

seek :: Int -> Whence -> Cdio Lsn Source #

Reposition the read pointer in the Cdio session for a future call to one of the read* functions.

readRaw :: Word -> Cdio ByteString Source #

Read a given number of sectors from the disc. With data of a known structure, use readAudio, readData, or readXa, which don't include the headers and footers described in Foreign.Libcdio.Sector.

readAudio :: Word -> Cdio ByteString Source #

Read a given number of sectors stored as CD-DA from the disc.

readData Source #

Arguments

:: Bool

If True Form 2, otherwise Form 1 (see Foreign.Libcdio.Sector).

-> Word 
-> Cdio ByteString 

Read a given number of sectors stored as Mode 1 data from the disc.

readXa Source #

Arguments

:: Bool

If True Form 2, otherwise Form 1 (see Foreign.Libcdio.Sector).

-> Word 
-> Cdio ByteString 

Read a given number of sectors stored according to the Mode 2 extension from the disc.

Basic counts

framesPerSec :: Word Source #

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

maxCdSectors :: Word Source #

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

maxCdMinutes :: Word Source #

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

defaultPregapSectors :: Word Source #

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

defaultPostgapSectors :: Word Source #

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