| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
DeferredFolds.Unfoldl
Synopsis
- newtype Unfoldl a = Unfoldl (forall x. (x -> a -> x) -> x -> x)
- fold :: Fold input output -> Unfoldl input -> output
- unfoldlM :: UnfoldlM Identity input -> Unfoldl input
- mapFoldInput :: (forall x. Fold b x -> Fold a x) -> Unfoldl a -> Unfoldl b
- foldable :: Foldable foldable => foldable a -> Unfoldl a
- filter :: (a -> Bool) -> Unfoldl a -> Unfoldl a
- intsInRange :: Int -> Int -> Unfoldl Int
- mapAssocs :: Map key value -> Unfoldl (key, value)
- intMapAssocs :: IntMap value -> Unfoldl (Int, value)
- byteStringBytes :: ByteString -> Unfoldl Word8
- shortByteStringBytes :: ShortByteString -> Unfoldl Word8
- primArray :: Prim prim => PrimArray prim -> Unfoldl prim
- primArrayWithIndices :: Prim prim => PrimArray prim -> Unfoldl (Int, prim)
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 for this abstraction can be derived from lists.
Let's consider the foldl` function for lists:
foldl' :: (b -> a -> b) -> b -> [a] -> b
If we rearrange 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 Unfoldl a = Unfoldl (forall b. (b -> a -> b) -> b -> b)
Then we get to this simple morphism:
list :: [a] -> Unfoldl a list list = Unfoldl (\ step init -> foldl' step init list)
We can do the same with say Data.Text.Text:
text :: Text -> Unfoldl Char text text = Unfoldl (\ step init -> Data.Text.foldl' step init text)
And then we can use those both to concatenate with just an O(1) cost:
abcdef :: Unfoldl 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
| Unfoldl (forall x. (x -> a -> x) -> x -> x) | 
Instances
| Foldable Unfoldl Source # | |
| Defined in DeferredFolds.Defs.Unfoldl Methods fold :: Monoid m => Unfoldl m -> m # foldMap :: Monoid m => (a -> m) -> Unfoldl a -> m # foldMap' :: Monoid m => (a -> m) -> Unfoldl a -> m # foldr :: (a -> b -> b) -> b -> Unfoldl a -> b # foldr' :: (a -> b -> b) -> b -> Unfoldl a -> b # foldl :: (b -> a -> b) -> b -> Unfoldl a -> b # foldl' :: (b -> a -> b) -> b -> Unfoldl a -> b # foldr1 :: (a -> a -> a) -> Unfoldl a -> a # foldl1 :: (a -> a -> a) -> Unfoldl a -> a # elem :: Eq a => a -> Unfoldl a -> Bool # maximum :: Ord a => Unfoldl a -> a # minimum :: Ord a => Unfoldl a -> a # | |
| Alternative Unfoldl Source # | |
| Applicative Unfoldl Source # | |
| Functor Unfoldl Source # | |
| Monad Unfoldl Source # | |
| MonadPlus Unfoldl Source # | |
| Monoid (Unfoldl a) Source # | |
| Semigroup (Unfoldl a) Source # | |
| IsList (Unfoldl a) Source # | |
| Show a => Show (Unfoldl a) Source # | |
| Eq a => Eq (Unfoldl a) Source # | |
| type Item (Unfoldl a) Source # | |
| Defined in DeferredFolds.Defs.Unfoldl | |
mapFoldInput :: (forall x. Fold b x -> Fold a x) -> Unfoldl a -> Unfoldl b Source #
Lift a fold input mapping function into a mapping of unfolds
byteStringBytes :: ByteString -> Unfoldl Word8 Source #
Bytes of a bytestring
shortByteStringBytes :: ShortByteString -> Unfoldl Word8 Source #
Bytes of a short bytestring