mono-traversable-0.3.0.3: 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

class (MonoFoldable mono, MonoFoldable (Nullable mono), Element mono ~ Element (Nullable mono)) => NonNull mono whereSource

a NonNull has 1 or more items

In contrast, MonoFoldable 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 mono Source

Methods

fromNullable :: Nullable mono -> Maybe monoSource

safely convert a Nullable to a NonNull

nonNull :: Nullable mono -> 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 :: mono -> Nullable monoSource

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

Instances

NonNull (NonEmpty a)

NonNull list reuses NonEmpty

MonoFoldable seq => NonNull (NotEmpty seq) 

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

safely construct a NonNull from a NonEmpty list

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

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

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

like filter, but starts with a NonNull

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

like filterM, but starts with a NonNull

nReplicate :: (NonNull seq, Num (Index (Nullable seq)), Ord (Index (Nullable seq)), IsSequence (Nullable seq)) => Index (Nullable seq) -> Element seq -> seqSource

i must be > 0. like replicate

i <= 0 is treated the same as providing 1

head :: (MonoFoldable (Nullable seq), NonNull seq) => seq -> Element seqSource

like Data.List, but not partial on a NonEmpty

tail :: (IsSequence (Nullable seq), NonNull seq) => seq -> Nullable seqSource

like Data.List, but not partial on a NonEmpty

last :: (MonoFoldable (Nullable seq), NonNull seq) => seq -> Element seqSource

like Data.List, but not partial on a NonEmpty

init :: (IsSequence (Nullable seq), NonNull seq) => seq -> Nullable seqSource

like Data.List, but not partial on a NonEmpty

data NotEmpty seq Source

a newtype wrapper indicating there are 1 or more elements unwrap with toNullable

Instances

Functor NotEmpty 
Typeable1 NotEmpty 
Eq seq => Eq (NotEmpty seq) 
Data seq => Data (NotEmpty seq) 
Ord seq => Ord (NotEmpty seq) 
Read seq => Read (NotEmpty seq) 
Show seq => Show (NotEmpty seq) 
Monoid seq => Semigroup (NotEmpty seq) 
MonoTraversable seq => MonoTraversable (NotEmpty seq) 
MonoFoldable seq => MonoFoldable (NotEmpty seq) 
MonoFunctor seq => MonoFunctor (NotEmpty seq) 
SemiSequence seq => SemiSequence (NotEmpty seq) 
MonoFoldable seq => NonNull (NotEmpty seq) 

asNotEmpty :: NotEmpty a -> NotEmpty aSource

Helper functions for type inferences.

Since 0.3.0

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

ofold1 :: (NonNull seq, Semigroup (Element seq)) => seq -> Element seqSource

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

ofoldl1' :: NonNull seq => (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

maximum :: (MonoFoldableOrd (Nullable seq), NonNull seq) => seq -> Element seqSource

like Data.List, but not partial on a NonNull

maximumBy :: (MonoFoldableOrd (Nullable seq), NonNull seq) => (Element seq -> Element seq -> Ordering) -> seq -> Element seqSource

like Data.List, but not partial on a NonNull

minimum :: (MonoFoldableOrd (Nullable seq), NonNull seq) => seq -> Element seqSource

like Data.List, but not partial on a NonNull

minimumBy :: (MonoFoldableOrd (Nullable seq), NonNull seq) => (Element seq -> Element seq -> Ordering) -> seq -> Element seqSource

like Data.List, but not partial on a NonNull

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

Prepend an element to a NonNull