foundation-0.0.23: 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 #

Minimal complete definition

Nothing

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 # 
Instance details

Defined in Foundation.Collection.Zippable

Methods

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

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

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

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

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

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

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

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

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

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

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

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

BoxedZippable (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Zippable

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 String Source # 
Instance details

Defined in Foundation.Collection.Element

type Element AsciiString Source # 
Instance details

Defined in Foundation.Collection.Element

type Element Bitmap Source # 
Instance details

Defined in Foundation.Array.Bitmap

type Element CSV Source # 
Instance details

Defined in Foundation.Format.CSV.Types

type Element CSV = Row
type Element Row Source # 
Instance details

Defined in Foundation.Format.CSV.Types

type Element [a] Source # 
Instance details

Defined in Foundation.Collection.Element

type Element [a] = a
type Element (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (Array ty) = ty
type Element (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (UArray ty) = ty
type Element (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (Block ty) = ty
type Element (NonEmpty a) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (NonEmpty a) = Element a
type Element (DList a) Source # 
Instance details

Defined in Foundation.List.DList

type Element (DList a) = a
type Element (ChunkedUArray ty) Source # 
Instance details

Defined in Foundation.Array.Chunked.Unboxed

type Element (ChunkedUArray ty) = ty
type Element (BlockN n ty) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (BlockN n ty) = ty
type Element (ListN n a) Source # 
Instance details

Defined in Foundation.Collection.Element

type Element (ListN n a) = a

class InnerFunctor c where Source #

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

Minimal complete definition

Nothing

Methods

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

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

Instances
InnerFunctor String Source # 
Instance details

Defined in Foundation.Collection.InnerFunctor

InnerFunctor Bitmap Source # 
Instance details

Defined in Foundation.Array.Bitmap

InnerFunctor [a] Source # 
Instance details

Defined in Foundation.Collection.InnerFunctor

Methods

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

InnerFunctor (Array ty) Source # 
Instance details

Defined in Foundation.Collection.InnerFunctor

Methods

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

PrimType ty => InnerFunctor (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.InnerFunctor

Methods

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

class Foldable collection where Source #

Give the ability to fold a collection on itself

Minimal complete definition

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.

Note that Foundation only provides foldl', a strict version of foldl because the lazy version is seldom useful.

Left-associative fold of a structure 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 # 
Instance details

Defined in Foundation.Array.Bitmap

Methods

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 # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

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

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

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

Foldable (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

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 #

PrimType ty => Foldable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

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 #

PrimType ty => Foldable (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

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

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

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

Foldable (DList a) Source # 
Instance details

Defined in Foundation.List.DList

Methods

foldl' :: (a0 -> Element (DList a) -> a0) -> a0 -> DList a -> a0 Source #

foldr :: (Element (DList a) -> a0 -> a0) -> a0 -> DList a -> a0 Source #

foldr' :: (Element (DList a) -> a0 -> a0) -> a0 -> DList a -> a0 Source #

PrimType ty => Foldable (ChunkedUArray ty) Source # 
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Methods

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

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

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

PrimType ty => Foldable (BlockN n ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

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

foldr :: (Element (BlockN n ty) -> a -> a) -> a -> BlockN n ty -> a Source #

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

Foldable (ListN n a) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl' :: (a0 -> Element (ListN n a) -> a0) -> a0 -> ListN n a -> a0 Source #

foldr :: (Element (ListN n a) -> a0 -> a0) -> a0 -> ListN n a -> a0 Source #

foldr' :: (Element (ListN n a) -> a0 -> a0) -> a0 -> ListN n a -> a0 Source #

class Foldable f => Fold1able f where Source #

Fold1's. Like folds, but they assume to operate on a NonEmpty collection.

Methods

foldl1' :: (Element f -> Element f -> Element f) -> NonEmpty f -> Element f Source #

Left associative strict fold.

foldr1 :: (Element f -> Element f -> Element f) -> NonEmpty f -> Element f Source #

Right associative lazy fold.

Instances
Fold1able [a] Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

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

foldr1 :: (Element [a] -> Element [a] -> Element [a]) -> NonEmpty [a] -> Element [a] Source #

Fold1able (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl1' :: (Element (Array ty) -> Element (Array ty) -> Element (Array ty)) -> NonEmpty (Array ty) -> Element (Array ty) Source #

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

PrimType ty => Fold1able (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl1' :: (Element (UArray ty) -> Element (UArray ty) -> Element (UArray ty)) -> NonEmpty (UArray ty) -> Element (UArray ty) Source #

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

PrimType ty => Fold1able (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl1' :: (Element (Block ty) -> Element (Block ty) -> Element (Block ty)) -> NonEmpty (Block ty) -> Element (Block ty) Source #

foldr1 :: (Element (Block ty) -> Element (Block ty) -> Element (Block ty)) -> NonEmpty (Block ty) -> Element (Block ty) Source #

1 <= n => Fold1able (ListN n a) Source # 
Instance details

Defined in Foundation.Collection.Foldable

Methods

foldl1' :: (Element (ListN n a) -> Element (ListN n a) -> Element (ListN n a)) -> NonEmpty (ListN n a) -> Element (ListN n a) Source #

foldr1 :: (Element (ListN n a) -> Element (ListN n a) -> Element (ListN n a)) -> NonEmpty (ListN n a) -> Element (ListN n a) Source #

class Functor collection => Mappable collection where Source #

Functors representing data structures that can be traversed from left to right.

Mostly like base's Traversable but applied to collections only.

Minimal complete definition

traverse | sequenceA

Methods

traverse :: Applicative f => (a -> f b) -> collection a -> f (collection b) Source #

Map each element of a structure to an action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see traverse_.

sequenceA :: Applicative f => collection (f a) -> f (collection a) Source #

Evaluate each actions of the given collections, from left to right, and collect the results. For a version that ignores the results, see sequenceA_

mapM :: (Applicative m, Monad m) => (a -> m b) -> collection a -> m (collection b) Source #

Map each element of the collection to an action, evaluate these actions from left to right, and collect the results. For a version that ignores the results see mapM_.

sequence :: (Applicative m, Monad m) => collection (m a) -> m (collection a) Source #

Evaluate each actions of the given collections, from left to right, and collect the results. For a version that ignores the results, see sequence_

Instances
Mappable [] Source # 
Instance details

Defined in Foundation.Collection.Mappable

Methods

traverse :: Applicative f => (a -> f b) -> [a] -> f [b] Source #

sequenceA :: Applicative f => [f a] -> f [a] Source #

mapM :: (Applicative m, Monad m) => (a -> m b) -> [a] -> m [b] Source #

sequence :: (Applicative m, Monad m) => [m a] -> m [a] Source #

Mappable Array Source # 
Instance details

Defined in Foundation.Collection.Mappable

Methods

traverse :: Applicative f => (a -> f b) -> Array a -> f (Array b) Source #

sequenceA :: Applicative f => Array (f a) -> f (Array a) Source #

mapM :: (Applicative m, Monad m) => (a -> m b) -> Array a -> m (Array b) Source #

sequence :: (Applicative m, Monad m) => Array (m a) -> m (Array a) Source #

traverse_ :: (Mappable col, Applicative f) => (a -> f b) -> col a -> f () Source #

Map each element of a collection to an action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see traverse

mapM_ :: (Mappable col, Applicative m, Monad m) => (a -> m b) -> col a -> m () Source #

Evaluate each action in the collection from left to right, and ignore the results. For a version that doesn't ignore the results see sequenceA. sequenceA_ :: (Mappable col, Applicative f) => col (f a) -> f () sequenceA_ col = sequenceA col *> pure ()

Map each element of a collection to a monadic action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see mapM.

forM :: (Mappable col, Applicative m, Monad m) => col a -> (a -> m b) -> m (col b) Source #

forM is mapM with its arguments flipped. For a version that ignores the results see forM_.

forM_ :: (Mappable col, Applicative m, Monad m) => col a -> (a -> m b) -> m () Source #

forM_ is mapM_ with its arguments flipped. For a version that doesn't ignore the results see forM.

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, all, any

Methods

null :: c -> Bool Source #

Check if a collection is empty

length :: c -> CountOf (Element c) 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

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

Determine is any elements of the collection satisfy the predicate

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

Determine is all elements of the collection satisfy the predicate

Instances
Collection String Source # 
Instance details

Defined in Foundation.Collection.Collection

Collection AsciiString Source # 
Instance details

Defined in Foundation.Collection.Collection

Collection Bitmap Source # 
Instance details

Defined in Foundation.Array.Bitmap

Collection CSV Source # 
Instance details

Defined in Foundation.Format.CSV.Types

Collection Row Source # 
Instance details

Defined in Foundation.Format.CSV.Types

Collection [a] Source # 
Instance details

Defined in Foundation.Collection.Collection

Methods

null :: [a] -> Bool Source #

length :: [a] -> CountOf (Element [a]) Source #

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

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

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

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

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

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

Collection (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Collection

Methods

null :: Array ty -> Bool Source #

length :: Array ty -> CountOf (Element (Array ty)) 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 #

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

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

PrimType ty => Collection (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Collection

Methods

null :: UArray ty -> Bool Source #

length :: UArray ty -> CountOf (Element (UArray ty)) 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 #

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

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

PrimType ty => Collection (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Collection

Methods

null :: Block ty -> Bool Source #

length :: Block ty -> CountOf (Element (Block ty)) Source #

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

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

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

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

any :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source #

all :: (Element (Block ty) -> Bool) -> Block ty -> Bool Source #

Collection c => Collection (NonEmpty c) Source # 
Instance details

Defined in Foundation.Collection.Collection

Collection (DList a) Source # 
Instance details

Defined in Foundation.List.DList

Methods

null :: DList a -> Bool Source #

length :: DList a -> CountOf (Element (DList a)) Source #

elem :: (Eq a0, a0 ~ Element (DList a)) => Element (DList a) -> DList a -> Bool Source #

notElem :: (Eq a0, a0 ~ Element (DList a)) => Element (DList a) -> DList a -> Bool Source #

maximum :: (Ord a0, a0 ~ Element (DList a)) => NonEmpty (DList a) -> Element (DList a) Source #

minimum :: (Ord a0, a0 ~ Element (DList a)) => NonEmpty (DList a) -> Element (DList a) Source #

any :: (Element (DList a) -> Bool) -> DList a -> Bool Source #

all :: (Element (DList a) -> Bool) -> DList a -> Bool Source #

PrimType ty => Collection (ChunkedUArray ty) Source # 
Instance details

Defined in Foundation.Array.Chunked.Unboxed

and :: (Collection col, Element col ~ Bool) => col -> Bool Source #

Return True if all the elements in the collection are True

or :: (Collection col, Element col ~ Bool) => col -> Bool Source #

Return True if at least one element in the collection is True

data NonEmpty a #

NonEmpty property for any Collection

Instances
IsList c => IsList (NonEmpty c) 
Instance details

Defined in Basement.NonEmpty

Associated Types

type Item (NonEmpty c) :: Type #

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) 
Instance details

Defined in Basement.NonEmpty

Methods

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

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

Show a => Show (NonEmpty a) 
Instance details

Defined in Basement.NonEmpty

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Collection c => Collection (NonEmpty c) Source # 
Instance details

Defined in Foundation.Collection.Collection

type Item (NonEmpty c) 
Instance details

Defined in Basement.NonEmpty

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

Defined in Foundation.Collection.Element

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.

nonEmptyFmap :: Functor f => (a -> b) -> NonEmpty (f a) -> NonEmpty (f b) Source #

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

A set of methods for ordered colection

Methods

take :: CountOf (Element c) -> c -> c Source #

Take the first @n elements of a collection

revTake :: CountOf (Element c) -> c -> c Source #

Take the last @n elements of a collection

drop :: CountOf (Element c) -> c -> c Source #

Drop the first @n elements of a collection

revDrop :: CountOf (Element c) -> c -> c Source #

Drop the last @n elements of a collection

splitAt :: CountOf (Element c) -> c -> (c, c) Source #

Split the collection at the @n'th elements

revSplitAt :: CountOf (Element c) -> 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

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

Split a collection when the predicate return true starting from the end of the collection

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

Split a collection at the given element

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

Return the longest prefix in the collection that satisfy the predicate

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

Return the longest prefix in the collection that satisfy the predicate

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

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

Split a collection while the predicate return true starting from the end of the collection

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 that 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.

replicate :: CountOf (Element c) -> Element c -> c Source #

Create a collection where the element in parameter is repeated N time

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.

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

Takes two collections and returns True iff the first collection is an infix of the second.

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

Takes two collections and returns True iff the first collection is an infix of the second.

stripPrefix :: Eq (Element c) => c -> c -> Maybe c Source #

Try to strip a prefix from a collection

stripSuffix :: Eq (Element c) => c -> c -> Maybe c Source #

Try to strip a suffix from a collection

Instances
Sequential String Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element String) -> String -> String Source #

revTake :: CountOf (Element String) -> String -> String Source #

drop :: CountOf (Element String) -> String -> String Source #

revDrop :: CountOf (Element String) -> String -> String Source #

splitAt :: CountOf (Element String) -> String -> (String, String) Source #

revSplitAt :: CountOf (Element String) -> String -> (String, String) Source #

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

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

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

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

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

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

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

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

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

spanEnd :: (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 #

replicate :: CountOf (Element String) -> Element String -> String Source #

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

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

isInfixOf :: String -> String -> Bool Source #

stripPrefix :: String -> String -> Maybe String Source #

stripSuffix :: String -> String -> Maybe String Source #

Sequential AsciiString Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

revTake :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

drop :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

revDrop :: CountOf (Element AsciiString) -> AsciiString -> AsciiString Source #

splitAt :: CountOf (Element AsciiString) -> AsciiString -> (AsciiString, AsciiString) Source #

revSplitAt :: CountOf (Element AsciiString) -> AsciiString -> (AsciiString, AsciiString) Source #

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

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

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

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

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

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

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

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

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

spanEnd :: (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 #

replicate :: CountOf (Element AsciiString) -> Element AsciiString -> AsciiString Source #

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

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

isInfixOf :: AsciiString -> AsciiString -> Bool Source #

stripPrefix :: AsciiString -> AsciiString -> Maybe AsciiString Source #

stripSuffix :: AsciiString -> AsciiString -> Maybe AsciiString Source #

Sequential Bitmap Source # 
Instance details

Defined in Foundation.Array.Bitmap

Methods

take :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

revTake :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

drop :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

revDrop :: CountOf (Element Bitmap) -> Bitmap -> Bitmap Source #

splitAt :: CountOf (Element Bitmap) -> Bitmap -> (Bitmap, Bitmap) Source #

revSplitAt :: CountOf (Element Bitmap) -> Bitmap -> (Bitmap, Bitmap) Source #

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

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

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

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

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

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

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

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

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

spanEnd :: (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 #

replicate :: CountOf (Element Bitmap) -> Element Bitmap -> Bitmap Source #

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

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

isInfixOf :: Bitmap -> Bitmap -> Bool Source #

stripPrefix :: Bitmap -> Bitmap -> Maybe Bitmap Source #

stripSuffix :: Bitmap -> Bitmap -> Maybe Bitmap Source #

Sequential CSV Source # 
Instance details

Defined in Foundation.Format.CSV.Types

Methods

take :: CountOf (Element CSV) -> CSV -> CSV Source #

revTake :: CountOf (Element CSV) -> CSV -> CSV Source #

drop :: CountOf (Element CSV) -> CSV -> CSV Source #

revDrop :: CountOf (Element CSV) -> CSV -> CSV Source #

splitAt :: CountOf (Element CSV) -> CSV -> (CSV, CSV) Source #

revSplitAt :: CountOf (Element CSV) -> CSV -> (CSV, CSV) Source #

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

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

breakEnd :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

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

takeWhile :: (Element CSV -> Bool) -> CSV -> CSV Source #

dropWhile :: (Element CSV -> Bool) -> CSV -> CSV Source #

intersperse :: Element CSV -> CSV -> CSV Source #

intercalate :: Element CSV -> CSV -> Element CSV Source #

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

spanEnd :: (Element CSV -> Bool) -> CSV -> (CSV, CSV) Source #

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

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

reverse :: CSV -> CSV Source #

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

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

snoc :: CSV -> Element CSV -> CSV Source #

cons :: Element CSV -> CSV -> CSV Source #

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

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

singleton :: Element CSV -> CSV Source #

head :: NonEmpty CSV -> Element CSV Source #

last :: NonEmpty CSV -> Element CSV Source #

tail :: NonEmpty CSV -> CSV Source #

init :: NonEmpty CSV -> CSV Source #

replicate :: CountOf (Element CSV) -> Element CSV -> CSV Source #

isPrefixOf :: CSV -> CSV -> Bool Source #

isSuffixOf :: CSV -> CSV -> Bool Source #

isInfixOf :: CSV -> CSV -> Bool Source #

stripPrefix :: CSV -> CSV -> Maybe CSV Source #

stripSuffix :: CSV -> CSV -> Maybe CSV Source #

Sequential Row Source # 
Instance details

Defined in Foundation.Format.CSV.Types

Methods

take :: CountOf (Element Row) -> Row -> Row Source #

revTake :: CountOf (Element Row) -> Row -> Row Source #

drop :: CountOf (Element Row) -> Row -> Row Source #

revDrop :: CountOf (Element Row) -> Row -> Row Source #

splitAt :: CountOf (Element Row) -> Row -> (Row, Row) Source #

revSplitAt :: CountOf (Element Row) -> Row -> (Row, Row) Source #

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

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

breakEnd :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

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

takeWhile :: (Element Row -> Bool) -> Row -> Row Source #

dropWhile :: (Element Row -> Bool) -> Row -> Row Source #

intersperse :: Element Row -> Row -> Row Source #

intercalate :: Element Row -> Row -> Element Row Source #

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

spanEnd :: (Element Row -> Bool) -> Row -> (Row, Row) Source #

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

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

reverse :: Row -> Row Source #

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

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

snoc :: Row -> Element Row -> Row Source #

cons :: Element Row -> Row -> Row Source #

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

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

singleton :: Element Row -> Row Source #

head :: NonEmpty Row -> Element Row Source #

last :: NonEmpty Row -> Element Row Source #

tail :: NonEmpty Row -> Row Source #

init :: NonEmpty Row -> Row Source #

replicate :: CountOf (Element Row) -> Element Row -> Row Source #

isPrefixOf :: Row -> Row -> Bool Source #

isSuffixOf :: Row -> Row -> Bool Source #

isInfixOf :: Row -> Row -> Bool Source #

stripPrefix :: Row -> Row -> Maybe Row Source #

stripSuffix :: Row -> Row -> Maybe Row Source #

Sequential [a] Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element [a]) -> [a] -> [a] Source #

revTake :: CountOf (Element [a]) -> [a] -> [a] Source #

drop :: CountOf (Element [a]) -> [a] -> [a] Source #

revDrop :: CountOf (Element [a]) -> [a] -> [a] Source #

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

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

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

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

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

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

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

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

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

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

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

spanEnd :: (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 #

replicate :: CountOf (Element [a]) -> Element [a] -> [a] Source #

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

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

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

stripPrefix :: [a] -> [a] -> Maybe [a] Source #

stripSuffix :: [a] -> [a] -> Maybe [a] Source #

Sequential (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revTake :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

drop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

revDrop :: CountOf (Element (Array ty)) -> Array ty -> Array ty Source #

splitAt :: CountOf (Element (Array ty)) -> Array ty -> (Array ty, Array ty) Source #

revSplitAt :: CountOf (Element (Array ty)) -> 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 #

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

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

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

dropWhile :: (Element (Array ty) -> Bool) -> 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 #

spanEnd :: (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 #

replicate :: CountOf (Element (Array ty)) -> Element (Array ty) -> Array ty Source #

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

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

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

stripPrefix :: Array ty -> Array ty -> Maybe (Array ty) Source #

stripSuffix :: Array ty -> Array ty -> Maybe (Array ty) Source #

PrimType ty => Sequential (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revTake :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

drop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

revDrop :: CountOf (Element (UArray ty)) -> UArray ty -> UArray ty Source #

splitAt :: CountOf (Element (UArray ty)) -> UArray ty -> (UArray ty, UArray ty) Source #

revSplitAt :: CountOf (Element (UArray ty)) -> 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 #

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

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

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

dropWhile :: (Element (UArray ty) -> Bool) -> 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 #

spanEnd :: (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 #

replicate :: CountOf (Element (UArray ty)) -> Element (UArray ty) -> UArray ty Source #

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

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

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

stripPrefix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

stripSuffix :: UArray ty -> UArray ty -> Maybe (UArray ty) Source #

PrimType ty => Sequential (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

revTake :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

drop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

revDrop :: CountOf (Element (Block ty)) -> Block ty -> Block ty Source #

splitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source #

revSplitAt :: CountOf (Element (Block ty)) -> Block ty -> (Block ty, Block ty) Source #

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

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

breakEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

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

takeWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

dropWhile :: (Element (Block ty) -> Bool) -> Block ty -> Block ty Source #

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

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

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

spanEnd :: (Element (Block ty) -> Bool) -> Block ty -> (Block ty, Block ty) Source #

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

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

reverse :: Block ty -> Block ty Source #

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

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

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

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

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

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

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

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

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

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

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

replicate :: CountOf (Element (Block ty)) -> Element (Block ty) -> Block ty Source #

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

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

isInfixOf :: Block ty -> Block ty -> Bool Source #

stripPrefix :: Block ty -> Block ty -> Maybe (Block ty) Source #

stripSuffix :: Block ty -> Block ty -> Maybe (Block ty) Source #

Sequential (DList a) Source # 
Instance details

Defined in Foundation.List.DList

Methods

take :: CountOf (Element (DList a)) -> DList a -> DList a Source #

revTake :: CountOf (Element (DList a)) -> DList a -> DList a Source #

drop :: CountOf (Element (DList a)) -> DList a -> DList a Source #

revDrop :: CountOf (Element (DList a)) -> DList a -> DList a Source #

splitAt :: CountOf (Element (DList a)) -> DList a -> (DList a, DList a) Source #

revSplitAt :: CountOf (Element (DList a)) -> DList a -> (DList a, DList a) Source #

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

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

breakEnd :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

breakElem :: Element (DList a) -> DList a -> (DList a, DList a) Source #

takeWhile :: (Element (DList a) -> Bool) -> DList a -> DList a Source #

dropWhile :: (Element (DList a) -> Bool) -> DList a -> DList a Source #

intersperse :: Element (DList a) -> DList a -> DList a Source #

intercalate :: Element (DList a) -> DList a -> Element (DList a) Source #

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

spanEnd :: (Element (DList a) -> Bool) -> DList a -> (DList a, DList a) Source #

filter :: (Element (DList a) -> Bool) -> DList a -> DList a Source #

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

reverse :: DList a -> DList a Source #

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

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

snoc :: DList a -> Element (DList a) -> DList a Source #

cons :: Element (DList a) -> DList a -> DList a Source #

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

sortBy :: (Element (DList a) -> Element (DList a) -> Ordering) -> DList a -> DList a Source #

singleton :: Element (DList a) -> DList a Source #

head :: NonEmpty (DList a) -> Element (DList a) Source #

last :: NonEmpty (DList a) -> Element (DList a) Source #

tail :: NonEmpty (DList a) -> DList a Source #

init :: NonEmpty (DList a) -> DList a Source #

replicate :: CountOf (Element (DList a)) -> Element (DList a) -> DList a Source #

isPrefixOf :: DList a -> DList a -> Bool Source #

isSuffixOf :: DList a -> DList a -> Bool Source #

isInfixOf :: DList a -> DList a -> Bool Source #

stripPrefix :: DList a -> DList a -> Maybe (DList a) Source #

stripSuffix :: DList a -> DList a -> Maybe (DList a) Source #

PrimType ty => Sequential (ChunkedUArray ty) Source # 
Instance details

Defined in Foundation.Array.Chunked.Unboxed

Methods

take :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revTake :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

drop :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

revDrop :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> ChunkedUArray ty Source #

splitAt :: CountOf (Element (ChunkedUArray ty)) -> ChunkedUArray ty -> (ChunkedUArray ty, ChunkedUArray ty) Source #

revSplitAt :: CountOf (Element (ChunkedUArray ty)) -> 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 #

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

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

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

dropWhile :: (Element (ChunkedUArray ty) -> Bool) -> 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 #

spanEnd :: (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 #

replicate :: CountOf (Element (ChunkedUArray ty)) -> Element (ChunkedUArray ty) -> ChunkedUArray ty Source #

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

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

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

stripPrefix :: ChunkedUArray ty -> ChunkedUArray ty -> Maybe (ChunkedUArray ty) Source #

stripSuffix :: ChunkedUArray ty -> ChunkedUArray ty -> Maybe (ChunkedUArray ty) 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 => CountOf (MutableValue c) -> 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 # 
Instance details

Defined in Foundation.Array.Bitmap

MutableCollection (MArray ty) Source # 
Instance details

Defined in Foundation.Collection.Mutable

Associated Types

type MutableFreezed (MArray ty) :: Type Source #

type MutableKey (MArray ty) :: Type Source #

type MutableValue (MArray ty) :: Type 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 => CountOf (MutableValue (MArray ty)) -> 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 #

PrimType ty => MutableCollection (MUArray ty) Source # 
Instance details

Defined in Foundation.Collection.Mutable

Associated Types

type MutableFreezed (MUArray ty) :: Type Source #

type MutableKey (MUArray ty) :: Type Source #

type MutableValue (MUArray ty) :: Type 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 => CountOf (MutableValue (MUArray ty)) -> 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 #

PrimType ty => MutableCollection (MutableBlock ty) Source # 
Instance details

Defined in Foundation.Collection.Mutable

class IndexedCollection c where Source #

Collection of elements that can indexed by int

Methods

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

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

Instances
IndexedCollection String Source # 
Instance details

Defined in Foundation.Collection.Indexed

IndexedCollection Bitmap Source # 
Instance details

Defined in Foundation.Array.Bitmap

IndexedCollection CSV Source # 
Instance details

Defined in Foundation.Format.CSV.Types

IndexedCollection Row Source # 
Instance details

Defined in Foundation.Format.CSV.Types

IndexedCollection [a] Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: [a] -> Offset (Element [a]) -> Maybe (Element [a]) Source #

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

IndexedCollection (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: Array ty -> Offset (Element (Array ty)) -> Maybe (Element (Array ty)) Source #

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

PrimType ty => IndexedCollection (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: UArray ty -> Offset (Element (UArray ty)) -> Maybe (Element (UArray ty)) Source #

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

PrimType ty => IndexedCollection (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: Block ty -> Offset (Element (Block ty)) -> Maybe (Element (Block ty)) Source #

findIndex :: (Element (Block ty) -> Bool) -> Block ty -> Maybe (Offset (Element (Block ty))) Source #

PrimType ty => IndexedCollection (ChunkedUArray ty) Source # 
Instance details

Defined in Foundation.Array.Chunked.Unboxed

(NatWithinBound (CountOf ty) n, KnownNat n, PrimType ty) => IndexedCollection (BlockN n ty) Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: BlockN n ty -> Offset (Element (BlockN n ty)) -> Maybe (Element (BlockN n ty)) Source #

findIndex :: (Element (BlockN n ty) -> Bool) -> BlockN n ty -> Maybe (Offset (Element (BlockN n ty))) Source #

(NatWithinBound Int n, KnownNat n) => IndexedCollection (ListN n a) Source # 
Instance details

Defined in Foundation.Collection.Indexed

Methods

(!) :: ListN n a -> Offset (Element (ListN n a)) -> Maybe (Element (ListN n a)) Source #

findIndex :: (Element (ListN n a) -> Bool) -> ListN n a -> Maybe (Offset (Element (ListN n a))) Source #

class KeyedCollection c where Source #

Collection of things that can be looked up by Key

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 # 
Instance details

Defined in Foundation.Collection.Keyed

Associated Types

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

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

Methods

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

class Sequential col => Zippable col where Source #

Minimal complete definition

Nothing

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 String Source # 
Instance details

Defined in Foundation.Collection.Zippable

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 AsciiString Source # 
Instance details

Defined in Foundation.Collection.Zippable

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 [c] Source # 
Instance details

Defined in Foundation.Collection.Zippable

Methods

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

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

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

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

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

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

Zippable (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Zippable

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 #

PrimType ty => Zippable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Zippable

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 #

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"

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 (Mutable col) (Step col) prim err () Source #

build Source #

Arguments

:: PrimMonad prim 
=> Int

CountOf of a chunk

-> Builder col (Mutable col) (Step col) prim err () 
-> prim (Either err col) 
Instances
Buildable String Source # 
Instance details

Defined in Foundation.Collection.Buildable

Associated Types

type Mutable String :: Type -> Type Source #

type Step String :: Type Source #

Methods

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

build :: PrimMonad prim => Int -> Builder String (Mutable String) (Step String) prim err () -> prim (Either err String) Source #

Buildable (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Buildable

Associated Types

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

type Step (Array ty) :: Type Source #

Methods

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

build :: PrimMonad prim => Int -> Builder (Array ty) (Mutable (Array ty)) (Step (Array ty)) prim err () -> prim (Either err (Array ty)) Source #

PrimType ty => Buildable (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Buildable

Associated Types

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

type Step (UArray ty) :: Type Source #

Methods

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

build :: PrimMonad prim => Int -> Builder (UArray ty) (Mutable (UArray ty)) (Step (UArray ty)) prim err () -> prim (Either err (UArray ty)) Source #

build_ Source #

Arguments

:: (Buildable c, PrimMonad prim) 
=> Int

CountOf of a chunk

-> Builder c (Mutable c) (Step c) prim () () 
-> prim c 

newtype Builder collection (mutCollection :: Type -> Type) step (state :: Type -> Type) err a #

Constructors

Builder 

Fields

Instances
Monad state => Monad (Builder collection mutCollection step state err) 
Instance details

Defined in Basement.MutableBuilder

Methods

(>>=) :: Builder collection mutCollection step state err a -> (a -> Builder collection mutCollection step state err b) -> Builder collection mutCollection step state err b #

(>>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b #

return :: a -> Builder collection mutCollection step state err a #

fail :: String -> Builder collection mutCollection step state err a #

Monad state => Functor (Builder collection mutCollection step state err) 
Instance details

Defined in Basement.MutableBuilder

Methods

fmap :: (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b #

(<$) :: a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a #

Monad state => Applicative (Builder collection mutCollection step state err) 
Instance details

Defined in Basement.MutableBuilder

Methods

pure :: a -> Builder collection mutCollection step state err a #

(<*>) :: Builder collection mutCollection step state err (a -> b) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b #

liftA2 :: (a -> b -> c) -> Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err c #

(*>) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err b #

(<*) :: Builder collection mutCollection step state err a -> Builder collection mutCollection step state err b -> Builder collection mutCollection step state err a #

Monad state => MonadFailure (Builder collection mutCollection step state err) 
Instance details

Defined in Basement.MutableBuilder

Associated Types

type Failure (Builder collection mutCollection step state err) :: Type #

Methods

mFail :: Failure (Builder collection mutCollection step state err) -> Builder collection mutCollection step state err () #

type Failure (Builder collection mutCollection step state err) 
Instance details

Defined in Basement.MutableBuilder

type Failure (Builder collection mutCollection step state err) = err

data BuildingState collection (mutCollection :: Type -> Type) step state #

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

class Copy a where Source #

Methods

copy :: a -> a Source #

Instances
Copy String Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: String -> String Source #

Copy [ty] Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: [ty] -> [ty] Source #

Copy (Array ty) Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: Array ty -> Array ty Source #

PrimType ty => Copy (UArray ty) Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: UArray ty -> UArray ty Source #

PrimType ty => Copy (Block ty) Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: Block ty -> Block ty Source #

(Countable ty n, PrimType ty, KnownNat n) => Copy (BlockN n ty) Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: BlockN n ty -> BlockN n ty Source #

Copy (ListN n ty) Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: ListN n ty -> ListN n ty Source #