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

Safe HaskellNone
LanguageHaskell2010

Data.MonoTraversable

Description

Type classes mirroring standard typeclasses, but working with monomorphic containers.

The motivation is that some commonly used data types (i.e., ByteString and Text) do not allow for instances of typeclasses like Functor and Foldable, since they are monomorphic structures. This module allows both monomorphic and polymorphic data types to be instances of the same typeclasses.

All of the laws for the polymorphic typeclasses apply to their monomorphic cousins. Thus, even though a MonoFunctor instance for Set could theoretically be defined, it is omitted since it could violate the functor law of omap f . omap g = omap (f . g).

Note that all typeclasses have been prefixed with Mono, and functions have been prefixed with o. The mnemonic for o is "only one", or alternatively "it's mono, but m is overused in Haskell, so we'll use the second letter instead." (Agreed, it's not a great mangling scheme, input is welcome!)

Synopsis

Documentation

type family Element mono Source #

Type family for getting the type of the elements of a monomorphic container.

Instances
type Element ByteString Source # 
Instance details

Defined in Data.MonoTraversable

type Element ByteString Source # 
Instance details

Defined in Data.MonoTraversable

type Element IntSet Source # 
Instance details

Defined in Data.MonoTraversable

type Element Text Source # 
Instance details

Defined in Data.MonoTraversable

type Element Text Source # 
Instance details

Defined in Data.MonoTraversable

type Element [a] Source # 
Instance details

Defined in Data.MonoTraversable

type Element [a] = a
type Element (Maybe a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Maybe a) = a
type Element (IO a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (IO a) = a
type Element (Par1 a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Par1 a) = a
type Element (Option a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Option a) = a
type Element (ZipList a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (ZipList a) = a
type Element (Identity a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Identity a) = a
type Element (NonEmpty a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (NonEmpty a) = a
type Element (IntMap a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (IntMap a) = a
type Element (Tree a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Tree a) = a
type Element (Seq a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Seq a) = a
type Element (ViewL a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (ViewL a) = a
type Element (ViewR a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (ViewR a) = a
type Element (Set e) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Set e) = e
type Element (HashSet e) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (HashSet e) = e
type Element (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Vector a) = a
type Element (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Vector a) = a
type Element (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Vector a) = a
type Element (NonNull mono) Source # 
Instance details

Defined in Data.NonNull

type Element (NonNull mono) = Element mono
type Element (r -> a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (r -> a) = a
type Element (Either a b) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Either a b) = b
type Element (V1 a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (V1 a) = a
type Element (U1 a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (U1 a) = a
type Element (a, b) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (a, b) = b
type Element (Arg a b) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Arg a b) = b
type Element (WrappedMonad m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (WrappedMonad m a) = a
type Element (Proxy a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Proxy a) = a
type Element (Map k v) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Map k v) = v
type Element (MaybeT m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (MaybeT m a) = a
type Element (ListT m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (ListT m a) = a
type Element (HashMap k v) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (HashMap k v) = v
type Element (Rec1 f a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Rec1 f a) = a
type Element (WrappedArrow a b c) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (WrappedArrow a b c) = c
type Element (Const m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Const m a) = a
type Element (WriterT w m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (WriterT w m a) = a
type Element (WriterT w m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (WriterT w m a) = a
type Element (StateT s m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (StateT s m a) = a
type Element (StateT s m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (StateT s m a) = a
type Element (IdentityT m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (IdentityT m a) = a
type Element (K1 i c a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (K1 i c a) = a
type Element ((f :+: g) a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element ((f :+: g) a) = a
type Element ((f :*: g) a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element ((f :*: g) a) = a
type Element (Product f g a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Product f g a) = a
type Element (ReaderT r m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (ReaderT r m a) = a
type Element (ContT r m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (ContT r m a) = a
type Element (M1 i c f a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (M1 i c f a) = a
type Element ((f :.: g) a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element ((f :.: g) a) = a
type Element (Compose f g a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (Compose f g a) = a
type Element (RWST r w s m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (RWST r w s m a) = a
type Element (RWST r w s m a) Source # 
Instance details

Defined in Data.MonoTraversable

type Element (RWST r w s m a) = a

class MonoFunctor mono where Source #

Monomorphic containers that can be mapped over.

Minimal complete definition

Nothing

Methods

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

Map over a monomorphic container

omap :: (Functor f, Element (f a) ~ a, f a ~ mono) => (Element mono -> Element mono) -> mono -> mono Source #

Map over a monomorphic container

Instances
MonoFunctor ByteString Source # 
Instance details

Defined in Data.MonoTraversable

MonoFunctor ByteString Source # 
Instance details

Defined in Data.MonoTraversable

MonoFunctor Text Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element Text -> Element Text) -> Text -> Text Source #

MonoFunctor Text Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element Text -> Element Text) -> Text -> Text Source #

MonoFunctor [a] Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element [a] -> Element [a]) -> [a] -> [a] Source #

MonoFunctor (Maybe a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Maybe a Source #

MonoFunctor (IO a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (IO a) -> Element (IO a)) -> IO a -> IO a Source #

MonoFunctor (Par1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Par1 a) -> Element (Par1 a)) -> Par1 a -> Par1 a Source #

MonoFunctor (Option a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Option a) -> Element (Option a)) -> Option a -> Option a Source #

MonoFunctor (ZipList a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (ZipList a) -> Element (ZipList a)) -> ZipList a -> ZipList a Source #

MonoFunctor (Identity a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Identity a) -> Element (Identity a)) -> Identity a -> Identity a Source #

MonoFunctor (NonEmpty a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (NonEmpty a) -> Element (NonEmpty a)) -> NonEmpty a -> NonEmpty a Source #

MonoFunctor (IntMap a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (IntMap a) -> Element (IntMap a)) -> IntMap a -> IntMap a Source #

MonoFunctor (Tree a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Tree a) -> Element (Tree a)) -> Tree a -> Tree a Source #

MonoFunctor (Seq a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Seq a) -> Element (Seq a)) -> Seq a -> Seq a Source #

MonoFunctor (ViewL a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (ViewL a) -> Element (ViewL a)) -> ViewL a -> ViewL a Source #

MonoFunctor (ViewR a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (ViewR a) -> Element (ViewR a)) -> ViewR a -> ViewR a Source #

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

Defined in Data.MonoTraversable

Methods

omap :: (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a Source #

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

Defined in Data.MonoTraversable

Methods

omap :: (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a Source #

MonoFunctor (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Vector a) -> Element (Vector a)) -> Vector a -> Vector a 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 #

MonoFunctor (r -> a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (r -> a) -> Element (r -> a)) -> (r -> a) -> r -> a Source #

MonoFunctor (Either a b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Either a b) -> Element (Either a b)) -> Either a b -> Either a b Source #

MonoFunctor (V1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (V1 a) -> Element (V1 a)) -> V1 a -> V1 a Source #

MonoFunctor (U1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (U1 a) -> Element (U1 a)) -> U1 a -> U1 a Source #

MonoFunctor (a, b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (a, b) -> Element (a, b)) -> (a, b) -> (a, b) Source #

MonoFunctor (Arg a b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Arg a b) -> Element (Arg a b)) -> Arg a b -> Arg a b Source #

Monad m => MonoFunctor (WrappedMonad m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (WrappedMonad m a) -> Element (WrappedMonad m a)) -> WrappedMonad m a -> WrappedMonad m a Source #

MonoFunctor (Proxy a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Proxy a) -> Element (Proxy a)) -> Proxy a -> Proxy a Source #

MonoFunctor (Map k v) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Map k v) -> Element (Map k v)) -> Map k v -> Map k v Source #

Functor m => MonoFunctor (MaybeT m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (MaybeT m a) -> Element (MaybeT m a)) -> MaybeT m a -> MaybeT m a Source #

Functor m => MonoFunctor (ListT m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (ListT m a) -> Element (ListT m a)) -> ListT m a -> ListT m a Source #

MonoFunctor (HashMap k v) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> HashMap k v Source #

Functor f => MonoFunctor (Rec1 f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Rec1 f a) -> Element (Rec1 f a)) -> Rec1 f a -> Rec1 f a Source #

Arrow a => MonoFunctor (WrappedArrow a b c) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (WrappedArrow a b c) -> Element (WrappedArrow a b c)) -> WrappedArrow a b c -> WrappedArrow a b c Source #

MonoFunctor (Const m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Const m a) -> Element (Const m a)) -> Const m a -> Const m a Source #

Functor m => MonoFunctor (WriterT w m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (WriterT w m a) -> Element (WriterT w m a)) -> WriterT w m a -> WriterT w m a Source #

Functor m => MonoFunctor (WriterT w m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (WriterT w m a) -> Element (WriterT w m a)) -> WriterT w m a -> WriterT w m a Source #

Functor m => MonoFunctor (StateT s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (StateT s m a) -> Element (StateT s m a)) -> StateT s m a -> StateT s m a Source #

Functor m => MonoFunctor (StateT s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (StateT s m a) -> Element (StateT s m a)) -> StateT s m a -> StateT s m a Source #

Functor m => MonoFunctor (IdentityT m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (IdentityT m a) -> Element (IdentityT m a)) -> IdentityT m a -> IdentityT m a Source #

MonoFunctor (K1 i c a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (K1 i c a) -> Element (K1 i c a)) -> K1 i c a -> K1 i c a Source #

(Functor f, Functor g) => MonoFunctor ((f :+: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element ((f :+: g) a) -> Element ((f :+: g) a)) -> (f :+: g) a -> (f :+: g) a Source #

(Functor f, Functor g) => MonoFunctor ((f :*: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element ((f :*: g) a) -> Element ((f :*: g) a)) -> (f :*: g) a -> (f :*: g) a Source #

(Functor f, Functor g) => MonoFunctor (Product f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Product f g a) -> Element (Product f g a)) -> Product f g a -> Product f g a Source #

Functor m => MonoFunctor (ReaderT r m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (ReaderT r m a) -> Element (ReaderT r m a)) -> ReaderT r m a -> ReaderT r m a Source #

Functor m => MonoFunctor (ContT r m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (ContT r m a) -> Element (ContT r m a)) -> ContT r m a -> ContT r m a Source #

Functor f => MonoFunctor (M1 i c f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (M1 i c f a) -> Element (M1 i c f a)) -> M1 i c f a -> M1 i c f a Source #

(Functor f, Functor g) => MonoFunctor ((f :.: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element ((f :.: g) a) -> Element ((f :.: g) a)) -> (f :.: g) a -> (f :.: g) a Source #

(Functor f, Functor g) => MonoFunctor (Compose f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (Compose f g a) -> Element (Compose f g a)) -> Compose f g a -> Compose f g a Source #

Functor m => MonoFunctor (RWST r w s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (RWST r w s m a) -> Element (RWST r w s m a)) -> RWST r w s m a -> RWST r w s m a Source #

Functor m => MonoFunctor (RWST r w s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

omap :: (Element (RWST r w s m a) -> Element (RWST r w s m a)) -> RWST r w s m a -> RWST r w s m a Source #

replaceElem :: (MonoFunctor mono, Eq (Element mono)) => Element mono -> Element mono -> mono -> mono Source #

replaceElem old new replaces all old elements with new.

Since: 1.0.1

class MonoFoldable mono where Source #

Monomorphic containers that can be folded.

Minimal complete definition

Nothing

Methods

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

Map each element of a monomorphic container to a Monoid and combine the results.

ofoldMap :: (t a ~ mono, a ~ Element (t a), Foldable t, Monoid m) => (Element mono -> m) -> mono -> m Source #

Map each element of a monomorphic container to a Monoid and combine the results.

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

Right-associative fold of a monomorphic container.

ofoldr :: (t a ~ mono, a ~ Element (t a), Foldable t) => (Element mono -> b -> b) -> b -> mono -> b Source #

Right-associative fold of a monomorphic container.

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

Strict left-associative fold of a monomorphic container.

ofoldl' :: (t b ~ mono, b ~ Element (t b), Foldable t) => (a -> Element mono -> a) -> a -> mono -> a Source #

Strict left-associative fold of a monomorphic container.

otoList :: mono -> [Element mono] Source #

Convert a monomorphic container to a list.

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

Are all of the elements in a monomorphic container converted to booleans True?

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

Are any of the elements in a monomorphic container converted to booleans True?

onull :: mono -> Bool Source #

Is the monomorphic container empty?

olength :: mono -> Int Source #

Length of a monomorphic container, returns a Int.

olength64 :: mono -> Int64 Source #

Length of a monomorphic container, returns a Int64.

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

Compare the length of a monomorphic container and a given number.

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

Map each element of a monomorphic container to an action, evaluate these actions from left to right, and ignore the results.

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

ofor_ is otraverse_ with its arguments flipped.

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

Map each element of a monomorphic container to a monadic action, evaluate these actions from left to right, and ignore the results.

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

oforM_ is omapM_ with its arguments flipped.

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

Monadic fold over the elements of a monomorphic container, associating to the left.

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

Map each element of a monomorphic container to a semigroup, and combine the results.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See ofoldMap1 from Data.NonNull for a total version of this function.

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

Right-associative fold of a monomorphic container with no base element.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See ofoldr1 from Data.NonNull for a total version of this function.

ofoldr1Ex :: (t a ~ mono, a ~ Element (t a), Foldable t) => (Element mono -> Element mono -> Element mono) -> mono -> Element mono Source #

Right-associative fold of a monomorphic container with no base element.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See ofoldr1 from Data.NonNull for a total version of this function.

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

Strict left-associative fold of a monomorphic container with no base element.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See ofoldl1' from Data.NonNull for a total version of this function.

ofoldl1Ex' :: (t a ~ mono, a ~ Element (t a), Foldable t) => (Element mono -> Element mono -> Element mono) -> mono -> Element mono Source #

Strict left-associative fold of a monomorphic container with no base element.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See ofoldl1' from Data.NonNull for a total version of this function.

headEx :: mono -> Element mono Source #

Get the first element of a monomorphic container.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See head from Data.NonNull for a total version of this function.

lastEx :: mono -> Element mono Source #

Get the last element of a monomorphic container.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See last from Data.NonNull for a total version of this function.

unsafeHead :: mono -> Element mono Source #

Equivalent to headEx.

unsafeLast :: mono -> Element mono Source #

Equivalent to lastEx.

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

Get the maximum element of a monomorphic container, using a supplied element ordering function.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See maximiumBy from Data.NonNull for a total version of this function.

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

Get the minimum element of a monomorphic container, using a supplied element ordering function.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See minimumBy from Data.NonNull for a total version of this function.

oelem :: Eq (Element mono) => Element mono -> mono -> Bool Source #

Checks if the monomorphic container includes the supplied element.

onotElem :: Eq (Element mono) => Element mono -> mono -> Bool Source #

Checks if the monomorphic container does not include the supplied element.

Instances
MonoFoldable ByteString Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

ofoldr :: (Element ByteString -> b -> b) -> b -> ByteString -> b Source #

ofoldl' :: (a -> Element ByteString -> a) -> a -> ByteString -> a Source #

otoList :: ByteString -> [Element ByteString] Source #

oall :: (Element ByteString -> Bool) -> ByteString -> Bool Source #

oany :: (Element ByteString -> Bool) -> ByteString -> Bool Source #

onull :: ByteString -> Bool Source #

olength :: ByteString -> Int Source #

olength64 :: ByteString -> Int64 Source #

ocompareLength :: Integral i => ByteString -> i -> Ordering Source #

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

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

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

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

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

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

ofoldr1Ex :: (Element ByteString -> Element ByteString -> Element ByteString) -> ByteString -> Element ByteString Source #

ofoldl1Ex' :: (Element ByteString -> Element ByteString -> Element ByteString) -> ByteString -> Element ByteString Source #

headEx :: ByteString -> Element ByteString Source #

lastEx :: ByteString -> Element ByteString Source #

unsafeHead :: ByteString -> Element ByteString Source #

unsafeLast :: ByteString -> Element ByteString Source #

maximumByEx :: (Element ByteString -> Element ByteString -> Ordering) -> ByteString -> Element ByteString Source #

minimumByEx :: (Element ByteString -> Element ByteString -> Ordering) -> ByteString -> Element ByteString Source #

oelem :: Element ByteString -> ByteString -> Bool Source #

onotElem :: Element ByteString -> ByteString -> Bool Source #

MonoFoldable ByteString Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

ofoldr :: (Element ByteString -> b -> b) -> b -> ByteString -> b Source #

ofoldl' :: (a -> Element ByteString -> a) -> a -> ByteString -> a Source #

otoList :: ByteString -> [Element ByteString] Source #

oall :: (Element ByteString -> Bool) -> ByteString -> Bool Source #

oany :: (Element ByteString -> Bool) -> ByteString -> Bool Source #

onull :: ByteString -> Bool Source #

olength :: ByteString -> Int Source #

olength64 :: ByteString -> Int64 Source #

ocompareLength :: Integral i => ByteString -> i -> Ordering Source #

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

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

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

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

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

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

ofoldr1Ex :: (Element ByteString -> Element ByteString -> Element ByteString) -> ByteString -> Element ByteString Source #

ofoldl1Ex' :: (Element ByteString -> Element ByteString -> Element ByteString) -> ByteString -> Element ByteString Source #

headEx :: ByteString -> Element ByteString Source #

lastEx :: ByteString -> Element ByteString Source #

unsafeHead :: ByteString -> Element ByteString Source #

unsafeLast :: ByteString -> Element ByteString Source #

maximumByEx :: (Element ByteString -> Element ByteString -> Ordering) -> ByteString -> Element ByteString Source #

minimumByEx :: (Element ByteString -> Element ByteString -> Ordering) -> ByteString -> Element ByteString Source #

oelem :: Element ByteString -> ByteString -> Bool Source #

onotElem :: Element ByteString -> ByteString -> Bool Source #

MonoFoldable IntSet Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

ofoldr :: (Element IntSet -> b -> b) -> b -> IntSet -> b Source #

ofoldl' :: (a -> Element IntSet -> a) -> a -> IntSet -> a Source #

otoList :: IntSet -> [Element IntSet] Source #

oall :: (Element IntSet -> Bool) -> IntSet -> Bool Source #

oany :: (Element IntSet -> Bool) -> IntSet -> Bool Source #

onull :: IntSet -> Bool Source #

olength :: IntSet -> Int Source #

olength64 :: IntSet -> Int64 Source #

ocompareLength :: Integral i => IntSet -> i -> Ordering Source #

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

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

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

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

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

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

ofoldr1Ex :: (Element IntSet -> Element IntSet -> Element IntSet) -> IntSet -> Element IntSet Source #

ofoldl1Ex' :: (Element IntSet -> Element IntSet -> Element IntSet) -> IntSet -> Element IntSet Source #

headEx :: IntSet -> Element IntSet Source #

lastEx :: IntSet -> Element IntSet Source #

unsafeHead :: IntSet -> Element IntSet Source #

unsafeLast :: IntSet -> Element IntSet Source #

maximumByEx :: (Element IntSet -> Element IntSet -> Ordering) -> IntSet -> Element IntSet Source #

minimumByEx :: (Element IntSet -> Element IntSet -> Ordering) -> IntSet -> Element IntSet Source #

oelem :: Element IntSet -> IntSet -> Bool Source #

onotElem :: Element IntSet -> IntSet -> Bool Source #

MonoFoldable Text Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

ofoldr :: (Element Text -> b -> b) -> b -> Text -> b Source #

ofoldl' :: (a -> Element Text -> a) -> a -> Text -> a Source #

otoList :: Text -> [Element Text] Source #

oall :: (Element Text -> Bool) -> Text -> Bool Source #

oany :: (Element Text -> Bool) -> Text -> Bool Source #

onull :: Text -> Bool Source #

olength :: Text -> Int Source #

olength64 :: Text -> Int64 Source #

ocompareLength :: Integral i => Text -> i -> Ordering Source #

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

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

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

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

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

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

ofoldr1Ex :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text Source #

ofoldl1Ex' :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text Source #

headEx :: Text -> Element Text Source #

lastEx :: Text -> Element Text Source #

unsafeHead :: Text -> Element Text Source #

unsafeLast :: Text -> Element Text Source #

maximumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text Source #

minimumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text Source #

oelem :: Element Text -> Text -> Bool Source #

onotElem :: Element Text -> Text -> Bool Source #

MonoFoldable Text Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

ofoldr :: (Element Text -> b -> b) -> b -> Text -> b Source #

ofoldl' :: (a -> Element Text -> a) -> a -> Text -> a Source #

otoList :: Text -> [Element Text] Source #

oall :: (Element Text -> Bool) -> Text -> Bool Source #

oany :: (Element Text -> Bool) -> Text -> Bool Source #

onull :: Text -> Bool Source #

olength :: Text -> Int Source #

olength64 :: Text -> Int64 Source #

ocompareLength :: Integral i => Text -> i -> Ordering Source #

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

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

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

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

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

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

ofoldr1Ex :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text Source #

ofoldl1Ex' :: (Element Text -> Element Text -> Element Text) -> Text -> Element Text Source #

headEx :: Text -> Element Text Source #

lastEx :: Text -> Element Text Source #

unsafeHead :: Text -> Element Text Source #

unsafeLast :: Text -> Element Text Source #

maximumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text Source #

minimumByEx :: (Element Text -> Element Text -> Ordering) -> Text -> Element Text Source #

oelem :: Element Text -> Text -> Bool Source #

onotElem :: Element Text -> Text -> Bool Source #

MonoFoldable [a] Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element [a] -> m) -> [a] -> m Source #

ofoldr :: (Element [a] -> b -> b) -> b -> [a] -> b Source #

ofoldl' :: (a0 -> Element [a] -> a0) -> a0 -> [a] -> a0 Source #

otoList :: [a] -> [Element [a]] Source #

oall :: (Element [a] -> Bool) -> [a] -> Bool Source #

oany :: (Element [a] -> Bool) -> [a] -> Bool Source #

onull :: [a] -> Bool Source #

olength :: [a] -> Int Source #

olength64 :: [a] -> Int64 Source #

ocompareLength :: Integral i => [a] -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element [a] -> f b) -> [a] -> f () Source #

ofor_ :: Applicative f => [a] -> (Element [a] -> f b) -> f () Source #

omapM_ :: Applicative m => (Element [a] -> m ()) -> [a] -> m () Source #

oforM_ :: Applicative m => [a] -> (Element [a] -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element [a] -> m a0) -> a0 -> [a] -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element [a] -> m) -> [a] -> m Source #

ofoldr1Ex :: (Element [a] -> Element [a] -> Element [a]) -> [a] -> Element [a] Source #

ofoldl1Ex' :: (Element [a] -> Element [a] -> Element [a]) -> [a] -> Element [a] Source #

headEx :: [a] -> Element [a] Source #

lastEx :: [a] -> Element [a] Source #

unsafeHead :: [a] -> Element [a] Source #

unsafeLast :: [a] -> Element [a] Source #

maximumByEx :: (Element [a] -> Element [a] -> Ordering) -> [a] -> Element [a] Source #

minimumByEx :: (Element [a] -> Element [a] -> Ordering) -> [a] -> Element [a] Source #

oelem :: Element [a] -> [a] -> Bool Source #

onotElem :: Element [a] -> [a] -> Bool Source #

MonoFoldable (Maybe a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Maybe a) -> m) -> Maybe a -> m Source #

ofoldr :: (Element (Maybe a) -> b -> b) -> b -> Maybe a -> b Source #

ofoldl' :: (a0 -> Element (Maybe a) -> a0) -> a0 -> Maybe a -> a0 Source #

otoList :: Maybe a -> [Element (Maybe a)] Source #

oall :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool Source #

oany :: (Element (Maybe a) -> Bool) -> Maybe a -> Bool Source #

onull :: Maybe a -> Bool Source #

olength :: Maybe a -> Int Source #

olength64 :: Maybe a -> Int64 Source #

ocompareLength :: Integral i => Maybe a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Maybe a) -> f b) -> Maybe a -> f () Source #

ofor_ :: Applicative f => Maybe a -> (Element (Maybe a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Maybe a) -> m ()) -> Maybe a -> m () Source #

oforM_ :: Applicative m => Maybe a -> (Element (Maybe a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Maybe a) -> m a0) -> a0 -> Maybe a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Maybe a) -> m) -> Maybe a -> m Source #

ofoldr1Ex :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) Source #

ofoldl1Ex' :: (Element (Maybe a) -> Element (Maybe a) -> Element (Maybe a)) -> Maybe a -> Element (Maybe a) Source #

headEx :: Maybe a -> Element (Maybe a) Source #

lastEx :: Maybe a -> Element (Maybe a) Source #

unsafeHead :: Maybe a -> Element (Maybe a) Source #

unsafeLast :: Maybe a -> Element (Maybe a) Source #

maximumByEx :: (Element (Maybe a) -> Element (Maybe a) -> Ordering) -> Maybe a -> Element (Maybe a) Source #

minimumByEx :: (Element (Maybe a) -> Element (Maybe a) -> Ordering) -> Maybe a -> Element (Maybe a) Source #

oelem :: Element (Maybe a) -> Maybe a -> Bool Source #

onotElem :: Element (Maybe a) -> Maybe a -> Bool Source #

MonoFoldable (Par1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Par1 a) -> m) -> Par1 a -> m Source #

ofoldr :: (Element (Par1 a) -> b -> b) -> b -> Par1 a -> b Source #

ofoldl' :: (a0 -> Element (Par1 a) -> a0) -> a0 -> Par1 a -> a0 Source #

otoList :: Par1 a -> [Element (Par1 a)] Source #

oall :: (Element (Par1 a) -> Bool) -> Par1 a -> Bool Source #

oany :: (Element (Par1 a) -> Bool) -> Par1 a -> Bool Source #

onull :: Par1 a -> Bool Source #

olength :: Par1 a -> Int Source #

olength64 :: Par1 a -> Int64 Source #

ocompareLength :: Integral i => Par1 a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Par1 a) -> f b) -> Par1 a -> f () Source #

