Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Data.NonEmpty
Synopsis
- data T (f :: Type -> Type) a = Cons {}
- (!:) :: a -> f a -> T f a
- force :: forall (f :: Type -> Type) a. T f a -> T f a
- apply :: forall (f :: Type -> Type) a b. (Applicative f, Cons f, Append f) => T f (a -> b) -> T f a -> T f b
- bind :: forall (f :: Type -> Type) a b. (Monad f, Cons f, Append f) => T f a -> (a -> T f b) -> T f b
- toList :: forall (f :: Type -> Type) a. Foldable f => T f a -> [a]
- flatten :: Cons f => T f a -> f a
- fetch :: ViewL f => f a -> Maybe (T f a)
- cons :: a -> f a -> T f a
- snoc :: Traversable f => f a -> a -> T f a
- singleton :: forall (f :: Type -> Type) a. Empty f => a -> T f a
- reverse :: forall (f :: Type -> Type) a. (Traversable f, Reverse f) => T f a -> T f a
- mapHead :: forall a (f :: Type -> Type). (a -> a) -> T f a -> T f a
- mapTail :: (f a -> g a) -> T f a -> T g a
- viewL :: T f a -> (a, f a)
- viewR :: Traversable f => T f a -> (f a, a)
- init :: Traversable f => T f a -> f a
- last :: forall (f :: Type -> Type) a. Foldable f => T f a -> a
- foldl1 :: forall (f :: Type -> Type) a. Foldable f => (a -> a -> a) -> T f a -> a
- foldl1Map :: forall (f :: Type -> Type) b a. Foldable f => (b -> b -> b) -> (a -> b) -> T f a -> b
- foldBalanced :: (a -> a -> a) -> T [] a -> a
- foldBalancedStrict :: (a -> a -> a) -> T [] a -> a
- maximum :: forall a (f :: Type -> Type). (Ord a, Foldable f) => T f a -> a
- maximumBy :: forall (f :: Type -> Type) a. Foldable f => (a -> a -> Ordering) -> T f a -> a
- maximumKey :: forall b (f :: Type -> Type) a. (Ord b, Foldable f) => (a -> b) -> T f a -> a
- minimum :: forall a (f :: Type -> Type). (Ord a, Foldable f) => T f a -> a
- minimumBy :: forall (f :: Type -> Type) a. Foldable f => (a -> a -> Ordering) -> T f a -> a
- minimumKey :: forall b (f :: Type -> Type) a. (Ord b, Foldable f) => (a -> b) -> T f a -> a
- sum :: forall a (f :: Type -> Type). (Num a, Foldable f) => T f a -> a
- product :: forall a (f :: Type -> Type). (Num a, Foldable f) => T f a -> a
- chop :: (a -> Bool) -> [a] -> T [] [a]
- append :: forall (f :: Type -> Type) a. (Append f, Traversable f) => T f a -> T f a -> T (T f) a
- appendLeft :: (Append f, Traversable f) => f a -> T f a -> T f a
- appendRight :: Append f => T f a -> f a -> T f a
- cycle :: forall (f :: Type -> Type) a. (Cons f, Append f) => T f a -> T f a
- zipWith :: forall (f :: Type -> Type) a b c. Zip f => (a -> b -> c) -> T f a -> T f b -> T f c
- mapAdjacent :: Traversable f => (a -> a -> b) -> T f a -> f b
- class Insert (f :: Type -> Type) where
- insertDefault :: (Ord a, InsertBy f, SortBy f) => a -> f a -> T f a
- class Insert f => InsertBy (f :: Type -> Type) where
- scanl :: Traversable f => (b -> a -> b) -> b -> f a -> T f b
- scanr :: Traversable f => (a -> b -> b) -> b -> f a -> T f b
- tails :: (Traversable f, Cons g, Empty g) => f a -> T f (g a)
- inits :: (Traversable f, Snoc g, Empty g) => f a -> T f (g a)
- initsRev :: (Traversable f, Cons g, Empty g, Reverse g) => f a -> T f (g a)
- removeEach :: Traversable f => T f a -> T f (a, f a)
- takeUntil :: (a -> Bool) -> T [] a -> T [] a
- partitionEithersLeft :: T [] (Either a b) -> Either (T [] a) ([a], T [] b)
- partitionEithersRight :: T [] (Either a b) -> Either (T [] a, [b]) (T [] b)
Documentation
data T (f :: Type -> Type) a Source #
The type T
can be used for many kinds of list-like structures
with restrictions on the size.
T [] a
is a lazy list containing at least one element.T (T []) a
is a lazy list containing at least two elements.T Vector a
is a vector with at least one element. You may also use unboxed vectors but the first element will be stored in a box and you will not be able to use many functions from this module.T Maybe a
is a list that contains one or two elements.Maybe
is isomorphic toOptional Empty
.T Empty a
is a list that contains exactly one element.T (T Empty) a
is a list that contains exactly two elements.Optional (T Empty) a
is a list that contains zero or two elements.- You can create a list type for every finite set of allowed list length
by nesting Optional and NonEmpty constructors.
If list length
n
is allowed, then placeOptional
at depthn
, if it is disallowed then placeNonEmpty
. The maximum length is marked byEmpty
.
Instances
Foldable f => Foldable (T f) Source # | |
Defined in Data.NonEmptyPrivate Methods fold :: Monoid m => T f m -> m # foldMap :: Monoid m => (a -> m) -> T f a -> m # foldMap' :: Monoid m => (a -> m) -> T f a -> m # foldr :: (a -> b -> b) -> b -> T f a -> b # foldr' :: (a -> b -> b) -> b -> T f a -> b # foldl :: (b -> a -> b) -> b -> T f a -> b # foldl' :: (b -> a -> b) -> b -> T f a -> b # foldr1 :: (a -> a -> a) -> T f a -> a # foldl1 :: (a -> a -> a) -> T f a -> a # elem :: Eq a => a -> T f a -> Bool # maximum :: Ord a => T f a -> a # | |
Traversable f => Traversable (T f) Source # | |
(Applicative f, Empty f, Cons f, Append f) => Applicative (T f) Source # | |
Functor f => Functor (T f) Source # | |
(Monad f, Empty f, Cons f, Append f) => Monad (T f) Source # | |
(Cons f, Append f) => Append (T f) Source # | |
Arbitrary f => Arbitrary (T f) Source # | |
Cons f => Cons (T f) Source # | |
Gen f => Gen (T f) Source # | |
Iterate f => Iterate (T f) Source # | |
Defined in Data.NonEmptyPrivate | |
Ix f => Ix (T f) Source # | forRange $ \b0 -> forRange $ \b1 -> forRange $ \b2 -> let b = FuncHT.unzip $ b0!:b1!:b2!:Empty.Cons in map (Ix.index b) (Ix.range b) == take (Ix.rangeSize b) [0..] |
Defined in Data.NonEmptyPrivate Methods range :: Ix i => (T f i, T f i) -> [T f i] Source # index :: Ix i => (T f i, T f i) -> T f i -> Int Source # inRange :: Ix i => (T f i, T f i) -> T f i -> Bool Source # rangeSize :: Ix i => (T f i, T f i) -> Int Source # rangeSizeIndex :: Ix i => (T f i, T f i) -> (Int, T f i -> Int) Source # indexHorner :: Ix i => (T f i, T f i) -> Int -> T f i -> Int Source # | |
NFData f => NFData (T f) Source # | |
Repeat f => Repeat (T f) Source # | |
Defined in Data.NonEmptyPrivate | |
(Traversable f, Reverse f) => Reverse (T f) Source # | |
Show f => Show (T f) Source # | |
Empty f => Singleton (T f) Source # | |
Defined in Data.NonEmptyPrivate | |
Snoc f => Snoc (T f) Source # | |
(Sort f, InsertBy f) => Sort (T f) Source # | If you nest too many non-empty lists then the efficient merge-sort (linear-logarithmic runtime) will degenerate to an inefficient insert-sort (quadratic runtime). |
(SortBy f, InsertBy f) => SortBy (T f) Source # | |
ViewL f => ViewL (T f) Source # | Caution:
This instance mainly exist to allow cascaded applications of |
Zip f => Zip (T f) Source # | |
Choose f => Choose (T f) Source # | |
Defined in Data.NonEmpty.Mixed | |
Insert f => Insert (T f) Source # | |
InsertBy f => InsertBy (T f) Source # | |
(Arbitrary a, Arbitrary f) => Arbitrary (T f a) Source # | |
(Ix f, Ix i, Ord (f i)) => Ix (T f i) Source # | |
(Show f, Show a) => Show (T f a) Source # | |
(NFData f, NFData a) => NFData (T f a) Source # | |
Defined in Data.NonEmptyPrivate | |
(Eq a, Eq (f a)) => Eq (T f a) Source # | |
(Ord a, Ord (f a)) => Ord (T f a) Source # | |
apply :: forall (f :: Type -> Type) a b. (Applicative f, Cons f, Append f) => T f (a -> b) -> T f a -> T f b Source #
bind :: forall (f :: Type -> Type) a b. (Monad f, Cons f, Append f) => T f a -> (a -> T f b) -> T f b Source #
snoc :: Traversable f => f a -> a -> T f a Source #
viewR :: Traversable f => T f a -> (f a, a) Source #
init :: Traversable f => T f a -> f a Source #
foldl1Map :: forall (f :: Type -> Type) b a. Foldable f => (b -> b -> b) -> (a -> b) -> T f a -> b Source #
foldBalanced :: (a -> a -> a) -> T [] a -> a Source #
Fold a non-empty list in a balanced way.
Balanced means that each element
has approximately the same depth in the operator tree.
Approximately the same depth means
that the difference between maximum and minimum depth is at most 1.
The accumulation operation must be associative and commutative
in order to get the same result as foldl1
or foldr1
.
foldBalancedStrict :: (a -> a -> a) -> T [] a -> a Source #
maximum :: forall a (f :: Type -> Type). (Ord a, Foldable f) => T f a -> a Source #
maximum is a total function
maximumBy :: forall (f :: Type -> Type) a. Foldable f => (a -> a -> Ordering) -> T f a -> a Source #
maximumBy is a total function
maximumKey :: forall b (f :: Type -> Type) a. (Ord b, Foldable f) => (a -> b) -> T f a -> a Source #
maximumKey is a total function
minimum :: forall a (f :: Type -> Type). (Ord a, Foldable f) => T f a -> a Source #
minimum is a total function
minimumBy :: forall (f :: Type -> Type) a. Foldable f => (a -> a -> Ordering) -> T f a -> a Source #
minimumBy is a total function
minimumKey :: forall b (f :: Type -> Type) a. (Ord b, Foldable f) => (a -> b) -> T f a -> a Source #
minimumKey is a total function
sum :: forall a (f :: Type -> Type). (Num a, Foldable f) => T f a -> a Source #
sum does not need a zero for initialization
product :: forall a (f :: Type -> Type). (Num a, Foldable f) => T f a -> a Source #
product does not need a one for initialization
append :: forall (f :: Type -> Type) a. (Append f, Traversable f) => T f a -> T f a -> T (T f) a infixr 5 Source #
appendLeft :: (Append f, Traversable f) => f a -> T f a -> T f a infixr 5 Source #
cycle :: forall (f :: Type -> Type) a. (Cons f, Append f) => T f a -> T f a Source #
generic variants:
cycle
or better Semigroup.cycle
zipWith :: forall (f :: Type -> Type) a b c. Zip f => (a -> b -> c) -> T f a -> T f b -> T f c Source #
mapAdjacent :: Traversable f => (a -> a -> b) -> T f a -> f b Source #
class Insert (f :: Type -> Type) where Source #
Methods
insert :: Ord a => a -> f a -> T f a Source #
Insert an element into an ordered list while preserving the order.
class Insert f => InsertBy (f :: Type -> Type) where Source #
scanl :: Traversable f => (b -> a -> b) -> b -> f a -> T f b Source #
scanr :: Traversable f => (a -> b -> b) -> b -> f a -> T f b Source #
inits :: (Traversable f, Snoc g, Empty g) => f a -> T f (g a) Source #
Only advised for structures with efficient appending of single elements
like Sequence
.
Alternatively you may consider initsRev
.
removeEach :: Traversable f => T f a -> T f (a, f a) Source #
takeUntil :: (a -> Bool) -> T [] a -> T [] a Source #
let takeUntil p xs = NonEmpty.zipWith const xs $ () !: void (takeWhile (not . p) $ NonEmpty.flatten xs) in \k xs -> takeUntil (>=k) xs == NonEmpty.takeUntil (>=(k::Int)) xs
partitionEithersLeft :: T [] (Either a b) -> Either (T [] a) ([a], T [] b) Source #
\xs -> mapMaybe EitherHT.maybeLeft (NonEmpty.flatten xs) == either NonEmpty.flatten fst (NonEmpty.partitionEithersLeft (xs::NonEmpty.T[](Either Char Int)))
\xs -> mapMaybe EitherHT.maybeRight (NonEmpty.flatten xs) == either (const []) (NonEmpty.flatten . snd) (NonEmpty.partitionEithersLeft (xs::NonEmpty.T[](Either Char Int)))
\xs -> NonEmpty.partitionEithersRight (fmap EitherHT.swap xs) == EitherHT.mapLeft swap (EitherHT.swap (NonEmpty.partitionEithersLeft (xs::NonEmpty.T[](Either Char Int))))