| Copyright | (c) 2019 Composewell Technologies | 
|---|---|
| License | BSD3 | 
| Maintainer | streamly@composewell.com | 
| Stability | experimental | 
| Portability | GHC | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Streamly.Internal.Data.Ring.Foreign
Description
A ring array is a circular mutable array.
Synopsis
- data Ring a = Ring {- ringStart :: !(ForeignPtr a)
- ringBound :: !(Ptr a)
 
- new :: forall a. Storable a => Int -> IO (Ring a, Ptr a)
- newRing :: Int -> m (Ring a)
- writeN :: Int -> Fold m a (Ring a)
- advance :: forall a. Storable a => Ring a -> Ptr a -> Ptr a
- moveBy :: forall a. Storable a => Int -> Ring a -> Ptr a -> Ptr a
- startOf :: Ring a -> Ptr a
- unsafeInsert :: Storable a => Ring a -> Ptr a -> a -> IO (Ptr a)
- slide :: Ring a -> a -> m (Ring a)
- putIndex :: Ring a -> Int -> a -> m ()
- modifyIndex :: Ring a -> Int -> (a -> (a, b)) -> m b
- read :: Unfold m (Ring a) a
- readRev :: Unfold m (Array a) a
- getIndex :: Ring a -> Int -> m a
- getIndexUnsafe :: Ring a -> Int -> m a
- getIndexRev :: Ring a -> Int -> m a
- length :: Ring a -> Int
- byteLength :: Ring a -> Int
- byteCapacity :: Ring a -> Int
- bytesFree :: Ring a -> Int
- cast :: forall a b. Storable b => Ring a -> Maybe (Ring b)
- castUnsafe :: Ring a -> Ring b
- asBytes :: Ring a -> Ring Word8
- fromArray :: Array a -> Ring a
- unsafeFoldRing :: forall a b. Storable a => Ptr a -> (b -> a -> b) -> b -> Ring a -> b
- unsafeFoldRingM :: forall m a b. (MonadIO m, Storable a) => Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b
- unsafeFoldRingFullM :: forall m a b. (MonadIO m, Storable a) => Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b
- unsafeFoldRingNM :: forall m a b. (MonadIO m, Storable a) => Int -> Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b
- ringsOf :: Int -> SerialT m a -> SerialT m (Array a)
- unsafeEqArray :: Ring a -> Ptr a -> Array a -> Bool
- unsafeEqArrayN :: Ring a -> Ptr a -> Array a -> Int -> Bool
- slidingWindow :: forall m a b. (MonadIO m, Storable a) => Int -> Fold m (a, Maybe a) b -> Fold m a b
Documentation
A ring buffer is a mutable array of fixed size. Initially the array is empty, with ringStart pointing at the start of allocated memory. We call the next location to be written in the ring as ringHead. Initially ringHead == ringStart. When the first item is added, ringHead points to ringStart + sizeof item. When the buffer becomes full ringHead would wrap around to ringStart. When the buffer is full, ringHead always points at the oldest item in the ring and the newest item added always overwrites the oldest item.
When using it we should keep in mind that a ringBuffer is a mutable data structure. We should not leak out references to it for immutable use.
Constructors
| Ring | |
| Fields 
 | |
Construction
new :: forall a. Storable a => Int -> IO (Ring a, Ptr a) Source #
Create a new ringbuffer and return the ring buffer and the ringHead. Returns the ring and the ringHead, the ringHead is same as ringStart.
newRing :: Int -> m (Ring a) Source #
newRing count allocates an empty array that can hold count items.  The
 memory of the array is uninitialized and the allocation is aligned as per
 the Storable instance of the type.
Unimplemented
writeN :: Int -> Fold m a (Ring a) Source #
writeN n is a rolling fold that keeps the last n elements of the stream
 in a ring array.
Unimplemented
advance :: forall a. Storable a => Ring a -> Ptr a -> Ptr a Source #
Advance the ringHead by 1 item, wrap around if we hit the end of the array.
moveBy :: forall a. Storable a => Int -> Ring a -> Ptr a -> Ptr a Source #
Move the ringHead by n items. The direction depends on the sign on whether n is positive or negative. Wrap around if we hit the beginning or end of the array.
Random writes
unsafeInsert :: Storable a => Ring a -> Ptr a -> a -> IO (Ptr a) Source #
Insert an item at the head of the ring, when the ring is full this replaces the oldest item in the ring with the new item. This is unsafe beause ringHead supplied is not verified to be within the Ring. Also, the ringStart foreignPtr must be guaranteed to be alive by the caller.
slide :: Ring a -> a -> m (Ring a) Source #
Insert an item at the head of the ring, when the ring is full this replaces the oldest item in the ring with the new item.
Unimplemented
putIndex :: Ring a -> Int -> a -> m () Source #
O(1) Write the given element at the given index in the ring array. Performs in-place mutation of the array.
>>>putIndex arr ix val = Ring.modifyIndex arr ix (const (val, ()))
Unimplemented
modifyIndex :: Ring a -> Int -> (a -> (a, b)) -> m b Source #
Modify a given index of a ring array using a modifier function.
Unimplemented
Unfolds
readRev :: Unfold m (Array a) a Source #
Unfold a ring array into a stream in reverse order.
Unimplemented
Random reads
getIndex :: Ring a -> Int -> m a Source #
O(1) Lookup the element at the given index. Index starts from 0.
getIndexUnsafe :: Ring a -> Int -> m a Source #
Return the element at the specified index without checking the bounds.
Unsafe because it does not check the bounds of the ring array.
getIndexRev :: Ring a -> Int -> m a Source #
O(1) Lookup the element at the given index from the end of the array. Index starts from 0.
Slightly faster than computing the forward index and using getIndex.
Size
length :: Ring a -> Int Source #
O(1) Get the length of the array i.e. the number of elements in the array.
Note that byteLength is less expensive than this operation, as length
 involves a costly division operation.
Unimplemented
byteLength :: Ring a -> Int Source #
O(1) Get the byte length of the array.
Unimplemented
byteCapacity :: Ring a -> Int Source #
Get the total capacity of an array. An array may have space reserved beyond the current used length of the array.
Pre-release
bytesFree :: Ring a -> Int Source #
The remaining capacity in the array for appending more elements without reallocation.
Pre-release
Casting
cast :: forall a b. Storable b => Ring a -> Maybe (Ring b) Source #
Cast an array having elements of type a into an array having elements of
 type b. The length of the array should be a multiple of the size of the
 target element otherwise Nothing is returned.
Pre-release
castUnsafe :: Ring a -> Ring b Source #
Cast an array having elements of type a into an array having elements of
 type b. The array size must be a multiple of the size of type b.
Unimplemented
Folds
unsafeFoldRing :: forall a b. Storable a => Ptr a -> (b -> a -> b) -> b -> Ring a -> b Source #
Fold the buffer starting from ringStart up to the given Ptr using a pure
 step function. This is useful to fold the items in the ring when the ring is
 not full. The supplied pointer is usually the end of the ring.
Unsafe because the supplied Ptr is not checked to be in range.
unsafeFoldRingM :: forall m a b. (MonadIO m, Storable a) => Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b Source #
Like unsafeFoldRing but with a monadic step function.
unsafeFoldRingFullM :: forall m a b. (MonadIO m, Storable a) => Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b Source #
Fold the entire length of a ring buffer starting at the supplied ringHead pointer. Assuming the supplied ringHead pointer points to the oldest item, this would fold the ring starting from the oldest item to the newest item in the ring.
Note, this will crash on ring of 0 size.
unsafeFoldRingNM :: forall m a b. (MonadIO m, Storable a) => Int -> Ptr a -> (b -> a -> m b) -> b -> Ring a -> m b Source #
Fold Int items in the ring starting at Ptr a.  Won't fold more
 than the length of the ring.
Note, this will crash on ring of 0 size.
Stream of Arrays
ringsOf :: Int -> SerialT m a -> SerialT m (Array a) Source #
ringsOf n stream groups the input stream into a stream of
 ring arrays of size n. Each ring is a sliding window of size n.
Unimplemented
Fast Byte Comparisons
unsafeEqArray :: Ring a -> Ptr a -> Array a -> Bool Source #
Byte compare the entire length of ringBuffer with the given array, starting at the supplied ringHead pointer. Returns true if the Array and the ringBuffer have identical contents.
This is unsafe because the ringHead Ptr is not checked to be in range. The supplied array must be equal to or bigger than the ringBuffer, ARRAY BOUNDS ARE NOT CHECKED.
unsafeEqArrayN :: Ring a -> Ptr a -> Array a -> Int -> Bool Source #
Like unsafeEqArray but compares only N bytes instead of entire length of
 the ring buffer. This is unsafe because the ringHead Ptr is not checked to
 be in range.
slidingWindow :: forall m a b. (MonadIO m, Storable a) => Int -> Fold m (a, Maybe a) b -> Fold m a b Source #
slidingWindow collector is an incremental sliding window
 fold that does not require all the intermediate elements in a computation.
 This maintains n elements in the window, when a new element comes it slides
 out the oldest element and the new element along with the old element are
 supplied to the collector fold.
The Maybe is for the case when initially the window is filling and there is no old element.