{-# LANGUAGE ForeignFunctionInterface #-} {-| Description: Functions providing a means to retrieve the data stored on a disc. Copyright: (c) 2018-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: stable Portability: non-portable (requires libcdio) After obtaining landmarks through "Foreign.Libcdio.Disc" (and likely "Foreign.Libcdio.Track"), this module provides the functions required to actually retrive the primary data from the disc. Some knowledge of its physical layout is required, which may be determined through 'Foreign.Libcdio.Track.trackFormat'. = @read.h@ == Types * @cdio_read_mode_t@ -> 'ReadMode' - @CDIO_READ_MODE_M1F1@ -> 'Mode1Form1' - @CDIO_READ_MODE_M1F2@ -> 'Mode1Form2' - @CDIO_READ_MODE_M2F1@ -> 'Mode2Form1' - @CDIO_READ_MODE_M2F2@ -> 'Mode2Form2' == Symbols * @cdio_lseek@ -> 'seek' * @cdio_read@ -> 'readBytes' * @cdio_read_audio_sector@ -> 'readAudioSector' * @cdio_read_audio_sectors@ -> 'readAudioSectors' * @cdio_read_data_sectors@ -> 'readDataSectors' * @cdio_read_mode1_sector@ -> 'readDataModeSector' * @cdio_read_mode1_sectors@ -> 'readDataModeSectors' * @cdio_read_mode2_sector@ -> 'readXaModeSector' * @cdio_read_mode2_sectors@ -> 'readXaModeSectors' * @cdio_read_sector@ -> 'readSector' * @cdio_read_sectors@ -> 'readSectors' = "Sound.Libcdio.Read.Data" Each of the single-sector @read*@ aliases have been removed for consistency. * 'ReadMode' (removed; unnecessary low-level detail) * 'readAudioSectors' -> 'Sound.Libcdio.Read.Data.readAudio' * 'readBytes' -> 'Sound.Libcdio.Read.Data.readRaw' (note that the count is now the number of /sectors/ rather than bytes) * 'readDataModeSectors' -> 'Sound.Libcdio.Read.Data.readData' * 'readDataSectors' (removed; unnecessary low-level detail) * 'readXaModeSectors' -> 'Sound.Libcdio.Read.Data.readXa' -} module Foreign.Libcdio.Read ( -- * Types ReadMode ( .. ) , Whence ( .. ) -- * Functions -- ** Raw , seek , readBytes -- ** Sector , readSector, readSectors , readAudioSector, readAudioSectors , readDataSectors , readDataModeSector, readDataModeSectors , readXaModeSector, readXaModeSectors ) where import qualified Control.Monad as N import qualified Data.ByteString as BS import qualified Data.Maybe as Y import qualified Foreign.C.Types as C import qualified Foreign.Ptr as C import qualified Foreign.Storable as S import qualified Foreign.Marshal.Alloc as M import qualified Foreign.Marshal.Utils as M import Foreign.Libcdio.Device import Foreign.Libcdio.Marshal import Foreign.Libcdio.Types.Enums import Foreign.Libcdio.Types.Internal -- | Reposition the read pointer in the 'Cdio' session for a future call to -- 'readBytes'. seek :: Cdio -> Int -> Whence -> IO (Either DriverReturnCode Word) seek c o w = do o' <- withCdio c $ \c' -> seek' c' (fromIntegral o) (fromIntegral $ fromEnum w) return . fmap fromIntegral $ maybe (Left Uninitialized) errorOrInt o' foreign import ccall safe "cdio/compat/read.h cdio_lseek" seek' :: C.Ptr Cdio -> C.CLong -> C.CInt -> IO C.CLong collapseReturnCode :: Maybe DriverReturnCode -> a -> Either DriverReturnCode a collapseReturnCode (Just Success) a = Right a collapseReturnCode (Just e) _ = Left e collapseReturnCode Nothing _ = Left Uninitialized withCdioByteString :: Cdio -> (C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> IO a) -- ^ A foreign function which will read a given number of bytes into a -- referenced buffer, potentially returning a numeric error code. Note -- that this marshalling /will/ try to free the inner pointer of the -- second argument, so the function should @malloc@ a temporary value -- accordingly. -> IO (Maybe a, Maybe BS.ByteString) withCdioByteString c g = M.alloca $ \bs' -> M.alloca $ \s' -> do a <- withCdio c $ \c' -> g c' bs' s' bs <- peekByteStringLen bs' s' p <- S.peek bs' N.unless (p == C.nullPtr) $ M.free p return (a, bs) -- | Marshalling function for handling read instructions operating on a given -- number of whole-sector blocks. readCdioSectors :: Cdio -> (C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> IO C.CInt) -> IO (Either DriverReturnCode BS.ByteString) readCdioSectors c f = do (r, bs) <- withCdioByteString c f return $ collapseReturnCode (toEnum . fromIntegral <$> r) (Y.fromMaybe BS.empty bs) -- | Read a given number of bytes from the disc. With data of a known -- structure, use 'readSectors' or similar instead, which /don't/ include the -- headers and footers described in "Foreign.Libcdio.Sector". readBytes :: Cdio -> Word -> IO (Maybe BS.ByteString) readBytes c l = fmap snd <$> withCdioByteString c $ \c' bs' s' -> readBytes' c' bs' s' $ fromIntegral l foreign import ccall safe "cdio/compat/read.h read_bytes" readBytes' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> C.CULong -> IO () -- | Read the data contained in a specific sector from the disc. readSector :: Cdio -> Lsn -> ReadMode -> IO (Either DriverReturnCode BS.ByteString) readSector c o m = readCdioSectors c $ \c' bs' s' -> readSector' c' bs' s' o (fromIntegral $ fromEnum m) foreign import ccall safe "cdio/compat/read.h read_sector" readSector' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CInt -> IO C.CInt -- | Read the data contained in the given number of sectors from the disc, -- beginning with the specified sector. readSectors :: Cdio -> Lsn -> ReadMode -> Word -> IO (Either DriverReturnCode BS.ByteString) readSectors c o m l = readCdioSectors c $ \c' bs' s' -> readSectors' c' bs' s' o (fromIntegral $ fromEnum m) (fromIntegral l) foreign import ccall safe "cdio/compat/read.h read_sectors" readSectors' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CInt -> C.CUInt -> IO C.CInt -- | Similar to calling 'readSector' with 'AudioMode', depending on the driver -- implementation. readAudioSector :: Cdio -> Lsn -> IO (Either DriverReturnCode BS.ByteString) readAudioSector c o = readCdioSectors c $ \c' bs' s' -> readAudioSector' c' bs' s' o foreign import ccall safe "cdio/compat/read.h read_audio_sector" readAudioSector' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> IO C.CInt -- | Similar to calling 'readSectors' with 'AudioMode', depending on the driver -- implementation. readAudioSectors :: Cdio -> Lsn -> Word -> IO (Either DriverReturnCode BS.ByteString) readAudioSectors c o l = readCdioSectors c $ \c' bs' s' -> readAudioSectors' c' bs' s' o $ fromIntegral l foreign import ccall safe "cdio/compat/read.h read_audio_sectors" readAudioSectors' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CUInt -> IO C.CInt -- | Read the raw data from a given number of sectors on the disc, beginning -- with the specified sector. readDataSectors :: Cdio -> Lsn -> Word -- ^ Sector size (e.g. 'Foreign.Libcdio.Sector.dataSize' or -- 'Foreign.Libcdio.Sector.dataSizeRawXa'). -> Word -- ^ Number of sectors to read. -> IO (Either DriverReturnCode BS.ByteString) readDataSectors c o z l = readCdioSectors c $ \c' bs' s' -> readDataSectors' c' bs' s' o (fromIntegral z) (fromIntegral l) foreign import ccall safe "cdio/compat/read.h read_data_sectors" readDataSectors' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CUShort -> C.CUInt -> IO C.CInt -- | Similar to calling 'readSector', depending on the driver implementation. readDataModeSector :: Cdio -> Lsn -> Bool -- ^ If 'True' Form 2, otherwise Form 1 (see "Foreign.Libcdio.Sector"). -> IO (Either DriverReturnCode BS.ByteString) readDataModeSector c o m = readCdioSectors c $ \c' bs' s' -> readDataModeSector' c' bs' s' o $ M.fromBool m foreign import ccall safe "cdio/compat/read.h read_mode1_sector" readDataModeSector' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CUChar -> IO C.CInt -- | Similar to calling 'readSectors', depending on the driver implementation. readDataModeSectors :: Cdio -> Lsn -> Bool -- ^ If 'True' Form 2, otherwise Form 1 (see "Foreign.Libcdio.Sector"). -> Word -> IO (Either DriverReturnCode BS.ByteString) readDataModeSectors c o m l = readCdioSectors c $ \c' bs' s' -> readDataModeSectors' c' bs' s' o (M.fromBool m) (fromIntegral l) foreign import ccall safe "cdio/compat/read.h read_mode1_sectors" readDataModeSectors' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CUChar -> C.CUInt -> IO C.CInt -- | Similar to calling 'readSector', depending on the driver implementation. readXaModeSector :: Cdio -> Lsn -> Bool -- ^ If 'True' Form 2, otherwise Form 1 (see "Foreign.Libcdio.Sector"). -> IO (Either DriverReturnCode BS.ByteString) readXaModeSector c o m = readCdioSectors c $ \c' bs' s' -> readXaModeSector' c' bs' s' o $ M.fromBool m foreign import ccall safe "cdio/compat/read.h read_mode2_sector" readXaModeSector' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CUChar -> IO C.CInt -- | Similar to calling 'readSectors', depending on the driver implementation. readXaModeSectors :: Cdio -> Lsn -> Bool -- ^ If 'True' Form 2, otherwise Form 1 (see "Foreign.Libcdio.Sector"). -> Word -> IO (Either DriverReturnCode BS.ByteString) readXaModeSectors c o m l = readCdioSectors c $ \c' bs' s' -> readXaModeSectors' c' bs' s' o (M.fromBool m) (fromIntegral l) foreign import ccall safe "cdio/compat/read.h read_mode2_sectors" readXaModeSectors' :: C.Ptr Cdio -> C.Ptr (C.Ptr ()) -> C.Ptr C.CUInt -> Lsn -> C.CUChar -> C.CUInt -> IO C.CInt