primus-0.3.0.0: nonempty and positive functions
Copyright(c) Grant Weyburne 2022
LicenseBSD-3
Safe HaskellSafe-Inferred
LanguageHaskell2010

Primus.Fold

Description

 
Synopsis

fill a container

fillTraversable :: forall t a z. Traversable t => t z -> [a] -> Either String ([a], t a) Source #

fill a traversable with a list and fail if not enough data

fillTraversableExact :: forall f a z. Traversable f => f z -> [a] -> Either String (f a) Source #

fill a traversable with a list and fail if there are leftovers: see fillTraversable

traverseLR :: forall t a b c. Traversable t => (c -> a -> Either String (c, b)) -> c -> t a -> Either String (c, t b) Source #

traverse a container using StateLR

extended traversals with access to past and future input

histMapL :: Traversable t => ([a] -> [a] -> z -> a -> (z, b)) -> z -> t a -> (z, t b) Source #

left/right fold over a list giving the caller access state "z" (for finite containers only)

histMapR :: Traversable t => ([a] -> [a] -> z -> a -> (z, b)) -> z -> t a -> (z, t b) Source #

left/right fold over a list giving the caller access state "z" (for finite containers only)

histMapL' :: forall a b t. Traversable t => ([a] -> [a] -> a -> b) -> t a -> t b Source #

same as histMapL or histMapR but skips state

histMapR' :: forall a b t. Traversable t => ([a] -> [a] -> a -> b) -> t a -> t b Source #

same as histMapL or histMapR but skips state

change inside of a container

wrapL :: forall (g :: Type -> Type) a b. Traversable g => ([a] -> [b]) -> g a -> Either String (g b) Source #

run a function against the contents of the Foldable container as a list

wrap1 :: forall (g :: Type -> Type) a b. (Traversable g, Foldable1 g) => (NonEmpty a -> NonEmpty b) -> g a -> Either String (g b) Source #

run a function against the contents of the Foldable1 container as a nonempty list

fold and unfolds

pFoldR :: forall a b. ([a] -> [a] -> b -> a -> b) -> b -> [a] -> b Source #

left/right fold that gives access to past input (reverse order) and future input

pFoldL :: forall a b. ([a] -> [a] -> b -> a -> b) -> b -> [a] -> b Source #

left/right fold that gives access to past input (reverse order) and future input

unfoldl :: forall s a. (s -> Maybe (a, s)) -> s -> [a] Source #

like unfoldr but reverses the order of the list

unfoldrM :: forall m s a. Monad m => (s -> m (Maybe (a, s))) -> s -> m [a] Source #

monadic unfoldr

unfoldlM :: forall m s a. Monad m => (s -> m (Maybe (a, s))) -> s -> m [a] Source #

monadic unfoldl

zip

zipExtrasT :: forall a b t. Traversable t => t a -> t b -> t (These a b) Source #

have to call a second time if the left container is bigger than the right one

zipExtrasRight :: forall a b t. Traversable t => [a] -> t b -> ([a], t (These a b)) Source #

zip a foldable into a traversable container and return any leftovers

zipWithExact :: forall t u a b c. (Traversable t, Foldable u) => (a -> b -> c) -> t a -> u b -> Either String (t c) Source #

splits a container "u" into parts of length "len" and fills container "t"

zipExact :: forall t u a b. (Traversable t, Foldable u) => t a -> u b -> Either String (t (a, b)) Source #

zipWithT :: (Applicative f, Traversable t, Applicative t) => (a -> b -> f c) -> t a -> t b -> f (t c) Source #

zipWith with an Applicative result

compare container lengths

data CLCount b Source #

difference between two foldables but quick exit if lhs is larger than rhs

Constructors

CError !String

error

CLT !(NonEmpty b)

leftovers from rhs: ie lhs is smaller than rhs

CEQ

same size

CGT

lhs is larger than rhs

Instances

Instances details
Functor CLCount Source # 
Instance details

Defined in Primus.Fold

Methods

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

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

