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

Safe HaskellNone
LanguageHaskell2010

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) mono Source

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

safely convert a Nullable to a NonNull

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

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 -> mono Source

convert a NonNull to a Nullable

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

safely construct a NonNull from a NonEmpty list

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

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 -> seq Source

like filter, but starts with a NonNull

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

like filterM, but starts with a NonNull

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

i must be > 0. like replicate

i <= 0 is treated the same as providing 1

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

Returns the first element.

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

like Data.List, but not partial on a NonEmpty

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

Returns the last element.

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

like Data.List, but not partial on a NonEmpty

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

Maps a function that returns a Semigroup over the container, then joins those semigroups together.

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

Joins a list of Semigroups together.

Examples

> let xs = "a" `mlcons` "b" `mlcons` "c" `mlcons` (toMinLenZero [])
> xs
MinLen {unMinLen = ["a","b","c"]}

> ofold1 xs
"abc"

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

A right fold that has no base case, and thus may only be applied to non-empty structures.

foldr1 f = 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

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

foldl1 f = foldl1 f . otoList

Examples

> let xs = "a" `mlcons` "b" `mlcons` "c" `mlcons` (toMinLenZero [])
> ofoldl1' (++) xs
"abc"

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

Like Data.List.maximum, but not partial on a MonoFoldable.

Examples

> let xs = toMinLen [1,2,3] :: Maybe (MinLen (Succ Zero) [Int])
> fmap maximum xs
Just 3

maximumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) mono -> Element mono Source

Like Data.List.maximumBy, but not partial on a MonoFoldable.

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

Like Data.List.minimum, but not partial on a MonoFoldable.

Examples

> let xs = toMinLen [1,2,3] :: Maybe (MinLen (Succ Zero) [Int])
> fmap minimum xs
Just 1

minimumBy :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> MinLen (Succ nat) mono -> Element mono Source

Like Data.List.minimumBy, but not partial on a MonoFoldable.

(<|) :: SemiSequence seq => Element seq -> NonNull seq -> NonNull seq infixr 5 Source

Prepend an element to a NonNull

toMinList :: NonEmpty a -> NonNull [a] Source