{-| Description: Methods of retreaving the actual stored data. Copyright: (c) 2019-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: stable Portability: non-portable (requires libcdio) 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". -} module Sound.Libcdio.Read.Data ( -- * Types Foreign.Lsn , Foreign.Whence ( .. ) , Foreign.DiscMode ( .. ) , Foreign.isCdRom , Foreign.isDvd -- * Info , discMode , discJolietLevel , lastAddress , lastSessionAddress , audioTimestamp , catalogue , isrc -- * Read -- $read-design , seek , readRaw , readAudio , readData , readXa -- * Basic counts , Foreign.framesPerSec , maxCdSectors , maxCdMinutes , defaultPregapSectors , defaultPostgapSectors ) where import qualified Data.ByteString as BS import qualified Data.Text as T import qualified Foreign.Libcdio.Device as Foreign import qualified Foreign.Libcdio.Disc as Foreign import qualified Foreign.Libcdio.Read as Foreign import qualified Foreign.Libcdio.Sector as Foreign import qualified Foreign.Libcdio.Track as Foreign import Sound.Libcdio.Device import Sound.Libcdio.Types.Cdio -- | Determine which type of disc is being accessed. discMode :: Cdio (Maybe Foreign.DiscMode) discMode = liftCdio Foreign.discMode -- | 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. discJolietLevel :: Cdio (Maybe Word) discJolietLevel = liftCdio Foreign.discJolietLevel -- | Get the size of a disc in blocks, or equivalently the address of the end -- of the readable data. lastAddress :: Cdio (Maybe Foreign.Lsn) lastAddress = liftCdio Foreign.lastLsn -- | Get the starting address of the last write session of a disc. lastSessionAddress :: Cdio (Either DriverReturnCode Foreign.Lsn) lastSessionAddress = liftCdio Foreign.lastSession -- | The number of sectors spanned by a track pre-gap by default. defaultPregapSectors :: Word defaultPregapSectors = Foreign.pregapSectors -- | The number of sectors spanned by a track post-gap by default. defaultPostgapSectors :: Word defaultPostgapSectors = Foreign.postgapSectors -- | Print a disc timestamp in the standard "MM:SS:FF" format, assuming the -- address refers to audio data. audioTimestamp :: Foreign.Lsn -> T.Text audioTimestamp = T.pack . Foreign.msfToStr . Foreign.lsnToMsf -- | The maximum number of sectors allowed to be stored on a disc. maxCdSectors :: Word maxCdSectors = Foreign.maxSectors -- | The typical maximum length of a disc, though it's not a strict limit. maxCdMinutes :: Word maxCdMinutes = Foreign.cdMins -- | Get the media catalog number from a disc. This may also be retrieved -- by @'Sound.Libcdio.Read.CdText.code' $ 'Sound.Libcdio.Read.CdText.info' -- 'Nothing'@, though that references a different source and thus may not have -- the same return value. catalogue :: Cdio (Maybe T.Text) catalogue = liftCdio $ \c -> fmap T.pack <$> Foreign.cdMcn c -- | The International Standard Recording Code the given track. This may also -- be retrieved by @'Sound.Libcdio.Read.CdText.code' . -- 'Sound.Libcdio.Read.CdText.info' $ 'Just' t@, though that references a -- different source and thus may not have the same return value. isrc :: Foreign.Track -> Cdio (Maybe T.Text) isrc t = liftCdio $ \c -> fmap T.pack <$> Foreign.trackIsrc c t -- $read-design -- For now, the library isn't able to automatically determine which @read*@ -- function should be used; refer to 'Sound.Libcdio.Track.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 -- 'Foreign.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. -- | Reposition the read pointer in the 'Cdio' session for a future call to -- one of the @read*@ functions. seek :: Int -> Foreign.Whence -> Cdio Foreign.Lsn seek o w = liftCdioError $ \c -> do o' <- Foreign.seek c (o * fromIntegral Foreign.sectorSize) w pos <- case flip mod Foreign.sectorSize <$> o' of Right drift | drift /= 0 -> Foreign.seek c (fromIntegral $ negate drift) Foreign.SeekCurrent _ -> return o' return . packCdioError' "seek" $ fromIntegral . flip div Foreign.sectorSize <$> pos -- | 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". readRaw :: Word -> Cdio BS.ByteString readRaw l = liftCdioError $ \c -> do bs <- Foreign.readBytes c (l * Foreign.sectorSize) return . packCdioError' "readAudio" $ maybe (Left Foreign.DriverError) Right bs -- | Read a given number of sectors stored as CD-DA from the disc. readAudio :: Word -> Cdio BS.ByteString readAudio l = seek 0 Foreign.SeekCurrent >>= liftCdioError' (\c o -> packCdioError' "readAudio" <$> Foreign.readAudioSectors c o l) -- | Read a given number of sectors stored as Mode 1 data from the disc. readData :: Bool -- ^ If 'True' Form 2, otherwise Form 1 (see "Foreign.Libcdio.Sector"). -> Word -> Cdio BS.ByteString readData m l = seek 0 Foreign.SeekCurrent >>= liftCdioError' (\c o -> packCdioError' "readData" <$> Foreign.readDataModeSectors c o m l) -- | Read a given number of sectors stored according to the Mode 2 extension -- from the disc. readXa :: Bool -- ^ If 'True' Form 2, otherwise Form 1 (see "Foreign.Libcdio.Sector"). -> Word -> Cdio BS.ByteString readXa f l = seek 0 Foreign.SeekCurrent >>= liftCdioError' (\c o -> packCdioError' "readXA" <$> Foreign.readXaModeSectors c o f l)