easytensor-2.1.0.0: Pure, type-indexed haskell vector, matrix, and tensor library.

Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.SubSpace

Contents

Description

This module provides a flexible interface to manipulate parts of a DataFrame.

A note on indexing and slicing

When you index or slice dataframes, the left part of the dimension list (as for indexing, plus b for slicing) determines the mechanics of accessing sub-dataframes. If compiler knows all dimensions at compile time, it can guarantee that the operation is safe (provided with valid indices). Otherwise, you can get an OutOfDimBounds exception at runtime.

When all dimensions in the indexing subspace satisfy d :: Nat or d ~ N n, slicing functions are safe to use, but you need some type-level proof for GHC that the indices align.

When any of the dimensions are unknown (d ~ XN m), these functions are unsafe -- they can yield an OutOfDimBounds exception if you give a bad index. But they are easy to use (no type-level proof needed).

Synopsis

Documentation

class (ConcatList as bs asbs, SubSpaceCtx t as bs asbs, PrimBytes t, KnownDimKind k) => SubSpace (t :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]) | asbs as -> bs, asbs bs -> as, as bs -> asbs Source #

Operations on DataFrames

as is an indexing dimensionality

bs is an element dimensionality

t is an underlying data type (i.e. Float, Int, Double)

Minimal complete definition

joinDataFrameI, indexOffsetI, updateOffsetI, indexI, updateI, ewmapI, iwmapI, ewgenI, iwgenI, ewfoldlI, iwfoldlI, ewfoldrI, iwfoldrI, indexWiseI

Associated Types

type SubSpaceCtx t as bs asbs :: Constraint Source #

Instances
(ConcatList as bs asbs, SubSpaceCtx t as bs asbs) => SubSpace t (as :: [Nat]) (bs :: [Nat]) (asbs :: [Nat]) Source # 
Instance details

Defined in Numeric.DataFrame.SubSpace

Associated Types

type SubSpaceCtx t as bs asbs :: Constraint Source #

Methods

joinDataFrameI :: DataFrame (DataFrame t bs) as -> DataFrame t asbs

indexOffsetI :: Int -> DataFrame t asbs -> DataFrame t bs

updateOffsetI :: Int -> DataFrame t bs -> DataFrame t asbs -> DataFrame t asbs

indexI :: Idxs as -> DataFrame t asbs -> DataFrame t bs

updateI :: Idxs as -> DataFrame t bs -> DataFrame t asbs -> DataFrame t asbs

