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

Primus.NonEmpty

Description

 
Synopsis

Documentation

data MLR a b Source #

represents an optional Either ie Maybe (Either (NonEmpty a) (NonEmpty b))

Constructors

MLRLeft !(NonEmpty a)

extra values on the left hand side

MLREqual

both values have the same length

MLRRight !(NonEmpty b)

extra values on the right hand side

Instances

Instances details
(Eq a, Eq b) => Eq (MLR a b) Source # 
Instance details

Defined in Primus.NonEmpty

Methods

(==) :: MLR a b -> MLR a b -> Bool #

(/=) :: MLR a b -> MLR a b -> Bool #

(Ord a, Ord b) => Ord (MLR a b) Source # 
Instance details

Defined in Primus.NonEmpty

Methods

compare :: MLR a b -> MLR a b -> Ordering #

(<) :: MLR a b -> MLR a b -> Bool #

(<=) :: MLR a b -> MLR a b -> Bool #

(>) :: MLR a b -> MLR a b -> Bool #

(>=) :: MLR a b -> MLR a b -> Bool #

max :: MLR a b -> MLR a b -> MLR a b #

min :: MLR a b -> MLR a b -> MLR a b #

(Show a, Show b) => Show (MLR a b) Source # 
Instance details

Defined in Primus.NonEmpty

Methods

showsPrec :: Int -> MLR a b -> ShowS #

show :: MLR a b -> String #

showList :: [MLR a b] -> ShowS #

zip

zipWithExtras1 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> (NonEmpty c, MLR a b) Source #

zips two nonempty lists together and puts any leftovers into MLR

zipWithExtras :: forall a b c. (a -> b -> c) -> [a] -> [b] -> ([c], MLR a b) Source #

zips two lists together and puts any leftovers into MLR

mlrOrdering :: MLR a b -> Ordering Source #

MLRLeft predicate

fromList1LR :: [a] -> Either String (NonEmpty a) Source #

conversion from list to a nonempty list

chunking

chunksOf1 :: Pos -> NonEmpty a -> NonEmpty (NonEmpty a) Source #

split a nonempty list into a nonempty list of nonempty chunks

chunksRange1 :: Pos -> Pos -> NonEmpty a -> NonEmpty (NonEmpty a) Source #

split a nonempty list into a nonempty list of nonempty chunks given a chunk size and how many to skip each iteration can decide the size of the chunks and how many elements to skip

chunkNLen :: forall t a u z. (Traversable t, Foldable u) => t z -> Pos -> u a -> Either String (t (NonEmpty a)) Source #

fills a container "tz" with chunks of size "len" must fill the container exactly

chunkNLen1 :: forall a u. Foldable u => Pos -> Pos -> u a -> Either String (NonEmpty (NonEmpty a)) Source #

creates a nonempty container of length "sz" with chunks of a given size: see chunkNLen must fill the container exactly

split

data Split1 a Source #

represents the status of a split a nonempty list

Constructors

SplitLT !Pos 
SplitEQ 
SplitGT !(NonEmpty a) 

Instances

Instances details
Eq a => Eq (Split1 a) Source # 
Instance details

Defined in Primus.NonEmpty

Methods

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

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

Ord a => Ord (Split1 a) Source # 
Instance details

Defined in Primus.NonEmpty

Methods

compare :: Split1 a -> Split1 a -> Ordering #

(<) :: Split1 a -> Split1 a -> Bool #

(<=) :: Split1 a -> Split1 a -> Bool #

(>) :: Split1 a -> Split1 a -> Bool #

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

max :: Split1 a -> Split1 a -> Split1 a #

min :: Split1 a -> Split1 a -> Split1 a #

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

Defined in Primus.NonEmpty

Methods

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

show :: Split1 a -> String #

showList :: [Split1 a] -> ShowS #

splitAt1 :: Pos -> NonEmpty a -> (NonEmpty a, [a]) Source #

splitAt for a nonempty list but doesnt guarantee the number of elements

splitAt1' :: forall a. Pos -> NonEmpty a -> (NonEmpty a, Split1 a) Source #

split a nonempty list preserving information about the split

splitAt1GE :: Pos -> NonEmpty a -> Either String (NonEmpty a, [a]) Source #

split a nonempty list but has to have enough elements else fails

splitAts1 :: Pos -> NonEmpty a -> NonEmpty (NonEmpty a) Source #

repeatedly split a nonempty list

splits1 :: forall a. NonEmpty a -> [(NonEmpty a, NonEmpty a)] Source #

break up a nonempty list into all possible pairs of nonempty lists

splits3 :: forall a. NonEmpty a -> NonEmpty ([a], a, [a]) Source #

break up a nonempty list into a nonempty list of three parts

partition

partition1 :: Foldable1 t => (a -> Bool) -> t a -> These (NonEmpty a) (NonEmpty a) Source #

partitionThese for a nonempty list

span

spanAdjacent1 :: (a -> a -> Bool) -> NonEmpty a -> (NonEmpty a, [a]) Source #

like span but applies the predicate to adjacent elements

breakAdjacent1 :: (a -> a -> Bool) -> NonEmpty a -> (NonEmpty a, [a]) Source #

like break but applies the predicate to adjacent elements

span1 :: Foldable1 t => (a -> Bool) -> t a -> These (NonEmpty a) (NonEmpty a) Source #

span for a nonempty list

break1 :: Foldable1 t => (a -> Bool) -> t a -> These (NonEmpty a) (NonEmpty a) Source #

break for a nonempty list

