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

Safe HaskellNone

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

class MonoFunctor mono whereSource

Methods

omap :: (Element mono -> Element mono) -> mono -> monoSource

Instances

MonoFunctor ByteString 
MonoFunctor ByteString 
MonoFunctor Text 
MonoFunctor Text 
MonoFunctor [a] 
MonoFunctor (IO a) 
MonoFunctor (ZipList a) 
MonoFunctor (Maybe a) 
MonoFunctor (Identity a) 
MonoFunctor (Tree a) 
MonoFunctor (Seq a) 
MonoFunctor (ViewL a) 
MonoFunctor (ViewR a) 
MonoFunctor (IntMap a) 
MonoFunctor (Option a) 
MonoFunctor (NonEmpty a) 
MonoFunctor (Vector a) 
Unbox a => MonoFunctor (Vector a) 
Storable a => MonoFunctor (Vector a) 
MonoFunctor seq => MonoFunctor (NotEmpty seq) 
MonoFunctor (r -> a) 
MonoFunctor (Either a b) 
MonoFunctor (a, b) 
MonoFunctor (Const m a) 
Monad m => MonoFunctor (WrappedMonad m a) 
Functor m => MonoFunctor (IdentityT m a) 
MonoFunctor (Map k v) 
Functor m => MonoFunctor (ListT m a) 
Functor f => MonoFunctor (WrappedApplicative f a) 
Functor f => MonoFunctor (MaybeApply f a) 
Functor m => MonoFunctor (MaybeT m a) 
MonoFunctor (HashMap k v) 
Arrow a => MonoFunctor (WrappedArrow a b c) 
MonoFunctor (Cokleisli w a b) 
Functor m => MonoFunctor (ContT r m a) 
Functor m => MonoFunctor (ErrorT e m a) 
Functor m => MonoFunctor (ReaderT r m a) 
Functor m => MonoFunctor (StateT s m a) 
Functor m => MonoFunctor (StateT s m a) 
Functor m => MonoFunctor (WriterT w m a) 
Functor m => MonoFunctor (WriterT w m a) 
(Functor f, Functor g) => MonoFunctor (Compose f g a) 
Functor f => MonoFunctor (Static f a b) 
(Functor f, Functor g) => MonoFunctor (Product f g a) 
Functor m => MonoFunctor (RWST r w s m a) 
Functor m => MonoFunctor (RWST r w s m a) 

class MonoFoldable mono whereSource

Methods

ofoldMap :: Monoid m => (Element mono -> m) -> mono -> mSource

ofoldr :: (Element mono -> b -> b) -> b -> mono -> bSource

ofoldl' :: (a -> Element mono -> a) -> a -> mono -> aSource

otoList :: mono -> [Element mono]Source

oall :: (Element mono -> Bool) -> mono -> BoolSource

oany :: (Element mono -> Bool) -> mono -> BoolSource

onull :: mono -> BoolSource

olength :: mono -> IntSource

olength64 :: mono -> Int64Source

ocompareLength :: Integral i => mono -> i -> OrderingSource

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

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

omapM_ :: (MonoFoldable mono, Monad m) => (Element mono -> m b) -> mono -> m ()Source

oforM_ :: (MonoFoldable mono, Monad m) => mono -> (Element mono -> m b) -> m ()Source

ofoldlM :: (MonoFoldable mono, Monad m) => (a -> Element mono -> m a) -> a -> mono -> m aSource

ofoldMap1Ex :: Semigroup m => (Element mono -> m) -> mono -> mSource

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception. See Data.NonNull for a total version of this function.

ofoldr1Ex :: (Element mono -> Element mono -> Element mono) -> mono -> Element monoSource

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception. See Data.NonNull for a total version of this function.

ofoldl1Ex' :: (Element mono -> Element mono -> Element mono) -> mono -> Element monoSource

Note: this is a partial function. On an empty MonoFoldable, it will throw an exception. See Data.NonNull for a total version of this function.

headEx :: mono -> Element monoSource

lastEx :: mono -> Element monoSource

unsafeHead :: mono -> Element monoSource

unsafeLast :: mono -> Element monoSource

headMay :: MonoFoldable mono => mono -> Maybe (Element mono)Source

like Data.List.head, but not partial

lastMay :: MonoFoldable mono => mono -> Maybe (Element mono)Source

like Data.List.last, but not partial

osum :: (MonoFoldable mono, Num (Element mono)) => mono -> Element monoSource

The sum function computes the sum of the numbers of a structure.

oproduct :: (MonoFoldable mono, Num (Element mono)) => mono -> Element monoSource

The product function computes the product of the numbers of a structure.

class (MonoFoldable mono, Ord (Element mono)) => MonoFoldableOrd mono whereSource

A typeclass for MonoFoldables containing elements which are an instance of Ord.

Methods

maximumEx :: mono -> Element monoSource

maximumByEx :: (Element mono -> Element mono -> Ordering) -> mono -> Element monoSource

minimumEx :: mono -> Element monoSource

minimumByEx :: (Element mono -> Element mono -> Ordering) -> mono -> Element monoSource

maximumMay :: MonoFoldableOrd mono => mono -> Maybe (Element mono)Source

maximumByMay :: MonoFoldableOrd mono => (Element mono -> Element mono -> Ordering) -> mono -> Maybe (Element mono)Source

minimumMay :: MonoFoldableOrd mono => mono -> Maybe (Element mono)Source

minimumByMay :: MonoFoldableOrd mono => (Element mono -> Element mono -> Ordering) -> mono -> Maybe (Element mono)Source

ofor :: (MonoTraversable mono, Applicative f) => mono -> (Element mono -> f (Element mono)) -> f monoSource

oforM :: (MonoTraversable mono, Monad f) => mono -> (Element mono -> f (Element mono)) -> f monoSource