-- | A concurrent, mutable ring buffer that supports atomic updates. This module supports buffers containing all lifted types. If you are using a buffer which contains some unboxable or unliftable type, consider using 'RingBuffers.Unboxed' or 'RingBuffers.Unlifted'.
module RingBuffers.Lifted
  ( RingBuffer
  , new
  , clear
  , append
  , extend
  , capacity
  , filledLength
  , latest
  , unsafeLatest
  , foldMap
  , toList
  ) where

import qualified RingBuffers.Internal as I

-- | A concurrent, mutable ring buffer that supports atomic updates.
newtype RingBuffer a = RingBuffer (I.RingBuffer Array a)

-- | Return a new ring buffer of the specified size.
new :: ()
  => Int -- ^ capacity of buffer
  -> IO (RingBuffer a)
new :: Int -> IO (RingBuffer a)
new Int
sz = (RingBuffer Array a -> RingBuffer a)
-> IO (RingBuffer Array a) -> IO (RingBuffer a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap RingBuffer Array a -> RingBuffer a
coerce (Int -> IO (RingBuffer Array a)
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
Int -> IO (RingBuffer arr a)
I.new Int
sz)

-- | Reset the buffer to its empty state.
clear :: ()
  => RingBuffer a -- ^ buffer to clear
  -> IO ()
clear :: RingBuffer a -> IO ()
clear RingBuffer a
rb = RingBuffer Array a -> IO ()
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
RingBuffer arr a -> IO ()
I.clear (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb)

-- | Get the current filled length of the ring
filledLength :: ()
  => RingBuffer a
  -> IO Int
filledLength :: RingBuffer a -> IO Int
filledLength RingBuffer a
rb = RingBuffer Array a -> IO Int
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
RingBuffer arr a -> IO Int
I.filledLength (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb)

-- | Get the maximum number of items the ring can contain
capacity :: ()
  => RingBuffer a
  -> IO Int
capacity :: RingBuffer a -> IO Int
capacity RingBuffer a
rb = RingBuffer Array a -> IO Int
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
RingBuffer arr a -> IO Int
I.capacity (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb)

-- | Retrieve the \(n\)th most-recently added item of the ring
latest :: ()
  => RingBuffer a
  -> Int
  -> IO (Maybe a)
latest :: RingBuffer a -> Int -> IO (Maybe a)
latest RingBuffer a
rb Int
n = RingBuffer Array a -> Int -> IO (Maybe a)
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
RingBuffer arr a -> Int -> IO (Maybe a)
I.latest (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb) Int
n

-- | Retrieve the \(n\)th most-recently added item of the ring
--
--   /Note/: This function may exhibit undefined behaviour if
--   the index is out-of-bounds or uninitialised.
unsafeLatest :: ()
  => RingBuffer a
  -> Int
  -> IO a
unsafeLatest :: RingBuffer a -> Int -> IO a
unsafeLatest RingBuffer a
rb Int
n = RingBuffer Array a -> Int -> IO a
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
RingBuffer arr a -> Int -> IO a
I.unsafeLatest (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb) Int
n

-- | Add an item to the end of the buffer.
append :: ()
  => a
  -> RingBuffer a
  -> IO ()
append :: a -> RingBuffer a -> IO ()
append a
x RingBuffer a
rb = a -> RingBuffer Array a -> IO ()
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
a -> RingBuffer arr a -> IO ()
I.append a
x (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb)

-- | Write multiple items to the end of the ring.
--
--   Ignores any elements of the input array whose indices
--   are higher than the length of the ring buffer.
extend :: ()
  => Array a
  -> RingBuffer a
  -> IO ()
extend :: Array a -> RingBuffer a -> IO ()
extend Array a
x RingBuffer a
rb = Array a -> RingBuffer Array a -> IO ()
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
arr a -> RingBuffer arr a -> IO ()
I.extend Array a
x (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb)

-- | Execute the given action with the items of the ring, accumulating its results.
--
foldMap :: (Monoid b)
  => RingBuffer a
  -> (a -> IO b)
  -> IO b
foldMap :: RingBuffer a -> (a -> IO b) -> IO b
foldMap RingBuffer a
rb a -> IO b
action = RingBuffer Array a -> (a -> IO b) -> IO b
forall (arr :: * -> *) a b.
(Contiguous arr, Element arr a, Monoid b) =>
RingBuffer arr a -> (a -> IO b) -> IO b
I.foldMap (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb) a -> IO b
action

-- | Convert the entire contents of the ring into a list,
--   with the most recently added element at the head.
toList :: ()
  => RingBuffer a
  -> IO [a]
toList :: RingBuffer a -> IO [a]
toList RingBuffer a
rb = RingBuffer Array a -> IO [a]
forall (arr :: * -> *) a.
(Contiguous arr, Element arr a) =>
RingBuffer arr a -> IO [a]
I.toList (RingBuffer a -> RingBuffer Array a
coerce RingBuffer a
rb)