mono-traversable-0.2.0.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 NonEmpty to any IsSequence.

NonNull is for a sequence with 1 or more elements. Stream is for a NonNull that supports efficient modification of the front of the sequence.

This code is experimental and likely to change dramatically and future versions. Please send your feedback.

Synopsis

Documentation

class (SemiSequence seq, IsSequence (Nullable seq), Element seq ~ Element (Nullable seq)) => NonNull seq whereSource

a NonNull sequence has 1 or more items In contrast, IsSequence is allowed to have zero items.

Any NonNull functions that decreases the number of elements in the sequences will return a different Nullable type.

The Nullable type for a NonEmpty List is the normal List '[]'

NonNull allows one to safely perform what would otherwise be partial functions. Hopefully you have abandoned partial functions, perhaps you are using the safe package. However, safe essentially provides convenience functions for null checking. With NonNull rather than always reacting with null checks we can proactively encode in our program when we know that a type is NonNull. Now we have an invariant encoded in our types, making our program easier to understand. This information is leveraged to avoid awkward null checking later on.

Associated Types

type Nullable seq Source

Methods

fromNonEmpty :: NonEmpty (Element seq) -> seqSource

safely construct a NonNull sequence from a NonEmpty list

fromNullable :: Nullable seq -> Maybe seqSource

safely convert a Nullable to a NonNull

nonNull :: Nullable seq -> seqSource

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 :: seq -> Nullable seqSource

used internally to construct a NonNull. does not check whether the Nullable is empty do not use this unless you have proved your structure is nonNull nonNullUnsafe :: Nullable seq -> seq

convert a NonNull to a Nullable

ncons :: Element seq -> Nullable seq -> 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 :: seq -> (Element seq, Maybe seq)Source

splitFirst :: seq -> (Element seq, Nullable seq)Source

nfilter :: (Element seq -> Bool) -> seq -> Nullable seqSource

like filter, but starts with a NonNull

nfilterM :: Monad m => (Element seq -> m Bool) -> seq -> m (Nullable seq)Source

like filterM, but starts with a NonNull

nReplicate :: Index seq -> Element seq -> seqSource

i must be > 0. like replicate

Instances

NonNull (NonEmpty a)

NonNull list reuses NonEmpty

IsSequence seq => NonNull (NotEmpty seq) 

class SafeSequence seq whereSource

SafeSequence contains functions that would be partial on a Nullable

Methods

head :: seq -> Element seqSource

like Data.List, but not partial on a NonEmpty

tail :: seq -> Nullable seqSource

like Data.List, but not partial on a NonEmpty

last :: seq -> Element seqSource

like Data.List, but not partial on a NonEmpty

init :: seq -> Nullable seqSource

like Data.List, but not partial on a NonEmpty

class (NonNull seq, MonoFoldable (Nullable seq)) => MonoFoldable1 seq whereSource

fold operations that assume one or more elements Guaranteed to be safe on a NonNull

Methods

ofoldMap1 :: Semigroup m => (Element seq -> m) -> seq -> mSource

ofoldr1 :: (Element seq -> Element seq -> Element seq) -> seq -> Element seqSource

ofoldl1' :: (Element seq -> Element seq -> Element seq) -> seq -> Element seqSource

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

'foldl1\'' f = foldl1 f . otoList

Instances

class (MonoFoldable1 seq, OrdSequence (Nullable seq)) => OrdNonNull seq whereSource

Methods

maximum :: seq -> Element seqSource

like Data.List, but not partial on a NonNull

minimum :: seq -> Element seqSource

like Data.List, but not partial on a NonNull

maximumBy :: (Element seq -> Element seq -> Ordering) -> seq -> Element seqSource

like Data.List, but not partial on a NonNull

minimumBy :: (Element seq -> Element seq -> Ordering) -> seq -> Element seqSource

like Data.List, but not partial on a NonNull

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

Prepend an element to a NonNull