Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Unfoldr a = Unfoldr (forall x. (a -> x -> x) -> x -> x)
- fold :: Fold input output -> Unfoldr input -> output
- foldM :: Monad m => FoldM m input output -> Unfoldr input -> m output
- foldable :: Foldable foldable => foldable a -> Unfoldr a
- intSet :: IntSet -> Unfoldr Int
- filter :: (a -> Bool) -> Unfoldr a -> Unfoldr a
- enumsFrom :: Enum a => a -> Unfoldr a
- enumsInRange :: (Enum a, Ord a) => a -> a -> Unfoldr a
- intsFrom :: Int -> Unfoldr Int
- intsInRange :: Int -> Int -> Unfoldr Int
- mapAssocs :: Map key value -> Unfoldr (key, value)
- intMapAssocs :: IntMap value -> Unfoldr (Int, value)
- hashMapKeys :: HashMap key value -> Unfoldr key
- hashMapAssocs :: HashMap key value -> Unfoldr (key, value)
- hashMapAt :: (Hashable key, Eq key) => HashMap key value -> key -> Unfoldr value
- hashMapValue :: (Hashable key, Eq key) => key -> HashMap key value -> Unfoldr value
- hashMapValues :: (Hashable key, Eq key) => HashMap key value -> Unfoldr key -> Unfoldr value
- byteStringBytes :: ByteString -> Unfoldr Word8
- shortByteStringBytes :: ShortByteString -> Unfoldr Word8
- primArray :: Prim prim => PrimArray prim -> Unfoldr prim
- primArrayWithIndices :: Prim prim => PrimArray prim -> Unfoldr (Int, prim)
- vector :: Vector vector a => vector a -> Unfoldr a
- vectorWithIndices :: Vector vector a => vector a -> Unfoldr (Int, a)
- binaryDigits :: Integral a => a -> Unfoldr a
- reverseBinaryDigits :: Integral a => a -> Unfoldr a
- octalDigits :: Integral a => a -> Unfoldr a
- reverseOctalDigits :: Integral a => a -> Unfoldr a
- decimalDigits :: Integral a => a -> Unfoldr a
- reverseDecimalDigits :: Integral a => a -> Unfoldr a
- hexadecimalDigits :: Integral a => a -> Unfoldr a
- reverseHexadecimalDigits :: Integral a => a -> Unfoldr a
- reverseDigits :: Integral a => a -> a -> Unfoldr a
- reverse :: Unfoldr a -> Unfoldr a
- zipWith :: (a -> b -> c) -> Unfoldr a -> Unfoldr b -> Unfoldr c
- zipWithIndex :: Unfoldr a -> Unfoldr (Int, a)
- zipWithReverseIndex :: Unfoldr a -> Unfoldr (Int, a)
- setBitIndices :: FiniteBits a => a -> Unfoldr Int
- unsetBitIndices :: FiniteBits a => a -> Unfoldr Int
- take :: Int -> Unfoldr a -> Unfoldr a
- takeWhile :: (a -> Bool) -> Unfoldr a -> Unfoldr a
- cons :: a -> Unfoldr a -> Unfoldr a
- snoc :: a -> Unfoldr a -> Unfoldr a
- intersperse :: a -> Unfoldr a -> Unfoldr a
- textChars :: Text -> Unfoldr Char
- textWords :: Text -> Unfoldr Text
- trimWhitespace :: Unfoldr Char -> Unfoldr Char
Documentation
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 rearrange 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
Unfoldr (forall x. (a -> x -> x) -> x -> x) |
Instances
Foldable Unfoldr Source # | |
Defined in DeferredFolds.Defs.Unfoldr fold :: Monoid m => Unfoldr m -> m # foldMap :: Monoid m => (a -> m) -> Unfoldr a -> 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 # elem :: Eq a => a -> Unfoldr a -> Bool # maximum :: Ord a => Unfoldr a -> a # minimum :: Ord a => Unfoldr a -> a # | |
Traversable Unfoldr Source # | |
Alternative Unfoldr Source # | |
Applicative Unfoldr Source # | |
Functor Unfoldr Source # | |
Monad Unfoldr Source # | |
MonadPlus Unfoldr Source # | |
Monoid (Unfoldr a) Source # | |
Semigroup (Unfoldr a) Source # | |
IsList (Unfoldr a) Source # | |
Show a => Show (Unfoldr a) Source # | |
Eq a => Eq (Unfoldr a) Source # | |
type Item (Unfoldr a) Source # | |
Defined in DeferredFolds.Defs.Unfoldr |
foldM :: Monad m => FoldM m input output -> Unfoldr input -> m output Source #
Apply a monadic Gonzalez fold
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
hashMapKeys :: HashMap key value -> Unfoldr key Source #
Keys of a hash-map
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
primArrayWithIndices :: Prim prim => PrimArray prim -> Unfoldr (Int, prim) Source #
Elements of a prim array coming paired with indices
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.
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.
intersperse :: a -> Unfoldr a -> Unfoldr a Source #
Insert a separator value between each element.
Behaves the same way as intersperse
.
textChars :: Text -> Unfoldr Char Source #
Reproduces the behaviour of unpack
.
Implementation is efficient and avoids allocation of an intermediate list.