{-# LANGUAGE ForeignFunctionInterface #-} {-| Description: Functions and types providing metadata about the disc contents. Copyright: (c) 2018-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: stable Portability: non-portable (requires libcdio) Metadata is stored in a binary format both library-internally and on the disc. Most audio archivists will recognize it as "those information fields in a CUE file" (though there are [other formats](https://www.gnu.org/software/libcdio/cd-text-format.html#Sony-Text-File-Format-_0028Input-Sheet-Version-0_002e7T_0029) as well), and casual listeners will recognize it as the scrolling text that you're always happy to see, on the rare times your music player shows it. Little-used and even-less-known, however, is that a single disc can theoretically contain metadata in up to eight different languages; because of the complexity that introduces, no unifying datatype is provided in favour of a function-based interface. = @cdtext.h@ == Defines * @MIN_CDTEXT_FIELD@ (removed; identical to @'minBound' :: 'Field'@) * @MAX_CDTEXT_FIELD@ (removed; identical to @'maxBound' :: 'Field'@) == Types * @cdtext_field_t@ -> 'Field' - @CDTEXT_FIELD_INVALID@ (removed; handled via 'Nothing') * @cdtext_genre_t@ -> 'Genre' - @CDTEXT_GENRE_UNUSED@ (removed; handled via 'Nothing') * @cdtext_lang_t@ -> 'Language' - @CDTEXT_LANGUAGE_UNKNOWN@ -> 'UnknownLanguage' - /Before libcdio 2.1.0: (often effectively removed; handled via 'Nothing')/ - @CDTEXT_LANGUAGE_INVALID@ (removed; handled via 'Nothing') - @CDTEXT_LANGUAGE_BLOCK_UNUSED@ (removed; handled via 'Nothing') * @cdtext_t@ (removed; merged into 'Cdio' objects) == Symbols * @cdtext_data_init@ -> 'cdTextDataInit' * @cdtext_destroy@ (removed; handled via the garbage collector) * @cdtext_field2str@ -> 'fieldString' * @cdtext_genre2str@ -> 'genreString' * @cdtext_get@ (removed; type conversion makes it identical to @cdtext_get_const@) * @cdtext_get_const@ -> 'cdTextGet' * @cdtext_get_first_track@ -> 'firstTrack' * @cdtext_get_genre@ -> 'genre' * @cdtext_get_language@ -> 'language' * @cdtext_get_last_track@ -> 'lastTrack' * @cdtext_init@ (removed; internal function without much external occasion) * @cdtext_lang2str@ -> 'languageString' * @cdtext_list_languages@ -> 'listLanguages' * @cdtext_list_languages_v2@ -> 'listAllLanguages' * @cdtext_select_language@ -> 'selectLanguage' * @cdtext_set@ (removed; primarily intended for internal use, and is more limited than would be expected) * @cdtext_set_language_index@ -> 'selectLanguageIndex' * @cdtext_str2lang@ -> 'parseLanguage' = "Sound.Libcdio.Read.CdText" While similar functionality is provided, the @"Sound.Libcdio.Read".'Sound.Libcdio.Read.CdText'@ is written as a separate monadic interface rather than in the 'Cdio'-bound style used here. * 'cdTextDataInit' -> 'Sound.Libcdio.Read.CdText.parseCdText' * 'cdTextGet' -> 'Sound.Libcdio.Read.CdText.discId', @'snd' 'Sound.Libcdio.Read.CdText.genre'@, and 'Sound.Libcdio.Read.CdText.info' * 'genre' -> @'fst' 'Sound.Libcdio.Read.CdText.genre'@ * 'listAllLanguages' -> 'Sound.Libcdio.Read.CdText.languages' * 'listLanguages' (removed; obsolete and imprecise) * 'selectLanguage' -> 'Sound.Libcdio.Read.CdText.withLanguage' * 'selectLanguageIndex' -> 'Sound.Libcdio.Read.CdText.withIndex' -} module Foreign.Libcdio.CdText ( -- * Types Cdio , Field ( .. ) , Genre ( .. ) , Language ( .. ) -- * Description , fieldString , languageString , parseLanguage , genreString -- * Management , cdTextDataInit , listLanguages , listAllLanguages , selectLanguage , selectLanguageIndex -- * Access , cdTextGet , genre , language , firstTrack , lastTrack ) where import qualified Data.List as L import qualified Data.Maybe as Y import qualified Foreign.C.String as C import qualified Foreign.C.Types as C import qualified Foreign.Ptr as C import qualified Foreign.Marshal.Array as M import qualified Foreign.Marshal.Utils as M import qualified System.IO.Unsafe as IO.Unsafe import Foreign.Libcdio.Device import Foreign.Libcdio.Marshal import Foreign.Libcdio.Track import Foreign.Libcdio.Types.Enums import Foreign.Libcdio.Types.Internal import Foreign.Libcdio.Version import Sound.Libcdio.Common -- | Return a canonical English name of the given genre, as opposed to the -- machine representation returned by the 'Show' instance. genreString :: Genre -> String genreString = IO.Unsafe.unsafePerformIO . C.peekCString . genreString' . fromIntegral . fromEnum foreign import ccall safe "cdio/compat/cdtext.h cdtext_genre2str" genreString' :: CGenre -> C.CString -- | Return a canonical English name of the given language, as opposed to the -- machine representation returned by the 'Show' instance. languageString :: Language -> String languageString = IO.Unsafe.unsafePerformIO . C.peekCString . languageString' . fromIntegral . fromEnum foreign import ccall safe "cdio/compat/cdtext.h cdtext_lang2str" languageString' :: CLanguage -> C.CString -- | Transform a string returned by 'languageString' back into its -- 'Language' representation. -- -- /Before libcdio 2.1.0: Always returns 'Nothing'/ parseLanguage :: String -> Maybe Language parseLanguage s | libcdioVersionNum >= makeVersion [2,1] = IO.Unsafe.unsafePerformIO $ do i <- C.withCString s parseLanguage' return . fmap (toEnum . fromIntegral) $ maybeError [languageInvalid, languageUnused] i | otherwise = Nothing foreign import ccall safe "cdio/compat/cdtext.h cdtext_str2lang_safe" parseLanguage' :: C.CString -> IO CLanguage foreign import ccall safe "cdio/compat/cdtext.h language_unknown" languageUnknown :: CLanguage foreign import ccall safe "cdio/compat/cdtext.h language_invalid" languageInvalid :: CLanguage foreign import ccall safe "cdio/compat/cdtext.h language_unused" languageUnused :: CLanguage -- | Describe the type of data in a human-readable manner, as opposed to the -- machine representation returned by the 'Show' instance. fieldString :: Field -> String fieldString = IO.Unsafe.unsafePerformIO . C.peekCString . fieldString' . fromIntegral . fromEnum foreign import ccall safe "cdio/compat/cdtext.h cdtext_field2str" fieldString' :: CField -> C.CString -- | Attempt to retrieve the value of a given field from the disc (if -- 'Nothing') or track (if 'Just') metadata, in the currently-active language. -- Note that 'GenreName' and 'DiscId' will /always/ refer to the disc-level -- data. cdTextGet :: Cdio -> Field -> Maybe Track -> IO (Maybe String) cdTextGet _ _ (Just DiscPregap) = return Nothing cdTextGet _ _ (Just DiscLeadout) = return Nothing cdTextGet c GenreName _ = cdTextGet_ c GenreName 0 cdTextGet c DiscId _ = cdTextGet_ c DiscId 0 cdTextGet c f Nothing = cdTextGet_ c f 0 cdTextGet c f (Just t) = cdTextGet_ c f t cdTextGet_ :: Cdio -> Field -> Track -> IO (Maybe String) cdTextGet_ c f t = withCdText' Nothing c $ \x -> cdTextGet' x (fromIntegral $ fromEnum f) (fromIntegral $ fromEnum t) >>= M.maybePeek C.peekCString foreign import ccall safe "cdio/compat/cdtext.h cdtext_get_const" cdTextGet' :: C.Ptr CdText -> CField -> CTrack -> IO C.CString -- | The machine-readable genre describing the music on this disc. For any -- associated human-readable name or subgenre, use @'cdTextGet' c 'GenreName' -- 'Nothing'@. genre :: Cdio -> IO (Maybe Genre) genre c = do g <- withCdText c genre' return $ if g == Just 0 then Nothing else toEnum . fromIntegral <$> g foreign import ccall safe "cdio/compat/cdtext.h cdtext_get_genre" genre' :: C.Ptr CdText -> IO CGenre -- | Indicate which language results will (currently) be returned in. See -- 'selectLanguage' to change this. language :: Cdio -> IO (Maybe Language) language c = fmap (toEnum . fromIntegral) <$> withCdText c language' foreign import ccall safe "cdio/compat/cdtext.h cdtext_get_language" language' :: C.Ptr CdText -> IO CLanguage -- | The earliest track with any associated metadata in the current language. -- Note that this may differ from 'minTrack'. firstTrack :: Cdio -> IO (Maybe Track) firstTrack c = fmap (toEnum . fromIntegral) . maybeError [0] <$> withCdText' 0 c firstTrack' foreign import ccall safe "cdio/compat/cdtext.h cdtext_get_first_track" firstTrack' :: C.Ptr CdText -> IO CTrack -- | The final track with any associated metadata in the current language. -- Note that this may differ from 'maxTrack'. lastTrack :: Cdio -> IO (Maybe Track) lastTrack c = fmap (toEnum . fromIntegral) . maybeError [0] <$> withCdText' 0 c lastTrack' foreign import ccall safe "cdio/compat/cdtext.h cdtext_get_last_track" lastTrack' :: C.Ptr CdText -> IO CTrack -- | Try to set the data associated with the given language as active for -- future calls to 'cdTextGet' and similar. If passed 'UnknownLanguage' or the -- CDTEXT does not provide the one requested, selects the first (default) data -- set instead, and returns 'False'. selectLanguage :: Cdio -> Language -> IO Bool selectLanguage c l = fmap M.toBool . withCdText' 0 c $ \x -> selectLanguage' x . fromIntegral $ fromEnum l foreign import ccall safe "cdio/compat/cdtext.h cdtext_select_language" selectLanguage' :: C.Ptr CdText -> CLanguage -> IO CBool -- | Retrieve the languages included in the disc metadata. Note that this does -- not save the index position or any duplicate language blocks (if that is -- desired, see 'listAllLanguages' instead). listLanguages :: Cdio -> IO [Language] listLanguages c = withCdText' [] c $ \x -> do l' <- listLanguages' x ls <- peekLanguages l' [languageUnknown, languageInvalid, languageUnused] return . L.nub $ Y.catMaybes ls foreign import ccall safe "cdio/compat/cdtext.h cdtext_list_languages" listLanguages' :: C.Ptr CdText -> IO (C.Ptr CLanguage) -- | Retrieve the languages included in the disc metadata, in the order they -- occur, and respecting any empty language blocks if there's a valid language -- after them (empty blocks at the end are cleaned away). -- -- /Before libcdio 2.1.0: Acts as 'listLanguages'/ listAllLanguages :: Cdio -> IO [Maybe Language] listAllLanguages c = withCdText' [] c $ \x -> do l' <- listAllLanguages' x ls <- peekLanguages l' [languageInvalid, languageUnused] return $ case L.dropWhileEnd Y.isNothing ls of [] -> [Just UnknownLanguage] ls' -> ls' foreign import ccall safe "cdio/compat/cdtext.h cdtext_list_languages_v2_safe" listAllLanguages' :: C.Ptr CdText -> IO (C.Ptr CLanguage) peekLanguages :: C.Ptr CLanguage -> [CLanguage] -> IO [Maybe Language] peekLanguages p es | p == C.nullPtr = return [] | otherwise = map (fmap (toEnum . fromIntegral) . maybeError es) <$> M.peekArray 8 p -- | Select the language at the given index of 'listAllLanguages' for future -- data retrieval. If the index is out of bounds or corresponds to a 'Nothing' -- in 'listAllLanguages', the first (default) data set is selected instead and -- 'False is returned. selectLanguageIndex :: Cdio -> Word -> IO Bool selectLanguageIndex c i = M.toBool <$> withCdText' 0 c (flip selectLanguageIndex' $ fromIntegral i) foreign import ccall safe "cdio/compat/cdtext.h cdtext_set_language_index_safe" selectLanguageIndex' :: C.Ptr CdText -> C.CInt -> IO CBool {- Primarily intended as an internal function -- | Set the given field at the given track to the given value. cdTextSet :: Cdio -> Field -> Maybe String -> Maybe Track -> IO () cdTextSet _ _ _ (Just DiscPregap) = mempty cdTextSet _ _ _ (Just DiscLeadout) = mempty cdTextSet c f v Nothing = cdTextSet_ c f v 0 cdTextSet c f v (Just t) = cdTextSet_ c f v t cdTextSet_ :: Cdio -> Field -> Maybe String -> Track -> IO () cdTextSet_ c f v t = withCdText_ c $ \x -> M.maybeWith C.withCString v $ \s -> cdTextSet' x (toCEnum f) s (withTrack t) C.nullPtr foreign import ccall safe "cdio/compat/cdtext.h cdtext_set" cdTextSet' :: C.Ptr CdText -> CField -> C.CString -> CTrack -> C.CString -> IO () -}