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

Safe HaskellNone
LanguageHaskell2010

Data.NonNull

Description

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

Documentation

data NonNull mono Source #

A monomorphic container that is not null.

Instances
Eq mono => Eq (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

(==) :: NonNull mono -> NonNull mono -> Bool #

(/=) :: NonNull mono -> NonNull mono -> Bool #

Data mono => Data (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> NonNull mono -> c (NonNull mono) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (NonNull mono) #

toConstr :: NonNull mono -> Constr #

dataTypeOf :: NonNull mono -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (NonNull mono)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (NonNull mono)) #

gmapT :: (forall b. Data b => b -> b) -> NonNull mono -> NonNull mono #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> NonNull mono -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> NonNull mono -> r #

gmapQ :: (forall d. Data d => d -> u) -> NonNull mono -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> NonNull mono -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> NonNull mono -> m (NonNull mono) #

Ord mono => Ord (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

compare :: NonNull mono -> NonNull mono -> Ordering #

(<) :: NonNull mono -> NonNull mono -> Bool #

(<=) :: NonNull mono -> NonNull mono -> Bool #

(>) :: NonNull mono -> NonNull mono -> Bool #

(>=) :: NonNull mono -> NonNull mono -> Bool #

max :: NonNull mono -> NonNull mono -> NonNull mono #

min :: NonNull mono -> NonNull mono -> NonNull mono #

Read mono => Read (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Show mono => Show (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

showsPrec :: Int -> NonNull mono -> ShowS #

show :: NonNull mono -> String #

showList :: [NonNull mono] -> ShowS #

(Semigroup mono, GrowingAppend mono) => Semigroup (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

(<>) :: NonNull mono -> NonNull mono -> NonNull mono #

sconcat :: NonEmpty (NonNull mono) -> NonNull mono #

stimes :: Integral b => b -> NonNull mono -> NonNull mono #

GrowingAppend mono => GrowingAppend (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

IsSequence mono => MonoComonad (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

oextract :: NonNull mono -> Element (NonNull mono) Source #

oextend :: (NonNull mono -> Element (NonNull mono)) -> NonNull mono -> NonNull mono Source #

MonoPointed mono => MonoPointed (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

opoint :: Element (NonNull mono) -> NonNull mono Source #

MonoTraversable mono => MonoTraversable (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

otraverse :: Applicative f => (Element (NonNull mono) -> f (Element (NonNull mono))) -> NonNull mono -> f (NonNull mono) Source #

omapM :: Applicative m => (Element (NonNull mono) -> m (Element (NonNull mono))) -> NonNull mono -> m (NonNull mono) Source #

MonoFoldable mono => MonoFoldable (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

ofoldMap :: Monoid m => (Element (NonNull mono) -> m) -> NonNull mono -> m Source #

ofoldr :: (Element (NonNull mono) -> b -> b) -> b -> NonNull mono -> b Source #

ofoldl' :: (a -> Element (NonNull mono) -> a) -> a -> NonNull mono -> a Source #

otoList :: NonNull mono -> [Element (NonNull mono)] Source #

oall :: (Element (NonNull mono) -> Bool) -> NonNull mono -> Bool Source #

oany :: (Element (NonNull mono) -> Bool) -> NonNull mono -> Bool Source #

onull :: NonNull mono -> Bool Source #

olength :: NonNull mono -> Int Source #

olength64 :: NonNull mono -> Int64 Source #

ocompareLength :: Integral i => NonNull mono -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (NonNull mono) -> f b) -> NonNull mono -> f () Source #

ofor_ :: Applicative f => NonNull mono -> (Element (NonNull mono) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (NonNull mono) -> m ()) -> NonNull mono -> m () Source #

oforM_ :: Applicative m => NonNull mono -> (Element (NonNull mono) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a -> Element (NonNull mono) -> m a) -> a -> NonNull mono -> m a Source #

ofoldMap1Ex :: Semigroup m => (Element (NonNull mono) -> m) -> NonNull mono -> m Source #

ofoldr1Ex :: (Element (NonNull mono) -> Element (NonNull mono) -> Element (NonNull mono)) -> NonNull mono -> Element (NonNull mono) Source #

ofoldl1Ex' :: (Element (NonNull mono) -> Element (NonNull mono) -> Element (NonNull mono)) -> NonNull mono -> Element (NonNull mono) Source #

headEx :: NonNull mono -> Element (NonNull mono) Source #

lastEx :: NonNull mono -> Element (NonNull mono) Source #

unsafeHead :: NonNull mono -> Element (NonNull mono) Source #

unsafeLast :: NonNull mono -> Element (NonNull mono) Source #

maximumByEx :: (Element (NonNull mono) -> Element (NonNull mono) -> Ordering) -> NonNull mono -> Element (NonNull mono) Source #

minimumByEx :: (Element (NonNull mono) -> Element (NonNull mono) -> Ordering) -> NonNull mono -> Element (NonNull mono) Source #

oelem :: Element (NonNull mono) -> NonNull mono -> Bool Source #

onotElem :: Element (NonNull mono) -> NonNull mono -> Bool Source #

MonoFunctor mono => MonoFunctor (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Methods

omap :: (Element (NonNull mono) -> Element (NonNull mono)) -> NonNull mono -> NonNull mono Source #

SemiSequence seq => SemiSequence (NonNull seq) Source # 
Instance details

Defined in Data.NonNull

Associated Types

type Index (NonNull seq) :: Type Source #

Methods

intersperse :: Element (NonNull seq) -> NonNull seq -> NonNull seq Source #

reverse :: NonNull seq -> NonNull seq Source #

find :: (Element (NonNull seq) -> Bool) -> NonNull seq -> Maybe (Element (NonNull seq)) Source #

sortBy :: (Element (NonNull seq) -> Element (NonNull seq) -> Ordering) -> NonNull seq -> NonNull seq Source #

cons :: Element (NonNull seq) -> NonNull seq -> NonNull seq Source #

snoc :: NonNull seq -> Element (NonNull seq) -> NonNull seq Source #

type Element (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

type Element (NonNull mono) = Element mono
type Index (NonNull seq) Source # 
Instance details

Defined in Data.NonNull

type Index (NonNull seq) = Index seq

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 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 #

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.filter, but works on non-nullable sequences.

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

Equivalent to Data.Sequences.filterM, but works on non-nullable sequences.

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

Equivalent to Data.Sequences.replicate

i must be > 0

i <= 0 is treated the same as providing 1

head :: MonoFoldable mono => NonNull mono -> Element mono Source #

Return the first element of a monomorphic container.

Safe version of headEx, only works on monomorphic containers wrapped in a NonNull.

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

Safe version of tailEx, only working on non-nullable sequences.

last :: MonoFoldable mono => NonNull mono -> Element mono Source #

Return the last element of a monomorphic container.

Safe version of lastEx, only works on monomorphic containers wrapped in a NonNull.

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

Expand
> let xs = ncons ("hello", 1 :: Integer) [(" world", 2)]
> ofoldMap1 fst xs
"hello world"

ofold1 :: (MonoFoldable mono, Semigroup (Element mono)) => NonNull mono -> Element mono Source #

Join a monomorphic container, whose elements are Semigroups, together.

Safe, only works on monomorphic containers wrapped in a NonNull.

Examples

Expand
> let xs = ncons "a" ["b", "c"]
> xs
NonNull {toNullable = ["a","b","c"]}

> ofold1 xs
"abc"

ofoldr1 :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> NonNull 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 NonNull.

foldr1 f = Prelude.foldr1 f . otoList

Examples

Expand
> let xs = ncons "a" ["b", "c"]
> ofoldr1 (++) xs
"abc"

ofoldl1' :: MonoFoldable mono => (Element mono -> Element mono -> Element mono) -> NonNull 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 NonNull.

foldl1' f = Prelude.foldl1' f . otoList

Examples

Expand
> let xs = ncons "a" ["b", "c"]
> ofoldl1' (++) xs
"abc"

maximum :: (MonoFoldable mono, Ord (Element mono)) => NonNull mono -> Element mono Source #

Get the maximum element of a monomorphic container.

Safe version of maximumEx, only works on monomorphic containers wrapped in a NonNull.

Examples

Expand
> let xs = ncons 1 [2, 3 :: Int]
> maximum xs
3

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.

minimum :: (MonoFoldable mono, Ord (Element mono)) => NonNull mono -> Element mono Source #

Get the minimum element of a monomorphic container.

Safe version of minimumEx, only works on monomorphic containers wrapped in a NonNull.

Examples

Expand
> let xs = ncons 1 [2, 3 :: Int]
> minimum xs
1

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.

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

Specializes fromNonEmpty to lists only.

mapNonNull :: (Functor f, MonoFoldable (f b)) => (a -> b) -> NonNull (f a) -> NonNull (f b) Source #

fmap over the underlying container in a NonNull.

Since: 1.0.6.0

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.

Instances
GrowingAppend ByteString Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend ByteString Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend IntSet Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend Text Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend Text Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend [a] Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend (NonEmpty a) Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend (IntMap v) Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend (Seq a) Source # 
Instance details

Defined in Data.MonoTraversable

Ord v => GrowingAppend (Set v) Source # 
Instance details

Defined in Data.MonoTraversable

(Eq v, Hashable v) => GrowingAppend (HashSet v) Source # 
Instance details

Defined in Data.MonoTraversable

Unbox a => GrowingAppend (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

Storable a => GrowingAppend (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

GrowingAppend mono => GrowingAppend (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

Ord k => GrowingAppend (Map k v) Source # 
Instance details

Defined in Data.MonoTraversable

(Eq k, Hashable k) => GrowingAppend (HashMap k v) Source # 
Instance details

Defined in Data.MonoTraversable