Frames-map-reduce-0.4.0.0: Frames wrapper for map-reduce-folds and some extra folds helpers.

Copyright(c) Adam Conner-Sax 2019
LicenseBSD
Maintaineradam_conner_sax@yahoo.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Frames.Folds.Maybe

Contents

Description

Frames.Folds contains various helper functions designed to simplify folding over Frames/Vinyl records given some way of folding over each column.

Synopsis

Types

type EndoFold a = Fold a a Source #

A Type synonym for folds like sum or, often, average.

Types to act as "interpretation functors" for records of folds

newtype FoldEndo f t Source #

Wrapper for Endo-folds of the field types of ElFields

Constructors

FoldEndo 

Fields

newtype FoldRecord record f g rs a Source #

Wrapper for folds from a record to an interpreted field. Usually g ~ ElField

Constructors

FoldRecord 

Fields

functions for building records of folds

toFoldRecord :: (a -> g b) -> Fold (record (Maybe :. ElField) rs) a -> FoldRecord record Maybe g rs b Source #

Create a FoldRecord from a Fold from a record to a specific type. This is helpful when creating folds from a record to another record (or the same record) by building it one field at a time. See examples for details.

recFieldF Source #

Arguments

:: KnownField t 
=> Fold a (Snd t)

A fold from some type a to the field type of an ElField

-> (record (Maybe :. ElField) rs -> Maybe a)

a function to get the a value from the input record

-> FoldRecord record Maybe (Maybe :. ElField) rs t

the resulting FoldRecord-wrapped fold

Helper for building a FoldRecord from a given fold and function of the record

fieldToFieldFold Source #

Arguments

:: (KnownField x, KnownField y, ElemOf rs x, RecGetFieldC x record Maybe rs) 
=> Fold (Snd x) (Snd y)

the fold to be wrapped

-> FoldRecord record Maybe (Maybe :. ElField) rs y

the wrapped fold

special case of recFieldF for the case when the function from the record to the folded type is just retrieving the value in a field.

functions for turning records of folds into folds of records

sequenceRecFold :: forall as rs record. IsoRec rs record Maybe => Rec (FoldRecord record Maybe (Maybe :. ElField) as) rs -> Fold (record (Maybe :. ElField) as) (record (Maybe :. ElField) rs) Source #

Turn a Record of folds into a fold over records

sequenceEndoFolds :: forall rs record. (RApply rs, RPureConstrained KnownField rs, EndoFieldFoldsToRecordFolds rs record Maybe, IsoRec rs record Maybe) => Rec (FoldEndo Maybe) rs -> Fold (record (Maybe :. ElField) rs) (record (Maybe :. ElField) rs) Source #

turn a record of endo-folds over each field, into a fold over records

functions using constraints to extend an endo-fold across a record

foldAll :: (RPureConstrained KnownField rs, RApply rs, EndoFieldFoldsToRecordFolds rs record Maybe, IsoRec rs record Maybe) => (forall a. Fold a a) -> Fold (record (Maybe :. ElField) rs) (record (Maybe :. ElField) rs) Source #

apply an unconstrained endo-fold, e.g., a fold which takes the last item in a container, to every field in a record

foldAllConstrained :: forall c rs record. (RPureConstrained (ConstrainedField c) rs, RPureConstrained KnownField rs, RApply rs, EndoFieldFoldsToRecordFolds rs record Maybe, IsoRec rs record Maybe) => (forall a. c a => Fold a a) -> Fold (record (Maybe :. ElField) rs) (record (Maybe :. ElField) rs) Source #

Apply a constrained endo-fold to all fields of a record. May require a use of TypeApplications, e.g., foldAllConstrained @Num FL.sum

maybeFoldAllConstrained :: forall c rs record. (RPureConstrained (ConstrainedField c) rs, RPureConstrained KnownField rs, RApply rs, EndoFieldFoldsToRecordFolds rs record Maybe, IsoRec rs record Maybe) => (forall a. c a => Fold (Maybe a) (Maybe a)) -> Fold (record (Maybe :. ElField) rs) (record (Maybe :. ElField) rs) Source #

foldAllMonoid :: forall g rs record. (RPureConstrained (ConstrainedField (MonoidalField g)) rs, RPureConstrained KnownField rs, RApply rs, EndoFieldFoldsToRecordFolds rs record Maybe, IsoRec rs record Maybe) => Fold (record (Maybe :. ElField) rs) (record (Maybe :. ElField) rs) Source #

Given a monoid-wrapper, e.g., Sum, apply the derived endo-fold to all fields of a record This is strictly less powerful than foldAllConstrained but might be simpler to use in some cases