ofor_ :: Applicative f => Par1 a -> (Element (Par1 a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Par1 a) -> m ()) -> Par1 a -> m () Source #

oforM_ :: Applicative m => Par1 a -> (Element (Par1 a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Par1 a) -> m a0) -> a0 -> Par1 a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Par1 a) -> m) -> Par1 a -> m Source #

ofoldr1Ex :: (Element (Par1 a) -> Element (Par1 a) -> Element (Par1 a)) -> Par1 a -> Element (Par1 a) Source #

ofoldl1Ex' :: (Element (Par1 a) -> Element (Par1 a) -> Element (Par1 a)) -> Par1 a -> Element (Par1 a) Source #

headEx :: Par1 a -> Element (Par1 a) Source #

lastEx :: Par1 a -> Element (Par1 a) Source #

unsafeHead :: Par1 a -> Element (Par1 a) Source #

unsafeLast :: Par1 a -> Element (Par1 a) Source #

maximumByEx :: (Element (Par1 a) -> Element (Par1 a) -> Ordering) -> Par1 a -> Element (Par1 a) Source #

minimumByEx :: (Element (Par1 a) -> Element (Par1 a) -> Ordering) -> Par1 a -> Element (Par1 a) Source #

oelem :: Element (Par1 a) -> Par1 a -> Bool Source #

onotElem :: Element (Par1 a) -> Par1 a -> Bool Source #

MonoFoldable (Option a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Option a) -> m) -> Option a -> m Source #

ofoldr :: (Element (Option a) -> b -> b) -> b -> Option a -> b Source #

ofoldl' :: (a0 -> Element (Option a) -> a0) -> a0 -> Option a -> a0 Source #

otoList :: Option a -> [Element (Option a)] Source #

oall :: (Element (Option a) -> Bool) -> Option a -> Bool Source #

oany :: (Element (Option a) -> Bool) -> Option a -> Bool Source #

onull :: Option a -> Bool Source #

olength :: Option a -> Int Source #

olength64 :: Option a -> Int64 Source #

ocompareLength :: Integral i => Option a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Option a) -> f b) -> Option a -> f () Source #

ofor_ :: Applicative f => Option a -> (Element (Option a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Option a) -> m ()) -> Option a -> m () Source #

oforM_ :: Applicative m => Option a -> (Element (Option a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Option a) -> m a0) -> a0 -> Option a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Option a) -> m) -> Option a -> m Source #

ofoldr1Ex :: (Element (Option a) -> Element (Option a) -> Element (Option a)) -> Option a -> Element (Option a) Source #

ofoldl1Ex' :: (Element (Option a) -> Element (Option a) -> Element (Option a)) -> Option a -> Element (Option a) Source #

headEx :: Option a -> Element (Option a) Source #

lastEx :: Option a -> Element (Option a) Source #

unsafeHead :: Option a -> Element (Option a) Source #

unsafeLast :: Option a -> Element (Option a) Source #

maximumByEx :: (Element (Option a) -> Element (Option a) -> Ordering) -> Option a -> Element (Option a) Source #

minimumByEx :: (Element (Option a) -> Element (Option a) -> Ordering) -> Option a -> Element (Option a) Source #

oelem :: Element (Option a) -> Option a -> Bool Source #

onotElem :: Element (Option a) -> Option a -> Bool Source #

MonoFoldable (Identity a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Identity a) -> m) -> Identity a -> m Source #

ofoldr :: (Element (Identity a) -> b -> b) -> b -> Identity a -> b Source #

ofoldl' :: (a0 -> Element (Identity a) -> a0) -> a0 -> Identity a -> a0 Source #

otoList :: Identity a -> [Element (Identity a)] Source #

oall :: (Element (Identity a) -> Bool) -> Identity a -> Bool Source #

oany :: (Element (Identity a) -> Bool) -> Identity a -> Bool Source #

onull :: Identity a -> Bool Source #

olength :: Identity a -> Int Source #

olength64 :: Identity a -> Int64 Source #

ocompareLength :: Integral i => Identity a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Identity a) -> f b) -> Identity a -> f () Source #

ofor_ :: Applicative f => Identity a -> (Element (Identity a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Identity a) -> m ()) -> Identity a -> m () Source #

oforM_ :: Applicative m => Identity a -> (Element (Identity a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Identity a) -> m a0) -> a0 -> Identity a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Identity a) -> m) -> Identity a -> m Source #

ofoldr1Ex :: (Element (Identity a) -> Element (Identity a) -> Element (Identity a)) -> Identity a -> Element (Identity a) Source #

ofoldl1Ex' :: (Element (Identity a) -> Element (Identity a) -> Element (Identity a)) -> Identity a -> Element (Identity a) Source #

headEx :: Identity a -> Element (Identity a) Source #

