----------------------------------------------------------------------------- -- -- Module : Data.Journal -- Copyright : (c) 2017 Brian W Bush -- License : MIT -- -- Maintainer : Brian W Bush -- Stability : Stable -- Portability : Portable -- -- | Simple logging to a journal. -- ----------------------------------------------------------------------------- {-# LANGUAGE FlexibleContexts #-} module Data.Journal ( -- * Types Key , Entry , Journal(..) ) where import Control.Monad.Except (MonadError, MonadIO) import Data.ByteString.Char8 (ByteString) -- | Journal entries are keyed by byte strings. type Key = ByteString -- | Journal entries are byte strings. type Entry = ByteString -- | Type class for logging to a journal. class Journal a where -- | Append a log entry. append :: (MonadIO m, MonadError String m) => a -- ^ The journal. -> (Key, Entry) -- ^ The key and value to be logged. -> m () -- ^ An action to peform the logging. -- | Erase a log entry. erase :: (MonadIO m, MonadError String m) => a -- ^ The journal. -> Key -- ^ The key for the entry to be erased. -> m () -- ^ An action to erase the log entry. -- | Replay the journal to extract all log entries. replay :: (MonadIO m, MonadError String m) => Bool -- ^ Whether to compress the journal, erasing obsolete entries. -> a -- ^ The journal. -> m [(Key, Entry)] -- ^ An action listing all log entries. -- | Erase all log entries from the journal. clear :: (MonadIO m, MonadError String m) => a -- ^ The journal. -> m () -- ^ An action to erase all log entries. -- | Close a journal. close :: (MonadIO m, MonadError String m) => a -- ^ The journal. -> m () -- ^ An action to close the journal.