ewmapI :: SubSpace s as bs' asbs' => (DataFrame s bs' -> DataFrame t bs) -> DataFrame s asbs' -> DataFrame t asbs

iwmapI :: SubSpace s as bs' asbs' => (Idxs as -> DataFrame s bs' -> DataFrame t bs) -> DataFrame s asbs' -> DataFrame t asbs

ewgenI :: DataFrame t bs -> DataFrame t asbs

iwgenI :: (Idxs as -> DataFrame t bs) -> DataFrame t asbs

ewfoldlI :: (b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b

iwfoldlI :: (Idxs as -> b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b

ewfoldrI :: (DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b

iwfoldrI :: (Idxs as -> DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b

elementWiseI :: (Applicative f, SubSpace s as bs' asbs') => (DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s asbs' -> f (DataFrame t asbs)

indexWiseI :: (Applicative f, SubSpace s as bs' asbs') => (Idxs as -> DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s asbs' -> f (DataFrame t asbs)

(ConcatList as bs asbs, SubSpaceCtx t as bs asbs) => SubSpace t (as :: [XNat]) (bs :: [XNat]) (asbs :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.SubSpace

Associated Types

type SubSpaceCtx t as bs asbs :: Constraint Source #

Methods

joinDataFrameI :: DataFrame (DataFrame t bs) as -> DataFrame t asbs

indexOffsetI :: Int -> DataFrame t asbs -> DataFrame t bs

updateOffsetI :: Int -> DataFrame t bs -> DataFrame t asbs -> DataFrame t asbs

indexI :: Idxs as -> DataFrame t asbs -> DataFrame t bs

updateI :: Idxs as -> DataFrame t bs -> DataFrame t asbs -> DataFrame t asbs

ewmapI :: SubSpace s as bs' asbs' => (DataFrame s bs' -> DataFrame t bs) -> DataFrame s asbs' -> DataFrame t asbs

iwmapI :: SubSpace s as bs' asbs' => (Idxs as -> DataFrame s bs' -> DataFrame t bs) -> DataFrame s asbs' -> DataFrame t asbs

ewgenI :: DataFrame t bs -> DataFrame t asbs

iwgenI :: (Idxs as -> DataFrame t bs) -> DataFrame t asbs

ewfoldlI :: (b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b

iwfoldlI :: (Idxs as -> b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b

ewfoldrI :: (DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b

iwfoldrI :: (Idxs as -> DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b

elementWiseI :: (Applicative f, SubSpace s as bs' asbs') => (DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s asbs' -> f (DataFrame t asbs)

indexWiseI :: (Applicative f, SubSpace s as bs' asbs') => (Idxs as -> DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s asbs' -> f (DataFrame t asbs)

type family CanSlice (t :: Type) (asbs :: [k]) :: Constraint where ... Source #

DataFrames indexed by Nats and XNats require slightly different sets of constraints to be sliced. This family hides the difference, so that I could write one function for both kinds.

Equations

CanSlice t (asbs :: [Nat]) = (PrimArray t (DataFrame t asbs), Dimensions asbs) 
CanSlice t (asbs :: [XNat]) = () 

Simple interface

sindexOffset Source #

Arguments

:: SubSpace t '[a] bs (a :+ bs) 
=> Int

Prim element offset

-> DataFrame t (a :+ bs) 
-> DataFrame t bs 

Unsafely get a sub-dataframe by its primitive element offset. The offset is not checked to be aligned to the space structure or for bounds.

Warning: this function is utterly unsafe -- it does not even throw an exception if the offset is too big; you just get an undefined behavior.

supdateOffset Source #

Arguments

:: SubSpace t '[a] bs (a :+ bs) 
=> Int

Prim element offset

-> DataFrame t bs 
-> DataFrame t (a :+ bs) 
-> DataFrame t (a :+ bs) 

Unsafely update a sub-dataframe by its primitive element offset. The offset is not checked to be aligned to the space structure or for bounds.

Warning: this function is utterly unsafe -- it does not even throw an exception if the offset is too big; you just get an undefined behavior.

(.!) :: forall t a bs. SubSpace t '[a] bs (a :+ bs) => DataFrame t (a :+ bs) -> Idx a -> DataFrame t bs infixl 4 Source #

Get an element by its index in the dataframe.

If (a ~ XN m) then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

slookup :: forall t (a :: XNat) (bs :: [XNat]). (All KnownDimType bs, PrimBytes t) => Idx a -> DataFrame t (a :+ bs) -> Maybe (DataFrame t bs) Source #

Get an element by its index in the dataframe. This is a safe alternative to `(.!)` function when the index dimension is not known at compile time (a ~ XN m).

supdate :: forall t a bs. SubSpace t '[a] bs (a :+ bs) => Idx a -> DataFrame t bs -> DataFrame t (a :+ bs) -> DataFrame t (a :+ bs) Source #

Set a new value to an element.

If (a ~ XN m) and the index falls outside of the DataFrame dim, then this function returns the original DataFrame.

sslice :: forall t b bi bd bs. (KnownDimKind (KindOfEl bs), CanSlice t (b :+ bs), SubFrameIndexCtx b bi bd, KnownDim bd, PrimArray t (DataFrame t (bd :+ bs))) => Idx bi -> DataFrame t (b :+ bs) -> DataFrame t (bd :+ bs) Source #

Get a few contiguous elements.

In a sense, this is just a more complicated version of sindex.

If (b ~ XN m) then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

ssliceMaybe :: forall (t :: Type) (b :: XNat) (bi :: XNat) (bd :: XNat) (bs :: [XNat]). (SubFrameIndexCtx b bi bd, KnownDim bd, All KnownDimType bs, PrimBytes t) => Idx bi -> DataFrame t (b :+ bs) -> Maybe (DataFrame t (bd :+ bs)) Source #

Get a few contiguous elements.

In a sense, this is just a more complicated version of slookup.

This is a safe alternative to sslice function when the slice dimension is not known at compile time (b ~ XN m).

supdateSlice :: forall t b bi bd bs. (KnownDimKind (KindOfEl bs), CanSlice t (b :+ bs), SubFrameIndexCtx b bi bd, KnownDim bd, ExactDims bs, PrimArray t (DataFrame t (bd :+ bs))) => Idx bi -> DataFrame t (bd :+ bs) -> DataFrame t (b :+ bs) -> DataFrame t (b :+ bs) Source #

Update a few contiguous elements.

In a sense, this is just a more complicated version of supdate.

If (b ~ XN m) and (Idx bi + Dim bd > Dim b), this function updates only as many elements as fits into the dataframe along this dimension (possibly none).

sewgen :: forall t a bs. (SubSpace t '[a] bs (a :+ bs), Dimensions '[a]) => DataFrame t bs -> DataFrame t (a :+ bs) Source #

Generate a DataFrame by repeating an element.

siwgen :: forall t a bs. (SubSpace t '[a] bs (a :+ bs), Dimensions '[a]) => (Idx a -> DataFrame t bs) -> DataFrame t (a :+ bs) Source #

Generate a DataFrame by iterating a function (index -> element).

sewmap :: forall t a bs s bs'. (SubSpace t '[a] bs (a :+ bs), SubSpace s '[a] bs' (a :+ bs')) => (DataFrame s bs' -> DataFrame t bs) -> DataFrame s (a :+ bs') -> DataFrame t (a :+ bs) Source #

Map a function over each element of DataFrame.

siwmap :: forall t a bs s bs'. (SubSpace t '[a] bs (a :+ bs), SubSpace s '[a] bs' (a :+ bs')) => (Idx a -> DataFrame s bs' -> DataFrame t bs) -> DataFrame s (a :+ bs') -> DataFrame t (a :+ bs) Source #

Map a function over each element with its index of DataFrame.

sewzip :: forall t a bs l bsL r bsR. (SubSpace t '[a] bs (a :+ bs), SubSpace l '[a] bsL (a :+ bsL), SubSpace r '[a] bsR (a :+ bsR)) => (DataFrame l bsL -> DataFrame r bsR -> DataFrame t bs) -> DataFrame l (a :+ bsL) -> DataFrame r (a :+ bsR) -> DataFrame t (a :+ bs) Source #

Zip two spaces on a specified subspace element-wise (without index)

siwzip :: forall t a bs l bsL r bsR. (SubSpace t '[a] bs (a :+ bs), SubSpace l '[a] bsL (a :+ bsL), SubSpace r '[a] bsR (a :+ bsR)) => (Idx a -> DataFrame l bsL -> DataFrame r bsR -> DataFrame t bs) -> DataFrame l (a :+ bsL) -> DataFrame r (a :+ bsR) -> DataFrame t (a :+ bs) Source #

Zip two spaces on a specified subspace index-wise (with index)

selement :: forall t a bs f. (SubSpace t '[a] bs (a :+ bs), Applicative f) => Idx a -> (DataFrame t bs -> f (DataFrame t bs)) -> DataFrame t (a :+ bs) -> f (DataFrame t (a :+ bs)) Source #

Apply a functor over a single element (simple lens)

If (a ~ XN m) and the index falls outside of the DataFrame Dim, the argument Functor is not called and the result is pure original DataFrame.

selementWise :: forall t a bs s bs' f. (SubSpace t '[a] bs (a :+ bs), SubSpace s '[a] bs' (a :+ bs'), Applicative f) => (DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s (a :+ bs') -> f (DataFrame t (a :+ bs)) Source #

Apply an applicative functor on each element (Lens-like traversal).

selementWise_ :: forall t a bs f b. (SubSpace t '[a] bs (a :+ bs), Applicative f) => (DataFrame t bs -> f b) -> DataFrame t (a :+ bs) -> f () Source #

Apply an applicative functor on each element (Lens-like traversal)

sindexWise :: forall t a bs s bs' f. (SubSpace t '[a] bs (a :+ bs), SubSpace s '[a] bs' (a :+ bs'), Applicative f) => (Idx a -> DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s (a :+ bs') -> f (DataFrame t (a :+ bs)) Source #

Apply an applicative functor on each element with its index (Lens-like indexed traversal).

sindexWise_ :: forall t a bs f b. (SubSpace t '[a] bs (a :+ bs), Applicative f) => (Idx a -> DataFrame t bs -> f b) -> DataFrame t (a :+ bs) -> f () Source #

Apply an applicative functor on each element with its index (Lens-like indexed traversal)

sewfoldl :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (b -> DataFrame t bs -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Left-associative lazy fold of a DataFrame. Same rules apply as for foldl.

sewfoldl' :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (b -> DataFrame t bs -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Left-associative strict fold of a DataFrame. Same rules apply as for foldl'.

sewfoldr :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (DataFrame t bs -> b -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Right-associative lazy fold of a DataFrame. Same rules apply as for foldr.

sewfoldr' :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (DataFrame t bs -> b -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Right-associative strict fold of a DataFrame. Same rules apply as for foldr'.

sewfoldMap :: forall t a bs m. (SubSpace t '[a] bs (a :+ bs), Monoid m) => (DataFrame t bs -> m) -> DataFrame t (a :+ bs) -> m Source #

Map each element of the DataFrame to a monoid, and combine the results.

siwfoldl :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (Idx a -> b -> DataFrame t bs -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Left-associative lazy fold of a DataFrame with an index. Same rules apply as for foldl.

siwfoldl' :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (Idx a -> b -> DataFrame t bs -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Left-associative strict fold of a DataFrame with an index. Same rules apply as for foldl'.

siwfoldr :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (Idx a -> DataFrame t bs -> b -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Right-associative lazy fold of a DataFrame with an index. Same rules apply as for foldr.

siwfoldr' :: forall t a bs b. SubSpace t '[a] bs (a :+ bs) => (Idx a -> DataFrame t bs -> b -> b) -> b -> DataFrame t (a :+ bs) -> b Source #

Right-associative strict fold of a DataFrame with an index. Same rules apply as for foldr'.

siwfoldMap :: forall t a bs m. (SubSpace t '[a] bs (a :+ bs), Monoid m) => (Idx a -> DataFrame t bs -> m) -> DataFrame t (a :+ bs) -> m Source #

Map each element of the DataFrame and its index to a monoid, and combine the results.

Flexible interface

joinDataFrame :: forall t as bs asbs. (SubSpace t as bs asbs, PrimBytes (DataFrame t bs)) => DataFrame (DataFrame t bs) as -> DataFrame t asbs Source #

Flatten a nested DataFrame, analogous to join.

indexOffset Source #

Arguments

:: SubSpace t as bs asbs 
=> Int

Prim element offset

-> DataFrame t asbs 
-> DataFrame t bs 

Unsafely get a sub-dataframe by its primitive element offset. The offset is not checked to be aligned to the space structure or for bounds.

Warning: this function is utterly unsafe -- it does not even throw an exception if the offset is too big; you just get an undefined behavior.

updateOffset Source #

Arguments

:: SubSpace t as bs asbs 
=> Int

Prim element offset

-> DataFrame t bs 
-> DataFrame t asbs 
-> DataFrame t asbs 

Unsafely update a sub-dataframe by its primitive element offset. The offset is not checked to be aligned to the space structure or for bounds.

Warning: this function is utterly unsafe -- it does not even throw an exception if the offset is too big; you just get an undefined behavior.

index :: forall t as bs asbs. SubSpace t as bs asbs => Idxs as -> DataFrame t asbs -> DataFrame t bs Source #

Get an element by its index in the dataframe.

If any of the dims in as is unknown (a ~ XN m), then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

lookup :: forall t (as :: [XNat]) (bs :: [XNat]) (asbs :: [XNat]). (ConcatList as bs asbs, All KnownDimType bs, PrimBytes t) => Idxs as -> DataFrame t asbs -> Maybe (DataFrame t bs) Source #

Get an element by its index in the dataframe. This is a safe alternative to index function when some of the dimensions are not known at compile time (d ~ XN m).

update :: forall t as bs asbs. SubSpace t as bs asbs => Idxs as -> DataFrame t bs -> DataFrame t asbs -> DataFrame t asbs Source #

Set a new value to an element.

If any of the dims in as is unknown (a ~ XN m), you may happen to update data beyond dataframe bounds. In this case, the original DataFrame is returned.

slice :: forall (t :: Type) b bi bd as bs asbs. (KnownDimKind (KindOfEl asbs), CanSlice t asbs, SubFrameIndexCtx b bi bd, KnownDim bd, ConcatList as (b :+ bs) asbs, PrimArray t (DataFrame t (bd :+ bs))) => Idxs (as +: bi) -> DataFrame t asbs -> DataFrame t (bd :+ bs) Source #

Get a few contiguous elements.

In a sense, this is just a more complicated version of index.

If any of the dims in as or b is unknown (a ~ XN m), then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

sliceMaybe :: forall (t :: Type) (b :: XNat) bi bd as bs asbs. (SubFrameIndexCtx b bi bd, KnownDim bd, ConcatList as (b :+ bs) asbs, All KnownDimType bs, PrimBytes t) => Idxs (as +: bi) -> DataFrame t asbs -> Maybe (DataFrame t (bd :+ bs)) Source #

Get a few contiguous elements.

In a sense, this is just a more complicated version of lookup.

This is a safe alternative to slice function when some of the dimensions are not known at compile time (d ~ XN m).

updateSlice :: forall (t :: Type) b bi bd as bs asbs. (KnownDimKind (KindOfEl asbs), CanSlice t asbs, SubFrameIndexCtx b bi bd, KnownDim bd, ExactDims bs, ConcatList as (b :+ bs) asbs, PrimArray t (DataFrame t (bd :+ bs))) => Idxs (as +: bi) -> DataFrame t (bd :+ bs) -> DataFrame t asbs -> DataFrame t asbs Source #

Update a few contiguous elements.

In a sense, this is just a more complicated version of update.

If any of the dims in as is unknown (a ~ XN m), you may happen to update data beyond dataframe bounds. In this case, the original DataFrame is returned. If (b ~ XN m) and (Idx bi + Dim bd > Dim b), this function updates only as many elements as fits into the dataframe along this dimension (possibly none).

ewgen :: forall t as bs asbs. (SubSpace t as bs asbs, Dimensions as) => DataFrame t bs -> DataFrame t asbs Source #

Generate a DataFrame by repeating an element.

iwgen :: forall t as bs asbs. (SubSpace t as bs asbs, Dimensions as) => (Idxs as -> DataFrame t bs) -> DataFrame t asbs Source #

Generate a DataFrame by iterating a function (index -> element).

ewmap :: forall t as bs asbs s bs' asbs'. (SubSpace t as bs asbs, SubSpace s as bs' asbs') => (DataFrame s bs' -> DataFrame t bs) -> DataFrame s asbs' -> DataFrame t asbs Source #

Map a function over each element of DataFrame.

iwmap :: forall t as bs asbs s bs' asbs'. (SubSpace t as bs asbs, SubSpace s as bs' asbs') => (Idxs as -> DataFrame s bs' -> DataFrame t bs) -> DataFrame s asbs' -> DataFrame t asbs Source #

Map a function over each element with its index of DataFrame.

ewzip :: forall t as bs asbs l bsL asbsL r bsR asbsR. (SubSpace t as bs asbs, SubSpace l as bsL asbsL, SubSpace r as bsR asbsR) => (DataFrame l bsL -> DataFrame r bsR -> DataFrame t bs) -> DataFrame l asbsL -> DataFrame r asbsR -> DataFrame t asbs Source #

Zip two spaces on a specified subspace element-wise (without index)

iwzip :: forall t as bs asbs l bsL asbsL r bsR asbsR. (SubSpace t as bs asbs, SubSpace l as bsL asbsL, SubSpace r as bsR asbsR) => (Idxs as -> DataFrame l bsL -> DataFrame r bsR -> DataFrame t bs) -> DataFrame l asbsL -> DataFrame r asbsR -> DataFrame t asbs Source #

Zip two spaces on a specified subspace index-wise (with index).

element :: forall t as bs asbs f. (SubSpace t as bs asbs, Applicative f) => Idxs as -> (DataFrame t bs -> f (DataFrame t bs)) -> DataFrame t asbs -> f (DataFrame t asbs) Source #

Apply a functor over a single element (simple lens)

If any of the dims in as is unknown (a ~ XN m) and any of the corresponding indices fall outside of the DataFrame Dims, then the argument Functor is not called and the result is pure original DataFrame.

elementWise :: forall t as bs asbs s bs' asbs' f. (SubSpace t as bs asbs, SubSpace s as bs' asbs', Applicative f) => (DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s asbs' -> f (DataFrame t asbs) Source #

Apply an applicative functor on each element (Lens-like traversal).

elementWise_ :: forall t as bs asbs f b. (SubSpace t as bs asbs, Applicative f) => (DataFrame t bs -> f b) -> DataFrame t asbs -> f () Source #

Apply an applicative functor on each element (Lens-like traversal)

indexWise :: forall t as bs asbs s bs' asbs' f. (SubSpace t as bs asbs, SubSpace s as bs' asbs', Applicative f) => (Idxs as -> DataFrame s bs' -> f (DataFrame t bs)) -> DataFrame s asbs' -> f (DataFrame t asbs) Source #

Apply an applicative functor on each element with its index (Lens-like indexed traversal).

indexWise_ :: forall t as bs asbs f b. (SubSpace t as bs asbs, Applicative f) => (Idxs as -> DataFrame t bs -> f b) -> DataFrame t asbs -> f () Source #

Apply an applicative functor on each element with its index (Lens-like indexed traversal)

ewfoldl :: forall t as bs asbs b. SubSpace t as bs asbs => (b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b Source #

Left-associative lazy fold of a DataFrame. Same rules apply as for foldl.

ewfoldl' :: forall t as bs asbs b. SubSpace t as bs asbs => (b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b Source #

Left-associative strict fold of a DataFrame. Same rules apply as for foldl'.

ewfoldr :: forall t as bs asbs b. SubSpace t as bs asbs => (DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b Source #

Right-associative lazy fold of a DataFrame. Same rules apply as for foldr.

ewfoldr' :: forall t as bs asbs b. SubSpace t as bs asbs => (DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b Source #

Right-associative strict fold of a DataFrame. Same rules apply as for foldr'.

ewfoldMap :: forall t as bs asbs m. (SubSpace t as bs asbs, Monoid m) => (DataFrame t bs -> m) -> DataFrame t asbs -> m Source #

Map each element of the DataFrame to a monoid, and combine the results.

iwfoldl :: forall t as bs asbs b. SubSpace t as bs asbs => (Idxs as -> b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b Source #

Left-associative lazy fold of a DataFrame with an index. Same rules apply as for foldl.

iwfoldl' :: forall t as bs asbs b. SubSpace t as bs asbs => (Idxs as -> b -> DataFrame t bs -> b) -> b -> DataFrame t asbs -> b Source #

Left-associative strict fold of a DataFrame with an index. Same rules apply as for foldl'.

iwfoldr :: forall t as bs asbs b. SubSpace t as bs asbs => (Idxs as -> DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b Source #

Right-associative lazy fold of a DataFrame with an index. Same rules apply as for foldr.

iwfoldr' :: forall t as bs asbs b. SubSpace t as bs asbs => (Idxs as -> DataFrame t bs -> b -> b) -> b -> DataFrame t asbs -> b Source #

Right-associative strict fold of a DataFrame with an index. Same rules apply as for foldr'.

iwfoldMap :: forall t as bs asbs m. (SubSpace t as bs asbs, Monoid m) => (Idxs as -> DataFrame t bs -> m) -> DataFrame t asbs -> m Source #

Map each element of the DataFrame and its index to a monoid, and combine the results.