lastEx :: Identity a -> Element (Identity a) Source #

unsafeHead :: Identity a -> Element (Identity a) Source #

unsafeLast :: Identity a -> Element (Identity a) Source #

maximumByEx :: (Element (Identity a) -> Element (Identity a) -> Ordering) -> Identity a -> Element (Identity a) Source #

minimumByEx :: (Element (Identity a) -> Element (Identity a) -> Ordering) -> Identity a -> Element (Identity a) Source #

oelem :: Element (Identity a) -> Identity a -> Bool Source #

onotElem :: Element (Identity a) -> Identity a -> Bool Source #

MonoFoldable (NonEmpty a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (NonEmpty a) -> m) -> NonEmpty a -> m Source #

ofoldr :: (Element (NonEmpty a) -> b -> b) -> b -> NonEmpty a -> b Source #

ofoldl' :: (a0 -> Element (NonEmpty a) -> a0) -> a0 -> NonEmpty a -> a0 Source #

otoList :: NonEmpty a -> [Element (NonEmpty a)] Source #

oall :: (Element (NonEmpty a) -> Bool) -> NonEmpty a -> Bool Source #

oany :: (Element (NonEmpty a) -> Bool) -> NonEmpty a -> Bool Source #

onull :: NonEmpty a -> Bool Source #

olength :: NonEmpty a -> Int Source #

olength64 :: NonEmpty a -> Int64 Source #

ocompareLength :: Integral i => NonEmpty a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (NonEmpty a) -> f b) -> NonEmpty a -> f () Source #

ofor_ :: Applicative f => NonEmpty a -> (Element (NonEmpty a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (NonEmpty a) -> m ()) -> NonEmpty a -> m () Source #

oforM_ :: Applicative m => NonEmpty a -> (Element (NonEmpty a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (NonEmpty a) -> m a0) -> a0 -> NonEmpty a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (NonEmpty a) -> m) -> NonEmpty a -> m Source #

ofoldr1Ex :: (Element (NonEmpty a) -> Element (NonEmpty a) -> Element (NonEmpty a)) -> NonEmpty a -> Element (NonEmpty a) Source #

ofoldl1Ex' :: (Element (NonEmpty a) -> Element (NonEmpty a) -> Element (NonEmpty a)) -> NonEmpty a -> Element (NonEmpty a) Source #

headEx :: NonEmpty a -> Element (NonEmpty a) Source #

lastEx :: NonEmpty a -> Element (NonEmpty a) Source #

unsafeHead :: NonEmpty a -> Element (NonEmpty a) Source #

unsafeLast :: NonEmpty a -> Element (NonEmpty a) Source #

maximumByEx :: (Element (NonEmpty a) -> Element (NonEmpty a) -> Ordering) -> NonEmpty a -> Element (NonEmpty a) Source #

minimumByEx :: (Element (NonEmpty a) -> Element (NonEmpty a) -> Ordering) -> NonEmpty a -> Element (NonEmpty a) Source #

oelem :: Element (NonEmpty a) -> NonEmpty a -> Bool Source #

onotElem :: Element (NonEmpty a) -> NonEmpty a -> Bool Source #

MonoFoldable (IntMap a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (IntMap a) -> m) -> IntMap a -> m Source #

ofoldr :: (Element (IntMap a) -> b -> b) -> b -> IntMap a -> b Source #

ofoldl' :: (a0 -> Element (IntMap a) -> a0) -> a0 -> IntMap a -> a0 Source #

otoList :: IntMap a -> [Element (IntMap a)] Source #

oall :: (Element (IntMap a) -> Bool) -> IntMap a -> Bool Source #

oany :: (Element (IntMap a) -> Bool) -> IntMap a -> Bool Source #

onull :: IntMap a -> Bool Source #

olength :: IntMap a -> Int Source #

olength64 :: IntMap a -> Int64 Source #

ocompareLength :: Integral i => IntMap a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (IntMap a) -> f b) -> IntMap a -> f () Source #

ofor_ :: Applicative f => IntMap a -> (Element (IntMap a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (IntMap a) -> m ()) -> IntMap a -> m () Source #

oforM_ :: Applicative m => IntMap a -> (Element (IntMap a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (IntMap a) -> m a0) -> a0 -> IntMap a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (IntMap a) -> m) -> IntMap a -> m Source #

ofoldr1Ex :: (Element (IntMap a) -> Element (IntMap a) -> Element (IntMap a)) -> IntMap a -> Element (IntMap a) Source #

ofoldl1Ex' :: (Element (IntMap a) -> Element (IntMap a) -> Element (IntMap a)) -> IntMap a -> Element (IntMap a) Source #

headEx :: IntMap a -> Element (IntMap a) Source #

lastEx :: IntMap a -> Element (IntMap a) Source #

unsafeHead :: IntMap a -> Element (IntMap a) Source #

unsafeLast :: IntMap a -> Element (IntMap a) Source #

maximumByEx :: (Element (IntMap a) -> Element (IntMap a) -> Ordering) -> IntMap a -> Element (IntMap a) Source #

minimumByEx :: (Element (IntMap a) -> Element (IntMap a) -> Ordering) -> IntMap a -> Element (IntMap a) Source #

oelem :: Element (IntMap a) -> IntMap a -> Bool Source #

onotElem :: Element (IntMap a) -> IntMap a -> Bool Source #

MonoFoldable (Tree a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Tree a) -> m) -> Tree a -> m Source #

ofoldr :: (Element (Tree a) -> b -> b) -> b -> Tree a -> b Source #

ofoldl' :: (a0 -> Element (Tree a) -> a0) -> a0 -> Tree a -> a0 Source #

otoList :: Tree a -> [Element (Tree a)] Source #

oall :: (Element (Tree a) -> Bool) -> Tree a -> Bool Source #

oany :: (Element (Tree a) -> Bool) -> Tree a -> Bool Source #

onull :: Tree a -> Bool Source #

olength :: Tree a -> Int Source #

olength64 :: Tree a -> Int64 Source #

ocompareLength :: Integral i => Tree a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Tree a) -> f b) -> Tree a -> f () Source #

ofor_ :: Applicative f => Tree a -> (Element (Tree a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Tree a) -> m ()) -> Tree a -> m () Source #

oforM_ :: Applicative m => Tree a -> (Element (Tree a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Tree a) -> m a0) -> a0 -> Tree a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Tree a) -> m) -> Tree a -> m Source #

ofoldr1Ex :: (Element (Tree a) -> Element (Tree a) -> Element (Tree a)) -> Tree a -> Element (Tree a) Source #

ofoldl1Ex' :: (Element (Tree a) -> Element (Tree a) -> Element (Tree a)) -> Tree a -> Element (Tree a) Source #

headEx :: Tree a -> Element (Tree a) Source #

lastEx :: Tree a -> Element (Tree a) Source #

unsafeHead :: Tree a -> Element (Tree a) Source #

unsafeLast :: Tree a -> Element (Tree a) Source #

maximumByEx :: (Element (Tree a) -> Element (Tree a) -> Ordering) -> Tree a -> Element (Tree a) Source #

minimumByEx :: (Element (Tree a) -> Element (Tree a) -> Ordering) -> Tree a -> Element (Tree a) Source #

oelem :: Element (Tree a) -> Tree a -> Bool Source #

onotElem :: Element (Tree a) -> Tree a -> Bool Source #

MonoFoldable (Seq a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Seq a) -> m) -> Seq a -> m Source #

ofoldr :: (Element (Seq a) -> b -> b) -> b -> Seq a -> b Source #

ofoldl' :: (a0 -> Element (Seq a) -> a0) -> a0 -> Seq a -> a0 Source #

otoList :: Seq a -> [Element (Seq a)] Source #

oall :: (Element (Seq a) -> Bool) -> Seq a -> Bool Source #

oany :: (Element (Seq a) -> Bool) -> Seq a -> Bool Source #

onull :: Seq a -> Bool Source #

olength :: Seq a -> Int Source #

olength64 :: Seq a -> Int64 Source #

ocompareLength :: Integral i => Seq a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Seq a) -> f b) -> Seq a -> f () Source #

ofor_ :: Applicative f => Seq a -> (Element (Seq a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Seq a) -> m ()) -> Seq a -> m () Source #

oforM_ :: Applicative m => Seq a -> (Element (Seq a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Seq a) -> m a0) -> a0 -> Seq a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Seq a) -> m) -> Seq a -> m Source #

ofoldr1Ex :: (Element (Seq a) -> Element (Seq a) -> Element (Seq a)) -> Seq a -> Element (Seq a) Source #

ofoldl1Ex' :: (Element (Seq a) -> Element (Seq a) -> Element (Seq a)) -> Seq a -> Element (Seq a) Source #

headEx :: Seq a -> Element (Seq a) Source #

lastEx :: Seq a -> Element (Seq a) Source #

unsafeHead :: Seq a -> Element (Seq a) Source #

unsafeLast :: Seq a -> Element (Seq a) Source #

maximumByEx :: (Element (Seq a) -> Element (Seq a) -> Ordering) -> Seq a -> Element (Seq a) Source #

minimumByEx :: (Element (Seq a) -> Element (Seq a) -> Ordering) -> Seq a -> Element (Seq a) Source #

oelem :: Element (Seq a) -> Seq a -> Bool Source #

onotElem :: Element (Seq a) -> Seq a -> Bool Source #

MonoFoldable (ViewL a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (ViewL a) -> m) -> ViewL a -> m Source #

ofoldr :: (Element (ViewL a) -> b -> b) -> b -> ViewL a -> b Source #

ofoldl' :: (a0 -> Element (ViewL a) -> a0) -> a0 -> ViewL a -> a0 Source #

otoList :: ViewL a -> [Element (ViewL a)] Source #

oall :: (Element (ViewL a) -> Bool) -> ViewL a -> Bool Source #

oany :: (Element (ViewL a) -> Bool) -> ViewL a -> Bool Source #

onull :: ViewL a -> Bool Source #

olength :: ViewL a -> Int Source #

olength64 :: ViewL a -> Int64 Source #

ocompareLength :: Integral i => ViewL a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (ViewL a) -> f b) -> ViewL a -> f () Source #

ofor_ :: Applicative f => ViewL a -> (Element (ViewL a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (ViewL a) -> m ()) -> ViewL a -> m () Source #

oforM_ :: Applicative m => ViewL a -> (Element (ViewL a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (ViewL a) -> m a0) -> a0 -> ViewL a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (ViewL a) -> m) -> ViewL a -> m Source #

ofoldr1Ex :: (Element (ViewL a) -> Element (ViewL a) -> Element (ViewL a)) -> ViewL a -> Element (ViewL a) Source #

ofoldl1Ex' :: (Element (ViewL a) -> Element (ViewL a) -> Element (ViewL a)) -> ViewL a -> Element (ViewL a) Source #

headEx :: ViewL a -> Element (ViewL a) Source #

lastEx :: ViewL a -> Element (ViewL a) Source #

unsafeHead :: ViewL a -> Element (ViewL a) Source #

unsafeLast :: ViewL a -> Element (ViewL a) Source #

maximumByEx :: (Element (ViewL a) -> Element (ViewL a) -> Ordering) -> ViewL a -> Element (ViewL a) Source #

minimumByEx :: (Element (ViewL a) -> Element (ViewL a) -> Ordering) -> ViewL a -> Element (ViewL a) Source #

oelem :: Element (ViewL a) -> ViewL a -> Bool Source #

onotElem :: Element (ViewL a) -> ViewL a -> Bool Source #

MonoFoldable (ViewR a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (ViewR a) -> m) -> ViewR a -> m Source #

ofoldr :: (Element (ViewR a) -> b -> b) -> b -> ViewR a -> b Source #

ofoldl' :: (a0 -> Element (ViewR a) -> a0) -> a0 -> ViewR a -> a0 Source #

otoList :: ViewR a -> [Element (ViewR a)] Source #

oall :: (Element (ViewR a) -> Bool) -> ViewR a -> Bool Source #

oany :: (Element (ViewR a) -> Bool) -> ViewR a -> Bool Source #

onull :: ViewR a -> Bool Source #

olength :: ViewR a -> Int Source #

olength64 :: ViewR a -> Int64 Source #

ocompareLength :: Integral i => ViewR a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (ViewR a) -> f b) -> ViewR a -> f () Source #

ofor_ :: Applicative f => ViewR a -> (Element (ViewR a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (ViewR a) -> m ()) -> ViewR a -> m () Source #

oforM_ :: Applicative m => ViewR a -> (Element (ViewR a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (ViewR a) -> m a0) -> a0 -> ViewR a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (ViewR a) -> m) -> ViewR a -> m Source #

ofoldr1Ex :: (Element (ViewR a) -> Element (ViewR a) -> Element (ViewR a)) -> ViewR a -> Element (ViewR a) Source #

ofoldl1Ex' :: (Element (ViewR a) -> Element (ViewR a) -> Element (ViewR a)) -> ViewR a -> Element (ViewR a) Source #

headEx :: ViewR a -> Element (ViewR a) Source #

lastEx :: ViewR a -> Element (ViewR a) Source #

unsafeHead :: ViewR a -> Element (ViewR a) Source #

unsafeLast :: ViewR a -> Element (ViewR a) Source #

maximumByEx :: (Element (ViewR a) -> Element (ViewR a) -> Ordering) -> ViewR a -> Element (ViewR a) Source #

minimumByEx :: (Element (ViewR a) -> Element (ViewR a) -> Ordering) -> ViewR a -> Element (ViewR a) Source #

oelem :: Element (ViewR a) -> ViewR a -> Bool Source #

onotElem :: Element (ViewR a) -> ViewR a -> Bool Source #

Ord e => MonoFoldable (Set e) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Set e) -> m) -> Set e -> m Source #

ofoldr :: (Element (Set e) -> b -> b) -> b -> Set e -> b Source #

ofoldl' :: (a -> Element (Set e) -> a) -> a -> Set e -> a Source #

otoList :: Set e -> [Element (Set e)] Source #

oall :: (Element (Set e) -> Bool) -> Set e -> Bool Source #

oany :: (Element (Set e) -> Bool) -> Set e -> Bool Source #

onull :: Set e -> Bool Source #

olength :: Set e -> Int Source #

olength64 :: Set e -> Int64 Source #

ocompareLength :: Integral i => Set e -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Set e) -> f b) -> Set e -> f () Source #

ofor_ :: Applicative f => Set e -> (Element (Set e) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Set e) -> m ()) -> Set e -> m () Source #

oforM_ :: Applicative m => Set e -> (Element (Set e) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a -> Element (Set e) -> m a) -> a -> Set e -> m a Source #

ofoldMap1Ex :: Semigroup m => (Element (Set e) -> m) -> Set e -> m Source #

ofoldr1Ex :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) Source #

ofoldl1Ex' :: (Element (Set e) -> Element (Set e) -> Element (Set e)) -> Set e -> Element (Set e) Source #

headEx :: Set e -> Element (Set e) Source #

lastEx :: Set e -> Element (Set e) Source #

unsafeHead :: Set e -> Element (Set e) Source #

unsafeLast :: Set e -> Element (Set e) Source #

maximumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) Source #

minimumByEx :: (Element (Set e) -> Element (Set e) -> Ordering) -> Set e -> Element (Set e) Source #

oelem :: Element (Set e) -> Set e -> Bool Source #

onotElem :: Element (Set e) -> Set e -> Bool Source #

