deferred-folds-0.9.10.1: Abstractions over deferred folds

Safe HaskellNone
LanguageHaskell2010

DeferredFolds.Unfoldl

Synopsis

Documentation

newtype Unfoldl a 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 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
Monad Unfoldl Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

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

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

return :: a -> Unfoldl a #

fail :: String -> Unfoldl a #

Functor Unfoldl Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

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

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

Applicative Unfoldl Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

pure :: a -> Unfoldl a #

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

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

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

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

Foldable Unfoldl Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

fold :: Monoid m => Unfoldl m -> 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 #

toList :: Unfoldl a -> [a] #

null :: Unfoldl a -> Bool #

length :: Unfoldl a -> Int #

elem :: Eq a => a -> Unfoldl a -> Bool #

maximum :: Ord a => Unfoldl a -> a #

minimum :: Ord a => Unfoldl a -> a #

sum :: Num a => Unfoldl a -> a #

product :: Num a => Unfoldl a -> a #

Alternative Unfoldl Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

empty :: Unfoldl a #

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

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

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

MonadPlus Unfoldl Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

mzero :: Unfoldl a #

mplus :: Unfoldl a -> Unfoldl a -> Unfoldl a #

IsList (Unfoldl a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Associated Types

type Item (Unfoldl a) :: Type #

Methods

fromList :: [Item (Unfoldl a)] -> Unfoldl a #

fromListN :: Int -> [Item (Unfoldl a)] -> Unfoldl a #

toList :: Unfoldl a -> [Item (Unfoldl a)] #

Eq a => Eq (Unfoldl a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

(==) :: Unfoldl a -> Unfoldl a -> Bool #

(/=) :: Unfoldl a -> Unfoldl a -> Bool #

Show a => Show (Unfoldl a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

showsPrec :: Int -> Unfoldl a -> ShowS #

show :: Unfoldl a -> String #

showList :: [Unfoldl a] -> ShowS #

Semigroup (Unfoldl a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

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

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

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

Monoid (Unfoldl a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

Methods

mempty :: Unfoldl a #

mappend :: Unfoldl a -> Unfoldl a -> Unfoldl a #

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

type Item (Unfoldl a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldl

type Item (Unfoldl a) = a

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

Apply a Gonzalez fold

unfoldlM :: UnfoldlM Identity input -> Unfoldl input Source #

Unlift a monadic unfold

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

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

Construct from any foldable

filter :: (a -> Bool) -> Unfoldl a -> Unfoldl a Source #

Filter the values given a predicate

intsInRange :: Int -> Int -> Unfoldl Int Source #

Ints in the specified inclusive range

mapAssocs :: Map key value -> Unfoldl (key, value) Source #

Associations of a map

intMapAssocs :: IntMap value -> Unfoldl (Int, value) Source #

Associations of an intmap

byteStringBytes :: ByteString -> Unfoldl Word8 Source #

Bytes of a bytestring

shortByteStringBytes :: ShortByteString -> Unfoldl Word8 Source #

Bytes of a short bytestring

primArray :: Prim prim => PrimArray prim -> Unfoldl prim Source #

Elements of a prim array

primArrayWithIndices :: Prim prim => PrimArray prim -> Unfoldl (Int, prim) Source #

Elements of a prim array coming paired with indices