foundation-0.0.2: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Foundation.Collection

Description

Different collections (list, vector, string, ..) unified under 1 API. an API to rules them all, and in the darkness bind them.

Synopsis

Documentation

class Zippable col => BoxedZippable col where Source #

Methods

zip :: (Sequential a, Sequential b, Element col ~ (Element a, Element b)) => a -> b -> col Source #

zip takes two collections and returns a collections of corresponding pairs. If one input collection is short, excess elements of the longer collection are discarded.

zip3 :: (Sequential a, Sequential b, Sequential c, Element col ~ (Element a, Element b, Element c)) => a -> b -> c -> col Source #

Like zip, but works with 3 collections.

zip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, Element col ~ (Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> col Source #

Like zip, but works with 4 collections.

zip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Element col ~ (Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> col Source #

Like zip, but works with 5 collections.

zip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> col Source #

Like zip, but works with 6 collections.

zip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> col Source #

Like zip, but works with 7 collections.

unzip :: (Sequential a, Sequential b, Element col ~ (Element a, Element b)) => col -> (a, b) Source #

unzip transforms a collection of pairs into a collection of first components and a collection of second components.

unzip3 :: (Sequential a, Sequential b, Sequential c, Element col ~ (Element a, Element b, Element c)) => col -> (a, b, c) Source #

Like unzip, but works on a collection of 3-element tuples.

unzip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, Element col ~ (Element a, Element b, Element c, Element d)) => col -> (a, b, c, d) Source #

Like unzip, but works on a collection of 4-element tuples.

unzip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Element col ~ (Element a, Element b, Element c, Element d, Element e)) => col -> (a, b, c, d, e) Source #

Like unzip, but works on a collection of 5-element tuples.

unzip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f)) => col -> (a, b, c, d, e, f) Source #

Like unzip, but works on a collection of 6-element tuples.

unzip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, Element col ~ (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => col -> (a, b, c, d, e, f, g) Source #

Like unzip, but works on a collection of 7-element tuples.

Instances

BoxedZippable [a] Source # 

Methods

zip :: (Sequential a, Sequential b, (* ~ Element [a]) (Element a, Element b)) => a -> b -> [a] Source #

zip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element [a]) (Element a, Element b, Element c)) => a -> b -> c -> [a] Source #

zip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element [a]) (Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> [a] Source #

zip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element [a]) (Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> [a] Source #

zip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element [a]) (Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> [a] Source #

zip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element [a]) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> [a] Source #

unzip :: (Sequential a, Sequential b, (* ~ Element [a]) (Element a, Element b)) => [a] -> (a, b) Source #

unzip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element [a]) (Element a, Element b, Element c)) => [a] -> (a, b, c) Source #

unzip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element [a]) (Element a, Element b, Element c, Element d)) => [a] -> (a, b, c, d) Source #

unzip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element [a]) (Element a, Element b, Element c, Element d, Element e)) => [a] -> (a, b, c, d, e) Source #

unzip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element [a]) (Element a, Element b, Element c, Element d, Element e, Element f)) => [a] -> (a, b, c, d, e, f) Source #

unzip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element [a]) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => [a] -> (a, b, c, d, e, f, g) Source #

BoxedZippable (Array ty) Source # 

Methods

zip :: (Sequential a, Sequential b, (* ~ Element (Array ty)) (Element a, Element b)) => a -> b -> Array ty Source #

zip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element (Array ty)) (Element a, Element b, Element c)) => a -> b -> c -> Array ty Source #

zip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d)) => a -> b -> c -> d -> Array ty Source #

zip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e)) => a -> b -> c -> d -> e -> Array ty Source #

zip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f)) => a -> b -> c -> d -> e -> f -> Array ty Source #

zip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => a -> b -> c -> d -> e -> f -> g -> Array ty Source #

unzip :: (Sequential a, Sequential b, (* ~ Element (Array ty)) (Element a, Element b)) => Array ty -> (a, b) Source #

unzip3 :: (Sequential a, Sequential b, Sequential c, (* ~ Element (Array ty)) (Element a, Element b, Element c)) => Array ty -> (a, b, c) Source #

unzip4 :: (Sequential a, Sequential b, Sequential c, Sequential d, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d)) => Array ty -> (a, b, c, d) Source #

unzip5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e)) => Array ty -> (a, b, c, d, e) Source #

unzip6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f)) => Array ty -> (a, b, c, d, e, f) Source #

unzip7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g, (* ~ Element (Array ty)) (Element a, Element b, Element c, Element d, Element e, Element f, Element g)) => Array ty -> (a, b, c, d, e, f, g) Source #

type family Element container Source #

Element type of a collection

Instances

type Element Bitmap Source # 
type Element AsciiString Source # 
type Element String Source # 
type Element [a] Source # 
type Element [a] = a
type Element (UArray ty) Source # 
type Element (UArray ty) = ty
type Element (NonEmpty a) Source # 
type Element (NonEmpty a) = Element a
type Element (Array ty) Source # 
type Element (Array ty) = ty
type Element (ChunkedUArray ty) Source # 
type Element (ChunkedUArray ty) = ty