MonoFoldable (HashSet e) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (HashSet e) -> m) -> HashSet e -> m Source #

ofoldr :: (Element (HashSet e) -> b -> b) -> b -> HashSet e -> b Source #

ofoldl' :: (a -> Element (HashSet e) -> a) -> a -> HashSet e -> a Source #

otoList :: HashSet e -> [Element (HashSet e)] Source #

oall :: (Element (HashSet e) -> Bool) -> HashSet e -> Bool Source #

oany :: (Element (HashSet e) -> Bool) -> HashSet e -> Bool Source #

onull :: HashSet e -> Bool Source #

olength :: HashSet e -> Int Source #

olength64 :: HashSet e -> Int64 Source #

ocompareLength :: Integral i => HashSet e -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (HashSet e) -> f b) -> HashSet e -> f () Source #

ofor_ :: Applicative f => HashSet e -> (Element (HashSet e) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (HashSet e) -> m ()) -> HashSet e -> m () Source #

oforM_ :: Applicative m => HashSet e -> (Element (HashSet e) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a -> Element (HashSet e) -> m a) -> a -> HashSet e -> m a Source #

ofoldMap1Ex :: Semigroup m => (Element (HashSet e) -> m) -> HashSet e -> m Source #

ofoldr1Ex :: (Element (HashSet e) -> Element (HashSet e) -> Element (HashSet e)) -> HashSet e -> Element (HashSet e) Source #

ofoldl1Ex' :: (Element (HashSet e) -> Element (HashSet e) -> Element (HashSet e)) -> HashSet e -> Element (HashSet e) Source #

headEx :: HashSet e -> Element (HashSet e) Source #

lastEx :: HashSet e -> Element (HashSet e) Source #

unsafeHead :: HashSet e -> Element (HashSet e) Source #

unsafeLast :: HashSet e -> Element (HashSet e) Source #

maximumByEx :: (Element (HashSet e) -> Element (HashSet e) -> Ordering) -> HashSet e -> Element (HashSet e) Source #

minimumByEx :: (Element (HashSet e) -> Element (HashSet e) -> Ordering) -> HashSet e -> Element (HashSet e) Source #

oelem :: Element (HashSet e) -> HashSet e -> Bool Source #

onotElem :: Element (HashSet e) -> HashSet e -> Bool Source #

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

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Vector a) -> m) -> Vector a -> m Source #

ofoldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b Source #

ofoldl' :: (a0 -> Element (Vector a) -> a0) -> a0 -> Vector a -> a0 Source #

otoList :: Vector a -> [Element (Vector a)] Source #

oall :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

oany :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

onull :: Vector a -> Bool Source #

olength :: Vector a -> Int Source #

olength64 :: Vector a -> Int64 Source #

ocompareLength :: Integral i => Vector a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Vector a) -> f b) -> Vector a -> f () Source #

ofor_ :: Applicative f => Vector a -> (Element (Vector a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Vector a) -> m ()) -> Vector a -> m () Source #

oforM_ :: Applicative m => Vector a -> (Element (Vector a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Vector a) -> m a0) -> a0 -> Vector a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Vector a) -> m) -> Vector a -> m Source #

ofoldr1Ex :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Element (Vector a) Source #

ofoldl1Ex' :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Element (Vector a) Source #

headEx :: Vector a -> Element (Vector a) Source #

lastEx :: Vector a -> Element (Vector a) Source #

unsafeHead :: Vector a -> Element (Vector a) Source #

unsafeLast :: Vector a -> Element (Vector a) Source #

maximumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering) -> Vector a -> Element (Vector a) Source #

minimumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering) -> Vector a -> Element (Vector a) Source #

oelem :: Element (Vector a) -> Vector a -> Bool Source #

onotElem :: Element (Vector a) -> Vector a -> Bool Source #

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

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Vector a) -> m) -> Vector a -> m Source #

ofoldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b Source #

ofoldl' :: (a0 -> Element (Vector a) -> a0) -> a0 -> Vector a -> a0 Source #

otoList :: Vector a -> [Element (Vector a)] Source #

oall :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

oany :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

onull :: Vector a -> Bool Source #

olength :: Vector a -> Int Source #

olength64 :: Vector a -> Int64 Source #

ocompareLength :: Integral i => Vector a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Vector a) -> f b) -> Vector a -> f () Source #

ofor_ :: Applicative f => Vector a -> (Element (Vector a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Vector a) -> m ()) -> Vector a -> m () Source #

oforM_ :: Applicative m => Vector a -> (Element (Vector a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Vector a) -> m a0) -> a0 -> Vector a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Vector a) -> m) -> Vector a -> m Source #

ofoldr1Ex :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Element (Vector a) Source #

ofoldl1Ex' :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Element (Vector a) Source #

headEx :: Vector a -> Element (Vector a) Source #

lastEx :: Vector a -> Element (Vector a) Source #

unsafeHead :: Vector a -> Element (Vector a) Source #

unsafeLast :: Vector a -> Element (Vector a) Source #

maximumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering) -> Vector a -> Element (Vector a) Source #

minimumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering) -> Vector a -> Element (Vector a) Source #

oelem :: Element (Vector a) -> Vector a -> Bool Source #

onotElem :: Element (Vector a) -> Vector a -> Bool Source #

MonoFoldable (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Vector a) -> m) -> Vector a -> m Source #

ofoldr :: (Element (Vector a) -> b -> b) -> b -> Vector a -> b Source #

ofoldl' :: (a0 -> Element (Vector a) -> a0) -> a0 -> Vector a -> a0 Source #

otoList :: Vector a -> [Element (Vector a)] Source #

oall :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

oany :: (Element (Vector a) -> Bool) -> Vector a -> Bool Source #

onull :: Vector a -> Bool Source #

olength :: Vector a -> Int Source #

olength64 :: Vector a -> Int64 Source #

ocompareLength :: Integral i => Vector a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Vector a) -> f b) -> Vector a -> f () Source #

ofor_ :: Applicative f => Vector a -> (Element (Vector a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Vector a) -> m ()) -> Vector a -> m () Source #

oforM_ :: Applicative m => Vector a -> (Element (Vector a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Vector a) -> m a0) -> a0 -> Vector a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Vector a) -> m) -> Vector a -> m Source #

ofoldr1Ex :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Element (Vector a) Source #

ofoldl1Ex' :: (Element (Vector a) -> Element (Vector a) -> Element (Vector a)) -> Vector a -> Element (Vector a) Source #

headEx :: Vector a -> Element (Vector a) Source #

lastEx :: Vector a -> Element (Vector a) Source #

unsafeHead :: Vector a -> Element (Vector a) Source #

unsafeLast :: Vector a -> Element (Vector a) Source #

maximumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering) -> Vector a -> Element (Vector a) Source #

minimumByEx :: (Element (Vector a) -> Element (Vector a) -> Ordering) -> Vector a -> Element (Vector a) Source #

oelem :: Element (Vector a) -> Vector a -> Bool Source #

onotElem :: Element (Vector a) -> Vector a -> Bool 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 #

MonoFoldable (Either a b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Either a b) -> m) -> Either a b -> m Source #

ofoldr :: (Element (Either a b) -> b0 -> b0) -> b0 -> Either a b -> b0 Source #

ofoldl' :: (a0 -> Element (Either a b) -> a0) -> a0 -> Either a b -> a0 Source #

otoList :: Either a b -> [Element (Either a b)] Source #

oall :: (Element (Either a b) -> Bool) -> Either a b -> Bool Source #

oany :: (Element (Either a b) -> Bool) -> Either a b -> Bool Source #

onull :: Either a b -> Bool Source #

olength :: Either a b -> Int Source #

olength64 :: Either a b -> Int64 Source #

ocompareLength :: Integral i => Either a b -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Either a b) -> f b0) -> Either a b -> f () Source #

ofor_ :: Applicative f => Either a b -> (Element (Either a b) -> f b0) -> f () Source #

omapM_ :: Applicative m => (Element (Either a b) -> m ()) -> Either a b -> m () Source #

oforM_ :: Applicative m => Either a b -> (Element (Either a b) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Either a b) -> m a0) -> a0 -> Either a b -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Either a b) -> m) -> Either a b -> m Source #

ofoldr1Ex :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) Source #

ofoldl1Ex' :: (Element (Either a b) -> Element (Either a b) -> Element (Either a b)) -> Either a b -> Element (Either a b) Source #

headEx :: Either a b -> Element (Either a b) Source #

lastEx :: Either a b -> Element (Either a b) Source #

unsafeHead :: Either a b -> Element (Either a b) Source #

unsafeLast :: Either a b -> Element (Either a b) Source #

maximumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b) Source #

minimumByEx :: (Element (Either a b) -> Element (Either a b) -> Ordering) -> Either a b -> Element (Either a b) Source #

oelem :: Element (Either a b) -> Either a b -> Bool Source #

onotElem :: Element (Either a b) -> Either a b -> Bool Source #

MonoFoldable (V1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (V1 a) -> m) -> V1 a -> m Source #

ofoldr :: (Element (V1 a) -> b -> b) -> b -> V1 a -> b Source #

ofoldl' :: (a0 -> Element (V1 a) -> a0) -> a0 -> V1 a -> a0 Source #

otoList :: V1 a -> [Element (V1 a)] Source #

oall :: (Element (V1 a) -> Bool) -> V1 a -> Bool Source #

oany :: (Element (V1 a) -> Bool) -> V1 a -> Bool Source #

onull :: V1 a -> Bool Source #

olength :: V1 a -> Int Source #

olength64 :: V1 a -> Int64 Source #

ocompareLength :: Integral i => V1 a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (V1 a) -> f b) -> V1 a -> f () Source #

ofor_ :: Applicative f => V1 a -> (Element (V1 a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (V1 a) -> m ()) -> V1 a -> m () Source #

oforM_ :: Applicative m => V1 a -> (Element (V1 a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (V1 a) -> m a0) -> a0 -> V1 a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (V1 a) -> m) -> V1 a -> m Source #

ofoldr1Ex :: (Element (V1 a) -> Element (V1 a) -> Element (V1 a)) -> V1 a -> Element (V1 a) Source #

ofoldl1Ex' :: (Element (V1 a) -> Element (V1 a) -> Element (V1 a)) -> V1 a -> Element (V1 a) Source #

headEx :: V1 a -> Element (V1 a) Source #

lastEx :: V1 a -> Element (V1 a) Source #

unsafeHead :: V1 a -> Element (V1 a) Source #

unsafeLast :: V1 a -> Element (V1 a) Source #

maximumByEx :: (Element (V1 a) -> Element (V1 a) -> Ordering) -> V1 a -> Element (V1 a) Source #

minimumByEx :: (Element (V1 a) -> Element (V1 a) -> Ordering) -> V1 a -> Element (V1 a) Source #

oelem :: Element (V1 a) -> V1 a -> Bool Source #

onotElem :: Element (V1 a) -> V1 a -> Bool Source #

MonoFoldable (U1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (U1 a) -> m) -> U1 a -> m Source #

ofoldr :: (Element (U1 a) -> b -> b) -> b -> U1 a -> b Source #

ofoldl' :: (a0 -> Element (U1 a) -> a0) -> a0 -> U1 a -> a0 Source #

otoList :: U1 a -> [Element (U1 a)] Source #

oall :: (Element (U1 a) -> Bool) -> U1 a -> Bool Source #

oany :: (Element (U1 a) -> Bool) -> U1 a -> Bool Source #

onull :: U1 a -> Bool Source #

olength :: U1 a -> Int Source #

olength64 :: U1 a -> Int64 Source #

ocompareLength :: Integral i => U1 a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (U1 a) -> f b) -> U1 a -> f () Source #

ofor_ :: Applicative f => U1 a -> (Element (U1 a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (U1 a) -> m ()) -> U1 a -> m () Source #

oforM_ :: Applicative m => U1 a -> (Element (U1 a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (U1 a) -> m a0) -> a0 -> U1 a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (U1 a) -> m) -> U1 a -> m Source #

ofoldr1Ex :: (Element (U1 a) -> Element (U1 a) -> Element (U1 a)) -> U1 a -> Element (U1 a) Source #

ofoldl1Ex' :: (Element (U1 a) -> Element (U1 a) -> Element (U1 a)) -> U1 a -> Element (U1 a) Source #

headEx :: U1 a -> Element (U1 a) Source #

lastEx :: U1 a -> Element (U1 a) Source #

unsafeHead :: U1 a -> Element (U1 a) Source #

unsafeLast :: U1 a -> Element (U1 a) Source #

maximumByEx :: (Element (U1 a) -> Element (U1 a) -> Ordering) -> U1 a -> Element (U1 a) Source #

minimumByEx :: (Element (U1 a) -> Element (U1 a) -> Ordering) -> U1 a -> Element (U1 a) Source #

oelem :: Element (U1 a) -> U1 a -> Bool Source #

onotElem :: Element (U1 a) -> U1 a -> Bool Source #

MonoFoldable (a, b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (a, b) -> m) -> (a, b) -> m Source #

ofoldr :: (Element (a, b) -> b0 -> b0) -> b0 -> (a, b) -> b0 Source #

ofoldl' :: (a0 -> Element (a, b) -> a0) -> a0 -> (a, b) -> a0 Source #

otoList :: (a, b) -> [Element (a, b)] Source #

oall :: (Element (a, b) -> Bool) -> (a, b) -> Bool Source #

oany :: (Element (a, b) -> Bool) -> (a, b) -> Bool Source #

onull :: (a, b) -> Bool Source #

olength :: (a, b) -> Int Source #

olength64 :: (a, b) -> Int64 Source #

ocompareLength :: Integral i => (a, b) -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (a, b) -> f b0) -> (a, b) -> f () Source #

ofor_ :: Applicative f => (a, b) -> (Element (a, b) -> f b0) -> f () Source #

omapM_ :: Applicative m => (Element (a, b) -> m ()) -> (a, b) -> m () Source #

oforM_ :: Applicative m => (a, b) -> (Element (a, b) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (a, b) -> m a0) -> a0 -> (a, b) -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (a, b) -> m) -> (a, b) -> m Source #

ofoldr1Ex :: (Element (a, b) -> Element (a, b) -> Element (a, b)) -> (a, b) -> Element (a, b) Source #

ofoldl1Ex' :: (Element (a, b) -> Element (a, b) -> Element (a, b)) -> (a, b) -> Element (a, b) Source #

headEx :: (a, b) -> Element (a, b) Source #

lastEx :: (a, b) -> Element (a, b) Source #

unsafeHead :: (a, b) -> Element (a, b) Source #

unsafeLast :: (a, b) -> Element (a, b) Source #

maximumByEx :: (Element (a, b) -> Element (a, b) -> Ordering) -> (a, b) -> Element (a, b) Source #

minimumByEx :: (Element (a, b) -> Element (a, b) -> Ordering) -> (a, b) -> Element (a, b) Source #

oelem :: Element (a, b) -> (a, b) -> Bool Source #

onotElem :: Element (a, b) -> (a, b) -> Bool Source #

MonoFoldable (Proxy a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Proxy a) -> m) -> Proxy a -> m Source #

ofoldr :: (Element (Proxy a) -> b -> b) -> b -> Proxy a -> b Source #

ofoldl' :: (a0 -> Element (Proxy a) -> a0) -> a0 -> Proxy a -> a0 Source #

