Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides a Fold1
type that is a "non-empty" analog of the
Fold
type, meaning that it requires at least one input element in order to
produce a result
This module does not provide all of the same utilities as the
Control.Foldl module. Instead, this module only provides the utilities
which can make use of the non-empty input guarantee (e.g. head
). For
all other utilities you can convert them from the equivalent Fold
using
fromFold
.
Import this module qualified to avoid clashing with the Prelude:
>>>
import qualified Control.Foldl.NonEmpty as Foldl1
Use fold1
to apply a Fold1
to a non-empty list:
>>>
Foldl1.fold1 Foldl1.last (1 :| [2..10])
10
Synopsis
- data Fold1 a b where
- fold1 :: Foldable1 f => Fold1 a b -> f a -> b
- fromFold :: Fold a b -> Fold1 a b
- toFold :: Fold1 a b -> Fold a (Maybe b)
- sconcat :: Semigroup a => Fold1 a a
- head :: Fold1 a a
- last :: Fold1 a a
- maximum :: Ord a => Fold1 a a
- maximumBy :: (a -> a -> Ordering) -> Fold1 a a
- minimum :: Ord a => Fold1 a a
- minimumBy :: (a -> a -> Ordering) -> Fold1 a a
- nonEmpty :: Fold1 a (NonEmpty a)
- purely :: (forall x. (a -> x) -> (x -> a -> x) -> (x -> b) -> r) -> Fold1 a b -> r
- purely_ :: (forall x. (a -> x) -> (x -> a -> x) -> x) -> Fold1 a b -> b
- premap :: (a -> b) -> Fold1 b r -> Fold1 a r
- newtype FromMaybe b = FromMaybe {
- appFromMaybe :: Maybe b -> b
- type Handler1 a b = forall x. (b -> Const (Dual (FromMaybe x)) b) -> a -> Const (Dual (FromMaybe x)) a
- handles :: forall a b r. Handler1 a b -> Fold1 b r -> Fold1 a r
- foldOver :: Handler1 s a -> Fold1 a b -> s -> b
- folded1 :: (Contravariant f, Apply f, Foldable1 t) => (a -> f a) -> t a -> f (t a)
Fold Types
pattern Fold1_ :: forall a b. forall x. (a -> x) -> (x -> a -> x) -> (x -> b) -> Fold1 a b |
|
Instances
Folding
Conversion between Fold and Fold1
Folds
maximumBy :: (a -> a -> Ordering) -> Fold1 a a Source #
Computes the maximum element with respect to the given comparison function
minimumBy :: (a -> a -> Ordering) -> Fold1 a a Source #
Computes the minimum element with respect to the given comparison function
Non-empty Container Folds
nonEmpty :: Fold1 a (NonEmpty a) Source #
Fold all values within a non-empty container into a NonEmpty
list
Utilities
purely :: (forall x. (a -> x) -> (x -> a -> x) -> (x -> b) -> r) -> Fold1 a b -> r Source #
Upgrade a fold to accept the Fold1
type
purely_ :: (forall x. (a -> x) -> (x -> a -> x) -> x) -> Fold1 a b -> b Source #
Upgrade a more traditional fold to accept the Fold1
type
premap :: (a -> b) -> Fold1 b r -> Fold1 a r Source #
(premap f folder)
returns a new Fold1
where f is applied at each step
Foldl1.fold1 (premap f folder) list = Foldl1.fold1 folder (NonEmpty.map f list)
>>>
Foldl1.fold1 (premap Sum Foldl1.sconcat) (1 :| [2..10])
Sum {getSum = 55}
>>>
Foldl1.fold1 Foldl1.sconcat $ NonEmpty.map Sum (1 :| [2..10])
Sum {getSum = 55}
premap id = id premap (f . g) = premap g . premap f
premap k (pure r) = pure r premap k (f <*> x) = premap k f <*> premap k x
instance Monad m => Semigroup (FromMaybe m a) where mappend (FromMaybe f) (FromMaybe g) = FromMaybeM (f . Just . g)
FromMaybe | |
|
type Handler1 a b = forall x. (b -> Const (Dual (FromMaybe x)) b) -> a -> Const (Dual (FromMaybe x)) a Source #
handles :: forall a b r. Handler1 a b -> Fold1 b r -> Fold1 a r Source #
(handles t folder)
transforms the input of a Fold1
using a Lens,
Traversal1, or Fold1 optic:
handles _1 :: Fold1 a r -> Fold1 (a, b) r handles traverse1 :: Traversable1 t => Fold1 a r -> Fold1 (t a) r handles folded1 :: Foldable1 t => Fold1 a r -> Fold1 (t a) r
>>>
Foldl1.fold1 (handles traverse1 Foldl1.nonEmpty) $ (1 :| [2..4]) :| [ 5 :| [6,7], 8 :| [9,10] ]
1 :| [2,3,4,5,6,7,8,9,10]
>>>
Foldl1.fold1 (handles _2 Foldl1.sconcat) $ (1,"Hello ") :| [(2,"World"),(3,"!")]
"Hello World!"
handles id = id handles (f . g) = handles f . handles g
handles t (pure r) = pure r handles t (f <*> x) = handles t f <*> handles t x
foldOver :: Handler1 s a -> Fold1 a b -> s -> b Source #
(foldOver f folder xs)
folds all values from a Lens, Traversal1 or Fold1 optic with the given folder
>>>
foldOver (_2 . both) Foldl1.nonEmpty (1, (2, 3))
2 :| [3]
Foldl1.foldOver f folder xs == Foldl1.fold1 folder (xs ^.. f)
Foldl1.foldOver (folded1 . f) folder == Foldl1.fold1 (Foldl1.handles f folder)
Foldl1.foldOver folded1 == Foldl1.fold1