class InnerFunctor c where Source #

A monomorphic functor that maps the inner values to values of the same type

Methods

imap :: (Element c -> Element c) -> c -> c Source #

imap :: (Functor f, Element (f a) ~ a, f a ~ c) => (a -> a) -> f a -> f a Source #

class Foldable collection where Source #

Give the ability to fold a collection on itself

Minimal complete definition

foldl, foldl', foldr

Methods

foldl :: (a -> Element collection -> a) -> a -> collection -> a Source #

Left-associative fold of a structure.

In the case of lists, foldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

Note that to produce the outermost application of the operator the entire input list must be traversed. This means that foldl' will diverge if given an infinite list.

Also note that if you want an efficient left-fold, you probably want to use foldl' instead of foldl. The reason for this is that latter does not force the "inner" results (e.g. z f x1 in the above example) before applying them to the operator (e.g. to (f x2)). This results in a thunk chain O(n) elements long, which then must be evaluated from the outside-in.

foldl' :: (a -> Element collection -> a) -> a -> collection -> a Source #

Left-associative fold of a structure but with strict application of the operator.

foldr :: (Element collection -> a -> a) -> a -> collection -> a Source #

Right-associative fold of a structure.

foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

foldr' :: (Element collection -> a -> a) -> a -> collection -> a Source #

Right-associative fold of a structure, but with strict application of the operator.

Instances

Foldable Bitmap Source # 

Methods

foldl :: (a -> Element Bitmap -> a) -> a -> Bitmap -> a Source #

foldl' :: (a -> Element Bitmap -> a) -> a -> Bitmap -> a Source #

foldr :: (Element Bitmap -> a -> a) -> a -> Bitmap -> a Source #

foldr' :: (Element Bitmap -> a -> a) -> a -> Bitmap -> a Source #

Foldable [a] Source # 

Methods

foldl :: (a -> Element [a] -> a) -> a -> [a] -> a Source #

foldl' :: (a -> Element [a] -> a) -> a -> [a] -> a Source #

foldr :: (Element [a] -> a -> a) -> a -> [a] -> a Source #

foldr' :: (Element [a] -> a -> a) -> a -> [a] -> a Source #

PrimType ty => Foldable (UArray ty) Source # 

Methods

foldl :: (a -> Element (UArray ty) -> a) -> a -> UArray ty -> a Source #

foldl' :: (a -> Element (UArray ty) -> a) -> a -> UArray ty -> a Source #

foldr :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

foldr' :: (Element (UArray ty) -> a -> a) -> a -> UArray ty -> a Source #

Foldable (Array ty) Source # 

Methods

foldl :: (a -> Element (Array ty) -> a) -> a -> Array ty -> a Source #

foldl' :: (a -> Element (Array ty) -> a) -> a -> Array ty -> a Source #

foldr :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

foldr' :: (Element (Array ty) -> a -> a) -> a -> Array ty -> a Source #

class (IsList c, Item c ~ Element c) => Collection c where Source #

A set of methods for ordered colection

Minimal complete definition

null, length, (elem | notElem), minimum, maximum

Methods

null :: c -> Bool Source #

Check if a collection is empty

length :: c -> Int Source #

Length of a collection (number of Element c)

elem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool Source #

Check if a collection contains a specific element

This is the inverse of notElem.

notElem :: forall a. (Eq a, a ~ Element c) => Element c -> c -> Bool Source #

Check if a collection does *not* contain a specific element

This is the inverse of elem.

maximum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c Source #

Get the maximum element of a collection

minimum :: forall a. (Ord a, a ~ Element c) => NonEmpty c -> Element c Source #

Get the minimum element of a collection

Instances

Collection Bitmap Source # 
Collection AsciiString Source # 
Collection String Source # 
Collection [a] Source # 

Methods

null :: [a] -> Bool Source #

length :: [a] -> Int Source #

elem :: (Eq a, (* ~ a) (Element [a])) => Element [a] -> [a] -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element [a])) => Element [a] -> [a] -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element [a])) => NonEmpty [a] -> Element [a] Source #

minimum :: (Ord a, (* ~ a) (Element [a])) => NonEmpty [a] -> Element [a] Source #

PrimType ty => Collection (UArray ty) Source # 

Methods

null :: UArray ty -> Bool Source #

length :: UArray ty -> Int Source #

elem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (UArray ty))) => Element (UArray ty) -> UArray ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

minimum :: (Ord a, (* ~ a) (Element (UArray ty))) => NonEmpty (UArray ty) -> Element (UArray ty) Source #

Collection c => Collection (NonEmpty c) Source # 

Methods

null :: NonEmpty c -> Bool Source #

length :: NonEmpty c -> Int Source #

elem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

minimum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

Collection (Array ty) Source # 

Methods

