array-chunks-0.1.1.0: Lists of chunks

Safe HaskellNone
LanguageHaskell2010

Data.Chunks

Synopsis

Documentation

data Chunks a Source #

A list of chunks. This is a foundation on top of which efficient builder-like abstractions can be implemented. There are no restrictions on the number of elements in each chunk, although extremely small chunks (singleton or doubleton chunks) may lead to poor performance.

Constructors

ChunksCons !(SmallArray a) !(Chunks a) 
ChunksNil 
Instances
Foldable Chunks Source # 
Instance details

Defined in Data.Chunks

Methods

fold :: Monoid m => Chunks m -> m #

foldMap :: Monoid m => (a -> m) -> Chunks a -> m #

foldr :: (a -> b -> b) -> b -> Chunks a -> b #

foldr' :: (a -> b -> b) -> b -> Chunks a -> b #

foldl :: (b -> a -> b) -> b -> Chunks a -> b #

foldl' :: (b -> a -> b) -> b -> Chunks a -> b #

foldr1 :: (a -> a -> a) -> Chunks a -> a #

foldl1 :: (a -> a -> a) -> Chunks a -> a #

toList :: Chunks a -> [a] #

null :: Chunks a -> Bool #

length :: Chunks a -> Int #

elem :: Eq a => a -> Chunks a -> Bool #

maximum :: Ord a => Chunks a -> a #

minimum :: Ord a => Chunks a -> a #

sum :: Num a => Chunks a -> a #

product :: Num a => Chunks a -> a #

IsList (Chunks a) Source # 
Instance details

Defined in Data.Chunks

Associated Types

type Item (Chunks a) :: Type #

Methods

fromList :: [Item (Chunks a)] -> Chunks a #

fromListN :: Int -> [Item (Chunks a)] -> Chunks a #

toList :: Chunks a -> [Item (Chunks a)] #

Eq a => Eq (Chunks a) Source # 
Instance details

Defined in Data.Chunks

Methods

(==) :: Chunks a -> Chunks a -> Bool #

(/=) :: Chunks a -> Chunks a -> Bool #

Show a => Show (Chunks a) Source # 
Instance details

Defined in Data.Chunks

Methods

showsPrec :: Int -> Chunks a -> ShowS #

show :: Chunks a -> String #

showList :: [Chunks a] -> ShowS #

Semigroup (Chunks a) Source # 
Instance details

Defined in Data.Chunks

Methods

(<>) :: Chunks a -> Chunks a -> Chunks a #

sconcat :: NonEmpty (Chunks a) -> Chunks a #

stimes :: Integral b => b -> Chunks a -> Chunks a #

Monoid (Chunks a) Source # 
Instance details

Defined in Data.Chunks

Methods

mempty :: Chunks a #

mappend :: Chunks a -> Chunks a -> Chunks a #

mconcat :: [Chunks a] -> Chunks a #

type Item (Chunks a) Source # 
Instance details

Defined in Data.Chunks

type Item (Chunks a) = SmallArray a

reverse :: Chunks a -> Chunks a Source #

Reverse chunks but not the elements within each chunk.

>>> reverse [[42,17,94],[6,12],[3,14]]
[[3,14],[6,12],[42,17,94]]

reverseOnto :: Chunks a -> Chunks a -> Chunks a Source #

Variant of reverse that allows the caller to provide an initial list of chunks that the reversed chunks will be pushed onto.

>>> reverseOnto [[15],[12,4]] [[42,17,94],[6,12],[3,14]]
[[3,14],[6,12],[42,17,94],[15],[12,4]]

copy Source #

Arguments

:: SmallMutableArray s a

Destination

-> Int

Destination offset

-> Chunks a

Source

-> ST s Int

Returns the next index into the destination after the payload

Copy the contents of the chunks into a mutable array. Precondition: The destination must have enough space to house the contents. This is not checked.

dest (before): [x,x,x,x,x,x,x,x,x,x,x,x]
copy dest 2 [[X,Y,Z],[A,B],[C,D]] (returns 9)
dest (after):  [x,x,X,Y,Z,A,B,C,D,x,x,x]

copyReverse Source #

Arguments

:: SmallMutableArray s a

Destination

-> Int

Destination range successor

-> Chunks a

Source

-> ST s Int

Returns the next index into the destination after the payload

Copy the contents of the chunks into a mutable array, reversing the order of the chunks. Precondition: The destination must have enough space to house the contents. This is not checked.

dest (before): [x,x,x,x,x,x,x,x,x,x,x,x]
copyReverse dest 10 [[X,Y,Z],[A,B],[C,D]] (returns 3)
dest (after):  [x,x,x,C,D,A,B,X,Y,Z,x,x]