ascending order methods

data Seq1 a Source #

possible results for determining if a nonempty list is in ascending order

Constructors

S1Short !(NonEmpty a)

generated enumerable sequence is shorter than the original list

S1Fail !(a, a)

first mismatch

S1Ok

both sequences match

Instances

Instances details
Functor Seq1 Source # 
Instance details

Defined in Primus.NonEmpty

Methods

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

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

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

Defined in Primus.NonEmpty

Methods

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

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

Ord a => Ord (Seq1 a) Source # 
Instance details

Defined in Primus.NonEmpty

Methods

compare :: Seq1 a -> Seq1 a -> Ordering #

(<) :: Seq1 a -> Seq1 a -> Bool #

(<=) :: Seq1 a -> Seq1 a -> Bool #

(>) :: Seq1 a -> Seq1 a -> Bool #

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

max :: Seq1 a -> Seq1 a -> Seq1 a #

min :: Seq1 a -> Seq1 a -> Seq1 a #

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

Defined in Primus.NonEmpty

Methods

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

show :: Seq1 a -> String #

showList :: [Seq1 a] -> ShowS #

isSequence1 :: (Foldable1 t, Eq a, Enum a) => t a -> Bool Source #

predicate for an ascending nonempty list

isEnumAscending :: forall t a. (Foldable1 t, Eq a, Enum a) => t a -> Seq1 a Source #

shows the first failure or if the length of the enum is too short

seq1Ordering :: Seq1 a -> Ordering Source #

predicate for S1Short

isomorphisms

uncons1 :: forall a. NonEmpty a -> (a, [a]) Source #

uncons for a nonempty list

unsnoc1 :: forall a. NonEmpty a -> ([a], a) Source #

unsnoc for a nonempty list

consNonEmpty :: Iso (NonEmpty a) (NonEmpty b) (a, [a]) (b, [b]) Source #

cons iso from NonEmpty

snocNonEmpty :: Iso (NonEmpty a) (NonEmpty b) ([a], a) ([b], b) Source #

snoc iso from NonEmpty

positive specific functions

sumP :: Foldable1 t => t Pos -> Pos Source #

sum of nonempty list of Pos values

lengthP :: Foldable1 t => t a -> Pos Source #

length of nonempty list

fold unfold

foldMapM1 :: forall b m f a. (Semigroup b, Monad m, Foldable1 f) => (a -> m b) -> f a -> m b Source #

"foldMapM" for nonempty containers: uses Semigroup instead of Monoid

unfoldr1NE :: forall s a. (NonEmpty s -> (a, [s])) -> NonEmpty s -> NonEmpty a Source #

unfoldr for a nonempty list

will not terminate if the user keeps returning a larger [s] than received

unfoldrM1 :: Monad m => (s -> m (a, Maybe s)) -> s -> m (NonEmpty a) Source #

unfoldM for nonempty results

iterators

iterateMaybe1 :: (a -> Bool) -> (a -> a) -> a -> NonEmpty a Source #

iterateMaybe1' :: (a -> Maybe a) -> a -> NonEmpty a Source #

like iterate but allows termination using Maybe

iterateN1 :: Pos -> (a -> a) -> a -> NonEmpty a Source #

iterate "n" times

replicateP :: Pos -> a -> NonEmpty a Source #

generate a repeated nonempty list of values for a fixed size

miscellaneous

appendL1 :: [a] -> NonEmpty a -> NonEmpty a Source #

append a list with a nonempty list

appendR1 :: NonEmpty a -> [a] -> NonEmpty a Source #

append a nonempty list with a list

snoc1 :: Foldable t => t a -> a -> NonEmpty a Source #

snoc for a nonempty list

updateAt1 :: Pos -> (a -> a) -> NonEmpty a -> Maybe (NonEmpty a) Source #

update a value at an index starting at one

at1 :: Pos -> NonEmpty a -> Maybe a Source #

get a value at an index starting at one

setAt1 :: Pos -> a -> NonEmpty a -> Maybe (NonEmpty a) Source #

set a value at an index starting at one

units1 :: Pos -> NonEmpty () Source #

generate a nonempty list of units for a fixed size

unitsF :: forall l a. (IsList (l a), Item (l a) ~ ()) => Pos -> l a Source #

generate a nonempty list of units for a given container of the given size

lengthExact1 :: Pos -> NonEmpty a -> Either String (NonEmpty a) Source #

compares the length of a potentially infinite nonempty list with "n" and succeeds if they are the same

take1 :: Pos -> NonEmpty a -> NonEmpty a Source #

take for a nonempty list

sum1 :: (Foldable1 t, Num a) => t a -> a Source #

sum for a nonempty list

groupByAdjacent1 :: forall a. (a -> a -> Bool) -> NonEmpty a -> NonEmpty (NonEmpty a) Source #

groupBy1 but applies the predicate to adjacent elements

findDupsBy :: forall a c. Ord c => (a -> c) -> [a] -> ([NonEmpty (Int, a)], [(Int, a)]) Source #

partition duplicates elements together with their positiion

replicate1 :: Pos -> a -> NonEmpty a Source #

replicate for a nonempty list

replicate1M :: Applicative m => Pos -> m a -> m (NonEmpty a) Source #

replicateM for a nonempty list

nonemptySnoc :: ([a] -> a -> b) -> NonEmpty a -> b Source #

nonempty :: (a -> [a] -> b) -> NonEmpty a -> b Source #

nonempty' :: NonEmpty a -> (a -> [a] -> b) -> b Source #