otoList :: Proxy a -> [Element (Proxy a)] Source #

oall :: (Element (Proxy a) -> Bool) -> Proxy a -> Bool Source #

oany :: (Element (Proxy a) -> Bool) -> Proxy a -> Bool Source #

onull :: Proxy a -> Bool Source #

olength :: Proxy a -> Int Source #

olength64 :: Proxy a -> Int64 Source #

ocompareLength :: Integral i => Proxy a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Proxy a) -> f b) -> Proxy a -> f () Source #

ofor_ :: Applicative f => Proxy a -> (Element (Proxy a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Proxy a) -> m ()) -> Proxy a -> m () Source #

oforM_ :: Applicative m => Proxy a -> (Element (Proxy a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Proxy a) -> m a0) -> a0 -> Proxy a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Proxy a) -> m) -> Proxy a -> m Source #

ofoldr1Ex :: (Element (Proxy a) -> Element (Proxy a) -> Element (Proxy a)) -> Proxy a -> Element (Proxy a) Source #

ofoldl1Ex' :: (Element (Proxy a) -> Element (Proxy a) -> Element (Proxy a)) -> Proxy a -> Element (Proxy a) Source #

headEx :: Proxy a -> Element (Proxy a) Source #

lastEx :: Proxy a -> Element (Proxy a) Source #

unsafeHead :: Proxy a -> Element (Proxy a) Source #

unsafeLast :: Proxy a -> Element (Proxy a) Source #

maximumByEx :: (Element (Proxy a) -> Element (Proxy a) -> Ordering) -> Proxy a -> Element (Proxy a) Source #

minimumByEx :: (Element (Proxy a) -> Element (Proxy a) -> Ordering) -> Proxy a -> Element (Proxy a) Source #

oelem :: Element (Proxy a) -> Proxy a -> Bool Source #

onotElem :: Element (Proxy a) -> Proxy a -> Bool Source #

MonoFoldable (Map k v) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Map k v) -> m) -> Map k v -> m Source #

ofoldr :: (Element (Map k v) -> b -> b) -> b -> Map k v -> b Source #

ofoldl' :: (a -> Element (Map k v) -> a) -> a -> Map k v -> a Source #

otoList :: Map k v -> [Element (Map k v)] Source #

oall :: (Element (Map k v) -> Bool) -> Map k v -> Bool Source #

oany :: (Element (Map k v) -> Bool) -> Map k v -> Bool Source #

onull :: Map k v -> Bool Source #

olength :: Map k v -> Int Source #

olength64 :: Map k v -> Int64 Source #

ocompareLength :: Integral i => Map k v -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Map k v) -> f b) -> Map k v -> f () Source #

ofor_ :: Applicative f => Map k v -> (Element (Map k v) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (Map k v) -> m ()) -> Map k v -> m () Source #

oforM_ :: Applicative m => Map k v -> (Element (Map k v) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a -> Element (Map k v) -> m a) -> a -> Map k v -> m a Source #

ofoldMap1Ex :: Semigroup m => (Element (Map k v) -> m) -> Map k v -> m Source #

ofoldr1Ex :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) Source #

ofoldl1Ex' :: (Element (Map k v) -> Element (Map k v) -> Element (Map k v)) -> Map k v -> Element (Map k v) Source #

headEx :: Map k v -> Element (Map k v) Source #

lastEx :: Map k v -> Element (Map k v) Source #

unsafeHead :: Map k v -> Element (Map k v) Source #

unsafeLast :: Map k v -> Element (Map k v) Source #

maximumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) Source #

minimumByEx :: (Element (Map k v) -> Element (Map k v) -> Ordering) -> Map k v -> Element (Map k v) Source #

oelem :: Element (Map k v) -> Map k v -> Bool Source #

onotElem :: Element (Map k v) -> Map k v -> Bool Source #

Foldable f => MonoFoldable (MaybeT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (MaybeT f a) -> m) -> MaybeT f a -> m Source #

ofoldr :: (Element (MaybeT f a) -> b -> b) -> b -> MaybeT f a -> b Source #

ofoldl' :: (a0 -> Element (MaybeT f a) -> a0) -> a0 -> MaybeT f a -> a0 Source #

otoList :: MaybeT f a -> [Element (MaybeT f a)] Source #

oall :: (Element (MaybeT f a) -> Bool) -> MaybeT f a -> Bool Source #

oany :: (Element (MaybeT f a) -> Bool) -> MaybeT f a -> Bool Source #

onull :: MaybeT f a -> Bool Source #

olength :: MaybeT f a -> Int Source #

olength64 :: MaybeT f a -> Int64 Source #

ocompareLength :: Integral i => MaybeT f a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (MaybeT f a) -> f0 b) -> MaybeT f a -> f0 () Source #

ofor_ :: Applicative f0 => MaybeT f a -> (Element (MaybeT f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (MaybeT f a) -> m ()) -> MaybeT f a -> m () Source #

oforM_ :: Applicative m => MaybeT f a -> (Element (MaybeT f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (MaybeT f a) -> m a0) -> a0 -> MaybeT f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (MaybeT f a) -> m) -> MaybeT f a -> m Source #

ofoldr1Ex :: (Element (MaybeT f a) -> Element (MaybeT f a) -> Element (MaybeT f a)) -> MaybeT f a -> Element (MaybeT f a) Source #

ofoldl1Ex' :: (Element (MaybeT f a) -> Element (MaybeT f a) -> Element (MaybeT f a)) -> MaybeT f a -> Element (MaybeT f a) Source #

headEx :: MaybeT f a -> Element (MaybeT f a) Source #

lastEx :: MaybeT f a -> Element (MaybeT f a) Source #

unsafeHead :: MaybeT f a -> Element (MaybeT f a) Source #

unsafeLast :: MaybeT f a -> Element (MaybeT f a) Source #

maximumByEx :: (Element (MaybeT f a) -> Element (MaybeT f a) -> Ordering) -> MaybeT f a -> Element (MaybeT f a) Source #

minimumByEx :: (Element (MaybeT f a) -> Element (MaybeT f a) -> Ordering) -> MaybeT f a -> Element (MaybeT f a) Source #

oelem :: Element (MaybeT f a) -> MaybeT f a -> Bool Source #

onotElem :: Element (MaybeT f a) -> MaybeT f a -> Bool Source #

Foldable f => MonoFoldable (ListT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (ListT f a) -> m) -> ListT f a -> m Source #

ofoldr :: (Element (ListT f a) -> b -> b) -> b -> ListT f a -> b Source #

ofoldl' :: (a0 -> Element (ListT f a) -> a0) -> a0 -> ListT f a -> a0 Source #

otoList :: ListT f a -> [Element (ListT f a)] Source #

oall :: (Element (ListT f a) -> Bool) -> ListT f a -> Bool Source #

oany :: (Element (ListT f a) -> Bool) -> ListT f a -> Bool Source #

onull :: ListT f a -> Bool Source #

olength :: ListT f a -> Int Source #

olength64 :: ListT f a -> Int64 Source #

ocompareLength :: Integral i => ListT f a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (ListT f a) -> f0 b) -> ListT f a -> f0 () Source #

ofor_ :: Applicative f0 => ListT f a -> (Element (ListT f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (ListT f a) -> m ()) -> ListT f a -> m () Source #

oforM_ :: Applicative m => ListT f a -> (Element (ListT f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (ListT f a) -> m a0) -> a0 -> ListT f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (ListT f a) -> m) -> ListT f a -> m Source #

ofoldr1Ex :: (Element (ListT f a) -> Element (ListT f a) -> Element (ListT f a)) -> ListT f a -> Element (ListT f a) Source #

ofoldl1Ex' :: (Element (ListT f a) -> Element (ListT f a) -> Element (ListT f a)) -> ListT f a -> Element (ListT f a) Source #

headEx :: ListT f a -> Element (ListT f a) Source #

lastEx :: ListT f a -> Element (ListT f a) Source #

unsafeHead :: ListT f a -> Element (ListT f a) Source #

unsafeLast :: ListT f a -> Element (ListT f a) Source #

maximumByEx :: (Element (ListT f a) -> Element (ListT f a) -> Ordering) -> ListT f a -> Element (ListT f a) Source #

minimumByEx :: (Element (ListT f a) -> Element (ListT f a) -> Ordering) -> ListT f a -> Element (ListT f a) Source #

oelem :: Element (ListT f a) -> ListT f a -> Bool Source #

onotElem :: Element (ListT f a) -> ListT f a -> Bool Source #

MonoFoldable (HashMap k v) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (HashMap k v) -> m) -> HashMap k v -> m Source #

ofoldr :: (Element (HashMap k v) -> b -> b) -> b -> HashMap k v -> b Source #

ofoldl' :: (a -> Element (HashMap k v) -> a) -> a -> HashMap k v -> a Source #

otoList :: HashMap k v -> [Element (HashMap k v)] Source #

oall :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Bool Source #

oany :: (Element (HashMap k v) -> Bool) -> HashMap k v -> Bool Source #

onull :: HashMap k v -> Bool Source #

olength :: HashMap k v -> Int Source #

olength64 :: HashMap k v -> Int64 Source #

ocompareLength :: Integral i => HashMap k v -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (HashMap k v) -> f b) -> HashMap k v -> f () Source #

ofor_ :: Applicative f => HashMap k v -> (Element (HashMap k v) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (HashMap k v) -> m ()) -> HashMap k v -> m () Source #

oforM_ :: Applicative m => HashMap k v -> (Element (HashMap k v) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a -> Element (HashMap k v) -> m a) -> a -> HashMap k v -> m a Source #

ofoldMap1Ex :: Semigroup m => (Element (HashMap k v) -> m) -> HashMap k v -> m Source #

ofoldr1Ex :: (Element (HashMap k v) -> Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> Element (HashMap k v) Source #

ofoldl1Ex' :: (Element (HashMap k v) -> Element (HashMap k v) -> Element (HashMap k v)) -> HashMap k v -> Element (HashMap k v) Source #

headEx :: HashMap k v -> Element (HashMap k v) Source #

lastEx :: HashMap k v -> Element (HashMap k v) Source #

unsafeHead :: HashMap k v -> Element (HashMap k v) Source #

unsafeLast :: HashMap k v -> Element (HashMap k v) Source #

maximumByEx :: (Element (HashMap k v) -> Element (HashMap k v) -> Ordering) -> HashMap k v -> Element (HashMap k v) Source #

minimumByEx :: (Element (HashMap k v) -> Element (HashMap k v) -> Ordering) -> HashMap k v -> Element (HashMap k v) Source #

oelem :: Element (HashMap k v) -> HashMap k v -> Bool Source #

onotElem :: Element (HashMap k v) -> HashMap k v -> Bool Source #

Foldable f => MonoFoldable (Rec1 f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Rec1 f a) -> m) -> Rec1 f a -> m Source #

ofoldr :: (Element (Rec1 f a) -> b -> b) -> b -> Rec1 f a -> b Source #

ofoldl' :: (a0 -> Element (Rec1 f a) -> a0) -> a0 -> Rec1 f a -> a0 Source #

otoList :: Rec1 f a -> [Element (Rec1 f a)] Source #

oall :: (Element (Rec1 f a) -> Bool) -> Rec1 f a -> Bool Source #

oany :: (Element (Rec1 f a) -> Bool) -> Rec1 f a -> Bool Source #

onull :: Rec1 f a -> Bool Source #

olength :: Rec1 f a -> Int Source #

olength64 :: Rec1 f a -> Int64 Source #

ocompareLength :: Integral i => Rec1 f a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (Rec1 f a) -> f0 b) -> Rec1 f a -> f0 () Source #

ofor_ :: Applicative f0 => Rec1 f a -> (Element (Rec1 f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (Rec1 f a) -> m ()) -> Rec1 f a -> m () Source #

oforM_ :: Applicative m => Rec1 f a -> (Element (Rec1 f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Rec1 f a) -> m a0) -> a0 -> Rec1 f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Rec1 f a) -> m) -> Rec1 f a -> m Source #

ofoldr1Ex :: (Element (Rec1 f a) -> Element (Rec1 f a) -> Element (Rec1 f a)) -> Rec1 f a -> Element (Rec1 f a) Source #

ofoldl1Ex' :: (Element (Rec1 f a) -> Element (Rec1 f a) -> Element (Rec1 f a)) -> Rec1 f a -> Element (Rec1 f a) Source #

headEx :: Rec1 f a -> Element (Rec1 f a) Source #

lastEx :: Rec1 f a -> Element (Rec1 f a) Source #

unsafeHead :: Rec1 f a -> Element (Rec1 f a) Source #

unsafeLast :: Rec1 f a -> Element (Rec1 f a) Source #

maximumByEx :: (Element (Rec1 f a) -> Element (Rec1 f a) -> Ordering) -> Rec1 f a -> Element (Rec1 f a) Source #

minimumByEx :: (Element (Rec1 f a) -> Element (Rec1 f a) -> Ordering) -> Rec1 f a -> Element (Rec1 f a) Source #

oelem :: Element (Rec1 f a) -> Rec1 f a -> Bool Source #

onotElem :: Element (Rec1 f a) -> Rec1 f a -> Bool Source #

MonoFoldable (Const m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m0 => (Element (Const m a) -> m0) -> Const m a -> m0 Source #

ofoldr :: (Element (Const m a) -> b -> b) -> b -> Const m a -> b Source #

ofoldl' :: (a0 -> Element (Const m a) -> a0) -> a0 -> Const m a -> a0 Source #

otoList :: Const m a -> [Element (Const m a)] Source #

oall :: (Element (Const m a) -> Bool) -> Const m a -> Bool Source #

oany :: (Element (Const m a) -> Bool) -> Const m a -> Bool Source #

onull :: Const m a -> Bool Source #

olength :: Const m a -> Int Source #

olength64 :: Const m a -> Int64 Source #

ocompareLength :: Integral i => Const m a -> i -> Ordering Source #

otraverse_ :: Applicative f => (Element (Const m a) -> f b) -> Const m a -> f () Source #

ofor_ :: Applicative f => Const m a -> (Element (Const m a) -> f b) -> f () Source #

omapM_ :: Applicative m0 => (Element (Const m a) -> m0 ()) -> Const m a -> m0 () Source #

oforM_ :: Applicative m0 => Const m a -> (Element (Const m a) -> m0 ()) -> m0 () Source #

ofoldlM :: Monad m0 => (a0 -> Element (Const m a) -> m0 a0) -> a0 -> Const m a -> m0 a0 Source #

ofoldMap1Ex :: Semigroup m0 => (Element (Const m a) -> m0) -> Const m a -> m0 Source #

ofoldr1Ex :: (Element (Const m a) -> Element (Const m a) -> Element (Const m a)) -> Const m a -> Element (Const m a) Source #

ofoldl1Ex' :: (Element (Const m a) -> Element (Const m a) -> Element (Const m a)) -> Const m a -> Element (Const m a) Source #

headEx :: Const m a -> Element (Const m a) Source #

lastEx :: Const m a -> Element (Const m a) Source #

unsafeHead :: Const m a -> Element (Const m a) Source #

unsafeLast :: Const m a -> Element (Const m a) Source #

maximumByEx :: (Element (Const m a) -> Element (Const m a) -> Ordering) -> Const m a -> Element (Const m a) Source #

minimumByEx :: (Element (Const m a) -> Element (Const m a) -> Ordering) -> Const m a -> Element (Const m a) Source #

oelem :: Element (Const m a) -> Const m a -> Bool Source #

onotElem :: Element (Const m a) -> Const m a -> Bool Source #

Foldable f => MonoFoldable (WriterT w f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (WriterT w f a) -> m) -> WriterT w f a -> m Source #

ofoldr :: (Element (WriterT w f a) -> b -> b) -> b -> WriterT w f a -> b Source #

ofoldl' :: (a0 -> Element (WriterT w f a) -> a0) -> a0 -> WriterT w f a -> a0 Source #

otoList :: WriterT w f a -> [Element (WriterT w f a)] Source #

oall :: (Element (WriterT w f a) -> Bool) -> WriterT w f a -> Bool Source #

oany :: (Element (WriterT w f a) -> Bool) -> WriterT w f a -> Bool Source #

onull :: WriterT w f a -> Bool Source #

olength :: WriterT w f a -> Int Source #

olength64 :: WriterT w f a -> Int64 Source #

ocompareLength :: Integral i => WriterT w f a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (WriterT w f a) -> f0 b) -> WriterT w f a -> f0 () Source #

