Copyright | (c) 2020 Composewell Technologies |
---|---|
License | BSD-3-Clause |
Maintainer | streamly@composewell.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Streamly.Internal.Data.MutArray
Description
Synopsis
- free :: Unbox a => MutArray a -> Int
- concat :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- foldr :: (MonadIO m, Unbox a) => (a -> b -> b) -> b -> MutArray a -> m b
- length :: Unbox a => MutArray a -> Int
- foldl' :: (MonadIO m, Unbox a) => (b -> a -> b) -> b -> MutArray a -> m b
- new :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- toList :: (MonadIO m, Unbox a) => MutArray a -> m [a]
- empty :: MutArray a
- dropWhile :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a)
- splitAt :: Unbox a => Int -> MutArray a -> (MutArray a, MutArray a)
- reverse :: (MonadIO m, Unbox a) => MutArray a -> m ()
- read :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Stream m a
- peek :: (MonadIO m, Unbox a) => MutArray Word8 -> m (Maybe a, MutArray Word8)
- poke :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (MutArray Word8)
- fold :: (MonadIO m, Unbox a) => Fold m a b -> MutArray a -> m b
- cast :: forall a b. Unbox b => MutArray a -> Maybe (MutArray b)
- write :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- realloc :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- reallocBytes :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- append :: (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a)
- capacity :: Unbox a => MutArray a -> Int
- snoc :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- create :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- strip :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a)
- chunksOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- reader :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a
- modify :: (MonadIO m, Unbox a) => MutArray a -> (a -> a) -> m ()
- fromStreamD :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a)
- splice :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a)
- unsafeGetIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- unsafeCast :: MutArray a -> MutArray b
- data MutArray a = MutArray {
- arrContents :: !MutByteArray
- arrStart :: !Int
- arrEnd :: !Int
- arrBound :: !Int
- nil :: MutArray a
- emptyOf :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- unsafeCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- createOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- createWith :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- fromStreamN :: (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a)
- fromStream :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a)
- fromPureStream :: (MonadIO m, Unbox a) => Stream Identity a -> m (MutArray a)
- putIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
- unsafePutIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
- putIndices :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Fold m (Int, a) ()
- unsafeModifyIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b
- modifyIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b
- snocWith :: (MonadIO m, Unbox a) => (Int -> Int) -> MutArray a -> a -> m (MutArray a)
- unsafeSnoc :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- producerWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Producer m (MutArray a) a
- producer :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Producer m (MutArray a) a
- readRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Stream m a
- toStreamK :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a
- getIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (Maybe a)
- dropAround :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a)
- cmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering
- unsafeSliceOffLen :: Unbox a => Int -> Int -> MutArray a -> MutArray a
- sliceOffLen :: Unbox a => Int -> Int -> MutArray a -> MutArray a
- clone :: MonadIO m => MutArray a -> m (MutArray a)
- getSlice :: Unbox a => Int -> Int -> MutArray a -> MutArray a
- writeNUnsafe :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- writeN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- writeWith :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- getIndexUnsafe :: (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- putIndexUnsafe :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m ()
- modifyIndexUnsafe :: (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b
- snocUnsafe :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- getSliceUnsafe :: Unbox a => Int -> Int -> MutArray a -> MutArray a
- mergeBy :: Int -> (MutArray a -> MutArray a -> m ()) -> MutArray a -> m ()
- indexReader :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a
- asBytes :: MutArray a -> MutArray Word8
- asCWString :: MutArray a -> (CWString -> IO b) -> IO b
- foldRev :: (MonadIO m, Unbox a) => Fold m a b -> MutArray a -> m b
- castUnsafe :: MutArray a -> MutArray b
- getIndices :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a
- splitOn :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a)
- asCString :: MutArray a -> (CString -> IO b) -> IO b
- writeChunks :: forall (m :: Type -> Type) a (n :: Type -> Type). (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a))
- byteLength :: MutArray a -> Int
- writeAppend :: (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a)
- writeAppendWith :: (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a)
- readerRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a
- toStreamWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a
- pin :: MutArray a -> IO (MutArray a)
- unpin :: MutArray a -> IO (MutArray a)
- isPinned :: MutArray a -> Bool
- emptyOf' :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- appendN :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- append2 :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Fold m a (MutArray a)
- pinnedEmptyOf :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- pinnedNew :: (MonadIO m, Unbox a) => Int -> m (MutArray a)
- writeAppendN :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- chunksOf' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- pinnedChunksOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a)
- data SpliceState s arr
- = SpliceInitial s
- | SpliceBuffering s arr
- | SpliceYielding arr (SpliceState s arr)
- | SpliceFinish
- compactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- flattenArrays :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- flattenArraysRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- fromArrayStreamK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a)
- concatRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a
- toStreamKRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a
- rangeBy :: (a -> a -> Ordering) -> MutArray a -> IO (Maybe (a, a))
- partitionBy :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a)
- fromPtrN :: MonadIO m => Int -> Ptr Word8 -> m (MutArray Word8)
- fromCString# :: MonadIO m => Addr# -> m (MutArray Word8)
- fromW16CString# :: MonadIO m => Addr# -> m (MutArray Word16)
- fromByteStr# :: MonadIO m => Addr# -> m (MutArray Word8)
- fromMutByteArray :: MonadIO m => MutByteArray -> Int -> Int -> m (MutArray a)
- toMutByteArray :: MutArray a -> (MutByteArray, Int, Int)
- unsafeAsPtr :: MonadIO m => MutArray a -> (Ptr a -> Int -> IO b) -> m b
- emptyWithAligned :: (MonadIO m, Unbox a) => (Int -> Int -> IO MutByteArray) -> Int -> Int -> m (MutArray a)
- unsafeBreakAt :: Unbox a => Int -> MutArray a -> (MutArray a, MutArray a)
- breakAt :: Unbox a => Int -> MutArray a -> (MutArray a, MutArray a)
- breakEndByWord8_ :: MonadIO m => Word8 -> MutArray Word8 -> m (MutArray Word8, Maybe (MutArray Word8))
- breakEndBy :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a)
- breakEndBy_ :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a)
- revBreakEndBy :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a)
- revBreakEndBy_ :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a)
- revDropWhile :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a)
- data ArrayUnsafe a = ArrayUnsafe !MutByteArray !Int !Int
- unsafeCreateWithOf :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- createWithOf :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- createMinOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- revCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- unsafeCreateOf' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- createOf' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- create' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- clone' :: MonadIO m => MutArray a -> m (MutArray a)
- fromListN' :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- fromList' :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- fromListRevN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- fromListRev :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- fromPureStreamN :: (MonadIO m, Unbox a) => Int -> Stream Identity a -> m (MutArray a)
- fromChunksK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a)
- fromChunksRealloced :: (MonadIO m, Unbox a) => Stream m (MutArray a) -> m (MutArray a)
- unsafeCreateWithPtr' :: MonadIO m => Int -> (Ptr Word8 -> IO Int) -> m (MutArray Word8)
- modifyIndices :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> (Int -> a -> a) -> Fold m Int ()
- swapIndices :: (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m ()
- unsafeSwapIndices :: (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m ()
- unsafeGetIndexRev :: (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- getIndexRev :: (MonadIO m, Unbox a) => Int -> MutArray a -> m a
- indexReaderWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a
- toStreamRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a
- toStreamKWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a
- toStreamKRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a
- readerRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Unfold m (MutArray a) a
- byteCapacity :: MutArray a -> Int
- bytesFree :: MutArray a -> Int
- blockSize :: Int
- arrayChunkBytes :: Int
- allocBytesToElemCount :: Unbox a => a -> Int -> Int
- reallocBytesWith :: (MonadIO m, Unbox a) => String -> (Int -> Int) -> Int -> MutArray a -> m (MutArray a)
- growTo :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- growBy :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- growExp :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- rightSize :: (MonadIO m, Unbox a) => MutArray a -> m (MutArray a)
- vacate :: MutArray a -> MutArray a
- byteCmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering
- byteEq :: MonadIO m => MutArray a -> MutArray a -> m Bool
- permute :: MutArray a -> m Bool
- shuffleBy :: (a -> a -> m Bool) -> MutArray a -> MutArray a -> m ()
- divideBy :: Int -> (MutArray a -> m (MutArray a, MutArray a)) -> MutArray a -> m ()
- bubble :: (MonadIO m, Unbox a) => (a -> a -> Ordering) -> MutArray a -> m ()
- snocGrowBy :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m (MutArray a)
- snocMay :: (MonadIO m, Unbox a) => MutArray a -> a -> m (Maybe (MutArray a))
- appendWith :: (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a)
- unsafeAppendMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> MutArray a -> Fold m a (MutArray a)
- appendMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> MutArray a -> Fold m a (MutArray a)
- appendGrowBy :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> MutArray a -> Fold m a (MutArray a)
- unsafeAppendPtrN :: MonadIO m => MutArray Word8 -> Ptr Word8 -> Int -> m (MutArray Word8)
- appendPtrN :: MonadIO m => MutArray Word8 -> Ptr Word8 -> Int -> m (MutArray Word8)
- appendCString :: MonadIO m => MutArray Word8 -> Ptr a -> m (MutArray Word8)
- appendCString# :: MonadIO m => MutArray Word8 -> Addr# -> m (MutArray Word8)
- appendStream :: (MonadIO m, Unbox a) => MutArray a -> Stream m a -> m (MutArray a)
- appendStreamN :: (MonadIO m, Unbox a) => Int -> MutArray a -> Stream m a -> m (MutArray a)
- spliceCopy :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a)
- spliceWith :: (MonadIO m, Unbox a) => (Int -> Int -> Int) -> MutArray a -> MutArray a -> m (MutArray a)
- spliceExp :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a)
- unsafeSplice :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a)
- pokeMay :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (Maybe (MutArray Word8))
- unsafePokeSkip :: Int -> MutArray Word8 -> MutArray Word8
- unsafePeek :: (MonadIO m, Unbox a) => MutArray Word8 -> m (a, MutArray Word8)
- unsafePeekSkip :: Int -> MutArray Word8 -> MutArray Word8
- buildChunks :: forall (m :: Type -> Type) a (n :: Type -> Type). (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a))
- chunksEndBy :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> Stream m a -> Stream m (MutArray a)
- chunksEndBy' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> Stream m a -> Stream m (MutArray a)
- chunksEndByLn :: forall (m :: Type -> Type). MonadIO m => Stream m Word8 -> Stream m (MutArray Word8)
- chunksEndByLn' :: forall (m :: Type -> Type). MonadIO m => Stream m Word8 -> Stream m (MutArray Word8)
- splitEndBy_ :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a)
- splitEndBy :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a)
- concatWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a
- concatRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a
- compactLeAs :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => PinnedState -> Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- createCompactMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a)
- createCompactMax' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a)
- createCompactMin :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a)
- createCompactMin' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a)
- compactMin :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactExact :: forall (m :: Type -> Type) a. Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- scanCompactMin :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Scanl m (MutArray a) (Maybe (MutArray a))
- scanCompactMin' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Scanl m (MutArray a) (Maybe (MutArray a))
- isPower2 :: Int -> Bool
- roundUpToPower2 :: Int -> Int
- breakOn :: MonadIO m => Word8 -> MutArray Word8 -> m (MutArray Word8, Maybe (MutArray Word8))
- createOfWith :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- peekUncons :: (MonadIO m, Unbox a) => MutArray Word8 -> m (Maybe a, MutArray Word8)
- peekUnconsUnsafe :: (MonadIO m, Unbox a) => MutArray Word8 -> m (a, MutArray Word8)
- pokeAppend :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (MutArray Word8)
- pokeAppendMay :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (Maybe (MutArray Word8))
- newArrayWith :: (MonadIO m, Unbox a) => (Int -> Int -> IO MutByteArray) -> Int -> Int -> m (MutArray a)
- spliceUnsafe :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a)
- pokeSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8
- peekSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8
- asPtrUnsafe :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b
- fromStreamDN :: (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a)
- getIndicesWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a
- resize :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- resizeExp :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- pinnedNewBytes :: MonadIO m => Int -> m (MutArray a)
- writeAppendNUnsafe :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- writeNWithUnsafe :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- writeNWith :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a)
- pinnedWriteNUnsafe :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedWriteN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedWriteNAligned :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Int -> Fold m a (MutArray a)
- pinnedWrite :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- writeRevN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pCompactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a)
- pPinnedCompactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a)
- fCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a)
- fPinnedCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a)
- lPinnedCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) ()
- lCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) ()
- pinnedCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedCreate :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a)
- pinnedFromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a)
- pinnedFromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a)
- pinnedClone :: MonadIO m => MutArray a -> m (MutArray a)
- unsafePinnedCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a)
- pinnedNewAligned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a)
- unsafePinnedAsPtr :: MonadIO m => MutArray a -> (Ptr a -> Int -> m b) -> m b
- grow :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a)
- snocLinear :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a)
- unsafeAppendN :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a)
- indexerFromLen :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (Int, Int)
- splitterFromLen :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (MutArray a)
- compactMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactMax' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactSepByByte_ :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- compactEndByByte_ :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- compactEndByLn_ :: forall (m :: Type -> Type). MonadIO m => Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- createOfLast :: forall a (m :: Type -> Type). (Unbox a, MonadIO m) => Int -> Fold m a (MutArray a)
- serialize :: (MonadIO m, Serialize a) => MutArray Word8 -> a -> m (MutArray Word8)
- deserialize :: (MonadIO m, Serialize a) => MutArray Word8 -> m (a, MutArray Word8)
- serializePtrN :: MutArray Word8 -> Ptr a -> Int -> m (MutArray Word8)
- deserializePtrN :: MutArray Word8 -> (Ptr a -> Int -> m b) -> m (a, MutArray Word8)
- slicerFromLen :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (MutArray a)
- sliceIndexerFromLen :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (Int, Int)
- genSlicesFromLen :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (Int, Int)
- getSlicesFromLen :: forall (m :: Type -> Type) a. (Monad m, Unbox a) => Int -> Int -> Unfold m (MutArray a) (MutArray a)
- compactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- pinnedCompactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a)
- compactOnByte :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- compactOnByteSuffix :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8)
- type IORef = IORef
- newIORef :: Unbox a => a -> IO (IORef a)
- writeIORef :: Unbox a => IORef a -> a -> IO ()
- modifyIORef' :: Unbox a => IORef a -> (a -> a) -> IO ()
- readIORef :: Unbox a => IORef a -> IO a
- pollIntIORef :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => IORef a -> Stream m a
MutArray.Type module
concat :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Same as the following but may be more efficient due to better fusion:
>>>
concat = Stream.unfoldEach MutArray.reader
foldr :: (MonadIO m, Unbox a) => (a -> b -> b) -> b -> MutArray a -> m b Source #
Right fold of an array.
length :: Unbox a => MutArray a -> Int Source #
O(1) Get the used 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.
foldl' :: (MonadIO m, Unbox a) => (b -> a -> b) -> b -> MutArray a -> m b Source #
Strict left fold of an array.
new :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Deprecated: Please use emptyOf instead.
fromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Create a MutArray
from a list. The list must be of finite size.
fromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Create a MutArray
from the first N elements of a list. The array is
allocated to size N, if the list terminates before N elements then the
array may hold less than N elements.
dropWhile :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a) Source #
Strip elements which match the predicate, from the start of the array.
>>>
arr <- MutArray.fromList " hello world"
>>>
a <- MutArray.dropWhile (== ' ') arr
>>>
MutArray.toList a
"hello world"
Pre-release
splitAt :: Unbox a => Int -> MutArray a -> (MutArray a, MutArray a) Source #
Deprecated: Please use breakAt instead.
Create two slices of an array without copying the original array. The
specified index i
is the first index of the second slice.
reverse :: (MonadIO m, Unbox a) => MutArray a -> m () Source #
You may not need to reverse an array because you can consume it in reverse
using readerRev
. To reverse large arrays you can read in reverse and write
to another array. However, in-place reverse can be useful to take adavantage
of cache locality and when you do not want to allocate additional memory.
read :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Stream m a Source #
Convert a MutArray
into a stream.
>>>
read = Stream.unfold MutArray.reader
peek :: (MonadIO m, Unbox a) => MutArray Word8 -> m (Maybe a, MutArray Word8) Source #
Create a Haskell value from its unboxed representation from the head of a byte array, return the value and the remaining array.
Like uncons
except that the value is deserialized from the byte array.
Note: If you are deserializing a large number of small fields, and the types
are statically known, then it may be more efficient to declare a record of
those fields and derive an Unbox
instance of the entire record.
poke :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (MutArray Word8) Source #
Unbox a Haskell type and append the resulting bytes to a mutable byte array. The array is grown exponentially when more space is needed.
Like snoc
except that the value is unboxed to the byte array.
Note: If you are serializing a large number of small fields, and the types
are statically known, then it may be more efficient to declare a record of
those fields and derive an Unbox
instance of the entire record.
fold :: (MonadIO m, Unbox a) => Fold m a b -> MutArray a -> m b Source #
Fold an array using a Fold
.
For example:
>>>
findIndex eq = MutArray.fold (Fold.findIndex eq)
Pre-release
cast :: forall a b. Unbox b => MutArray a -> Maybe (MutArray 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.
write :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Deprecated: Please use create instead.
realloc :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use reallocBytes instead.
realloc newCapacity array
reallocates the array to the specified
capacity in bytes.
If the new size is less than the original array the array gets truncated.
If the new size is not a multiple of array element size then it is rounded
down to multiples of array size. If the new size is more than
largeObjectThreshold
then it is rounded up to the block size (4K).
If the original array is pinned, the newly allocated array is also pinned.
reallocBytes :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
realloc newCapacity array
reallocates the array to the specified
capacity in bytes.
If the new size is less than the original array the array gets truncated.
If the new size is not a multiple of array element size then it is rounded
down to multiples of array size. If the new size is more than
largeObjectThreshold
then it is rounded up to the block size (4K).
If the original array is pinned, the newly allocated array is also pinned.
append :: (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use append2 instead.
append action
mutates the array generated by action
to append the
input stream. If there is no reserved space available in the array it is
reallocated to double the size and aligned to power of 2.
Note that the returned array may be a mutated version of original array.
>>>
append = Fold.foldlM' MutArray.snoc
snoc :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a) Source #
The array is mutated to append an additional element to it. If there is no reserved space available in the array then it is reallocated to double the original size and aligned to a power of 2.
This is useful to reduce allocations when appending unknown number of elements.
Note that the returned array may be a mutated version of the original array.
Performs only O(n * log n) copies to grow, but is liberal with memory
allocation compared to snocGrowBy
.
create :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Fold the whole input to a single array.
Same as 'createMinOf using an initial array size of arrayChunkBytes
bytes
rounded up to the element size. If the array is expected to be smaller than
arrayChunkBytes
then use createMinOf
to avoid wasting memory.
Caution! Do not use this on infinite streams.
strip :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use dropAround instead.
Strip elements which match the predicate, from both ends.
>>>
arr <- MutArray.fromList " hello world "
>>>
a <- MutArray.dropAround (== ' ') arr
>>>
MutArray.toList a
"hello world"
Pre-release
chunksOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
chunksOf n stream
groups the elements in the input stream into arrays of
n
elements each.
Same as the following but may be more efficient:
>>>
chunksOf n = Stream.foldMany (MutArray.createOf n)
Pre-release
reader :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a Source #
Unfold an array into a stream.
modify :: (MonadIO m, Unbox a) => MutArray a -> (a -> a) -> m () Source #
Modify each element of an array using the supplied modifier function.
This is an in-place equivalent of an immutable map operation.
Pre-release
fromStreamD :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a) Source #
Deprecated: Please use fromStream instead.
We could take the approach of doubling the memory allocation on each overflow. This would result in more or less the same amount of copying as in the chunking approach. However, if we have to shrink in the end then it may result in an extra copy of the entire data.
>>>
fromStreamD = StreamD.fold MutArray.create
splice :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a) Source #
The first array is extended in-place to append the second array. If there is no reserved space available in the first array then a new allocation of exact required size is done.
Note that the returned array may be an extended version of first array, referring to the same memory as the original array.
>>>
splice = MutArray.spliceWith (+)
If the original array is pinned the spliced array is also pinned.
Pre-release
unsafeGetIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> m a Source #
Return the element at the specified index without checking the bounds.
Unsafe because it does not check the bounds of the array.
unsafeCast :: MutArray a -> MutArray 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
otherwise accessing the last element of the array may result into a crash or
a random value.
Pre-release
An unboxed mutable array. An array is created with a given length and capacity. Length is the number of valid elements in the array. Capacity is the maximum number of elements that the array can be expanded to without having to reallocate the memory.
The elements in the array can be mutated in-place without changing the reference (constructor). However, the length of the array cannot be mutated in-place. A new array reference is generated when the length changes. When the length is increased (upto the maximum reserved capacity of the array), the array is not reallocated and the new reference uses the same underlying memory as the old one.
Several routines in this module allow the programmer to control the capacity of the array. The programmer can control the trade-off between memory usage and performance impact due to reallocations when growing or shrinking the array.
Constructors
MutArray | |
Fields
|
emptyOf :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Allocates an unpinned array of zero length but growable to the specified capacity without reallocation.
unsafeCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like createOf
but does not check the array bounds when writing. The fold
driver must not call the step function more than n
times otherwise it will
corrupt the memory and crash. This function exists mainly because any
conditional in the step function blocks fusion causing 10x performance
slowdown.
>>>
unsafeCreateOf = MutArray.unsafeCreateWithOf MutArray.emptyOf
createOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
createOf n
folds a maximum of n
elements from the input stream to an
MutArray
.
The array capacity is guranteed to be at least n
.
>>>
createOf = MutArray.createWithOf MutArray.emptyOf
>>>
createOf n = Fold.take n (MutArray.unsafeCreateOf n)
>>>
createOf n = MutArray.appendMax n MutArray.empty
createWith :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createMinOf instead.
createMinOf count
folds the whole input to a single array. The array
starts at a size big enough to hold minCount elements, the size is doubled
every time the array needs to be grown.
The array capacity is guaranteed to be at least count.
Caution! Do not use this on infinite streams.
>>>
f n = MutArray.appendWith (* 2) (MutArray.emptyOf n)
>>>
createWith n = Fold.rmapM MutArray.rightSize (f n)
>>>
createWith n = Fold.rmapM MutArray.fromChunksK (MutArray.buildChunks n)
Pre-release
fromStreamN :: (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a) Source #
Create a MutArray of given size from a stream.
>>>
fromStreamN n = Stream.fold (MutArray.createOf n)
fromStream :: (MonadIO m, Unbox a) => Stream m a -> m (MutArray a) Source #
Create an Array
from a stream. This is useful when we want to create a
single array from a stream of unknown size. createOf
is at least twice
as efficient when the size is already known.
Note that if the input stream is too large memory allocation for the array
may fail. When the stream size is not known, chunksOf
followed by
processing of indvidual arrays in the resulting stream should be preferred.
Pre-release
fromPureStream :: (MonadIO m, Unbox a) => Stream Identity a -> m (MutArray a) Source #
Convert a pure stream in Identity monad to a mutable array.
putIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m () Source #
O(1) Write the given element at the given index in the array. Performs in-place mutation of the array.
>>>
putIndex ix arr val = MutArray.modifyIndex ix arr (const (val, ()))
>>>
f = MutArray.putIndices
>>>
putIndex ix arr val = Stream.fold (f arr) (Stream.fromPure (ix, val))
unsafePutIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m () Source #
Write the given element to the given index of the array. Does not check if the index is out of bounds of the array.
Pre-release
putIndices :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Fold m (Int, a) () Source #
Write an input stream of (index, value) pairs to an array. Throws an error if any index is out of bounds.
Pre-release
unsafeModifyIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b Source #
Modify a given index of an array using a modifier function.
Unsafe because it does not check the bounds of the array.
Pre-release
modifyIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b Source #
Modify a given index of an array using a modifier function.
Pre-release
snocWith :: (MonadIO m, Unbox a) => (Int -> Int) -> MutArray a -> a -> m (MutArray a) Source #
snocWith sizer arr elem
mutates arr
to append elem
. The used length
of the array increases by 1.
If there is no reserved space available in arr
it is reallocated to a size
in bytes determined by the sizer oldSizeBytes
function, where
oldSizeBytes
is the original size of the array in bytes. The sizer
function should return a capacity more than or equal to the current used
size. If the capacity returned is less than or equal to the current used
size, the array is still grown by one element.
If the new array size is more than largeObjectThreshold
then it is rounded
up to blockSize
.
Note that the returned array may be a mutated version of the original array.
Pre-release
unsafeSnoc :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a) Source #
Really really unsafe, appends the element into the first array, may cause silent data corruption or if you are lucky a segfault if the first array does not have enough space to append the element.
Internal
producer :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Producer m (MutArray a) a Source #
Resumable unfold of an array.
readRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Stream m a Source #
Convert a MutArray
into a stream in reverse order.
>>>
readRev = Stream.unfold MutArray.readerRev
toStreamK :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a Source #
getIndex :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (Maybe a) Source #
O(1) Lookup the element at the given index. Index starts from 0.
dropAround :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a) Source #
Strip elements which match the predicate, from both ends.
>>>
arr <- MutArray.fromList " hello world "
>>>
a <- MutArray.dropAround (== ' ') arr
>>>
MutArray.toList a
"hello world"
Pre-release
cmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering Source #
Deprecated: Please use byteCmp instead.
O(1) Slice an array in constant time.
Unsafe: The bounds of the slice are not checked.
Unsafe
Pre-release
O(1) Get a reference to a slice from a mutable array. Throws an error if the slice extends out of the array bounds.
The capacity of the slice is the same as its length i.e. it does not have any unused or reserved space at the end.
The slice shares the same underlying mutable array when created. However, if the slice or the original array is reallocated by growing or shrinking then it will be copied to new memory and they will no longer share the same memory.
Pre-release
Deprecated: Please use sliceOffLen instead.
O(1) Get a reference to a slice from a mutable array. Throws an error if the slice extends out of the array bounds.
The capacity of the slice is the same as its length i.e. it does not have any unused or reserved space at the end.
The slice shares the same underlying mutable array when created. However, if the slice or the original array is reallocated by growing or shrinking then it will be copied to new memory and they will no longer share the same memory.
Pre-release
writeNUnsafe :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateOf instead.
writeN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createOf instead.
writeWith :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createMinOf instead.
getIndexUnsafe :: (MonadIO m, Unbox a) => Int -> MutArray a -> m a Source #
Deprecated: Please use unsafeGetIndex instead.
Return the element at the specified index without checking the bounds.
Unsafe because it does not check the bounds of the array.
putIndexUnsafe :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m () Source #
Deprecated: Please use unsafePutIndex instead.
Write the given element to the given index of the array. Does not check if the index is out of bounds of the array.
Pre-release
modifyIndexUnsafe :: (MonadIO m, Unbox a) => Int -> MutArray a -> (a -> (a, b)) -> m b Source #
Deprecated: Please use unsafeModifyIndex instead.
Modify a given index of an array using a modifier function.
Unsafe because it does not check the bounds of the array.
Pre-release
snocUnsafe :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a) Source #
Deprecated: Please use unsafeSnoc instead.
Really really unsafe, appends the element into the first array, may cause silent data corruption or if you are lucky a segfault if the first array does not have enough space to append the element.
Internal
Deprecated: Please use unsafeSliceOffLen instead.
O(1) Slice an array in constant time.
Unsafe: The bounds of the slice are not checked.
Unsafe
Pre-release
mergeBy :: Int -> (MutArray a -> MutArray a -> m ()) -> MutArray a -> m () Source #
mergeBy level merge array
performs a pairwise bottom up fold recursively
merging the pairs using the supplied merge function. Level indicates the
level in the tree where the fold would stop.
This performs a random shuffle if the merge function is random. If we stop at level 0 and repeatedly apply the function then we can do a bubble sort.
Unimplemented
indexReader :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a Source #
Given an unfold that generates array indices, read the elements on those indices from the supplied MutArray. An error is thrown if an index is out of bounds.
Pre-release
foldRev :: (MonadIO m, Unbox a) => Fold m a b -> MutArray a -> m b Source #
Fold an arary starting from end up to beginning.
For example:
>>>
findIndexRev eq = MutArray.foldRev (Fold.findIndex eq)
castUnsafe :: MutArray a -> MutArray b Source #
Deprecated: Please use unsafeCast instead.
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
otherwise accessing the last element of the array may result into a crash or
a random value.
Pre-release
getIndices :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m Int -> Unfold m (MutArray a) a Source #
Deprecated: Please use indexReader instead.
splitOn :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a) Source #
Deprecated: Please use splitEndBy_ instead.
Generate a stream of array slices using a predicate. The array element matching the predicate is dropped.
Pre-release
writeChunks :: forall (m :: Type -> Type) a (n :: Type -> Type). (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a)) Source #
Deprecated: Please use buildChunks instead.
byteLength :: MutArray a -> Int Source #
O(1) Get the byte length of the array.
writeAppend :: (MonadIO m, Unbox a) => m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use append instead.
writeAppendWith :: (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use appendWith instead.
readerRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Unfold m (MutArray a) a Source #
Unfold an array into a stream in reverse order.
pin :: MutArray a -> IO (MutArray a) Source #
Return a copy of the array in pinned memory if unpinned, else return the original array.
unpin :: MutArray a -> IO (MutArray a) Source #
Return a copy of the array in unpinned memory if pinned, else return the original array.
emptyOf' :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Allocates a pinned array of zero length but growable to the specified capacity without reallocation.
appendN :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use appendMax instead.
Append n
elements to an existing array. Any free space left in the array
after appending n
elements is lost.
>>>
appendN n initial = Fold.take n (MutArray.unsafeAppendN n initial)
append2 :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> Fold m a (MutArray a) Source #
Fold append2 arr
mutates the array arr to append the input stream. If
there is no reserved space available in the array it is reallocated to
double the size and aligned to power of 2.
Note that the returned array may be a mutated version of original array.
>>>
append2 arr = Fold.foldlM' MutArray.snoc (pure arr)
pinnedEmptyOf :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Deprecated: Please use emptyOf' instead.
Allocates a pinned array of zero length but growable to the specified capacity without reallocation.
pinnedNew :: (MonadIO m, Unbox a) => Int -> m (MutArray a) Source #
Deprecated: Please use emptyOf' instead.
writeAppendN :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use appendN instead.
chunksOf' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
Like chunksOf
but creates pinned arrays.
pinnedChunksOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m a -> Stream m (MutArray a) Source #
Deprecated: Please use chunksOf' instead.
Like chunksOf
but creates pinned arrays.
data SpliceState s arr Source #
Constructors
SpliceInitial s | |
SpliceBuffering s arr | |
SpliceYielding arr (SpliceState s arr) | |
SpliceFinish |
compactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Deprecated: Please use compactMin instead.
compactMin n stream
coalesces adjacent arrays in the stream
until
the compacted array size becomes greater than or equal to n
.
>>>
compactMin n = Stream.foldMany (MutArray.createCompactMin n)
flattenArrays :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Deprecated: Please use "unfoldMany reader" instead.
flattenArraysRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Deprecated: Please use "unfoldMany readerRev" instead.
fromArrayStreamK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a) Source #
Deprecated: Please use fromChunksK instead.
concatRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Stream m (MutArray a) -> Stream m a Source #
Use the "readerRev" unfold instead.
concat = unfoldMany readerRev
We can try this if there are any fusion issues in the unfold.
toStreamKRev :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> StreamK m a Source #
rangeBy :: (a -> a -> Ordering) -> MutArray a -> IO (Maybe (a, a)) Source #
Find the minimum and maximum elements in the array using the provided comparison function.
partitionBy :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a) Source #
fromPtrN :: MonadIO m => Int -> Ptr Word8 -> m (MutArray Word8) Source #
fromPtrN len addr
copies len
bytes from addr
into an array.
Unsafe:
The caller has to ensure that:
- the pointer is pinned and alive during the call.
- the pointer passed is valid up to the given length.
fromCString# :: MonadIO m => Addr# -> m (MutArray Word8) Source #
fromCString# addr
copies a C string consisting of bytes and
terminated by a null byte, into a Word8 array. The null byte is not copied.
>>>
MutArray.fromCString# "hello"#
Unsafe:
The caller has to ensure that:
- the
addr
is pinned and alive during the call. - the pointer passed is valid up to the point where null byte is found.
fromW16CString# :: MonadIO m => Addr# -> m (MutArray Word16) Source #
fromW16CString# addr
copies a C string consisting of 16-bit wide chars
and terminated by a 16-bit null char, into a Word16 array. The null
character is not copied.
Useful for copying UTF16 strings on Windows.
Unsafe:
The caller has to ensure that:
- the
addr
is pinned and alive during the call. - the pointer passed is valid up to the point where null Word16 is found.
fromByteStr# :: MonadIO m => Addr# -> m (MutArray Word8) Source #
Deprecated: Please fromCString# instead.
fromMutByteArray :: MonadIO m => MutByteArray -> Int -> Int -> m (MutArray a) Source #
toMutByteArray :: MutArray a -> (MutByteArray, Int, Int) Source #
unsafeAsPtr :: MonadIO m => MutArray a -> (Ptr a -> Int -> IO b) -> m b Source #
unsafeAsPtr arr f
, f is a function used as f ptr len
where ptr
is a
pointer to the beginning of array and len
is the byte-length of the array.
Unsafe WARNING:
- The array must be pinned, otherwise it will lead to memory corruption.
- The user must not use the pointer beyond the supplied length.
Pre-release
emptyWithAligned :: (MonadIO m, Unbox a) => (Int -> Int -> IO MutByteArray) -> Int -> Int -> m (MutArray a) Source #
emptyWithAligned allocator alignment count
allocates a new array of zero
length and with a capacity to hold count
elements, using allocator
size alignment
as the memory allocator function.
Alignment must be greater than or equal to machine word size and a power of 2.
Alignment is ignored if the allocator allocates unpinned memory.
Pre-release
unsafeBreakAt :: Unbox a => Int -> MutArray a -> (MutArray a, MutArray a) Source #
Like breakAt
but does not check whether the index is valid.
>>>
unsafeBreakAt i arr = (MutArray.unsafeSliceOffLen 0 i arr, MutArray.unsafeSliceOffLen i (MutArray.length arr - i) arr)
breakAt :: Unbox a => Int -> MutArray a -> (MutArray a, MutArray a) Source #
Create two slices of an array without copying the original array. The
specified index i
is the first index of the second slice.
breakEndByWord8_ :: MonadIO m => Word8 -> MutArray Word8 -> m (MutArray Word8, Maybe (MutArray Word8)) Source #
Drops the separator byte
breakEndBy :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a) Source #
>>>
arr <- MutArray.fromList "hello world"
>>>
(a,b) <- MutArray.breakEndBy (== ' ') arr
>>>
MutArray.toList a
"hello ">>>
MutArray.toList b
"world"
breakEndBy_ :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a) Source #
Break the array into two slices when the predicate succeeds. The array element matching the predicate is dropped. If the predicate never succeeds the second array is empty.
>>>
arr <- MutArray.fromList "hello world"
>>>
(a,b) <- MutArray.breakEndBy_ (== ' ') arr
>>>
MutArray.toList a
"hello">>>
MutArray.toList b
"world"
Pre-release
revBreakEndBy :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a) Source #
>>>
arr <- MutArray.fromList "hello world"
>>>
(a,b) <- MutArray.revBreakEndBy (== ' ') arr
>>>
MutArray.toList a
"hello">>>
MutArray.toList b
" world"
revBreakEndBy_ :: (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> m (MutArray a, MutArray a) Source #
>>>
arr <- MutArray.fromList "hello world"
>>>
(a,b) <- MutArray.revBreakEndBy_ (== ' ') arr
>>>
MutArray.toList a
"hello">>>
MutArray.toList b
"world"
revDropWhile :: (Unbox a, MonadIO m) => (a -> Bool) -> MutArray a -> m (MutArray a) Source #
Strip elements which match the predicate, from the end of the array.
>>>
arr <- MutArray.fromList "hello world "
>>>
a <- MutArray.revDropWhile (== ' ') arr
>>>
MutArray.toList a
"hello world"
Pre-release
data ArrayUnsafe a Source #
Constructors
ArrayUnsafe !MutByteArray !Int !Int |
unsafeCreateWithOf :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Like unsafeCreateOf
but takes a new array allocator alloc size
function as argument.
>>>
unsafeCreateWithOf alloc n = MutArray.unsafeAppendN (alloc n) n
Pre-release
createWithOf :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
createWithOf alloc n
folds a maximum of n
elements into an array
allocated using the alloc
function.
The array capacity is guranteed to be at least n
.
>>>
createWithOf alloc n = Fold.take n (MutArray.unsafeCreateWithOf alloc n)
>>>
createWithOf alloc n = MutArray.appendN (alloc n) n
createMinOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
createMinOf count
folds the whole input to a single array. The array
starts at a size big enough to hold minCount elements, the size is doubled
every time the array needs to be grown.
The array capacity is guaranteed to be at least count.
Caution! Do not use this on infinite streams.
>>>
f n = MutArray.appendWith (* 2) (MutArray.emptyOf n)
>>>
createWith n = Fold.rmapM MutArray.rightSize (f n)
>>>
createWith n = Fold.rmapM MutArray.fromChunksK (MutArray.buildChunks n)
Pre-release
revCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like createOf
but writes the array in reverse order.
Pre-release
unsafeCreateOf' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like unsafeCreateOf
but creates a pinned array.
createOf' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Like createOf
but creates a pinned array.
create' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Like create
but creates a pinned array.
fromListN' :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Like fromListN
but creates a pinned array.
fromList' :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Like fromList
but creates a pinned array.
fromListRevN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Like fromListN but writes the array in reverse order.
Pre-release
fromListRev :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Like fromList
but writes the contents of the list in reverse order.
fromPureStreamN :: (MonadIO m, Unbox a) => Int -> Stream Identity a -> m (MutArray a) Source #
Convert a pure stream in Identity monad to a mutable array.
fromChunksK :: (Unbox a, MonadIO m) => StreamK m (MutArray a) -> m (MutArray a) Source #
Convert an array stream to an array. Note that this requires peak memory that is double the size of the array stream.
Also see fromChunksRealloced
.
fromChunksRealloced :: (MonadIO m, Unbox a) => Stream m (MutArray a) -> m (MutArray a) Source #
Also see fromChunksK
.
unsafeCreateWithPtr' :: MonadIO m => Int -> (Ptr Word8 -> IO Int) -> m (MutArray Word8) Source #
unsafeCreateWithPtr' capacity populator
creates a pinned array of
capacity
bytes and invokes the populator
function to populate it.
populator ptr len
gets the pointer to the array and MUST return the amount
of the capacity populated in bytes.
Unsafe because the populator is allowed to use the pointer only up to specified length. In other words, bytes populated MUST be less than or equal to the total capacity.
modifyIndices :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => MutArray a -> (Int -> a -> a) -> Fold m Int () Source #
Modify the array indices generated by the supplied stream.
Pre-release
swapIndices :: (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m () Source #
Swap the elements at two indices.
Pre-release
unsafeSwapIndices :: (MonadIO m, Unbox a) => Int -> Int -> MutArray a -> m () Source #
Swap the elements at two indices without validating the indices.
Unsafe: This could result in memory corruption if indices are not valid.
Pre-release
getIndexRev :: (MonadIO m, Unbox a) => Int -> MutArray a -> 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.
indexReaderWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a Source #
toStreamRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> Stream m a Source #
toStreamKWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a Source #
toStreamKRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> MutArray a -> StreamK m a Source #
byteCapacity :: MutArray 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 :: MutArray a -> Int Source #
The remaining capacity in the array for appending more elements without reallocation.
Pre-release
The page or block size used by the GHC allocator. Allocator allocates at least a block and then allocates smaller allocations from within a block.
arrayChunkBytes :: Int Source #
The default chunk size by which the array creation routines increase the size of the array when the array is grown linearly.
allocBytesToElemCount :: Unbox a => a -> Int -> Int Source #
Given an Unboxed
type (unused first arg) and real allocation size
(including overhead), return how many elements of that type will completely
fit in it, returns at least 1.
reallocBytesWith :: (MonadIO m, Unbox a) => String -> (Int -> Int) -> Int -> MutArray a -> m (MutArray a) Source #
reallocBytesWith label capSizer minIncrBytes array
. The label is used
in error messages and the capSizer is used to determine the capacity of the
new array in bytes given the current byte length of the array.
growTo :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
growTo newCapacity array
changes the total capacity of the array so that
it is enough to hold the specified number of elements. Nothing is done if
the specified capacity is less than the length of the array.
If the capacity is more than largeObjectThreshold
then it is rounded up to
the block size (4K).
Nothing is done if the requested capacity is <= 0.
Pre-release
growBy :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Like growTo
but specifies the required reserve (unused) capacity rather
than the total capacity. Increases the reserve capacity, if required, to at
least the given amount.
Nothing is done if the requested capacity is <= 0.
growExp :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Like growTo
but if the requested byte capacity is more than
largeObjectThreshold
then it is rounded up to the closest power of 2.
Nothing is done if the requested capacity is <= 0.
Pre-release
rightSize :: (MonadIO m, Unbox a) => MutArray a -> m (MutArray a) Source #
Resize the allocated memory to drop any reserved free space at the end of the array and reallocate it to reduce wastage.
Up to 25% wastage is allowed to avoid reallocations. If the capacity is
more than largeObjectThreshold
then free space up to the blockSize
is
retained.
Pre-release
vacate :: MutArray a -> MutArray a Source #
Reset the array end position to start, thus truncating the array to 0 length, making it empty. The capacity of the array remains unchanged. The array refers to the same memory as before.
byteCmp :: MonadIO m => MutArray a -> MutArray a -> m Ordering Source #
Byte compare two arrays. Compare the length of the arrays. If the length is equal, compare the lexicographical ordering of two underlying byte arrays otherwise return the result of length comparison.
Unsafe: Note that the Unbox
instance of sum types with constructors of
different sizes may leave some memory uninitialized which can make byte
comparison unreliable.
Pre-release
byteEq :: MonadIO m => MutArray a -> MutArray a -> m Bool Source #
Byte equality of two arrays.
>>>
byteEq arr1 arr2 = (==) EQ <$> MutArray.byteCmp arr1 arr2
Unsafe: See byteCmp
.
permute :: MutArray a -> m Bool Source #
Generate the next permutation of the sequence, returns False if this is the last permutation.
Unimplemented
shuffleBy :: (a -> a -> m Bool) -> MutArray a -> MutArray a -> m () Source #
Shuffle corresponding elements from two arrays using a shuffle function.
If the shuffle function returns False
then do nothing otherwise swap the
elements. This can be used in a bottom up fold to shuffle or reorder the
elements.
Unimplemented
divideBy :: Int -> (MutArray a -> m (MutArray a, MutArray a)) -> MutArray a -> m () Source #
divideBy level partition array
performs a top down hierarchical
recursive partitioning fold of items in the container using the given
function as the partition function. Level indicates the level in the tree
where the fold would stop.
This performs a quick sort if the partition function is 'partitionBy (< pivot)'.
Unimplemented
bubble :: (MonadIO m, Unbox a) => (a -> a -> Ordering) -> MutArray a -> m () Source #
Given an array sorted in ascending order except the last element being out of order, use bubble sort to place the last element at the right place such that the array remains sorted in ascending order.
Pre-release
snocGrowBy :: (MonadIO m, Unbox a) => Int -> MutArray a -> a -> m (MutArray a) Source #
The array is mutated to append an additional element to it.
If there is no reserved space available in the array then it is reallocated
to grow it by adding space for the requested number of elements, the new
size is rounded up to blockSize
when the size becomes more than
largeObjectThreshold
. If the size specified is <= 0 then the array is
grown by one element.
Note that the returned array may be a mutated version of the original array.
Performs O(n^2) copies to grow but is thrifty on memory compared to snoc
.
Pre-release
snocMay :: (MonadIO m, Unbox a) => MutArray a -> a -> m (Maybe (MutArray a)) Source #
Like snoc
but does not reallocate when pre-allocated array capacity
becomes full.
Internal
appendWith :: (MonadIO m, Unbox a) => (Int -> Int) -> m (MutArray a) -> Fold m a (MutArray a) Source #
appendWith sizer action
mutates the array generated by action
to
append the input stream. If there is no reserved space available in the
array it is reallocated to a size in bytes determined by sizer oldSize
,
where oldSize
is the current size of the array in bytes. If the sizer
returns less than or equal to the current size then the size is incremented
by one element.
Note that the returned array may be a mutated version of original array.
>>>
appendWith sizer = Fold.foldlM' (MutArray.snocWith sizer)
Pre-release
unsafeAppendMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> MutArray a -> Fold m a (MutArray a) Source #
unsafeAppendMax n arr
appends up to n
input items to the supplied
array.
Unsafe: Do not drive the fold beyond n
elements, it will lead to memory
corruption or segfault.
Internal
appendMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> MutArray a -> Fold m a (MutArray a) Source #
Allocates space for n additional elements. The fold terminates after appending n elements. If less than n elements are supplied then the space for the remaining elements is guaranteed to be reserved.
>>>
appendMax n arr = Fold.take n (MutArray.unsafeAppendMax n arr)
appendGrowBy :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> MutArray a -> Fold m a (MutArray a) Source #
appendGrowBy arr
mutates the array arr to append the input stream. If
there is no reserved space available in the array it is reallocated to add
space for the min number of elements supplied and align to block size if the
array becomes larger than largeObjectThreshold
.
Note that the returned array may be a mutated version of original array.
>>>
appendGrowBy n arr = Fold.foldlM' (MutArray.snocGrowBy n) (pure arr)
unsafeAppendPtrN :: MonadIO m => MutArray Word8 -> Ptr Word8 -> Int -> m (MutArray Word8) Source #
Append specified number of bytes from a given pointer to the MutArray.
Unsafe:
The caller has to ensure that:
- the MutArray is valid up to the given length.
- the source pointer is pinned and alive during the call.
- the pointer passed is valid up to the given length.
appendCString# :: MonadIO m => MutArray Word8 -> Addr# -> m (MutArray Word8) Source #
The array is grown only by the required amount of space.
appendStream :: (MonadIO m, Unbox a) => MutArray a -> Stream m a -> m (MutArray a) Source #
>>>
appendStream arr = Stream.fold (MutArray.append (pure arr))
appendStreamN :: (MonadIO m, Unbox a) => Int -> MutArray a -> Stream m a -> m (MutArray a) Source #
>>>
appendStreamN n arr = Stream.fold (MutArray.appendMax n arr)
spliceCopy :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a) Source #
Copy two arrays into a newly allocated array. If the first array is pinned the spliced array is also pinned.
Note: If you freeze and splice it will create a new array.
spliceWith :: (MonadIO m, Unbox a) => (Int -> Int -> Int) -> MutArray a -> MutArray a -> m (MutArray a) Source #
spliceWith sizer dst src
mutates dst
to append src
. If there is no
reserved space available in dst
it is reallocated to a size determined by
the sizer dstBytes srcBytes
function, where dstBytes
is the size of the
first array and srcBytes
is the size of the second array, in bytes.
Note that the returned array may be a mutated version of first array.
Pre-release
spliceExp :: (MonadIO m, Unbox a) => MutArray a -> MutArray a -> m (MutArray a) Source #
Like append
but the growth of the array is exponential. Whenever a new
allocation is required the previous array size is at least doubled.
This is useful to reduce allocations when folding many arrays together.
Note that the returned array may be a mutated version of first array.
>>>
spliceExp = MutArray.spliceWith (\l1 l2 -> max (l1 * 2) (l1 + l2))
Pre-release
unsafeSplice :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a) Source #
Really really unsafe, appends the second array into the first array. If the first array does not have enough space it may cause silent data corruption or if you are lucky a segfault.
pokeMay :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (Maybe (MutArray Word8)) Source #
Like poke
but does not grow the array when pre-allocated array
capacity becomes full.
Internal
unsafePokeSkip :: Int -> MutArray Word8 -> MutArray Word8 Source #
Skip the specified number of bytes in the array. The data in the skipped region remains uninitialzed.
unsafePeek :: (MonadIO m, Unbox a) => MutArray Word8 -> m (a, MutArray Word8) Source #
Really really unsafe, create a Haskell value from an unboxed byte array, does not check if the array is big enough, may return garbage or if you are lucky may cause a segfault.
Internal
unsafePeekSkip :: Int -> MutArray Word8 -> MutArray Word8 Source #
Discard the specified number of bytes at the beginning of the array.
buildChunks :: forall (m :: Type -> Type) a (n :: Type -> Type). (MonadIO m, Unbox a) => Int -> Fold m a (StreamK n (MutArray a)) Source #
Buffer a stream into a stream of arrays.
>>>
buildChunks n = Fold.many (MutArray.createOf n) Fold.toStreamK
Breaking an array into an array stream can be useful to consume a large array sequentially such that memory of the array is released incrementatlly.
See also: arrayStreamKFromStreamD
.
Unimplemented
chunksEndBy :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> Stream m a -> Stream m (MutArray a) Source #
Create arrays from the input stream using a predicate to find the end of the chunk. When the predicate matches, the chunk ends, the matching element is included in the chunk.
Definition:
>>>
chunksEndBy p = Stream.foldMany (Fold.takeEndBy p MutArray.create)
chunksEndBy' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> Stream m a -> Stream m (MutArray a) Source #
Like chunksEndBy
but creates pinned arrays.
chunksEndByLn :: forall (m :: Type -> Type). MonadIO m => Stream m Word8 -> Stream m (MutArray Word8) Source #
Create chunks using newline as the separator, including it.
chunksEndByLn' :: forall (m :: Type -> Type). MonadIO m => Stream m Word8 -> Stream m (MutArray Word8) Source #
Like chunksEndByLn
but creates pinned arrays.
splitEndBy_ :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a) Source #
Generate a stream of array slices using a predicate. The array element matching the predicate is dropped.
Pre-release
splitEndBy :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => (a -> Bool) -> MutArray a -> Stream m (MutArray a) Source #
Generate a stream of array slices using a predicate. The array element matching the predicate is included.
Pre-release
concatWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a Source #
concatRevWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m (MutArray a) -> Stream m a Source #
compactLeAs :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => PinnedState -> Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
This mutates the first array (if it has space) to append values from the second one. This would work for immutable arrays as well because an immutable array never has additional space so a new array is allocated instead of mutating it.
createCompactMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a) Source #
Parser createCompactMax maxElems
coalesces adjacent arrays in the
input stream only if the combined size would be less than or equal to
maxElems
elements. Note that it won't split an array if the original array
is already larger than maxElems.
maxElems
must be greater than 0.
Generates unpinned arrays irrespective of the pinning status of input arrays.
Note that a fold compacting to less than or equal to a given size is not possible, as folds cannot backtrack.
Internal
createCompactMax' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a) Source #
Pinned version of createCompactMax
.
createCompactMin :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a) Source #
Fold createCompactMin minElems
coalesces adjacent arrays in the
input stream until the size becomes greater than or equal to minElems
.
Generates unpinned arrays irrespective of the pinning status of input arrays.
createCompactMin' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a) Source #
Pinned version of createCompactMin
.
compactMin :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
compactMin n stream
coalesces adjacent arrays in the stream
until
the compacted array size becomes greater than or equal to n
.
>>>
compactMin n = Stream.foldMany (MutArray.createCompactMin n)
compactExact :: forall (m :: Type -> Type) a. Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
'compactExact n' coalesces adajacent arrays in the input stream to
arrays of exact size n
.
Unimplemented
scanCompactMin :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Scanl m (MutArray a) (Maybe (MutArray a)) Source #
Like compactMin
but a scan.
scanCompactMin' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Scanl m (MutArray a) (Maybe (MutArray a)) Source #
Like compactMin'
but a scan.
roundUpToPower2 :: Int -> Int Source #
breakOn :: MonadIO m => Word8 -> MutArray Word8 -> m (MutArray Word8, Maybe (MutArray Word8)) Source #
Deprecated: Please use breakEndByWord8_ instead.
Drops the separator byte
createOfWith :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createWithOf instead.
createWithOf alloc n
folds a maximum of n
elements into an array
allocated using the alloc
function.
The array capacity is guranteed to be at least n
.
>>>
createWithOf alloc n = Fold.take n (MutArray.unsafeCreateWithOf alloc n)
>>>
createWithOf alloc n = MutArray.appendN (alloc n) n
peekUncons :: (MonadIO m, Unbox a) => MutArray Word8 -> m (Maybe a, MutArray Word8) Source #
Deprecated: Please use peek instead.
Create a Haskell value from its unboxed representation from the head of a byte array, return the value and the remaining array.
Like uncons
except that the value is deserialized from the byte array.
Note: If you are deserializing a large number of small fields, and the types
are statically known, then it may be more efficient to declare a record of
those fields and derive an Unbox
instance of the entire record.
peekUnconsUnsafe :: (MonadIO m, Unbox a) => MutArray Word8 -> m (a, MutArray Word8) Source #
Deprecated: Please use unsafePeek instead.
Really really unsafe, create a Haskell value from an unboxed byte array, does not check if the array is big enough, may return garbage or if you are lucky may cause a segfault.
Internal
pokeAppend :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (MutArray Word8) Source #
Deprecated: Please use poke instead.
Unbox a Haskell type and append the resulting bytes to a mutable byte array. The array is grown exponentially when more space is needed.
Like snoc
except that the value is unboxed to the byte array.
Note: If you are serializing a large number of small fields, and the types
are statically known, then it may be more efficient to declare a record of
those fields and derive an Unbox
instance of the entire record.
pokeAppendMay :: (MonadIO m, Unbox a) => MutArray Word8 -> a -> m (Maybe (MutArray Word8)) Source #
Deprecated: Please use pokeMay instead.
Like poke
but does not grow the array when pre-allocated array
capacity becomes full.
Internal
newArrayWith :: (MonadIO m, Unbox a) => (Int -> Int -> IO MutByteArray) -> Int -> Int -> m (MutArray a) Source #
Deprecated: Please use emptyWithAligned instead.
emptyWithAligned allocator alignment count
allocates a new array of zero
length and with a capacity to hold count
elements, using allocator
size alignment
as the memory allocator function.
Alignment must be greater than or equal to machine word size and a power of 2.
Alignment is ignored if the allocator allocates unpinned memory.
Pre-release
spliceUnsafe :: MonadIO m => MutArray a -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use unsafeSplice instead.
Really really unsafe, appends the second array into the first array. If the first array does not have enough space it may cause silent data corruption or if you are lucky a segfault.
pokeSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8 Source #
Deprecated: Please use unsafePokeSkip instead.
Skip the specified number of bytes in the array. The data in the skipped region remains uninitialzed.
peekSkipUnsafe :: Int -> MutArray Word8 -> MutArray Word8 Source #
Deprecated: Please use unsafePeekSkip instead.
Discard the specified number of bytes at the beginning of the array.
asPtrUnsafe :: MonadIO m => MutArray a -> (Ptr a -> m b) -> m b Source #
Deprecated: Pin the array and then use unsafeAsPtr.
fromStreamDN :: (MonadIO m, Unbox a) => Int -> Stream m a -> m (MutArray a) Source #
Deprecated: Please use fromStreamN instead.
getIndicesWith :: (Monad m, Unbox a) => (forall b. IO b -> m b) -> Stream m Int -> Unfold m (MutArray a) a Source #
Deprecated: Please use indexReaderWith instead.
resize :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use growTo instead.
resizeExp :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use growExp instead.
pinnedNewBytes :: MonadIO m => Int -> m (MutArray a) Source #
Deprecated: Please use emptyOf' to create a Word8 array and cast it accordingly.
Allocates a pinned empty array that with a reserved capacity of bytes.
The memory of the array is uninitialized and the allocation is aligned as
per the Unboxed
instance of the type.
pinnedNewBytes = (unsafeCast :: Array Word8 -> a) . emptyOf'
Pre-release
writeAppendNUnsafe :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeAppendN instead.
writeNWithUnsafe :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateWithOf instead.
writeNWith :: (MonadIO m, Unbox a) => (Int -> m (MutArray a)) -> Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createWithOf instead.
pinnedWriteNUnsafe :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateOf' instead.
pinnedWriteN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createOf' instead.
pinnedWriteNAligned :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Int -> Fold m a (MutArray a) Source #
pinnedWriteNAligned align n
folds a maximum of n
elements from the
input stream to a MutArray
aligned to the given size.
Pre-release
pinnedWrite :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Deprecated: Please use create' instead.
writeRevN :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use revCreateOf instead.
pCompactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a) Source #
Deprecated: Please use createCompactMax instead.
Parser createCompactMax maxElems
coalesces adjacent arrays in the
input stream only if the combined size would be less than or equal to
maxElems
elements. Note that it won't split an array if the original array
is already larger than maxElems.
maxElems
must be greater than 0.
Generates unpinned arrays irrespective of the pinning status of input arrays.
Note that a fold compacting to less than or equal to a given size is not possible, as folds cannot backtrack.
Internal
pPinnedCompactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Parser (MutArray a) m (MutArray a) Source #
Deprecated: Please use createCompactMax' instead.
Pinned version of createCompactMax
.
fCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a) Source #
Deprecated: Please use createCompactMin instead.
Fold createCompactMin minElems
coalesces adjacent arrays in the
input stream until the size becomes greater than or equal to minElems
.
Generates unpinned arrays irrespective of the pinning status of input arrays.
fPinnedCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) (MutArray a) Source #
Deprecated: Please use createCompactMin' instead.
Pinned version of createCompactMin
.
lPinnedCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) () Source #
Deprecated: Please use scanCompactMin' instead.
Pinned version of lCompactGE
.
lCompactGE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m (MutArray a) () -> Fold m (MutArray a) () Source #
Deprecated: Please use scanCompactMin instead.
Like compactGE
but for transforming folds instead of stream.
> lCompactGE n = Fold.many (MutArray.fCompactGE n)
Generates unpinned arrays irrespective of the pinning status of input arrays.
pinnedCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use createOf' instead.
Like createOf
but creates a pinned array.
pinnedCreate :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Fold m a (MutArray a) Source #
Deprecated: Please use create' instead.
Like create
but creates a pinned array.
pinnedFromListN :: (MonadIO m, Unbox a) => Int -> [a] -> m (MutArray a) Source #
Deprecated: Please use fromListN' instead.
Like fromListN
but creates a pinned array.
pinnedFromList :: (MonadIO m, Unbox a) => [a] -> m (MutArray a) Source #
Deprecated: Please use fromList' instead.
Like fromList
but creates a pinned array.
pinnedClone :: MonadIO m => MutArray a -> m (MutArray a) Source #
Deprecated: Please use clone' instead.
unsafePinnedCreateOf :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeCreateOf' instead.
Like unsafeCreateOf
but creates a pinned array.
pinnedNewAligned :: (MonadIO m, Unbox a) => Int -> Int -> m (MutArray a) Source #
Deprecated: Please use emptyOf' to create a Word8 array and cast it accordingly.
Like emptyWithAligned
but using an allocator is a pinned memory allocator and
the alignment is dictated by the Unboxed
instance of the type.
Internal
unsafePinnedAsPtr :: MonadIO m => MutArray a -> (Ptr a -> Int -> m b) -> m b Source #
Deprecated: Pin the array and then use unsafeAsPtr.
NOTE: this is deprecated because it can lead to accidental problems if the user tries to use it to mutate the array because it does not return the new array after pinning.
grow :: (MonadIO m, Unbox a) => Int -> MutArray a -> m (MutArray a) Source #
Deprecated: Please use growTo instead.
growTo newCapacity array
changes the total capacity of the array so that
it is enough to hold the specified number of elements. Nothing is done if
the specified capacity is less than the length of the array.
If the capacity is more than largeObjectThreshold
then it is rounded up to
the block size (4K).
Nothing is done if the requested capacity is <= 0.
Pre-release
snocLinear :: (MonadIO m, Unbox a) => MutArray a -> a -> m (MutArray a) Source #
Deprecated: Please use snocGrowBy instead. snocLinear ~ snocGrowBy (1024 / sizeOf (Proxy :: Proxy a) + 1)
The array is mutated to append an additional element to it. If there
is no reserved space available in the array then it is reallocated to grow
it by arrayChunkBytes
rounded up to blockSize
when the size becomes more
than largeObjectThreshold
.
Note that the returned array may be a mutated version of the original array.
Performs O(n^2) copies to grow but is thrifty on memory.
Pre-release
unsafeAppendN :: (MonadIO m, Unbox a) => Int -> m (MutArray a) -> Fold m a (MutArray a) Source #
Deprecated: Please use unsafeAppendMax instead.
unsafeAppendN n arr
appends up to n
input items to the supplied
array.
Unsafe: Do not drive the fold beyond n
elements, it will lead to memory
corruption or segfault.
Any free space left in the array after appending n
elements is lost.
Internal
MutArray module
Arguments
:: forall (m :: Type -> Type) a. (Monad m, Unbox a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (MutArray a) (Int, Int) |
Generate a stream of array slice descriptors ((index, len)) of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
Arguments
:: forall (m :: Type -> Type) a. (Monad m, Unbox a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (MutArray a) (MutArray a) |
Generate a stream of slices of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
compactMax :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
compactLE maxElems
coalesces adjacent arrays in the input stream
only if the combined size would be less than or equal to maxElems
elements. Note that it won't split an array if the original array is already
larger than maxElems.
maxElems
must be greater than 0.
Generates unpinned arrays irrespective of the pinning status of input arrays.
compactMax' :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Like compactBySizeLE
but generates pinned arrays.
compactSepByByte_ :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.
compactEndByByte_ :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.
compactEndByLn_ :: forall (m :: Type -> Type). MonadIO m => Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Compact byte arrays on newline character, dropping the newline char.
createOfLast :: forall a (m :: Type -> Type). (Unbox a, MonadIO m) => Int -> Fold m a (MutArray a) Source #
createOfLast n
folds a maximum of n
elements from the end of the input
stream to an MutArray
.
Serialization
serialize :: (MonadIO m, Serialize a) => MutArray Word8 -> a -> m (MutArray Word8) Source #
Serialize the supplied Haskell value at the end of the mutable array, growing the array size. If there is no reserve capacity left in the array the array is reallocated to double the current size.
Like snoc
except that the value is serialized to the byte array.
Note: If you are serializing a large number of small fields, and the types
are statically known, then it may be more efficient to declare a record of
those fields and derive an Serialize
instance of the entire record.
Unstable API
deserialize :: (MonadIO m, Serialize a) => MutArray Word8 -> m (a, MutArray Word8) Source #
Deserialize a Haskell value from the beginning of a mutable array. The deserialized value is removed from the array and the remaining array is returned.
Like uncons
except that the value is deserialized from the byte array.
Note: If you are deserializing a large number of small fields, and the types
are statically known, then it may be more efficient to declare a record of
those fields and derive Serialize
instance of the entire record.
Unstable API
serializePtrN :: MutArray Word8 -> Ptr a -> Int -> m (MutArray Word8) Source #
Serializes a (Ptr, len) pair in the same way as an array. The serialized value can be de-serialized as an array or consumed as a pointer using deserializePtrN.
The Ptr must be pinned or the existence of the Ptr must be ensured by the user of this API.
Unimplemented
deserializePtrN :: MutArray Word8 -> (Ptr a -> Int -> m b) -> m (a, MutArray Word8) Source #
Consume a serialized array or (Ptr, length) from the MutArray using an IO action that consumes the pointer directly.
WARNING! The array must be a pinned array.
Unimplemented
Deprecated
Arguments
:: forall (m :: Type -> Type) a. (Monad m, Unbox a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (MutArray a) (MutArray a) |
Deprecated: Please use splitterFromLen instead.
Generate a stream of slices of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
Arguments
:: forall (m :: Type -> Type) a. (Monad m, Unbox a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (MutArray a) (Int, Int) |
Deprecated: Please use indexerFromLen instead.
Generate a stream of array slice descriptors ((index, len)) of specified length from an array, starting from the supplied array index. The last slice may be shorter than the requested length depending on the array length.
Pre-release
Arguments
:: forall (m :: Type -> Type) a. (Monad m, Unbox a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (MutArray a) (Int, Int) |
Deprecated: Please use indexerFromLen instead.
Arguments
:: forall (m :: Type -> Type) a. (Monad m, Unbox a) | |
=> Int | from index |
-> Int | length of the slice |
-> Unfold m (MutArray a) (MutArray a) |
Deprecated: Please use splitterFromLen instead.
compactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Deprecated: Please use compactMax instead.
compactLE maxElems
coalesces adjacent arrays in the input stream
only if the combined size would be less than or equal to maxElems
elements. Note that it won't split an array if the original array is already
larger than maxElems.
maxElems
must be greater than 0.
Generates unpinned arrays irrespective of the pinning status of input arrays.
pinnedCompactLE :: forall (m :: Type -> Type) a. (MonadIO m, Unbox a) => Int -> Stream m (MutArray a) -> Stream m (MutArray a) Source #
Deprecated: Please use compactMax' instead.
Like compactBySizeLE
but generates pinned arrays.
compactOnByte :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Deprecated: Please use compactSepByByte_ instead.
Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.
compactOnByteSuffix :: forall (m :: Type -> Type). MonadIO m => Word8 -> Stream m (MutArray Word8) -> Stream m (MutArray Word8) Source #
Deprecated: Please use compactEndByByte_ instead.
Split a stream of arrays on a given separator byte, dropping the separator and coalescing all the arrays between two separators into a single array.
writeIORef :: Unbox a => IORef a -> a -> IO () Source #
Deprecated: Use writeIORef from MutByteArray module.