mono-traversable-0.1.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 mofu Source

class MonoFunctor mofu whereSource

Methods

omap :: (Element mofu -> Element mofu) -> mofu -> mofuSource

class MonoFoldable mofo whereSource

Methods

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

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

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

otoList :: mofo -> [Element mofo]Source

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

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

onull :: mofo -> BoolSource

olength :: mofo -> IntSource

olength64 :: mofo -> Int64Source

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

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

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

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

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

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

osum :: (MonoFoldable mofo, Num (Element mofo)) => mofo -> Element mofoSource

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

oproduct :: (MonoFoldable mofo, Num (Element mofo)) => mofo -> Element mofoSource

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

ofor :: (MonoTraversable mot, Applicative f) => mot -> (Element mot -> f (Element mot)) -> f motSource

oforM :: (MonoTraversable mot, Monad f) => mot -> (Element mot -> f (Element mot)) -> f motSource