deferred-folds-0.9.10: Abstractions over deferred folds

Safe HaskellNone
LanguageHaskell2010

DeferredFolds.Unfoldr

Synopsis

Documentation

newtype Unfoldr a Source #

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

It is a monad and a monoid, and is very useful for efficiently aggregating the projections on data intended for right-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 foldr function for lists:

foldr :: (a -> b -> b) -> b -> [a] -> b

If we reverse its parameters we get

foldr :: [a] -> (a -> b -> b) -> b -> b

Which in Haskell is essentially the same as

foldr :: [a] -> (forall b. (a -> b -> b) -> b -> b)

We can isolate that part into an abstraction:

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

Then we get to this simple morphism:

list :: [a] -> Unfoldr a
list list = Unfoldr (\ step init -> foldr step init list)

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

text :: Text -> Unfoldr Char
text text = Unfoldr (\ step init -> Data.Text.foldr step init text)

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

abcdef :: Unfoldr 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 right-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

Unfoldr (forall x. (a -> x -> x) -> x -> x) 
Instances
Monad Unfoldr Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

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

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

return :: a -> Unfoldr a #

fail :: String -> Unfoldr a #

Functor Unfoldr Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

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

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

Applicative Unfoldr Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

pure :: a -> Unfoldr a #

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

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

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

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

Foldable Unfoldr Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

fold :: Monoid m => Unfoldr m -> m #

foldMap :: Monoid m => (a -> m) -> Unfoldr a -> m #

foldr :: (a -> b -> b) -> b -> Unfoldr a -> b #

foldr' :: (a -> b -> b) -> b -> Unfoldr a -> b #

foldl :: (b -> a -> b) -> b -> Unfoldr a -> b #

foldl' :: (b -> a -> b) -> b -> Unfoldr a -> b #

foldr1 :: (a -> a -> a) -> Unfoldr a -> a #

foldl1 :: (a -> a -> a) -> Unfoldr a -> a #

toList :: Unfoldr a -> [a] #

null :: Unfoldr a -> Bool #

length :: Unfoldr a -> Int #

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

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

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

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

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

Alternative Unfoldr Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

empty :: Unfoldr a #

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

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

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

MonadPlus Unfoldr Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

mzero :: Unfoldr a #

mplus :: Unfoldr a -> Unfoldr a -> Unfoldr a #

IsList (Unfoldr a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Associated Types

type Item (Unfoldr a) :: Type #

Methods

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

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

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

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

Defined in DeferredFolds.Defs.Unfoldr

Methods

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

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

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

Defined in DeferredFolds.Defs.Unfoldr

Methods

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

show :: Unfoldr a -> String #

showList :: [Unfoldr a] -> ShowS #

Semigroup (Unfoldr a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

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

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

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

Monoid (Unfoldr a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

Methods

mempty :: Unfoldr a #

mappend :: Unfoldr a -> Unfoldr a -> Unfoldr a #

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

type Item (Unfoldr a) Source # 
Instance details

Defined in DeferredFolds.Defs.Unfoldr

type Item (Unfoldr a) = a

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

Apply a Gonzalez fold

foldM :: Monad m => FoldM m input output -> Unfoldr input -> m output Source #

Apply a monadic Gonzalez fold

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

Construct from any foldable

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

Filter the values given a predicate

enumsFrom :: Enum a => a -> Unfoldr a Source #

Ascending infinite stream of enums starting from the one specified

enumsInRange :: (Enum a, Ord a) => a -> a -> Unfoldr a Source #

Enums in the specified inclusive range

intsFrom :: Int -> Unfoldr Int Source #

Ascending infinite stream of ints starting from the one specified

intsInRange :: Int -> Int -> Unfoldr Int Source #

Ints in the specified inclusive range

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

Associations of a map

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

Associations of an intmap

hashMapAssocs :: HashMap key value -> Unfoldr (key, value) Source #

Associations of a hash-map

hashMapAt :: (Hashable key, Eq key) => HashMap key value -> key -> Unfoldr value Source #

Value of a hash-map by key

hashMapValue :: (Hashable key, Eq key) => key -> HashMap key value -> Unfoldr value Source #

Deprecated: Use hashMapAt instead

Value of a hash-map by key

hashMapValues :: (Hashable key, Eq key) => HashMap key value -> Unfoldr key -> Unfoldr value Source #

Values of a hash-map by their keys

byteStringBytes :: ByteString -> Unfoldr Word8 Source #

Bytes of a bytestring

shortByteStringBytes :: ShortByteString -> Unfoldr Word8 Source #

Bytes of a short bytestring

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

Elements of a prim array

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

Elements of a prim array coming paired with indices

vector :: Vector vector a => vector a -> Unfoldr a Source #

Elements of a vector

vectorWithIndices :: Vector vector a => vector a -> Unfoldr (Int, a) Source #

Elements of a vector coming paired with indices

binaryDigits :: Integral a => a -> Unfoldr a Source #

Binary digits of a non-negative integral number.

reverseBinaryDigits :: Integral a => a -> Unfoldr a Source #

Binary digits of a non-negative integral number in reverse order.

octalDigits :: Integral a => a -> Unfoldr a Source #

Octal digits of a non-negative integral number.

reverseOctalDigits :: Integral a => a -> Unfoldr a Source #

Octal digits of a non-negative integral number in reverse order.

decimalDigits :: Integral a => a -> Unfoldr a Source #

Decimal digits of a non-negative integral number.

reverseDecimalDigits :: Integral a => a -> Unfoldr a Source #

Decimal digits of a non-negative integral number in reverse order. More efficient than decimalDigits.

hexadecimalDigits :: Integral a => a -> Unfoldr a Source #

Hexadecimal digits of a non-negative number.

reverseHexadecimalDigits :: Integral a => a -> Unfoldr a Source #

Hexadecimal digits of a non-negative number in reverse order.

reverseDigits Source #

Arguments

:: Integral a 
=> a

Radix

-> a

Number

-> Unfoldr a 

Digits of a non-negative number in numeral system based on the specified radix. The digits come in reverse order.

E.g., here's how an unfold of binary digits in proper order looks:

binaryDigits :: Integral a => a -> Unfoldr a
binaryDigits = reverse . reverseDigits 2

reverse :: Unfoldr a -> Unfoldr a Source #

Reverse the order.

Use with care, because it requires to allocate all elements.

zipWithIndex :: Unfoldr a -> Unfoldr (Int, a) Source #

Lift into an unfold, which produces pairs with index.

zipWithReverseIndex :: Unfoldr a -> Unfoldr (Int, a) Source #

Deprecated: This function builds up stack. Use zipWithIndex instead.

Lift into an unfold, which produces pairs with right-associative index.

setBitIndices :: FiniteBits a => a -> Unfoldr Int Source #

Indices of set bits.

unsetBitIndices :: FiniteBits a => a -> Unfoldr Int Source #

Indices of unset bits.

takeWhile :: (a -> Bool) -> Unfoldr a -> Unfoldr a Source #

cons :: a -> Unfoldr a -> Unfoldr a Source #

snoc :: a -> Unfoldr a -> Unfoldr a Source #