ofor_ :: Applicative f0 => WriterT w f a -> (Element (WriterT w f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (WriterT w f a) -> m ()) -> WriterT w f a -> m () Source #

oforM_ :: Applicative m => WriterT w f a -> (Element (WriterT w f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (WriterT w f a) -> m a0) -> a0 -> WriterT w f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (WriterT w f a) -> m) -> WriterT w f a -> m Source #

ofoldr1Ex :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Element (WriterT w f a)) -> WriterT w f a -> Element (WriterT w f a) Source #

ofoldl1Ex' :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Element (WriterT w f a)) -> WriterT w f a -> Element (WriterT w f a) Source #

headEx :: WriterT w f a -> Element (WriterT w f a) Source #

lastEx :: WriterT w f a -> Element (WriterT w f a) Source #

unsafeHead :: WriterT w f a -> Element (WriterT w f a) Source #

unsafeLast :: WriterT w f a -> Element (WriterT w f a) Source #

maximumByEx :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Ordering) -> WriterT w f a -> Element (WriterT w f a) Source #

minimumByEx :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Ordering) -> WriterT w f a -> Element (WriterT w f a) Source #

oelem :: Element (WriterT w f a) -> WriterT w f a -> Bool Source #

onotElem :: Element (WriterT w f a) -> WriterT w f a -> Bool Source #

Foldable f => MonoFoldable (WriterT w f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (WriterT w f a) -> m) -> WriterT w f a -> m Source #

ofoldr :: (Element (WriterT w f a) -> b -> b) -> b -> WriterT w f a -> b Source #

ofoldl' :: (a0 -> Element (WriterT w f a) -> a0) -> a0 -> WriterT w f a -> a0 Source #

otoList :: WriterT w f a -> [Element (WriterT w f a)] Source #

oall :: (Element (WriterT w f a) -> Bool) -> WriterT w f a -> Bool Source #

oany :: (Element (WriterT w f a) -> Bool) -> WriterT w f a -> Bool Source #

onull :: WriterT w f a -> Bool Source #

olength :: WriterT w f a -> Int Source #

olength64 :: WriterT w f a -> Int64 Source #

ocompareLength :: Integral i => WriterT w f a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (WriterT w f a) -> f0 b) -> WriterT w f a -> f0 () Source #

ofor_ :: Applicative f0 => WriterT w f a -> (Element (WriterT w f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (WriterT w f a) -> m ()) -> WriterT w f a -> m () Source #

oforM_ :: Applicative m => WriterT w f a -> (Element (WriterT w f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (WriterT w f a) -> m a0) -> a0 -> WriterT w f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (WriterT w f a) -> m) -> WriterT w f a -> m Source #

ofoldr1Ex :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Element (WriterT w f a)) -> WriterT w f a -> Element (WriterT w f a) Source #

ofoldl1Ex' :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Element (WriterT w f a)) -> WriterT w f a -> Element (WriterT w f a) Source #

headEx :: WriterT w f a -> Element (WriterT w f a) Source #

lastEx :: WriterT w f a -> Element (WriterT w f a) Source #

unsafeHead :: WriterT w f a -> Element (WriterT w f a) Source #

unsafeLast :: WriterT w f a -> Element (WriterT w f a) Source #

maximumByEx :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Ordering) -> WriterT w f a -> Element (WriterT w f a) Source #

minimumByEx :: (Element (WriterT w f a) -> Element (WriterT w f a) -> Ordering) -> WriterT w f a -> Element (WriterT w f a) Source #

oelem :: Element (WriterT w f a) -> WriterT w f a -> Bool Source #

onotElem :: Element (WriterT w f a) -> WriterT w f a -> Bool Source #

Foldable f => MonoFoldable (IdentityT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (IdentityT f a) -> m) -> IdentityT f a -> m Source #

ofoldr :: (Element (IdentityT f a) -> b -> b) -> b -> IdentityT f a -> b Source #

ofoldl' :: (a0 -> Element (IdentityT f a) -> a0) -> a0 -> IdentityT f a -> a0 Source #

otoList :: IdentityT f a -> [Element (IdentityT f a)] Source #

oall :: (Element (IdentityT f a) -> Bool) -> IdentityT f a -> Bool Source #

oany :: (Element (IdentityT f a) -> Bool) -> IdentityT f a -> Bool Source #

onull :: IdentityT f a -> Bool Source #

olength :: IdentityT f a -> Int Source #

olength64 :: IdentityT f a -> Int64 Source #

ocompareLength :: Integral i => IdentityT f a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (IdentityT f a) -> f0 b) -> IdentityT f a -> f0 () Source #

ofor_ :: Applicative f0 => IdentityT f a -> (Element (IdentityT f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (IdentityT f a) -> m ()) -> IdentityT f a -> m () Source #

oforM_ :: Applicative m => IdentityT f a -> (Element (IdentityT f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (IdentityT f a) -> m a0) -> a0 -> IdentityT f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (IdentityT f a) -> m) -> IdentityT f a -> m Source #

ofoldr1Ex :: (Element (IdentityT f a) -> Element (IdentityT f a) -> Element (IdentityT f a)) -> IdentityT f a -> Element (IdentityT f a) Source #

ofoldl1Ex' :: (Element (IdentityT f a) -> Element (IdentityT f a) -> Element (IdentityT f a)) -> IdentityT f a -> Element (IdentityT f a) Source #

headEx :: IdentityT f a -> Element (IdentityT f a) Source #

lastEx :: IdentityT f a -> Element (IdentityT f a) Source #

unsafeHead :: IdentityT f a -> Element (IdentityT f a) Source #

unsafeLast :: IdentityT f a -> Element (IdentityT f a) Source #

maximumByEx :: (Element (IdentityT f a) -> Element (IdentityT f a) -> Ordering) -> IdentityT f a -> Element (IdentityT f a) Source #

minimumByEx :: (Element (IdentityT f a) -> Element (IdentityT f a) -> Ordering) -> IdentityT f a -> Element (IdentityT f a) Source #

oelem :: Element (IdentityT f a) -> IdentityT f a -> Bool Source #

onotElem :: Element (IdentityT f a) -> IdentityT f a -> Bool Source #

MonoFoldable (K1 i c a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (K1 i c a) -> m) -> K1 i c a -> m Source #

ofoldr :: (Element (K1 i c a) -> b -> b) -> b -> K1 i c a -> b Source #

ofoldl' :: (a0 -> Element (K1 i c a) -> a0) -> a0 -> K1 i c a -> a0 Source #

otoList :: K1 i c a -> [Element (K1 i c a)] Source #

oall :: (Element (K1 i c a) -> Bool) -> K1 i c a -> Bool Source #

oany :: (Element (K1 i c a) -> Bool) -> K1 i c a -> Bool Source #

onull :: K1 i c a -> Bool Source #

olength :: K1 i c a -> Int Source #

olength64 :: K1 i c a -> Int64 Source #

ocompareLength :: Integral i0 => K1 i c a -> i0 -> Ordering Source #

otraverse_ :: Applicative f => (Element (K1 i c a) -> f b) -> K1 i c a -> f () Source #

ofor_ :: Applicative f => K1 i c a -> (Element (K1 i c a) -> f b) -> f () Source #

omapM_ :: Applicative m => (Element (K1 i c a) -> m ()) -> K1 i c a -> m () Source #

oforM_ :: Applicative m => K1 i c a -> (Element (K1 i c a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (K1 i c a) -> m a0) -> a0 -> K1 i c a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (K1 i c a) -> m) -> K1 i c a -> m Source #

ofoldr1Ex :: (Element (K1 i c a) -> Element (K1 i c a) -> Element (K1 i c a)) -> K1 i c a -> Element (K1 i c a) Source #

ofoldl1Ex' :: (Element (K1 i c a) -> Element (K1 i c a) -> Element (K1 i c a)) -> K1 i c a -> Element (K1 i c a) Source #

headEx :: K1 i c a -> Element (K1 i c a) Source #

lastEx :: K1 i c a -> Element (K1 i c a) Source #

unsafeHead :: K1 i c a -> Element (K1 i c a) Source #

unsafeLast :: K1 i c a -> Element (K1 i c a) Source #

maximumByEx :: (Element (K1 i c a) -> Element (K1 i c a) -> Ordering) -> K1 i c a -> Element (K1 i c a) Source #

minimumByEx :: (Element (K1 i c a) -> Element (K1 i c a) -> Ordering) -> K1 i c a -> Element (K1 i c a) Source #

oelem :: Element (K1 i c a) -> K1 i c a -> Bool Source #

onotElem :: Element (K1 i c a) -> K1 i c a -> Bool Source #

(Foldable f, Foldable g) => MonoFoldable ((f :+: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element ((f :+: g) a) -> m) -> (f :+: g) a -> m Source #

ofoldr :: (Element ((f :+: g) a) -> b -> b) -> b -> (f :+: g) a -> b Source #

ofoldl' :: (a0 -> Element ((f :+: g) a) -> a0) -> a0 -> (f :+: g) a -> a0 Source #

otoList :: (f :+: g) a -> [Element ((f :+: g) a)] Source #

oall :: (Element ((f :+: g) a) -> Bool) -> (f :+: g) a -> Bool Source #

oany :: (Element ((f :+: g) a) -> Bool) -> (f :+: g) a -> Bool Source #

onull :: (f :+: g) a -> Bool Source #

olength :: (f :+: g) a -> Int Source #

olength64 :: (f :+: g) a -> Int64 Source #

ocompareLength :: Integral i => (f :+: g) a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element ((f :+: g) a) -> f0 b) -> (f :+: g) a -> f0 () Source #

ofor_ :: Applicative f0 => (f :+: g) a -> (Element ((f :+: g) a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element ((f :+: g) a) -> m ()) -> (f :+: g) a -> m () Source #

oforM_ :: Applicative m => (f :+: g) a -> (Element ((f :+: g) a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element ((f :+: g) a) -> m a0) -> a0 -> (f :+: g) a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element ((f :+: g) a) -> m) -> (f :+: g) a -> m Source #

ofoldr1Ex :: (Element ((f :+: g) a) -> Element ((f :+: g) a) -> Element ((f :+: g) a)) -> (f :+: g) a -> Element ((f :+: g) a) Source #

ofoldl1Ex' :: (Element ((f :+: g) a) -> Element ((f :+: g) a) -> Element ((f :+: g) a)) -> (f :+: g) a -> Element ((f :+: g) a) Source #

headEx :: (f :+: g) a -> Element ((f :+: g) a) Source #

lastEx :: (f :+: g) a -> Element ((f :+: g) a) Source #

unsafeHead :: (f :+: g) a -> Element ((f :+: g) a) Source #

unsafeLast :: (f :+: g) a -> Element ((f :+: g) a) Source #

maximumByEx :: (Element ((f :+: g) a) -> Element ((f :+: g) a) -> Ordering) -> (f :+: g) a -> Element ((f :+: g) a) Source #

minimumByEx :: (Element ((f :+: g) a) -> Element ((f :+: g) a) -> Ordering) -> (f :+: g) a -> Element ((f :+: g) a) Source #

oelem :: Element ((f :+: g) a) -> (f :+: g) a -> Bool Source #

onotElem :: Element ((f :+: g) a) -> (f :+: g) a -> Bool Source #

(Foldable f, Foldable g) => MonoFoldable ((f :*: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element ((f :*: g) a) -> m) -> (f :*: g) a -> m Source #

ofoldr :: (Element ((f :*: g) a) -> b -> b) -> b -> (f :*: g) a -> b Source #

ofoldl' :: (a0 -> Element ((f :*: g) a) -> a0) -> a0 -> (f :*: g) a -> a0 Source #

otoList :: (f :*: g) a -> [Element ((f :*: g) a)] Source #

oall :: (Element ((f :*: g) a) -> Bool) -> (f :*: g) a -> Bool Source #

oany :: (Element ((f :*: g) a) -> Bool) -> (f :*: g) a -> Bool Source #

onull :: (f :*: g) a -> Bool Source #

olength :: (f :*: g) a -> Int Source #

olength64 :: (f :*: g) a -> Int64 Source #

ocompareLength :: Integral i => (f :*: g) a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element ((f :*: g) a) -> f0 b) -> (f :*: g) a -> f0 () Source #

ofor_ :: Applicative f0 => (f :*: g) a -> (Element ((f :*: g) a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element ((f :*: g) a) -> m ()) -> (f :*: g) a -> m () Source #

oforM_ :: Applicative m => (f :*: g) a -> (Element ((f :*: g) a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element ((f :*: g) a) -> m a0) -> a0 -> (f :*: g) a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element ((f :*: g) a) -> m) -> (f :*: g) a -> m Source #

ofoldr1Ex :: (Element ((f :*: g) a) -> Element ((f :*: g) a) -> Element ((f :*: g) a)) -> (f :*: g) a -> Element ((f :*: g) a) Source #

ofoldl1Ex' :: (Element ((f :*: g) a) -> Element ((f :*: g) a) -> Element ((f :*: g) a)) -> (f :*: g) a -> Element ((f :*: g) a) Source #

headEx :: (f :*: g) a -> Element ((f :*: g) a) Source #

lastEx :: (f :*: g) a -> Element ((f :*: g) a) Source #

unsafeHead :: (f :*: g) a -> Element ((f :*: g) a) Source #

unsafeLast :: (f :*: g) a -> Element ((f :*: g) a) Source #

maximumByEx :: (Element ((f :*: g) a) -> Element ((f :*: g) a) -> Ordering) -> (f :*: g) a -> Element ((f :*: g) a) Source #

minimumByEx :: (Element ((f :*: g) a) -> Element ((f :*: g) a) -> Ordering) -> (f :*: g) a -> Element ((f :*: g) a) Source #

oelem :: Element ((f :*: g) a) -> (f :*: g) a -> Bool Source #

onotElem :: Element ((f :*: g) a) -> (f :*: g) a -> Bool Source #

(Foldable f, Foldable g) => MonoFoldable (Product f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Product f g a) -> m) -> Product f g a -> m Source #

ofoldr :: (Element (Product f g a) -> b -> b) -> b -> Product f g a -> b Source #

ofoldl' :: (a0 -> Element (Product f g a) -> a0) -> a0 -> Product f g a -> a0 Source #

otoList :: Product f g a -> [Element (Product f g a)] Source #

oall :: (Element (Product f g a) -> Bool) -> Product f g a -> Bool Source #

oany :: (Element (Product f g a) -> Bool) -> Product f g a -> Bool Source #

onull :: Product f g a -> Bool Source #

olength :: Product f g a -> Int Source #

olength64 :: Product f g a -> Int64 Source #

ocompareLength :: Integral i => Product f g a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (Product f g a) -> f0 b) -> Product f g a -> f0 () Source #

ofor_ :: Applicative f0 => Product f g a -> (Element (Product f g a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (Product f g a) -> m ()) -> Product f g a -> m () Source #

oforM_ :: Applicative m => Product f g a -> (Element (Product f g a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Product f g a) -> m a0) -> a0 -> Product f g a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Product f g a) -> m) -> Product f g a -> m Source #

