deferred-folds-0.4.1: Abstractions over deferred folds

Safe HaskellNone
LanguageHaskell2010

DeferredFolds.Unfold

Synopsis

Documentation

newtype Unfold input Source #

A projection on data, which only knows how to execute a strict left-fold.

It is a monad and a monoid, and is very useful for efficiently aggregating the projections on data intended for left-folding, since its concatenation (<>) has complexity of O(1).

Intuition

The intuition of what this abstraction is all about can be derived from lists.

Let's consider the foldl' function for lists:

foldl' :: (b -> a -> b) -> b -> [a] -> b

If we reverse its parameters we get

foldl' :: [a] -> (b -> a -> b) -> b -> b

Which in Haskell is essentially the same as

foldl' :: [a] -> (forall b. (b -> a -> b) -> b -> b)

We can isolate that part into an abstraction:

newtype Unfold a = Unfold (forall b. (b -> a -> b) -> b -> b)

Then we get to this simple morphism:

list :: [a] -> Unfold a
list list = Unfold (\ step init -> foldl' step init list)

We can do the same with say Data.Text.Text:

text :: Text -> Unfold Char
text text = Unfold (\ step init -> Data.Text.foldl' step init text)

And then we can use those both to concatenate with just an O(1) cost:

abcdef :: Unfold Char
abcdef = list ['a', 'b', 'c'] <> text "def"

Please notice that up until this moment no actual data materialization has happened and hence no traversals have appeared. All that we've done is just composed a function, which only specifies which parts of data structures to traverse to perform a left-fold. Only at the moment where the actual folding will happen will we actually traverse the source data. E.g., using the "fold" function:

abcdefLength :: Int
abcdefLength = fold Control.Foldl.length abcdef

Constructors

Unfold (forall output. (output -> input -> output) -> output -> output) 

Instances

Monad Unfold Source # 

Methods

(>>=) :: Unfold a -> (a -> Unfold b) -> Unfold b #

(>>) :: Unfold a -> Unfold b -> Unfold b #

return :: a -> Unfold a #

fail :: String -> Unfold a #

Functor Unfold Source # 

Methods

fmap :: (a -> b) -> Unfold a -> Unfold b #

(<$) :: a -> Unfold b -> Unfold a #

Applicative Unfold Source # 

Methods

pure :: a -> Unfold a #

(<*>) :: Unfold (a -> b) -> Unfold a -> Unfold b #

liftA2 :: (a -> b -> c) -> Unfold a -> Unfold b -> Unfold c #

(*>) :: Unfold a -> Unfold b -> Unfold b #

(<*) :: Unfold a -> Unfold b -> Unfold a #

Alternative Unfold Source # 

Methods

empty :: Unfold a #

(<|>) :: Unfold a -> Unfold a -> Unfold a #

some :: Unfold a -> Unfold [a] #

many :: Unfold a -> Unfold [a] #

MonadPlus Unfold Source # 

Methods

mzero :: Unfold a #

mplus :: Unfold a -> Unfold a -> Unfold a #

Semigroup (Unfold a) Source # 

Methods

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

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

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

Monoid (Unfold a) Source # 

Methods

mempty :: Unfold a #

mappend :: Unfold a -> Unfold a -> Unfold a #

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

foldl' :: (output -> input -> output) -> output -> Unfold input -> output Source #

Perform a strict left fold

fold :: Fold input output -> Unfold input -> output Source #

Apply a Gonzalez fold

foldable :: Foldable foldable => foldable a -> Unfold a Source #

Construct from any foldable

intsInRange :: Int -> Int -> Unfold Int Source #

Ints in the specified inclusive range

map :: Map key value -> Unfold (key, value) Source #

intMap :: IntMap value -> Unfold (Int, value) Source #