Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Unfold input = Unfold (forall output. (output -> input -> output) -> output -> output)
- fold :: Fold input output -> Unfold input -> output
- unfoldM :: UnfoldM Identity input -> Unfold input
- foldable :: Foldable foldable => foldable a -> Unfold a
- intsInRange :: Int -> Int -> Unfold Int
- map :: Map key value -> Unfold (key, value)
- intMap :: IntMap value -> Unfold (Int, value)
Documentation
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
Unfold (forall output. (output -> input -> output) -> output -> output) |
Instances
Monad Unfold Source # | |
Functor Unfold Source # | |
Applicative Unfold Source # | |
Foldable Unfold Source # | |
Defined in DeferredFolds.Unfold fold :: Monoid m => Unfold m -> m # foldMap :: Monoid m => (a -> m) -> Unfold a -> m # foldr :: (a -> b -> b) -> b -> Unfold a -> b # foldr' :: (a -> b -> b) -> b -> Unfold a -> b # foldl :: (b -> a -> b) -> b -> Unfold a -> b # foldl' :: (b -> a -> b) -> b -> Unfold a -> b # foldr1 :: (a -> a -> a) -> Unfold a -> a # foldl1 :: (a -> a -> a) -> Unfold a -> a # elem :: Eq a => a -> Unfold a -> Bool # maximum :: Ord a => Unfold a -> a # minimum :: Ord a => Unfold a -> a # | |
Alternative Unfold Source # | |
MonadPlus Unfold Source # | |
Semigroup (Unfold a) Source # | |
Monoid (Unfold a) Source # | |