ofoldr1Ex :: (Element (Product f g a) -> Element (Product f g a) -> Element (Product f g a)) -> Product f g a -> Element (Product f g a) Source #

ofoldl1Ex' :: (Element (Product f g a) -> Element (Product f g a) -> Element (Product f g a)) -> Product f g a -> Element (Product f g a) Source #

headEx :: Product f g a -> Element (Product f g a) Source #

lastEx :: Product f g a -> Element (Product f g a) Source #

unsafeHead :: Product f g a -> Element (Product f g a) Source #

unsafeLast :: Product f g a -> Element (Product f g a) Source #

maximumByEx :: (Element (Product f g a) -> Element (Product f g a) -> Ordering) -> Product f g a -> Element (Product f g a) Source #

minimumByEx :: (Element (Product f g a) -> Element (Product f g a) -> Ordering) -> Product f g a -> Element (Product f g a) Source #

oelem :: Element (Product f g a) -> Product f g a -> Bool Source #

onotElem :: Element (Product f g a) -> Product f g a -> Bool Source #

Foldable f => MonoFoldable (M1 i c f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (M1 i c f a) -> m) -> M1 i c f a -> m Source #

ofoldr :: (Element (M1 i c f a) -> b -> b) -> b -> M1 i c f a -> b Source #

ofoldl' :: (a0 -> Element (M1 i c f a) -> a0) -> a0 -> M1 i c f a -> a0 Source #

otoList :: M1 i c f a -> [Element (M1 i c f a)] Source #

oall :: (Element (M1 i c f a) -> Bool) -> M1 i c f a -> Bool Source #

oany :: (Element (M1 i c f a) -> Bool) -> M1 i c f a -> Bool Source #

onull :: M1 i c f a -> Bool Source #

olength :: M1 i c f a -> Int Source #

olength64 :: M1 i c f a -> Int64 Source #

ocompareLength :: Integral i0 => M1 i c f a -> i0 -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (M1 i c f a) -> f0 b) -> M1 i c f a -> f0 () Source #

ofor_ :: Applicative f0 => M1 i c f a -> (Element (M1 i c f a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (M1 i c f a) -> m ()) -> M1 i c f a -> m () Source #

oforM_ :: Applicative m => M1 i c f a -> (Element (M1 i c f a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (M1 i c f a) -> m a0) -> a0 -> M1 i c f a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (M1 i c f a) -> m) -> M1 i c f a -> m Source #

ofoldr1Ex :: (Element (M1 i c f a) -> Element (M1 i c f a) -> Element (M1 i c f a)) -> M1 i c f a -> Element (M1 i c f a) Source #

ofoldl1Ex' :: (Element (M1 i c f a) -> Element (M1 i c f a) -> Element (M1 i c f a)) -> M1 i c f a -> Element (M1 i c f a) Source #

headEx :: M1 i c f a -> Element (M1 i c f a) Source #

lastEx :: M1 i c f a -> Element (M1 i c f a) Source #

unsafeHead :: M1 i c f a -> Element (M1 i c f a) Source #

unsafeLast :: M1 i c f a -> Element (M1 i c f a) Source #

maximumByEx :: (Element (M1 i c f a) -> Element (M1 i c f a) -> Ordering) -> M1 i c f a -> Element (M1 i c f a) Source #

minimumByEx :: (Element (M1 i c f a) -> Element (M1 i c f a) -> Ordering) -> M1 i c f a -> Element (M1 i c f a) Source #

oelem :: Element (M1 i c f a) -> M1 i c f a -> Bool Source #

onotElem :: Element (M1 i c f a) -> M1 i c f a -> Bool Source #

(Foldable f, Foldable g) => MonoFoldable ((f :.: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element ((f :.: g) a) -> m) -> (f :.: g) a -> m Source #

ofoldr :: (Element ((f :.: g) a) -> b -> b) -> b -> (f :.: g) a -> b Source #

ofoldl' :: (a0 -> Element ((f :.: g) a) -> a0) -> a0 -> (f :.: g) a -> a0 Source #

otoList :: (f :.: g) a -> [Element ((f :.: g) a)] Source #

oall :: (Element ((f :.: g) a) -> Bool) -> (f :.: g) a -> Bool Source #

oany :: (Element ((f :.: g) a) -> Bool) -> (f :.: g) a -> Bool Source #

onull :: (f :.: g) a -> Bool Source #

olength :: (f :.: g) a -> Int Source #

olength64 :: (f :.: g) a -> Int64 Source #

ocompareLength :: Integral i => (f :.: g) a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element ((f :.: g) a) -> f0 b) -> (f :.: g) a -> f0 () Source #

ofor_ :: Applicative f0 => (f :.: g) a -> (Element ((f :.: g) a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element ((f :.: g) a) -> m ()) -> (f :.: g) a -> m () Source #

oforM_ :: Applicative m => (f :.: g) a -> (Element ((f :.: g) a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element ((f :.: g) a) -> m a0) -> a0 -> (f :.: g) a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element ((f :.: g) a) -> m) -> (f :.: g) a -> m Source #

ofoldr1Ex :: (Element ((f :.: g) a) -> Element ((f :.: g) a) -> Element ((f :.: g) a)) -> (f :.: g) a -> Element ((f :.: g) a) Source #

ofoldl1Ex' :: (Element ((f :.: g) a) -> Element ((f :.: g) a) -> Element ((f :.: g) a)) -> (f :.: g) a -> Element ((f :.: g) a) Source #

headEx :: (f :.: g) a -> Element ((f :.: g) a) Source #

lastEx :: (f :.: g) a -> Element ((f :.: g) a) Source #

unsafeHead :: (f :.: g) a -> Element ((f :.: g) a) Source #

unsafeLast :: (f :.: g) a -> Element ((f :.: g) a) Source #

maximumByEx :: (Element ((f :.: g) a) -> Element ((f :.: g) a) -> Ordering) -> (f :.: g) a -> Element ((f :.: g) a) Source #

minimumByEx :: (Element ((f :.: g) a) -> Element ((f :.: g) a) -> Ordering) -> (f :.: g) a -> Element ((f :.: g) a) Source #

oelem :: Element ((f :.: g) a) -> (f :.: g) a -> Bool Source #

onotElem :: Element ((f :.: g) a) -> (f :.: g) a -> Bool Source #

(Foldable f, Foldable g) => MonoFoldable (Compose f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

ofoldMap :: Monoid m => (Element (Compose f g a) -> m) -> Compose f g a -> m Source #

ofoldr :: (Element (Compose f g a) -> b -> b) -> b -> Compose f g a -> b Source #

ofoldl' :: (a0 -> Element (Compose f g a) -> a0) -> a0 -> Compose f g a -> a0 Source #

otoList :: Compose f g a -> [Element (Compose f g a)] Source #

oall :: (Element (Compose f g a) -> Bool) -> Compose f g a -> Bool Source #

oany :: (Element (Compose f g a) -> Bool) -> Compose f g a -> Bool Source #

onull :: Compose f g a -> Bool Source #

olength :: Compose f g a -> Int Source #

olength64 :: Compose f g a -> Int64 Source #

ocompareLength :: Integral i => Compose f g a -> i -> Ordering Source #

otraverse_ :: Applicative f0 => (Element (Compose f g a) -> f0 b) -> Compose f g a -> f0 () Source #

ofor_ :: Applicative f0 => Compose f g a -> (Element (Compose f g a) -> f0 b) -> f0 () Source #

omapM_ :: Applicative m => (Element (Compose f g a) -> m ()) -> Compose f g a -> m () Source #

oforM_ :: Applicative m => Compose f g a -> (Element (Compose f g a) -> m ()) -> m () Source #

ofoldlM :: Monad m => (a0 -> Element (Compose f g a) -> m a0) -> a0 -> Compose f g a -> m a0 Source #

ofoldMap1Ex :: Semigroup m => (Element (Compose f g a) -> m) -> Compose f g a -> m Source #

ofoldr1Ex :: (Element (Compose f g a) -> Element (Compose f g a) -> Element (Compose f g a)) -> Compose f g a -> Element (Compose f g a) Source #

ofoldl1Ex' :: (Element (Compose f g a) -> Element (Compose f g a) -> Element (Compose f g a)) -> Compose f g a -> Element (Compose f g a) Source #

headEx :: Compose f g a -> Element (Compose f g a) Source #

lastEx :: Compose f g a -> Element (Compose f g a) Source #

unsafeHead :: Compose f g a -> Element (Compose f g a) Source #

unsafeLast :: Compose f g a -> Element (Compose f g a) Source #

maximumByEx :: (Element (Compose f g a) -> Element (Compose f g a) -> Ordering) -> Compose f g a -> Element (Compose f g a) Source #

minimumByEx :: (Element (Compose f g a) -> Element (Compose f g a) -> Ordering) -> Compose f g a -> Element (Compose f g a) Source #

oelem :: Element (Compose f g a) -> Compose f g a -> Bool Source #

onotElem :: Element (Compose f g a) -> Compose f g a -> Bool Source #

headMay :: MonoFoldable mono => mono -> Maybe (Element mono) Source #

Safe version of headEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

lastMay :: MonoFoldable mono => mono -> Maybe (Element mono) Source #

Safe version of lastEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

osum :: (MonoFoldable mono, Num (Element mono)) => mono -> Element mono Source #

osum computes the sum of the numbers of a monomorphic container.

oproduct :: (MonoFoldable mono, Num (Element mono)) => mono -> Element mono Source #

oproduct computes the product of the numbers of a monomorphic container.

oand :: (Element mono ~ Bool, MonoFoldable mono) => mono -> Bool Source #

Are all of the elements True?

Since: 0.6.0

oor :: (Element mono ~ Bool, MonoFoldable mono) => mono -> Bool Source #

Are any of the elements True?

Since: 0.6.0

oconcatMap :: (MonoFoldable mono, Monoid m) => (Element mono -> m) -> mono -> m Source #

Synonym for ofoldMap

Since: 1.0.0

ofold :: (MonoFoldable mono, Monoid (Element mono)) => mono -> Element mono Source #

Monoidally combine all values in the container

Since: 1.0.0

oconcat :: (MonoFoldable mono, Monoid (Element mono)) => mono -> Element mono Source #

Synonym for ofold

Since: 1.0.0

ofoldM :: (MonoFoldable mono, Monad m) => (a -> Element mono -> m a) -> a -> mono -> m a Source #

Synonym for ofoldlM

Since: 1.0.0

osequence_ :: (Applicative m, MonoFoldable mono, Element mono ~ m ()) => mono -> m () Source #

Perform all actions in the given container

Since: 1.0.0

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

Get the minimum element of a monomorphic container.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See maximum from Data.NonNull for a total version of this function.

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

Get the maximum element of a monomorphic container.

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception.

See minimum from Data.NonNull for a total version of this function.

maximumMay :: (MonoFoldable mono, Ord (Element mono)) => mono -> Maybe (Element mono) Source #

Safe version of maximumEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

maximumByMay :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> mono -> Maybe (Element mono) Source #

Safe version of maximumByEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

minimumMay :: (MonoFoldable mono, Ord (Element mono)) => mono -> Maybe (Element mono) Source #

Safe version of minimumEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

minimumByMay :: MonoFoldable mono => (Element mono -> Element mono -> Ordering) -> mono -> Maybe (Element mono) Source #

Safe version of minimumByEx.

Returns Nothing instead of throwing an exception when encountering an empty monomorphic container.

class (MonoFunctor mono, MonoFoldable mono) => MonoTraversable mono where Source #

Monomorphic containers that can be traversed from left to right.

NOTE: Due to limitations with the role system, GHC is yet unable to provide newtype-derivation of MonoTraversable. See https://stackoverflow.com/questions/49776924/newtype-deriving-issequence.

Minimal complete definition

Nothing

Methods

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

Map each element of a monomorphic container to an action, evaluate these actions from left to right, and collect the results.

otraverse :: (Traversable t, mono ~ t a, a ~ Element mono, Applicative f) => (Element mono -> f (Element mono)) -> mono -> f mono Source #

Map each element of a monomorphic container to an action, evaluate these actions from left to right, and collect the results.

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

Map each element of a monomorphic container to a monadic action, evaluate these actions from left to right, and collect the results.

Instances
MonoTraversable ByteString Source # 
Instance details

Defined in Data.MonoTraversable

MonoTraversable ByteString Source # 
Instance details

Defined in Data.MonoTraversable

MonoTraversable Text Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

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

MonoTraversable Text Source # 
Instance details

Defined in Data.MonoTraversable

Methods

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

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

MonoTraversable [a] Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element [a] -> f (Element [a])) -> [a] -> f [a] Source #

omapM :: Applicative m => (Element [a] -> m (Element [a])) -> [a] -> m [a] Source #

MonoTraversable (Maybe a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Maybe a) -> f (Element (Maybe a))) -> Maybe a -> f (Maybe a) Source #

omapM :: Applicative m => (Element (Maybe a) -> m (Element (Maybe a))) -> Maybe a -> m (Maybe a) Source #

MonoTraversable (Par1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Par1 a) -> f (Element (Par1 a))) -> Par1 a -> f (Par1 a) Source #

omapM :: Applicative m => (Element (Par1 a) -> m (Element (Par1 a))) -> Par1 a -> m (Par1 a) Source #

MonoTraversable (Option a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Option a) -> f (Element (Option a))) -> Option a -> f (Option a) Source #

omapM :: Applicative m => (Element (Option a) -> m (Element (Option a))) -> Option a -> m (Option a) Source #

MonoTraversable (Identity a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Identity a) -> f (Element (Identity a))) -> Identity a -> f (Identity a) Source #

omapM :: Applicative m => (Element (Identity a) -> m (Element (Identity a))) -> Identity a -> m (Identity a) Source #

MonoTraversable (NonEmpty a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (NonEmpty a) -> f (Element (NonEmpty a))) -> NonEmpty a -> f (NonEmpty a) Source #

omapM :: Applicative m => (Element (NonEmpty a) -> m (Element (NonEmpty a))) -> NonEmpty a -> m (NonEmpty a) Source #

MonoTraversable (IntMap a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (IntMap a) -> f (Element (IntMap a))) -> IntMap a -> f (IntMap a) Source #

omapM :: Applicative m => (Element (IntMap a) -> m (Element (IntMap a))) -> IntMap a -> m (IntMap a) Source #

MonoTraversable (Tree a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Tree a) -> f (Element (Tree a))) -> Tree a -> f (Tree a) Source #

omapM :: Applicative m => (Element (Tree a) -> m (Element (Tree a))) -> Tree a -> m (Tree a) Source #

MonoTraversable (Seq a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Seq a) -> f (Element (Seq a))) -> Seq a -> f (Seq a) Source #

