{-# LANGUAGE ForeignFunctionInterface #-} {-| Description: Control over and access to library log output. Copyright: (c) 2020-2021 Sam May License: GPL-3.0-or-later Maintainer: ag@eitilt.life Stability: stable Portability: non-portable (requires libcdio) The underlying library is rather loud in its error and warning messages, potentially emitting a lot of impure terminal clutter even on some otherwise-pure functions. Very helpfully, it also provides a mechanism for integrating the logs with whatever framework is in place for the larger project; that mechanism can be leveraged to cache the logs in memory until specifically asked for, at which point they can be packaged into Haskell types. Some of the immediacy—and therefore user ability to match note to source—is unfortunately lost, but the apparent purity is worth it. = @logging.h@ == Types * @cdio_log_level_t@ -> 'Foreign.Libcdio.Logging.LogLevel' == Symbols * @cdio_default_log_handler@ (removed; always handled through 'Foreign.Libcdio.Logging.readLog') * @cdio_assert@ -> @'Foreign.Libcdio.Logging.putLog' 'Forign.Libcdio.Logging.LogAssert'@ * @cdio_debug@ -> @'Foreign.Libcdio.Logging.putLog' 'Forign.Libcdio.Logging.LogDebug'@ * @cdio_error@ -> @'Foreign.Libcdio.Logging.putLog' 'Forign.Libcdio.Logging.LogError'@ * @cdio_info@ -> @'Foreign.Libcdio.Logging.putLog' 'Forign.Libcdio.Logging.LogInfo'@ * @cdio_log@ -> 'Foreign.Libcdio.Logging.putLog' * @cdio_log_set_handler@ (removed; always handled through 'Foreign.Libcdio.Logging.readLog') * @cdio_loglevel_default@ -> 'Foreign.Libcdio.Logging.logCutoff' and 'Foreign.Libcdio.Logging.setLogCutoff' * @cdio_warn@ -> @'Foreign.Libcdio.Logging.putLog' 'Forign.Libcdio.Logging.LogWarn'@ = "Sound.Libcdio.Logging" Most functions have been re-contextulized as being provided through a 'Sound.Libcdio.Logging.LibcdioLogger' instance, but the interface is otherwise unchanged. -} module Foreign.Libcdio.Logging ( -- * Types LogEntry ( .. ) , LogLevel ( .. ) -- * Message interaction , putLog , readLog , clearLog -- * Management , logCutoff , setLogCutoff , setupLogger ) where import qualified Control.Monad as N 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 Foreign.Storable as S import Foreign.Libcdio.Marshal import Foreign.Libcdio.Types.Enums import Foreign.Libcdio.Types.Offsets -- | Check the current minimum severity which will be recorded in the logs. -- -- See 'setLogCutoff'. logCutoff :: IO LogLevel logCutoff = toEnum . fromIntegral <$> logCutoff' foreign import ccall safe "cdio/compat/logging.h get_cdio_log_level" logCutoff' :: IO CLogLevel -- | Set the minimum severity required for a message to be recorded in the -- logs. -- -- See 'logCutoff'. setLogCutoff :: LogLevel -> IO () setLogCutoff = setLogCutoff' . fromIntegral . fromEnum foreign import ccall safe "cdio/compat/logging.h set_cdio_log_level" setLogCutoff' :: CLogLevel -> IO () -- | An unstructured message emitted from the library to let the user know -- what's going on behind the scenes. data LogEntry = LogEntry { logLevel :: LogLevel -- ^ How critical it is that the user receive this particular message. , logMessage :: String -- ^ The text of the message itself. } deriving ( Eq, Show, Read ) instance S.Storable LogEntry where sizeOf _ = leSizeOf alignment _ = leAlign peek c = do l <- S.peekByteOff c leLevel :: IO CLogLevel m' <- S.peekByteOff c leMessage m <- if m' == C.nullPtr then return "" else C.peekCString m' return $ LogEntry { logLevel = toEnum $ fromIntegral l , logMessage = m } poke c hs = do S.pokeByteOff c leLevel (fromIntegral . fromEnum $ logLevel hs :: CLogLevel) m <- C.newCString $ logMessage hs S.pokeByteOff c leMessage m S.pokeByteOff c lePrevious C.nullPtr -- | Retrieve all messages currently in the log for further processing. Note -- that this retains the contents of the log for future calls; to remove them, -- a separate call to 'clearLog' must be made. -- -- >>> setupLogger -- >>> putLog $ LogEntry LogWarn "Testing log reading" -- >>> readLog -- [LogEntry LogWarn "Testing log reading"] -- >>> readLog -- [LogEntry LogWarn "Testing log reading"] -- >>> clearLog -- >>> readLog -- [] readLog :: IO [LogEntry] readLog = do es' <- readLog' es <- Y.fromMaybe [] <$> M.maybePeek (M.peekArray0 C.nullPtr) es' N.forM es S.peek foreign import ccall safe "cdio/compat/logging.h read_cdio_log" readLog' :: IO (C.Ptr (C.Ptr LogEntry)) -- | Empty all messages currently in the log. There is no way to selectively -- remove only some messages; if that is desired, call 'readLog' first: -- -- >>> setupLogger -- >>> msgs <- readLog -- >>> clearLog -- >>> mapM_ putLog $ filter p msgs foreign import ccall safe "cdio/compat/logging.h free_cdio_log" clearLog :: IO () -- | Append a message to the logs. putLog :: LogEntry -> IO () putLog e = C.withCString (logMessage e) $ putLog' (fromIntegral . fromEnum $ logLevel e) foreign import ccall safe "cdio/compat/logging.h cdio_log" putLog' :: CLogLevel -> C.CString -> IO ()