{-# LANGUAGE ForeignFunctionInterface #-} {-| Description: Information-gathering on the location and form of disc tracks. Copyright: (c) 2018-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: stable Portability: non-portable (requires libcdio) What many people would think of as the most important division on a CD isn't quite as an integral a part of the physical data layout: they are described in a table of contents before the first track of any recording session, and may have lower-resolution "echoes" in the subchannels alongside the data, but it would be hard to otherwise recover the track boundaries from the data itself. This module, then, provides the functions to retrieve that metadata from the table of contents and from the subchannels. = @track.h@ == Defines * @CDIO_CDROM_CDI_TRACK@ (removed; only has utility in library code) * @CDIO_CDROM_DATA_TRACK@ (removed; only has utility in library code) * @CDIO_INVALID_TRACK@ (removed; handled via 'Nothing') * @CDIO_CDROM_LBA@ (removed; only has utility in library code) * @CDIO_CDROM_LEADOUT_TRACK@ -> 'DiscLeadout' * @CDIO_CDROM_MSF@ (removed; only has utility in library code) * @CDIO_CDROM_XA_TRACK@ (removed; only has utility in library code) * @CDIO_CD_MAX_TRACKS@ -> 'maxTrack' * @CDIO_CD_MIN_TRACK_NO@ -> 'minTrack' == Types * @track_flag_t@ -> 'Maybe' 'Bool' (CDIO_TRACK_FLAG_ERROR is never used in library code) * @track_flags_t@ (removed; never used in the public interface) * @track_format_t@ -> 'TrackFormat' -@TRACK_FORMAT_PSX@ -> 'FormatPlaystation' -@TRACK_FORMAT_ERROR@ (removed; handled via 'Nothing') * @trackmode_t@ (removed; never used in the public API) == Symbols * @cdio_get_first_track_num@ -> 'firstTrackNum' * @cdio_get_last_track_num@ -> 'lastTrackNum' * @cdio_get_track@ -> 'trackAt' * @cdio_get_track_channels@ -> 'numChannels' * @cdio_get_track_copy_permit@ -> 'copyPermit' * @cdio_get_track_format@ -> 'trackFormat' * @cdio_get_track_green@ -> 'isGreen' * @cdio_get_track_isrc@ -> 'trackIsrc' * @cdio_get_track_last_lsn@ -> 'trackLastLsn' * @cdio_get_track_lba@ -> 'trackLba' * @cdio_get_track_lsn@ -> 'trackLsn' * @cdio_get_track_msf@ -> 'trackMsf' * @cdio_get_track_preemphasis@ -> 'hasPreemphasis' * @cdio_get_track_pregap_lba@ -> 'pregapLba' * @cdio_get_track_pregap_lsn@ -> 'pregapLsn' * @cdio_get_track_sec_count@ -> 'sectorCount' * @track_format2str@ -> 'trackFormatString' = "Sound.Libcdio.Track" * 'firstTrackNum' -> 'Sound.Libcdio.Track.firstDiscTrack' * 'isrcLength' (removed; unnecessary low-level detail) * 'lastTrackNum' -> 'Sound.Libcdio.Track.lastDiscTrack' * 'numChannels' -> 'Sound.Libcdio.Track.quadAudio' * 'pregapLba' (removed; only 'Lsn' is used in @Sound@) * 'pregapLsn' -> 'Sound.Libcdio.Track.pregap' * 'sectorCount' -> 'Sound.Libcdio.Track.totalLength' * 'trackFormat' -> 'Sound.Libcdio.Track.format' * 'trackIsrc' -> @"Sound.Libcdio.Read.Data".'Sound.Libcdio.Read.Data.isrc'@ * 'trackLastLsn' -> 'Sound.Libcdio.Track.offsetEnd' * 'trackLba' (removed; only 'Lsn' is used in @Sound@) * 'trackLsn' -> 'Sound.Libcdio.Track.offset' * 'trackMsf' (removed; only 'Lsn' is used in @Sound@) -} module Foreign.Libcdio.Track ( -- * Types Track ( .. ) , TrackNum , minTrack , maxTrack , TrackFormat ( .. ) , trackFormatString -- * Location , firstTrackNum , lastTrackNum , trackAt , trackLba, trackLsn , trackMsf , trackLastLsn , pregapLba, pregapLsn , sectorCount -- * Data , trackFormat, isGreen , hasPreemphasis , copyPermit , numChannels , trackIsrc , isrcLength ) where import qualified Foreign.C.String as C import qualified Foreign.C.Types as C import qualified Foreign.Ptr as C import qualified Foreign.Marshal.Alloc as M import qualified Foreign.Marshal.Utils as M import qualified Foreign.Storable as S import qualified System.IO.Unsafe as IO.Unsafe import Foreign.Libcdio.Marshal import Foreign.Libcdio.Sector import Foreign.Libcdio.Types.Enums import Foreign.Libcdio.Types.Internal import Sound.Libcdio.Common withCdioTrack :: (C.Ptr Cdio -> CTrack -> IO a) -> (a -> Maybe b) -> Cdio -> Track -> IO (Maybe b) withCdioTrack f g c = fmap (>>= g) . withCdio c . flip f . withTrack -- | Filter out @TRACK_FORMAT_ERROR@ values to fit the 'Enum'. invalidFormat :: CTrackFormat -> Maybe TrackFormat invalidFormat = fmap (toEnum . fromIntegral) . maybeError [trackFormatError] foreign import ccall safe "cdio/compat/track.h track_format_error" trackFormatError :: CTrackFormat -- | Describe the data layout of a 'Track' in a human-readable manner, as -- opposed to the machine representation returned by the 'Show' instance. trackFormatString :: TrackFormat -> String trackFormatString = IO.Unsafe.unsafePerformIO . C.peekCString . trackFormatString' . fromIntegral . fromEnum foreign import ccall safe "cdio/compat/track.h track_format_string" trackFormatString' :: CTrackFormat -> C.CString -- | Give up a small amount of nuance in order to use standard types. fromTrackFlagStatus :: Integral a => a -> Maybe Bool fromTrackFlagStatus c = case toEnum $ fromIntegral c of FlagTrue -> Just True FlagFalse -> Just False _ -> Nothing -- | The number of the first track on the disc. This will almost always be 1, -- but that is not strictly guaranteed; the (perhaps theoretical) example is of -- a multi-disc set, where later discs pick the numbering back up where the -- previous one left off. -- -- Returns 'Nothing' if the 'Cdio' object has already been closed, or if the -- disc table of contents can't be read. firstTrackNum :: Cdio -> IO (Maybe Track) firstTrackNum c = (>>= invalidTrack) <$> withCdio c firstTrackNum' foreign import ccall safe "cdio/compat/track.h cdio_get_first_track_num" firstTrackNum' :: C.Ptr Cdio -> IO CTrack -- | The number of the last track on the disc. -- -- Returns 'Nothing' if the 'Cdio' object has already been closed, or if the -- disc table of contents can't be read. lastTrackNum :: Cdio -> IO (Maybe Track) lastTrackNum c = (>>= invalidTrack) <$> withCdio c lastTrackNum' foreign import ccall safe "cdio/compat/track.h cdio_get_last_track_num" lastTrackNum' :: C.Ptr Cdio -> IO CTrack -- | The track which contains the given address. -- -- Returns 'Nothing' if the 'Cdio' object has already been closed, or if the -- address is beyond the written data on the disc. Note that 'DiscLeadout' is -- treated as if it were a single sector long: -- -- >>> Just endTrack <- lastTrackNum cdio -- >>> Just endAddr <- trackLastLsn cdio endTrack -- >>> trackAt cdio $ endAddr + 1 -- Just DiscLeadout -- >>> trackAt cdio $ endAddr + 2 -- Nothing trackAt :: Cdio -> Lsn -> IO (Maybe Track) trackAt c = fmap (>>= invalidTrack) . withCdio c . flip trackAt' . fromIntegral foreign import ccall safe "cdio/compat/track.h cdio_get_track" trackAt' :: C.Ptr Cdio -> C.CInt -> IO CTrack -- | The number of channels in the given track; either 2 or 4 per the standard. numChannels :: Cdio -> Track -> IO (Maybe Word) numChannels = withCdioTrack numChannels' numChannelsError -- | The user doesn't care about which type of error it is here. numChannelsError :: (Integral a, Integral b) => a -> Maybe b numChannelsError i | i < 0 = Nothing | otherwise = Just $ fromIntegral i foreign import ccall safe "cdio/compat/track.h cdio_get_track_channels" numChannels' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | Whether the track may be legally copied. copyPermit :: Cdio -> Track -> IO (Maybe Bool) copyPermit = withCdioTrack copyPermit' fromTrackFlagStatus foreign import ccall safe "cdio/compat/track.h cdio_get_track_copy_permit" copyPermit' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | Whether preemphasis has been applied to the track for noise reduction. hasPreemphasis :: Cdio -> Track -> IO (Maybe Bool) hasPreemphasis = withCdioTrack hasPreemphasis' fromTrackFlagStatus foreign import ccall safe "cdio/compat/track.h cdio_get_track_preemphasis" hasPreemphasis' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | The raw data structure of a track. trackFormat :: Cdio -> Track -> IO (Maybe TrackFormat) trackFormat = withCdioTrack trackFormat' invalidFormat foreign import ccall safe "cdio/compat/track.h cdio_get_track_format" trackFormat' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | Whether the track data was stored using the Green Book (CD-i) standard. isGreen :: Cdio -> Track -> IO (Maybe Bool) isGreen c t = do f <- firstTrackNum c l <- lastTrackNum c if Just t < f || Just t > l then return Nothing else withCdioTrack isGreen' (Just . M.toBool) c t foreign import ccall safe "cdio/compat/track.h cdio_get_track_green" isGreen' :: C.Ptr Cdio -> CTrack -> IO C.CUChar -- | The address of the end of the given track. trackLastLsn :: Cdio -> Track -> IO (Maybe Lsn) trackLastLsn = withCdioTrack trackLastLsn' invalidLsn foreign import ccall safe "cdio/compat/track.h cdio_get_track_last_lsn" trackLastLsn' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | The address of the start of the given track. trackLba :: Cdio -> Track -> IO (Maybe Lba) trackLba = withCdioTrack trackLba' invalidLba foreign import ccall safe "cdio/compat/track.h cdio_get_track_lba" trackLba' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | The address of the start of the given track. trackLsn :: Cdio -> Track -> IO (Maybe Lsn) trackLsn = withCdioTrack trackLsn' invalidLsn foreign import ccall safe "cdio/compat/track.h cdio_get_track_lsn" trackLsn' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | The address of the start of any pregap before the given track. pregapLba :: Cdio -> Track -> IO (Maybe Lba) pregapLba = withCdioTrack pregapLba' invalidLba foreign import ccall safe "cdio/compat/track.h cdio_get_track_pregap_lba" pregapLba' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | The address of the start of any pregap before the given track. pregapLsn :: Cdio -> Track -> IO (Maybe Lsn) pregapLsn = withCdioTrack pregapLsn' invalidLsn foreign import ccall safe "cdio/compat/track.h cdio_get_track_pregap_lsn" pregapLsn' :: C.Ptr Cdio -> CTrack -> IO C.CInt -- | The International Standard Recording Code the given track. This may also -- be retrieved by @'Foreign.Libcdio.CdText.getField' -- 'Foreign.Libcdio.CdText.Isrc' $ 'Just' t@, though that references a -- different source and thus may not have the same return value. trackIsrc :: Cdio -> Track -> IO (Maybe String) trackIsrc c t = withCdio c (flip trackIsrc' $ withTrack t) >>= maybe (return Nothing) (M.maybePeek peekFString) foreign import ccall safe "cdio/compat/track.h cdio_get_track_isrc" trackIsrc' :: C.Ptr Cdio -> CTrack -> IO C.CString -- | The timestamp at which the given track begins. trackMsf :: Cdio -> Track -> IO (Maybe Msf) trackMsf c t = M.alloca $ \m' -> do b <- withCdio c $ \c' -> trackMsf' c' (withTrack t) m' case M.toBool <$> b of Just True -> M.maybePeek S.peek m' _ -> return Nothing foreign import ccall safe "cdio/compat/track.h cdio_get_track_msf" trackMsf' :: C.Ptr Cdio -> CTrack -> C.Ptr Msf -> IO CBool -- | The number of sectors "assigned" to the specified track, including any in -- the pregap between it and the following one. sectorCount :: Cdio -> Track -> IO (Maybe Word) sectorCount = withCdioTrack sectorCount' $ maybeError [0] . fromIntegral foreign import ccall safe "cdio/compat/track.h cdio_get_track_sec_count" sectorCount' :: C.Ptr Cdio -> CTrack -> IO C.CUInt