null :: Array ty -> Bool Source #

length :: Array ty -> Int Source #

elem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (Array ty))) => Element (Array ty) -> Array ty -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

minimum :: (Ord a, (* ~ a) (Element (Array ty))) => NonEmpty (Array ty) -> Element (Array ty) Source #

PrimType ty => Collection (ChunkedUArray ty) Source # 

data NonEmpty a Source #

NonEmpty property for any Collection

This can only be made, through the nonEmpty smart contructor

Instances

Collection c => IsList (NonEmpty c) Source # 

Associated Types

type Item (NonEmpty c) :: * #

Methods

fromList :: [Item (NonEmpty c)] -> NonEmpty c #

fromListN :: Int -> [Item (NonEmpty c)] -> NonEmpty c #

toList :: NonEmpty c -> [Item (NonEmpty c)] #

Eq a => Eq (NonEmpty a) Source # 

Methods

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

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

Show a => Show (NonEmpty a) Source # 

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Collection c => Collection (NonEmpty c) Source # 

Methods

null :: NonEmpty c -> Bool Source #

length :: NonEmpty c -> Int Source #

elem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

notElem :: (Eq a, (* ~ a) (Element (NonEmpty c))) => Element (NonEmpty c) -> NonEmpty c -> Bool Source #

maximum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

minimum :: (Ord a, (* ~ a) (Element (NonEmpty c))) => NonEmpty (NonEmpty c) -> Element (NonEmpty c) Source #

type Item (NonEmpty c) Source # 
type Item (NonEmpty c) = Item c
type Element (NonEmpty a) Source # 
type Element (NonEmpty a) = Element a

nonEmpty :: Collection c => c -> Maybe (NonEmpty c) Source #

Smart constructor to create a NonEmpty collection

If the collection is empty, then Nothing is returned Otherwise, the collection is wrapped in the NonEmpty property

nonEmpty_ :: Collection c => c -> NonEmpty c Source #

same as nonEmpty, but assume that the collection is non empty, and return an asynchronous error if it is.

class (IsList c, Item c ~ Element c, Monoid c, Collection c) => Sequential c where Source #

A set of methods for ordered colection

Methods

take :: Int -> c -> c Source #

Take the first @n elements of a collection

revTake :: Int -> c -> c Source #

Take the last @n elements of a collection

drop :: Int -> c -> c Source #

Drop the first @n elements of a collection

revDrop :: Int -> c -> c Source #

Drop the last @n elements of a collection

splitAt :: Int -> c -> (c, c) Source #

Split the collection at the @n'th elements

revSplitAt :: Int -> c -> (c, c) Source #

Split the collection at the @n'th elements from the end

splitOn :: (Element c -> Bool) -> c -> [c] Source #

Split on a specific elements returning a list of colletion

break :: (Element c -> Bool) -> c -> (c, c) Source #

Split a collection when the predicate return true

breakElem :: Eq (Element c) => Element c -> c -> (c, c) Source #

Split a collection when the predicate return true

intersperse :: Element c -> c -> c Source #

