Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type NonNull mono = MinLen (Succ Zero) mono
- fromNullable :: MonoFoldable mono => mono -> Maybe (NonNull mono)
- nonNull :: MonoFoldable mono => mono -> NonNull mono
- toNullable :: NonNull mono -> mono
- fromNonEmpty :: IsSequence seq => NonEmpty (Element seq) -> NonNull seq
- 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 => MinLen (Succ nat) mono -> Element mono
- tail :: IsSequence seq => NonNull seq -> seq
- last :: MonoFoldable mono => MinLen (Succ nat) mono -> Element mono
- init :: IsSequence seq => NonNull seq -> seq
- ofoldMap1 :: (MonoFoldable mono, Semigroup m) => (Element mono -> m) -> MinLen (Succ nat) mono -> m
- ofold1 :: (MonoFoldable mono, Semigroup (Element mono)) => MinLen (Succ nat) mono -> Element mono
- ofoldr1 :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> MinLen (Succ nat) mono -> Element mono
- ofoldl1' :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> MinLen (Succ nat) mono -> Element mono
- maximum :: MonoFoldableOrd mono => MinLen (Succ nat) mono -> Element mono
- maximumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) mono -> Element mono
- minimum :: MonoFoldableOrd mono => MinLen (Succ nat) mono -> Element mono
- minimumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) mono -> Element mono
- (<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seq
- toMinList :: NonEmpty a -> NonNull [a]
Documentation
fromNullable :: MonoFoldable mono => mono -> Maybe (NonNull mono) Source
Safely convert from an unsafe monomorphic container to a safe non-null monomorphic container.
nonNull :: 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.
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.
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.Sequence.
,
but works on non-nullable sequences.filter
nfilterM :: (Monad m, IsSequence seq) => (Element seq -> m Bool) -> NonNull seq -> m seq Source
Equivalent to Data.Sequence.
,
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) -> MinLen (Succ nat) 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
.MinLen
(Succ
nat)
Examples
> let xs = ("hello", 1 ::Integer
) `mlcons` (" world", 2) `mlcons` (toMinLenZero
[]) >ofoldMap1
fst
xs "hello world"
ofold1 :: (MonoFoldable mono, Semigroup (Element mono)) => MinLen (Succ nat) mono -> Element mono Source
ofoldr1 :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> MinLen (Succ nat) mono -> Element mono Source
Right-associative fold of a monomorphic container with no base element.
Safe version of ofoldr1Ex
, only works on monomorphic containers wrapped in a
.MinLen
(Succ
nat)
foldr1
f = Prelude.foldr1
f .otoList
Examples
> let xs = "a" `mlcons` "b" `mlcons` "c" `mlcons` (toMinLenZero
[]) >ofoldr1
(++) xs "abc"
ofoldl1' :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> MinLen (Succ nat) mono -> Element mono Source
Strict left-associative fold of a monomorphic container with no base element.
Safe version of ofoldl1Ex'
, only works on monomorphic containers wrapped in a
.MinLen
(Succ
nat)
foldl1'
f = Prelude.foldl1'
f .otoList
Examples
> let xs = "a" `mlcons` "b" `mlcons` "c" `mlcons` (toMinLenZero
[]) >ofoldl1'
(++) xs "abc"
maximumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) 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
.MinLen
(Succ
nat)
minimumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) 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
.MinLen
(Succ
nat)
(<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seq infixr 5 Source
Prepend an element to a non-null SemiSequence
.
toMinList :: NonEmpty a -> NonNull [a] Source
Specializes fromNonEmpty
to lists only.