mono-traversable-0.4.0: Type classes for mapping, folding, and traversing monomorphic containers

Safe HaskellNone

Data.NonNull

Description

Warning, this is Experimental!

Data.NonNull attempts to extend the concepts from Data.List.NonEmpty to any MonoFoldable.

NonNull is a typeclass for a container with 1 or more elements. Data.List.NonEmpty and 'NotEmpty a' are members of the typeclass

Synopsis

Documentation

type NonNull mono = MinLen (Succ Zero) monoSource

fromNullable :: MonoFoldable mono => mono -> Maybe (NonNull mono)Source

safely convert a Nullable to a NonNull

nonNull :: MonoFoldable mono => mono -> NonNull monoSource

convert a Nullable with elements to a NonNull throw an exception if the Nullable is empty. do not use this unless you have proved your structure is non-null

toNullable :: NonNull mono -> monoSource

convert a NonNull to a Nullable

fromNonEmpty :: IsSequence seq => NonEmpty (Element seq) -> NonNull seqSource

safely construct a NonNull from a NonEmpty list

ncons :: SemiSequence seq => Element seq -> seq -> NonNull seqSource

Like cons, prepends an element. However, the prepend is to a Nullable, creating a NonNull

Generally this uses cons underneath. cons is not efficient for most data structures.

Alternatives: * if you don't need to cons, use fromNullable or nonNull if you can create your structure in one go. * if you need to cons, you might be able to start off with an efficient data structure such as a NonEmpty List. fronNonEmpty will convert that to your data structure using the structure's fromList function.

nuncons :: IsSequence seq => NonNull seq -> (Element seq, Maybe (NonNull seq))Source

splitFirst :: IsSequence seq => NonNull seq -> (Element seq, seq)Source

nfilter :: IsSequence seq => (Element seq -> Bool) -> NonNull seq -> seqSource

like filter, but starts with a NonNull

nfilterM :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> NonNull seq -> m seqSource

like filterM, but starts with a NonNull

nReplicate :: IsSequence seq => Index seq -> Element seq -> NonNull seqSource

i must be > 0. like replicate

i <= 0 is treated the same as providing 1

head :: MonoTraversable mono => MinLen (Succ nat) mono -> Element monoSource

tail :: IsSequence seq => NonNull seq -> seqSource

like Data.List, but not partial on a NonEmpty

last :: MonoTraversable mono => MinLen (Succ nat) mono -> Element monoSource

init :: IsSequence seq => NonNull seq -> seqSource

like Data.List, but not partial on a NonEmpty

ofoldMap1 :: (MonoFoldable mono, Semigroup m) => (Element mono -> m) -> MinLen (Succ nat) mono -> mSource

ofold1 :: (MonoFoldable mono, Semigroup (Element mono)) => MinLen (Succ nat) mono -> Element monoSource

ofoldr1 :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> MinLen (Succ nat) mono -> Element monoSource

ofoldl1' :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> MinLen (Succ nat) mono -> Element monoSource

A variant of 'ofoldl\'' that has no base case, and thus may only be applied to non-empty structures.

'foldl1\'' f = foldl1 f . otoList

maximum :: MonoFoldableOrd mono => MinLen (Succ nat) mono -> Element monoSource

like Data.List, but not partial on a MonoFoldable

maximumBy :: MonoFoldableOrd mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) mono -> Element monoSource

like Data.List, but not partial on a MonoFoldable

minimum :: MonoFoldableOrd mono => MinLen (Succ nat) mono -> Element monoSource

like Data.List, but not partial on a MonoFoldable

minimumBy :: MonoFoldableOrd mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) mono -> Element monoSource

like Data.List, but not partial on a MonoFoldable

(<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seqSource

Prepend an element to a NonNull