The intersperse function takes an element and a list and `intersperses' that element between the elements of the list. For example,

intersperse ',' "abcde" == "a,b,c,d,e"

intercalate :: Monoid (Item c) => Element c -> c -> Element c Source #

intercalate xs xss is equivalent to (mconcat (intersperse xs xss)). It inserts the list xs in between the lists in xss and concatenates the result.

span :: (Element c -> Bool) -> c -> (c, c) Source #

Split a collection while the predicate return true

filter :: (Element c -> Bool) -> c -> c Source #

Filter all the elements that satisfy the predicate

partition :: (Element c -> Bool) -> c -> (c, c) Source #

Partition the elements thtat satisfy the predicate and those that don't

reverse :: c -> c Source #

Reverse a collection

uncons :: c -> Maybe (Element c, c) Source #

Decompose a collection into its first element and the remaining collection. If the collection is empty, returns Nothing.

unsnoc :: c -> Maybe (c, Element c) Source #

Decompose a collection into a collection without its last element, and the last element If the collection is empty, returns Nothing.

snoc :: c -> Element c -> c Source #

Prepend an element to an ordered collection

cons :: Element c -> c -> c Source #

Append an element to an ordered collection

find :: (Element c -> Bool) -> c -> Maybe (Element c) Source #

Find an element in an ordered collection

sortBy :: (Element c -> Element c -> Ordering) -> c -> c Source #

Sort an ordered collection using the specified order function

singleton :: Element c -> c Source #

Create a collection with a single element

head :: NonEmpty c -> Element c Source #

get the first element of a non-empty collection

last :: NonEmpty c -> Element c Source #

get the last element of a non-empty collection

tail :: NonEmpty c -> c Source #

Extract the elements after the first element of a non-empty collection.

init :: NonEmpty c -> c Source #

Extract the elements before the last element of a non-empty collection.

isPrefixOf :: Eq (Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a prefix of the second.

isPrefixOf :: Eq c => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a prefix of the second.

isSuffixOf :: Eq (Element c) => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a suffix of the second.

isSuffixOf :: Eq c => c -> c -> Bool Source #

Takes two collections and returns True iff the first collection is a suffix of the second.

Instances

Sequential Bitmap Source # 

Methods

take :: Int -> Bitmap -> Bitmap Source #

revTake :: Int -> Bitmap -> Bitmap Source #

drop :: Int -> Bitmap -> Bitmap Source #

revDrop :: Int -> Bitmap -> Bitmap Source #

splitAt :: Int -> Bitmap -> (Bitmap, Bitmap) Source #

revSplitAt :: Int -> Bitmap -> (Bitmap, Bitmap) Source #

splitOn :: (Element Bitmap -> Bool) -> Bitmap -> [Bitmap] Source #

break :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

breakElem :: Element Bitmap -> Bitmap -> (Bitmap, Bitmap) Source #

intersperse :: Element Bitmap -> Bitmap -> Bitmap Source #

intercalate :: Element Bitmap -> Bitmap -> Element Bitmap Source #

span :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

filter :: (Element Bitmap -> Bool) -> Bitmap -> Bitmap Source #

partition :: (Element Bitmap -> Bool) -> Bitmap -> (Bitmap, Bitmap) Source #

reverse :: Bitmap -> Bitmap Source #

uncons :: Bitmap -> Maybe (Element Bitmap, Bitmap) Source #

unsnoc :: Bitmap -> Maybe (Bitmap, Element Bitmap) Source #

snoc :: Bitmap -> Element Bitmap -> Bitmap Source #

cons :: Element Bitmap -> Bitmap -> Bitmap Source #

find :: (Element Bitmap -> Bool) -> Bitmap -> Maybe (Element Bitmap) Source #

sortBy :: (Element Bitmap -> Element Bitmap -> Ordering) -> Bitmap -> Bitmap Source #

singleton :: Element Bitmap -> Bitmap Source #

head :: NonEmpty Bitmap -> Element Bitmap Source #

last :: NonEmpty Bitmap -> Element Bitmap Source #

tail :: NonEmpty Bitmap -> Bitmap Source #

init :: NonEmpty Bitmap -> Bitmap Source #

isPrefixOf :: Bitmap -> Bitmap -> Bool Source #

isSuffixOf :: Bitmap -> Bitmap -> Bool Source #

Sequential AsciiString Source # 

Methods

take :: Int -> AsciiString -> AsciiString Source #

revTake :: Int -> AsciiString -> AsciiString Source #

drop :: Int -> AsciiString -> AsciiString Source #

revDrop :: Int -> AsciiString -> AsciiString Source #

splitAt :: Int -> AsciiString -> (AsciiString, AsciiString) Source #

revSplitAt :: Int -> AsciiString -> (AsciiString, AsciiString) Source #

splitOn :: (Element AsciiString -> Bool) -> AsciiString -> [AsciiString] Source #

break :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

breakElem :: Element AsciiString -> AsciiString -> (AsciiString, AsciiString) Source #

intersperse :: Element AsciiString -> AsciiString -> AsciiString Source #

intercalate :: Element AsciiString -> AsciiString -> Element AsciiString Source #

span :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

filter :: (Element AsciiString -> Bool) -> AsciiString -> AsciiString Source #

partition :: (Element AsciiString -> Bool) -> AsciiString -> (AsciiString, AsciiString) Source #

reverse :: AsciiString -> AsciiString Source #

uncons :: AsciiString -> Maybe (Element AsciiString, AsciiString) Source #

unsnoc :: AsciiString -> Maybe (AsciiString, Element AsciiString) Source #

snoc :: AsciiString -> Element AsciiString -> AsciiString Source #

cons :: Element AsciiString -> AsciiString -> AsciiString Source #

find :: (Element AsciiString -> Bool) -> AsciiString -> Maybe (Element AsciiString) Source #

sortBy :: (Element AsciiString -> Element AsciiString -> Ordering) -> AsciiString -> AsciiString Source #

singleton :: Element AsciiString -> AsciiString Source #

head :: NonEmpty AsciiString -> Element AsciiString Source #

last :: NonEmpty AsciiString -> Element AsciiString Source #

tail :: NonEmpty AsciiString -> AsciiString Source #

init :: NonEmpty AsciiString -> AsciiString Source #

isPrefixOf :: AsciiString -> AsciiString -> Bool Source #

isSuffixOf :: AsciiString -> AsciiString -> Bool Source #

Sequential String Source # 

Methods

take :: Int -> String -> String Source #

revTake :: Int -> String -> String Source #

drop :: Int -> String -> String Source #

revDrop :: Int -> String -> String Source #

splitAt :: Int -> String -> (String, String) Source #

revSplitAt :: Int -> String -> (String, String) Source #

splitOn :: (Element String -> Bool) -> String -> [String] Source #

break :: (Element String -> Bool) -> String -> (String, String) Source #

breakElem :: Element String -> String -> (String, String) Source #

intersperse :: Element String -> String -> String Source #

intercalate :: Element String -> String -> Element String Source #

span :: (Element String -> Bool) -> String -> (String, String) Source #

filter :: (Element String -> Bool) -> String -> String Source #

partition :: (Element String -> Bool) -> String -> (String, String) Source #

reverse :: String -> String Source #

uncons :: String -> Maybe (Element String, String) Source #

unsnoc :: String -> Maybe (String, Element String) Source #

snoc :: String -> Element String -> String Source #

cons :: Element String -> String -> String Source #

find :: (Element String -> Bool) -> String -> Maybe (Element String) Source #

sortBy :: (Element String -> Element String -> Ordering) -> String -> String Source #

singleton :: Element String -> String Source #

head :: NonEmpty String -> Element String Source #

last :: NonEmpty String -> Element String Source #

tail :: NonEmpty String -> String Source #

init :: NonEmpty String -> String Source #

isPrefixOf :: String -> String -> Bool Source #

isSuffixOf :: String -> String -> Bool Source #

Sequential [a] Source # 

Methods

take :: Int -> [a] -> [a] Source #

revTake :: Int -> [a] -> [a] Source #

drop :: Int -> [a] -> [a] Source #

revDrop :: Int -> [a] -> [a] Source #

splitAt :: Int -> [a] -> ([a], [a]) Source #

revSplitAt :: Int -> [a] -> ([a], [a]) Source #

splitOn :: (Element [a] -> Bool) -> [a] -> [[a]] Source #

break :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

breakElem :: Element [a] -> [a] -> ([a], [a]) Source #

intersperse :: Element [a] -> [a] -> [a] Source #

intercalate :: Element [a] -> [a] -> Element [a] Source #

span :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

filter :: (Element [a] -> Bool) -> [a] -> [a] Source #

partition :: (Element [a] -> Bool) -> [a] -> ([a], [a]) Source #

reverse :: [a] -> [a] Source #

uncons :: [a] -> Maybe (Element [a], [a]) Source #

unsnoc :: [a] -> Maybe ([a], Element [a]) Source #

snoc :: [a] -> Element [a] -> [a] Source #

cons :: Element [a] -> [a] -> [a] Source #

find :: (Element [a] -> Bool) -> [a] -> Maybe (Element [a]) Source #

sortBy :: (Element [a] -> Element [a] -> Ordering) -> [a] -> [a] Source #

singleton :: Element [a] -> [a] Source #

head :: NonEmpty [a] -> Element [a] Source #

last :: NonEmpty [a] -> Element [a] Source #

tail :: NonEmpty [a] -> [a] Source #

init :: NonEmpty [a] -> [a] Source #

isPrefixOf :: [a] -> [a] -> Bool Source #

isSuffixOf :: [a] -> [a] -> Bool Source #

PrimType ty => Sequential (UArray ty) Source # 

Methods

take :: Int -> UArray ty -> UArray ty Source #

revTake :: Int -> UArray ty -> UArray ty Source #

drop :: Int -> UArray ty -> UArray ty Source #

revDrop :: Int -> UArray ty -> UArray ty Source #

splitAt :: Int -> UArray ty -> (UArray ty, UArray ty) Source #

revSplitAt :: Int -> UArray ty -> (UArray ty, UArray ty) Source #

splitOn :: (Element (UArray ty) -> Bool) -> UArray ty -> [UArray ty] Source #

break :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

breakElem :: Element (UArray ty) -> UArray ty -> (UArray ty, UArray ty) Source #

intersperse :: Element (UArray ty) -> UArray ty -> UArray ty Source #

intercalate :: Element (UArray ty) -> UArray ty -> Element (UArray ty) Source #

span :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

filter :: (Element (UArray ty) -> Bool) -> UArray ty -> UArray ty Source #

partition :: (Element (UArray ty) -> Bool) -> UArray ty -> (UArray ty, UArray ty) Source #

reverse :: UArray ty -> UArray ty Source #

uncons :: UArray ty -> Maybe (Element (UArray ty), UArray ty) Source #

unsnoc :: UArray ty -> Maybe (UArray ty, Element (UArray ty)) Source #

snoc :: UArray ty -> Element (UArray ty) -> UArray ty Source #

cons :: Element (UArray ty) -> UArray ty -> UArray ty Source #

find :: (Element (UArray ty) -> Bool) -> UArray ty -> Maybe (Element (UArray ty)) Source #

sortBy :: (Element (UArray ty) -> Element (UArray ty) -> Ordering) -> UArray ty -> UArray ty Source #

singleton :: Element (UArray ty) -> UArray ty Source #

head :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

last :: NonEmpty (UArray ty) -> Element (UArray ty) Source #

tail :: NonEmpty (UArray ty) -> UArray ty Source #

init :: NonEmpty (UArray ty) -> UArray ty Source #

isPrefixOf :: UArray ty -> UArray ty -> Bool Source #

isSuffixOf :: UArray ty -> UArray ty -> Bool Source #

Sequential (Array ty) Source # 

Methods

take :: Int -> Array ty -> Array ty Source #

revTake :: Int -> Array ty -> Array ty Source #

drop :: Int -> Array ty -> Array ty Source #

revDrop :: Int -> Array ty -> Array ty Source #

splitAt :: Int -> Array ty -> (Array ty, Array ty) Source #

revSplitAt :: Int -> Array ty -> (Array ty, Array ty) Source #

splitOn :: (Element (Array ty) -> Bool) -> Array ty -> [Array ty] Source #

break :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

breakElem :: Element (Array ty) -> Array ty -> (Array ty, Array ty) Source #

intersperse :: Element (Array ty) -> Array ty -> Array ty Source #

intercalate :: Element (Array ty) -> Array ty -> Element (Array ty) Source #

span :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

filter :: (Element (Array ty) -> Bool) -> Array ty -> Array ty Source #

partition :: (Element (Array ty) -> Bool) -> Array ty -> (Array ty, Array ty) Source #

reverse :: Array ty -> Array ty Source #

uncons :: Array ty -> Maybe (Element (Array ty), Array ty) Source #

unsnoc :: Array ty -> Maybe (Array ty, Element (Array ty)) Source #

snoc :: Array ty -> Element (Array ty) -> Array ty Source #

cons :: Element (Array ty) -> Array ty -> Array ty Source #

find :: (Element (Array ty) -> Bool) -> Array ty -> Maybe (Element (Array ty)) Source #

sortBy :: (Element (Array ty) -> Element (Array ty) -> Ordering) -> Array ty -> Array ty Source #

singleton :: Element (Array ty) -> Array ty Source #

head :: NonEmpty (Array ty) -> Element (Array ty) Source #

last :: NonEmpty (Array ty) -> Element (Array ty) Source #

tail :: NonEmpty (Array ty) -> Array ty Source #

init :: NonEmpty (Array ty) -> Array ty Source #

isPrefixOf :: Array ty -> Array ty -> Bool Source #

isSuffixOf :: Array ty -> Array ty -> Bool Source #

PrimType ty => Sequential (ChunkedUArray ty) Source # 

Methods

take :: Int -> ChunkedUArray ty -> ChunkedUArray ty Source #

revTake :: Int -> ChunkedUArray ty -> ChunkedUArray ty Source #

drop :: Int -> ChunkedUArray ty -> ChunkedUArray ty Source #

revDrop :: Int -> ChunkedUArray ty -> ChunkedUArray ty Source #

splitAt :: Int -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

revSplitAt :: Int -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

splitOn :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> [ChunkedUArray ty] Source #

break :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

breakElem :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

intersperse :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

intercalate :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> Element (ChunkedUArray ty) Source #

span :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

filter :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> ChunkedUArray ty Source #

partition :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

reverse :: ChunkedUArray ty -> ChunkedUArray ty Source #

uncons :: ChunkedUArray ty -> Maybe (Element (ChunkedUArray ty), ChunkedUArray ty) Source #

unsnoc :: ChunkedUArray ty -> Maybe (ChunkedUArray ty, Element (ChunkedUArray ty)) Source #

snoc :: ChunkedUArray ty -> Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

cons :: Element (ChunkedUArray ty) -> ChunkedUArray ty -> ChunkedUArray ty Source #

find :: (Element (ChunkedUArray ty) -> Bool) -> ChunkedUArray ty -> Maybe (Element (ChunkedUArray ty)) Source #

sortBy :: (Element (ChunkedUArray ty) -> Element (ChunkedUArray ty) -> Ordering) -> ChunkedUArray ty -> ChunkedUArray ty Source #

singleton :: Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

head :: NonEmpty (ChunkedUArray ty) -> Element (ChunkedUArray ty) Source #

last :: NonEmpty (ChunkedUArray ty) -> Element (ChunkedUArray ty) Source #

tail :: NonEmpty (ChunkedUArray ty) -> ChunkedUArray ty Source #

init :: NonEmpty (ChunkedUArray ty) -> ChunkedUArray ty Source #

isPrefixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

isSuffixOf :: ChunkedUArray ty -> ChunkedUArray ty -> Bool Source #

class MutableCollection c where Source #

Collection of things that can be made mutable, modified and then freezed into an MutableFreezed collection

Minimal complete definition

thaw, freeze, mutNew, mutWrite, mutRead, mutUnsafeWrite, mutUnsafeRead

Associated Types

type MutableFreezed c Source #

type MutableKey c Source #

type MutableValue c Source #

Methods

unsafeThaw :: PrimMonad prim => MutableFreezed c -> prim (c (PrimState prim)) Source #

unsafeFreeze :: PrimMonad prim => c (PrimState prim) -> prim (MutableFreezed c) Source #

thaw :: PrimMonad prim => MutableFreezed c -> prim (c (PrimState prim)) Source #

freeze :: PrimMonad prim => c (PrimState prim) -> prim (MutableFreezed c) Source #

mutNew :: PrimMonad prim => Int -> prim (c (PrimState prim)) Source #

mutUnsafeWrite :: PrimMonad prim => c (PrimState prim) -> MutableKey c -> MutableValue c -> prim () Source #

mutWrite :: PrimMonad prim => c (PrimState prim) -> MutableKey c -> MutableValue c -> prim () Source #

mutUnsafeRead :: PrimMonad prim => c (PrimState prim) -> MutableKey c -> prim (MutableValue c) Source #

mutRead :: PrimMonad prim => c (PrimState prim) -> MutableKey c -> prim (MutableValue c) Source #

Instances

MutableCollection MutableBitmap Source # 
PrimType ty => MutableCollection (MUArray ty) Source # 

Associated Types

type MutableFreezed (MUArray ty :: * -> *) :: * Source #

type MutableKey (MUArray ty :: * -> *) :: * Source #

type MutableValue (MUArray ty :: * -> *) :: * Source #

Methods

unsafeThaw :: PrimMonad prim => MutableFreezed (MUArray ty) -> prim (MUArray ty (PrimState prim)) Source #

unsafeFreeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (MutableFreezed (MUArray ty)) Source #

thaw :: PrimMonad prim => MutableFreezed (MUArray ty) -> prim (MUArray ty (PrimState prim)) Source #

freeze :: PrimMonad prim => MUArray ty (PrimState prim) -> prim (MutableFreezed (MUArray ty)) Source #

mutNew :: PrimMonad prim => Int -> prim (MUArray ty (PrimState prim)) Source #

mutUnsafeWrite :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> MutableValue (MUArray ty) -> prim () Source #

mutWrite :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> MutableValue (MUArray ty) -> prim () Source #

mutUnsafeRead :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> prim (MutableValue (MUArray ty)) Source #

mutRead :: PrimMonad prim => MUArray ty (PrimState prim) -> MutableKey (MUArray ty) -> prim (MutableValue (MUArray ty)) Source #

MutableCollection (MArray ty) Source # 

Associated Types

type MutableFreezed (MArray ty :: * -> *) :: * Source #

type MutableKey (MArray ty :: * -> *) :: * Source #

type MutableValue (MArray ty :: * -> *) :: * Source #

Methods

unsafeThaw :: PrimMonad prim => MutableFreezed (MArray ty) -> prim (MArray ty (PrimState prim)) Source #

unsafeFreeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (MutableFreezed (MArray ty)) Source #

thaw :: PrimMonad prim => MutableFreezed (MArray ty) -> prim (MArray ty (PrimState prim)) Source #

freeze :: PrimMonad prim => MArray ty (PrimState prim) -> prim (MutableFreezed (MArray ty)) Source #

mutNew :: PrimMonad prim => Int -> prim (MArray ty (PrimState prim)) Source #

mutUnsafeWrite :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> MutableValue (MArray ty) -> prim () Source #

mutWrite :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> MutableValue (MArray ty) -> prim () Source #

mutUnsafeRead :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> prim (MutableValue (MArray ty)) Source #

mutRead :: PrimMonad prim => MArray ty (PrimState prim) -> MutableKey (MArray ty) -> prim (MutableValue (MArray ty)) Source #

class IndexedCollection c where Source #

Collection of elements that can indexed by int

Minimal complete definition

(!), findIndex

Methods

(!) :: c -> Int -> Maybe (Element c) Source #

findIndex :: (Element c -> Bool) -> c -> Maybe Int Source #

class KeyedCollection c where Source #

Collection of things that can be looked up by Key

Minimal complete definition

lookup

Associated Types

type Key c Source #

type Value c Source #

Methods

lookup :: Key c -> c -> Maybe (Value c) Source #

Instances

Eq k => KeyedCollection [(k, v)] Source # 

Associated Types

type Key [(k, v)] :: * Source #

type Value [(k, v)] :: * Source #

Methods

lookup :: Key [(k, v)] -> [(k, v)] -> Maybe (Value [(k, v)]) Source #

class Sequential col => Zippable col where Source #

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element col) -> a -> b -> col Source #

zipWith generalises zip by zipping with the function given as the first argument, instead of a tupling function. For example, zipWith (+) is applied to two collections to produce the collection of corresponding sums.

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element col) -> a -> b -> c -> col Source #

Like zipWith, but works with 3 collections.

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element col) -> a -> b -> c -> d -> col Source #

Like zipWith, but works with 4 collections.

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element col) -> a -> b -> c -> d -> e -> col Source #

Like zipWith, but works with 5 collections.

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element col) -> a -> b -> c -> d -> e -> f -> col Source #

Like zipWith, but works with 6 collections.

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element col) -> a -> b -> c -> d -> e -> f -> g -> col Source #

Like zipWith, but works with 7 collections.

Instances

Zippable AsciiString Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element AsciiString) -> a -> b -> AsciiString Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element AsciiString) -> a -> b -> c -> AsciiString Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element AsciiString) -> a -> b -> c -> d -> AsciiString Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element AsciiString) -> a -> b -> c -> d -> e -> AsciiString Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element AsciiString) -> a -> b -> c -> d -> e -> f -> AsciiString Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element AsciiString) -> a -> b -> c -> d -> e -> f -> g -> AsciiString Source #

Zippable String Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element String) -> a -> b -> String Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element String) -> a -> b -> c -> String Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element String) -> a -> b -> c -> d -> String Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element String) -> a -> b -> c -> d -> e -> String Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element String) -> a -> b -> c -> d -> e -> f -> String Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element String) -> a -> b -> c -> d -> e -> f -> g -> String Source #

Zippable [c] Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element [c]) -> a -> b -> [c] Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element [c]) -> a -> b -> c -> [c] Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element [c]) -> a -> b -> c -> d -> [c] Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element [c]) -> a -> b -> c -> d -> e -> [c] Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element [c]) -> a -> b -> c -> d -> e -> f -> [c] Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element [c]) -> a -> b -> c -> d -> e -> f -> g -> [c] Source #

PrimType ty => Zippable (UArray ty) Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (UArray ty)) -> a -> b -> UArray ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (UArray ty)) -> a -> b -> c -> UArray ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (UArray ty)) -> a -> b -> c -> d -> UArray ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (UArray ty)) -> a -> b -> c -> d -> e -> UArray ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> UArray ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (UArray ty)) -> a -> b -> c -> d -> e -> f -> g -> UArray ty Source #

Zippable (Array ty) Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element (Array ty)) -> a -> b -> Array ty Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element (Array ty)) -> a -> b -> c -> Array ty Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element (Array ty)) -> a -> b -> c -> d -> Array ty Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element (Array ty)) -> a -> b -> c -> d -> e -> Array ty Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element (Array ty)) -> a -> b -> c -> d -> e -> f -> Array ty Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element (Array ty)) -> a -> b -> c -> d -> e -> f -> g -> Array ty Source #

class Buildable col where Source #

Collections that can be built chunk by chunk.

Use the Monad instance of Builder to chain append operations and feed it into build:

>>> runST $ build 32 (append 'a' >> append 'b' >> append 'c') :: UArray Char
"abc"

Minimal complete definition

append, build

Associated Types

type Mutable col :: * -> * Source #

Mutable collection type used for incrementally writing chunks.

type Step col Source #

Unit of the smallest step possible in an append operation.

A UTF-8 character can have a size between 1 and 4 bytes, so this should be defined as 1 byte for collections of Char.

Methods

append :: PrimMonad prim => Element col -> Builder col prim () Source #

build :: PrimMonad prim => Int -> Builder col prim () -> prim col Source #

Instances

Buildable String Source # 

Associated Types

type Mutable String :: * -> * Source #

type Step String :: * Source #

Methods

append :: PrimMonad prim => Element String -> Builder String prim () Source #

build :: PrimMonad prim => Int -> Builder String prim () -> prim String Source #

PrimType ty => Buildable (UArray ty) Source # 

Associated Types

type Mutable (UArray ty) :: * -> * Source #

type Step (UArray ty) :: * Source #

Methods

append :: PrimMonad prim => Element (UArray ty) -> Builder (UArray ty) prim () Source #

build :: PrimMonad prim => Int -> Builder (UArray ty) prim () -> prim (UArray ty) Source #

Buildable (Array ty) Source # 

Associated Types

type Mutable (Array ty) :: * -> * Source #

type Step (Array ty) :: * Source #

Methods

append :: PrimMonad prim => Element (Array ty) -> Builder (Array ty) prim () Source #

build :: PrimMonad prim => Int -> Builder (Array ty) prim () -> prim (Array ty) Source #

newtype Builder col st a Source #

Constructors

Builder 

Fields

Instances

Monad st => Monad (Builder col st) Source # 

Methods

(>>=) :: Builder col st a -> (a -> Builder col st b) -> Builder col st b #

(>>) :: Builder col st a -> Builder col st b -> Builder col st b #

return :: a -> Builder col st a #

fail :: String -> Builder col st a #

Monad st => Functor (Builder col st) Source # 

Methods

fmap :: (a -> b) -> Builder col st a -> Builder col st b #

(<$) :: a -> Builder col st b -> Builder col st a #

Monad st => Applicative (Builder col st) Source # 

Methods

pure :: a -> Builder col st a #

(<*>) :: Builder col st (a -> b) -> Builder col st a -> Builder col st b #

(*>) :: Builder col st a -> Builder col st b -> Builder col st b #

(<*) :: Builder col st a -> Builder col st b -> Builder col st a #

data BuildingState col st Source #

The in-progress state of a building operation.

The previous buffers are in reverse order, and this contains the current buffer and the state of progress packing the elements inside.

Constructors

BuildingState 

Fields