Safe Haskell | None |
---|---|
Language | Haskell2010 |
Data.NonNull extends the concepts from
Data.List.NonEmpty to any MonoFoldable
.
NonNull
is a newtype wrapper for a container with 1 or more elements.
Synopsis
- data NonNull mono
- fromNullable :: MonoFoldable mono => mono -> Maybe (NonNull mono)
- impureNonNull :: MonoFoldable mono => mono -> NonNull mono
- nonNull :: MonoFoldable mono => mono -> NonNull mono
- toNullable :: NonNull mono -> mono
- fromNonEmpty :: IsSequence seq => NonEmpty (Element seq) -> NonNull seq
- toNonEmpty :: MonoFoldable mono => NonNull mono -> NonEmpty (Element mono)
- ncons :: SemiSequence seq => Element seq -> seq -> NonNull seq
- nuncons :: IsSequence seq => NonNull seq -> (Element seq, Maybe (NonNull seq))
- splitFirst :: IsSequence seq => NonNull seq -> (Element seq, seq)
- nfilter :: IsSequence seq => (Element seq -> Bool) -> NonNull seq -> seq
- nfilterM :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> NonNull seq -> m seq
- nReplicate :: IsSequence seq => Index seq -> Element seq -> NonNull seq
- head :: MonoFoldable mono => NonNull mono -> Element mono
- tail :: IsSequence seq => NonNull seq -> seq
- last :: MonoFoldable mono => NonNull mono -> Element mono
- init :: IsSequence seq => NonNull seq -> seq
- ofoldMap1 :: (MonoFoldable mono, Semigroup m) => (Element mono -> m) -> NonNull mono -> m
- ofold1 :: (MonoFoldable mono, Semigroup (Element mono)) => NonNull mono -> Element mono
- ofoldr1 :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> NonNull mono -> Element mono
- ofoldl1' :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> NonNull mono -> Element mono
- maximum :: (MonoFoldable mono, Ord (Element mono)) => NonNull mono -> Element mono
- maximumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> NonNull mono -> Element mono
- minimum :: (MonoFoldable mono, Ord (Element mono)) => NonNull mono -> Element mono
- minimumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> NonNull mono -> Element mono
- (<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seq
- toMinList :: NonEmpty a -> NonNull [a]
- mapNonNull :: (Functor f, MonoFoldable (f b)) => (a -> b) -> NonNull (f a) -> NonNull (f b)
- class MonoFoldable mono => GrowingAppend mono
Documentation
A monomorphic container that is not null.
Instances
fromNullable :: MonoFoldable mono => mono -> Maybe (NonNull mono) Source #
Safely convert from an unsafe monomorphic container to a safe non-null monomorphic container.
impureNonNull :: MonoFoldable mono => mono -> NonNull mono Source #
Unsafely convert from an unsafe monomorphic container to a safe non-null monomorphic container.
Throws an exception if the monomorphic container is empty.
Since: 1.0.0
nonNull :: MonoFoldable mono => mono -> NonNull mono Source #
Deprecated: Please use the more explicit impureNonNull instead
Old synonym for impureNonNull
toNullable :: NonNull mono -> mono Source #
Safely convert from a non-null monomorphic container to a nullable monomorphic container.
fromNonEmpty :: IsSequence seq => NonEmpty (Element seq) -> NonNull seq Source #
Safely convert from a NonEmpty
list to a non-null monomorphic container.
toNonEmpty :: MonoFoldable mono => NonNull mono -> NonEmpty (Element mono) Source #
Safely convert from a NonNull
container to a NonEmpty
list.
Since: 1.0.15.0
ncons :: SemiSequence seq => Element seq -> seq -> NonNull seq Source #
Prepend an element to a SemiSequence
, creating a non-null SemiSequence
.
Generally this uses cons underneath. cons is not efficient for most data structures.
Alternatives:
- if you don't need to cons, use
fromNullable
ornonNull
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 #
Extract the first element of a sequnce and the rest of the non-null sequence if it exists.
splitFirst :: IsSequence seq => NonNull seq -> (Element seq, seq) Source #
Same as nuncons
with no guarantee that the rest of the sequence is non-null.
nfilter :: IsSequence seq => (Element seq -> Bool) -> NonNull seq -> seq Source #
Equivalent to Data.Sequences.
,
but works on non-nullable sequences.filter
nfilterM :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> NonNull seq -> m seq Source #
Equivalent to Data.Sequences.
,
but works on non-nullable sequences.filterM
nReplicate :: IsSequence seq => Index seq -> Element seq -> NonNull seq Source #
tail :: IsSequence seq => NonNull seq -> seq Source #
Safe version of tailEx
, only working on non-nullable sequences.
init :: IsSequence seq => NonNull seq -> seq Source #
Safe version of initEx
, only working on non-nullable sequences.
ofoldMap1 :: (MonoFoldable mono, Semigroup m) => (Element mono -> m) -> NonNull mono -> m Source #
Map each element of a monomorphic container to a semigroup, and combine the results.
Safe version of ofoldMap1Ex
, only works on monomorphic containers wrapped in a
NonNull
.
Examples
ofoldr1 :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> NonNull mono -> Element mono Source #
ofoldl1' :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> NonNull mono -> Element mono Source #
maximumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> NonNull mono -> Element mono Source #
Get the maximum element of a monomorphic container, using a supplied element ordering function.
Safe version of maximumByEx
, only works on monomorphic containers wrapped in a
NonNull
.
minimumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> NonNull mono -> Element mono Source #
Get the minimum element of a monomorphic container, using a supplied element ordering function.
Safe version of minimumByEx
, only works on monomorphic containers wrapped in a
NonNull
.
(<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seq infixr 5 Source #
Prepend an element to a non-null SemiSequence
.
mapNonNull :: (Functor f, MonoFoldable (f b)) => (a -> b) -> NonNull (f a) -> NonNull (f b) Source #
class MonoFoldable mono => GrowingAppend mono Source #
Containers which, when two values are combined, the combined length is no less than the larger of the two inputs. In code:
olength (x <> y) >= max (olength x) (olength y)
This class has no methods, and is simply used to assert that this law holds, in order to provide guarantees of correctness (see, for instance, Data.NonNull).
This should have a Semigroup
superclass constraint, however, due to
Semigroup
only recently moving to base, some packages do not provide
instances.