foldl-1.4.17: Composable, streaming, and efficient left folds
Safe HaskellSafe-Inferred
LanguageHaskell2010

Control.Foldl.NonEmpty

Description

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

Fold Types

data Fold1 a b Source #

A Fold1 is like a Fold except that it consumes at least one input element

Constructors

Fold1 (a -> Fold a b) 

Bundled Patterns

pattern Fold1_ :: forall a b. forall x. (a -> x) -> (x -> a -> x) -> (x -> b) -> Fold1 a b

Fold1_ is an alternative to the Fold1 constructor if you need to explicitly work with an initial, step and extraction function.

Fold1_ is similar to the Fold constructor, which also works with an initial, step and extraction function. However, note that Fold takes the step function as the first argument and the initial accumulator as the second argument, whereas Fold1_ takes them in swapped order:

Fold1_ initial step extract

While Fold resembles foldl, Fold1_ resembles foldlMap1.

Instances

Instances details
Profunctor Fold1 Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

dimap :: (a -> b) -> (c -> d) -> Fold1 b c -> Fold1 a d #

lmap :: (a -> b) -> Fold1 b c -> Fold1 a c #

rmap :: (b -> c) -> Fold1 a b -> Fold1 a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Fold1 a b -> Fold1 a c #

(.#) :: forall a b c q. Coercible b a => Fold1 b c -> q a b -> Fold1 a c #

Applicative (Fold1 a) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

pure :: a0 -> Fold1 a a0 #

(<*>) :: Fold1 a (a0 -> b) -> Fold1 a a0 -> Fold1 a b #

liftA2 :: (a0 -> b -> c) -> Fold1 a a0 -> Fold1 a b -> Fold1 a c #

(*>) :: Fold1 a a0 -> Fold1 a b -> Fold1 a b #

(<*) :: Fold1 a a0 -> Fold1 a b -> Fold1 a a0 #

Functor (Fold1 a) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

fmap :: (a0 -> b) -> Fold1 a a0 -> Fold1 a b #

(<$) :: a0 -> Fold1 a b -> Fold1 a a0 #

Monoid b => Monoid (Fold1 a b) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

mempty :: Fold1 a b #

mappend :: Fold1 a b -> Fold1 a b -> Fold1 a b #

mconcat :: [Fold1 a b] -> Fold1 a b #

Semigroup b => Semigroup (Fold1 a b) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

(<>) :: Fold1 a b -> Fold1 a b -> Fold1 a b #

sconcat :: NonEmpty (Fold1 a b) -> Fold1 a b #

stimes :: Integral b0 => b0 -> Fold1 a b -> Fold1 a b #

Floating b => Floating (Fold1 a b) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

pi :: Fold1 a b #

exp :: Fold1 a b -> Fold1 a b #

log :: Fold1 a b -> Fold1 a b #

sqrt :: Fold1 a b -> Fold1 a b #

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

logBase :: Fold1 a b -> Fold1 a b -> Fold1 a b #

sin :: Fold1 a b -> Fold1 a b #

cos :: Fold1 a b -> Fold1 a b #

tan :: Fold1 a b -> Fold1 a b #

asin :: Fold1 a b -> Fold1 a b #

acos :: Fold1 a b -> Fold1 a b #

atan :: Fold1 a b -> Fold1 a b #

sinh :: Fold1 a b -> Fold1 a b #

cosh :: Fold1 a b -> Fold1 a b #

tanh :: Fold1 a b -> Fold1 a b #

asinh :: Fold1 a b -> Fold1 a b #

acosh :: Fold1 a b -> Fold1 a b #

atanh :: Fold1 a b -> Fold1 a b #

log1p :: Fold1 a b -> Fold1 a b #

expm1 :: Fold1 a b -> Fold1 a b #

log1pexp :: Fold1 a b -> Fold1 a b #

log1mexp :: Fold1 a b -> Fold1 a b #

Num b => Num (Fold1 a b) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

(+) :: Fold1 a b -> Fold1 a b -> Fold1 a b #

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

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

negate :: Fold1 a b -> Fold1 a b #

abs :: Fold1 a b -> Fold1 a b #

signum :: Fold1 a b -> Fold1 a b #

fromInteger :: Integer -> Fold1 a b #

Fractional b => Fractional (Fold1 a b) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

(/) :: Fold1 a b -> Fold1 a b -> Fold1 a b #

recip :: Fold1 a b -> Fold1 a b #

fromRational :: Rational -> Fold1 a b #

Folding

fold1 :: Foldable1 f => Fold1 a b -> f a -> b Source #

Apply a strict left Fold1 to a NonEmpty list

Conversion between Fold and Fold1

fromFold :: Fold a b -> Fold1 a b Source #

Promote any Fold to an equivalent Fold1

toFold :: Fold1 a b -> Fold a (Maybe b) Source #

Promote any Fold1 to an equivalent Fold

Folds

sconcat :: Semigroup a => Fold1 a a Source #

Fold all values within a non-empty container using (<>)

head :: Fold1 a a Source #

Get the first element of a non-empty container

last :: Fold1 a a Source #

Get the last element of a non-empty container

maximum :: Ord a => Fold1 a a Source #

Computes the maximum element

maximumBy :: (a -> a -> Ordering) -> Fold1 a a Source #

Computes the maximum element with respect to the given comparison function

minimum :: Ord a => Fold1 a a Source #

Computes the minimum element

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

newtype FromMaybe b Source #

instance Monad m => Semigroup (FromMaybe m a) where
    mappend (FromMaybe f) (FromMaybe g) = FromMaybeM (f . Just . g)

Constructors

FromMaybe 

Fields

Instances

Instances details
Semigroup (FromMaybe b) Source # 
Instance details

Defined in Control.Foldl.NonEmpty

Methods

(<>) :: FromMaybe b -> FromMaybe b -> FromMaybe b #

sconcat :: NonEmpty (FromMaybe b) -> FromMaybe b #

stimes :: Integral b0 => b0 -> FromMaybe b -> FromMaybe b #

type Handler1 a b = forall x. (b -> Const (Dual (FromMaybe x)) b) -> a -> Const (Dual (FromMaybe x)) a Source #

A handler for the upstream input of a Fold1

This is compatible with van Laarhoven optics as defined in the lens package. Any lens, fold1 or traversal1 will type-check as a Handler1.

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

folded1 :: (Contravariant f, Apply f, Foldable1 t) => (a -> f a) -> t a -> f (t a) Source #

handles folded1 :: Foldable1 t => Fold1 a r -> Fold1 (t a) r