omapM :: Applicative m => (Element (Seq a) -> m (Element (Seq a))) -> Seq a -> m (Seq a) Source #

MonoTraversable (ViewL a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (ViewL a) -> f (Element (ViewL a))) -> ViewL a -> f (ViewL a) Source #

omapM :: Applicative m => (Element (ViewL a) -> m (Element (ViewL a))) -> ViewL a -> m (ViewL a) Source #

MonoTraversable (ViewR a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (ViewR a) -> f (Element (ViewR a))) -> ViewR a -> f (ViewR a) Source #

omapM :: Applicative m => (Element (ViewR a) -> m (Element (ViewR a))) -> ViewR a -> m (ViewR a) Source #

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

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Vector a) -> f (Element (Vector a))) -> Vector a -> f (Vector a) Source #

omapM :: Applicative m => (Element (Vector a) -> m (Element (Vector a))) -> Vector a -> m (Vector a) Source #

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

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Vector a) -> f (Element (Vector a))) -> Vector a -> f (Vector a) Source #

omapM :: Applicative m => (Element (Vector a) -> m (Element (Vector a))) -> Vector a -> m (Vector a) Source #

MonoTraversable (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Vector a) -> f (Element (Vector a))) -> Vector a -> f (Vector a) Source #

omapM :: Applicative m => (Element (Vector a) -> m (Element (Vector a))) -> Vector a -> m (Vector a) 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 #

MonoTraversable (Either a b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Either a b) -> f (Element (Either a b))) -> Either a b -> f (Either a b) Source #

omapM :: Applicative m => (Element (Either a b) -> m (Element (Either a b))) -> Either a b -> m (Either a b) Source #

MonoTraversable (V1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (V1 a) -> f (Element (V1 a))) -> V1 a -> f (V1 a) Source #

omapM :: Applicative m => (Element (V1 a) -> m (Element (V1 a))) -> V1 a -> m (V1 a) Source #

MonoTraversable (U1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (U1 a) -> f (Element (U1 a))) -> U1 a -> f (U1 a) Source #

omapM :: Applicative m => (Element (U1 a) -> m (Element (U1 a))) -> U1 a -> m (U1 a) Source #

MonoTraversable (a, b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (a, b) -> f (Element (a, b))) -> (a, b) -> f (a, b) Source #

omapM :: Applicative m => (Element (a, b) -> m (Element (a, b))) -> (a, b) -> m (a, b) Source #

MonoTraversable (Proxy a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Proxy a) -> f (Element (Proxy a))) -> Proxy a -> f (Proxy a) Source #

omapM :: Applicative m => (Element (Proxy a) -> m (Element (Proxy a))) -> Proxy a -> m (Proxy a) Source #

MonoTraversable (Map k v) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Map k v) -> f (Element (Map k v))) -> Map k v -> f (Map k v) Source #

omapM :: Applicative m => (Element (Map k v) -> m (Element (Map k v))) -> Map k v -> m (Map k v) Source #

Traversable f => MonoTraversable (MaybeT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (MaybeT f a) -> f0 (Element (MaybeT f a))) -> MaybeT f a -> f0 (MaybeT f a) Source #

omapM :: Applicative m => (Element (MaybeT f a) -> m (Element (MaybeT f a))) -> MaybeT f a -> m (MaybeT f a) Source #

Traversable f => MonoTraversable (ListT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (ListT f a) -> f0 (Element (ListT f a))) -> ListT f a -> f0 (ListT f a) Source #

omapM :: Applicative m => (Element (ListT f a) -> m (Element (ListT f a))) -> ListT f a -> m (ListT f a) Source #

MonoTraversable (HashMap k v) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (HashMap k v) -> f (Element (HashMap k v))) -> HashMap k v -> f (HashMap k v) Source #

omapM :: Applicative m => (Element (HashMap k v) -> m (Element (HashMap k v))) -> HashMap k v -> m (HashMap k v) Source #

Traversable f => MonoTraversable (Rec1 f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (Rec1 f a) -> f0 (Element (Rec1 f a))) -> Rec1 f a -> f0 (Rec1 f a) Source #

omapM :: Applicative m => (Element (Rec1 f a) -> m (Element (Rec1 f a))) -> Rec1 f a -> m (Rec1 f a) Source #

MonoTraversable (Const m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (Const m a) -> f (Element (Const m a))) -> Const m a -> f (Const m a) Source #

omapM :: Applicative m0 => (Element (Const m a) -> m0 (Element (Const m a))) -> Const m a -> m0 (Const m a) Source #

Traversable f => MonoTraversable (WriterT w f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (WriterT w f a) -> f0 (Element (WriterT w f a))) -> WriterT w f a -> f0 (WriterT w f a) Source #

omapM :: Applicative m => (Element (WriterT w f a) -> m (Element (WriterT w f a))) -> WriterT w f a -> m (WriterT w f a) Source #

Traversable f => MonoTraversable (WriterT w f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (WriterT w f a) -> f0 (Element (WriterT w f a))) -> WriterT w f a -> f0 (WriterT w f a) Source #

omapM :: Applicative m => (Element (WriterT w f a) -> m (Element (WriterT w f a))) -> WriterT w f a -> m (WriterT w f a) Source #

Traversable f => MonoTraversable (IdentityT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (IdentityT f a) -> f0 (Element (IdentityT f a))) -> IdentityT f a -> f0 (IdentityT f a) Source #

omapM :: Applicative m => (Element (IdentityT f a) -> m (Element (IdentityT f a))) -> IdentityT f a -> m (IdentityT f a) Source #

MonoTraversable (K1 i c a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f => (Element (K1 i c a) -> f (Element (K1 i c a))) -> K1 i c a -> f (K1 i c a) Source #

omapM :: Applicative m => (Element (K1 i c a) -> m (Element (K1 i c a))) -> K1 i c a -> m (K1 i c a) Source #

(Traversable f, Traversable g) => MonoTraversable ((f :+: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element ((f :+: g) a) -> f0 (Element ((f :+: g) a))) -> (f :+: g) a -> f0 ((f :+: g) a) Source #

omapM :: Applicative m => (Element ((f :+: g) a) -> m (Element ((f :+: g) a))) -> (f :+: g) a -> m ((f :+: g) a) Source #

(Traversable f, Traversable g) => MonoTraversable ((f :*: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element ((f :*: g) a) -> f0 (Element ((f :*: g) a))) -> (f :*: g) a -> f0 ((f :*: g) a) Source #

omapM :: Applicative m => (Element ((f :*: g) a) -> m (Element ((f :*: g) a))) -> (f :*: g) a -> m ((f :*: g) a) Source #

(Traversable f, Traversable g) => MonoTraversable (Product f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (Product f g a) -> f0 (Element (Product f g a))) -> Product f g a -> f0 (Product f g a) Source #

omapM :: Applicative m => (Element (Product f g a) -> m (Element (Product f g a))) -> Product f g a -> m (Product f g a) Source #

Traversable f => MonoTraversable (M1 i c f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (M1 i c f a) -> f0 (Element (M1 i c f a))) -> M1 i c f a -> f0 (M1 i c f a) Source #

omapM :: Applicative m => (Element (M1 i c f a) -> m (Element (M1 i c f a))) -> M1 i c f a -> m (M1 i c f a) Source #

(Traversable f, Traversable g) => MonoTraversable ((f :.: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element ((f :.: g) a) -> f0 (Element ((f :.: g) a))) -> (f :.: g) a -> f0 ((f :.: g) a) Source #

omapM :: Applicative m => (Element ((f :.: g) a) -> m (Element ((f :.: g) a))) -> (f :.: g) a -> m ((f :.: g) a) Source #

(Traversable f, Traversable g) => MonoTraversable (Compose f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

otraverse :: Applicative f0 => (Element (Compose f g a) -> f0 (Element (Compose f g a))) -> Compose f g a -> f0 (Compose f g a) Source #

omapM :: Applicative m => (Element (Compose f g a) -> m (Element (Compose f g a))) -> Compose f g a -> m (Compose f g a) Source #

ofor :: (MonoTraversable mono, Applicative f) => mono -> (Element mono -> f (Element mono)) -> f mono Source #

ofor is otraverse with its arguments flipped.

oforM :: (MonoTraversable mono, Applicative f) => mono -> (Element mono -> f (Element mono)) -> f mono Source #

oforM is omapM with its arguments flipped.

ofoldlUnwrap :: MonoFoldable mono => (x -> Element mono -> x) -> x -> (x -> b) -> mono -> b Source #

A strict left fold, together with an unwrap function.

This is convenient when the accumulator value is not the same as the final expected type. It is provided mainly for integration with the foldl package, to be used in conjunction with purely.

Since: 0.3.1

ofoldMUnwrap :: (Monad m, MonoFoldable mono) => (x -> Element mono -> m x) -> m x -> (x -> m b) -> mono -> m b Source #

A monadic strict left fold, together with an unwrap function.

Similar to foldlUnwrap, but allows monadic actions. To be used with impurely from foldl.

Since: 0.3.1

class MonoPointed mono where Source #

Typeclass for monomorphic containers that an element can be lifted into.

For any MonoFunctor, the following law holds:

omap f . opoint = opoint . f

Minimal complete definition

Nothing

Methods

opoint :: Element mono -> mono Source #

Lift an element into a monomorphic container.

opoint is the same as pure for an Applicative

opoint :: (Applicative f, f a ~ mono, Element (f a) ~ a) => Element mono -> mono Source #

Lift an element into a monomorphic container.

opoint is the same as pure for an Applicative

Instances
MonoPointed ByteString Source # 
Instance details

Defined in Data.MonoTraversable

MonoPointed ByteString Source # 
Instance details

Defined in Data.MonoTraversable

MonoPointed IntSet Source # 
Instance details

Defined in Data.MonoTraversable

MonoPointed Text Source # 
Instance details

Defined in Data.MonoTraversable

MonoPointed Text Source # 
Instance details

Defined in Data.MonoTraversable

MonoPointed [a] Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element [a] -> [a] Source #

MonoPointed (Maybe a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Maybe a) -> Maybe a Source #

MonoPointed (IO a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (IO a) -> IO a Source #

MonoPointed (Par1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Par1 a) -> Par1 a Source #

MonoPointed (Option a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Option a) -> Option a Source #

MonoPointed (ZipList a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (ZipList a) -> ZipList a Source #

MonoPointed (Identity a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Identity a) -> Identity a Source #

MonoPointed (NonEmpty a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (NonEmpty a) -> NonEmpty a Source #

MonoPointed (Tree a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Tree a) -> Tree a Source #

MonoPointed (Seq a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Seq a) -> Seq a Source #

MonoPointed (ViewL a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (ViewL a) -> ViewL a Source #

MonoPointed (ViewR a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (ViewR a) -> ViewR a Source #

MonoPointed (Set a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Set a) -> Set a Source #

Hashable a => MonoPointed (HashSet a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (HashSet a) -> HashSet a Source #

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

Defined in Data.MonoTraversable

Methods

opoint :: Element (Vector a) -> Vector a Source #

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

Defined in Data.MonoTraversable

Methods

opoint :: Element (Vector a) -> Vector a Source #

MonoPointed (Vector a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Vector a) -> Vector a Source #

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

Defined in Data.NonNull

Methods

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

MonoPointed (r -> a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (r -> a) -> r -> a Source #

MonoPointed (Either a b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Either a b) -> Either a b Source #

MonoPointed (U1 a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (U1 a) -> U1 a Source #

Monoid a => MonoPointed (a, b) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (a, b) -> (a, b) Source #

Monad m => MonoPointed (WrappedMonad m a) Source # 
Instance details

Defined in Data.MonoTraversable

MonoPointed (Proxy a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Proxy a) -> Proxy a Source #

Applicative f => MonoPointed (MaybeT f a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (MaybeT f a) -> MaybeT f a Source #

Applicative m => MonoPointed (ListT m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (ListT m a) -> ListT m a Source #

Applicative f => MonoPointed (Rec1 f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Rec1 f a) -> Rec1 f a Source #

Arrow a => MonoPointed (WrappedArrow a b c) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (WrappedArrow a b c) -> WrappedArrow a b c Source #

Monoid m => MonoPointed (Const m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Const m a) -> Const m a Source #

(Monoid w, Applicative m) => MonoPointed (WriterT w m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (WriterT w m a) -> WriterT w m a Source #

(Monoid w, Applicative m) => MonoPointed (WriterT w m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (WriterT w m a) -> WriterT w m a Source #

Applicative m => MonoPointed (StateT s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (StateT s m a) -> StateT s m a Source #

Applicative m => MonoPointed (StateT s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (StateT s m a) -> StateT s m a Source #

Applicative m => MonoPointed (IdentityT m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (IdentityT m a) -> IdentityT m a Source #

(Applicative f, Applicative g) => MonoPointed ((f :+: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element ((f :+: g) a) -> (f :+: g) a Source #

(Applicative f, Applicative g) => MonoPointed ((f :*: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element ((f :*: g) a) -> (f :*: g) a Source #

(Applicative f, Applicative g) => MonoPointed (Product f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Product f g a) -> Product f g a Source #

Applicative m => MonoPointed (ReaderT r m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (ReaderT r m a) -> ReaderT r m a Source #

MonoPointed (ContT r m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (ContT r m a) -> ContT r m a Source #

Applicative f => MonoPointed (M1 i c f a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (M1 i c f a) -> M1 i c f a Source #

(Applicative f, Applicative g) => MonoPointed ((f :.: g) a) Source #

Since: 1.0.11.0

Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element ((f :.: g) a) -> (f :.: g) a Source #

(Applicative f, Applicative g) => MonoPointed (Compose f g a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (Compose f g a) -> Compose f g a Source #

(Monoid w, Applicative m) => MonoPointed (RWST r w s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (RWST r w s m a) -> RWST r w s m a Source #

(Monoid w, Applicative m) => MonoPointed (RWST r w s m a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

opoint :: Element (RWST r w s m a) -> RWST r w s m a Source #

class MonoFunctor mono => MonoComonad mono where Source #

Typeclass for monomorphic containers where it is always okay to "extract" a value from with oextract, and where you can extrapolate any "extracting" function to be a function on the whole part with oextend.

oextend and oextract should work together following the laws:

oextend oextract      = id
oextract . oextend f  = f
oextend f . oextend g = oextend (f . oextend g)

As an intuition, oextend f uses f to "build up" a new mono with pieces from the old one received by f.

Methods

oextract :: mono -> Element mono Source #

Extract an element from mono. Can be thought of as a dual concept to opoint.

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

Extend a mono -> Element mono function to be a mono -> mono; that is, builds a new mono from the old one by using pieces glimpsed from the given function.

Instances
MonoComonad (ViewL a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

oextract :: ViewL a -> Element (ViewL a) Source #

oextend :: (ViewL a -> Element (ViewL a)) -> ViewL a -> ViewL a Source #

MonoComonad (ViewR a) Source # 
Instance details

Defined in Data.MonoTraversable

Methods

oextract :: ViewR a -> Element (ViewR a) Source #

oextend :: (ViewR a -> Element (ViewR a)) -> ViewR a -> ViewR a Source #

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 #

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

ointercalate :: (MonoFoldable mono, Monoid (Element mono)) => Element mono -> mono -> Element mono Source #

intercalate seq seqs inserts seq in between seqs and concatenates the result.

Since: 1.0.0