Foldable CLCount Source # 
Instance details

Defined in Primus.Fold

Methods

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

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

foldMap' :: Monoid m => (a -> m) -> CLCount a -> m #

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

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

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

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

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

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

toList :: CLCount a -> [a] #

null :: CLCount a -> Bool #

length :: CLCount a -> Int #

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

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

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

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

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

Traversable CLCount Source # 
Instance details

Defined in Primus.Fold

Methods

traverse :: Applicative f => (a -> f b) -> CLCount a -> f (CLCount b) #

sequenceA :: Applicative f => CLCount (f a) -> f (CLCount a) #

mapM :: Monad m => (a -> m b) -> CLCount a -> m (CLCount b) #

sequence :: Monad m => CLCount (m a) -> m (CLCount a) #

Eq b => Eq (CLCount b) Source # 
Instance details

Defined in Primus.Fold

Methods

(==) :: CLCount b -> CLCount b -> Bool #

(/=) :: CLCount b -> CLCount b -> Bool #

Ord b => Ord (CLCount b) Source # 
Instance details

Defined in Primus.Fold

Methods

compare :: CLCount b -> CLCount b -> Ordering #

(<) :: CLCount b -> CLCount b -> Bool #

(<=) :: CLCount b -> CLCount b -> Bool #

(>) :: CLCount b -> CLCount b -> Bool #

(>=) :: CLCount b -> CLCount b -> Bool #

max :: CLCount b -> CLCount b -> CLCount b #

min :: CLCount b -> CLCount b -> CLCount b #

Show b => Show (CLCount b) Source # 
Instance details

Defined in Primus.Fold

Methods

showsPrec :: Int -> CLCount b -> ShowS #

show :: CLCount b -> String #

showList :: [CLCount b] -> ShowS #

compareLength :: forall t u a b. (Foldable t, Foldable u) => t a -> u b -> CLCount b Source #

compare length where lhs or rhs can be infinite but not both

compareLengthBy :: forall t u a b. (Foldable t, Foldable u) => (Int -> a -> b -> Maybe String) -> t a -> u b -> CLCount b Source #

compare length where lhs or rhs can be infinite but not both

compareLengths :: forall a b t u. (Foldable t, Foldable u) => t a -> [u b] -> [CLCount b] Source #

compare lengths of foldables

clOrdering :: CLCount b -> Maybe Ordering Source #

predicate for CEQ

pad containers

padR :: forall t a. Traversable t => t a -> [a] -> Either String (t a) Source #

pad fill "as" to the right or left with values from "zs"

padL :: forall t a. Traversable t => t a -> [a] -> Either String (t a) Source #

pad fill "as" to the right or left with values from "zs"

chunking

chunkN :: forall t s b z. Traversable t => (s -> Either String (s, b)) -> t z -> s -> Either String (s, t b) Source #

fills a container with chunks using a user supplied unfold function

chunkN' :: forall t a u b z. (Traversable t, Foldable u) => (u a -> Either String (u a, b)) -> t z -> u a -> Either String (t b) Source #

similar to chunkN but "s" is restricted to a foldable: if there is data left then will fail

scan

postscanl :: Traversable f => (b -> a -> b) -> b -> f a -> f b Source #

scanl for a traversable that drops the first value

postscanr :: Traversable f => (a -> b -> b) -> b -> f a -> f b Source #

scanr for a traversable that drops the last value

miscellaneous

initsT :: forall a t. Traversable t => t a -> t (NonEmpty a) Source #

inits for a traversable container

tailsT :: forall a t. Traversable t => t a -> t (NonEmpty a) Source #

tails for a traversable container

reverseT :: forall a t. Traversable t => t a -> t a Source #

reverse for a traversable container

sortByT :: forall a t. Traversable t => (a -> a -> Ordering) -> t a -> t a Source #

sortBy for a traversable container

unzipF :: Functor f => f (a, b) -> (f a, f b) Source #

unzip for a functor of pairs

reverseF :: Foldable t => t a -> [a] Source #

reverse a foldable