mono-traversable-0.9.0.2: 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 = Word8 
type Element ByteString = Word8 
type Element IntSet = Int 
type Element Text = Char 
type Element Text = Char 
type Element [a] = a 
type Element (IO a) = a 
type Element (ZipList a) = a 
type Element (Maybe a) = a 
type Element (IntMap a) = a 
type Element (Set e) = e 
type Element (Tree a) = a 
type Element (Seq a) = a 
type Element (ViewL a) = a 
type Element (ViewR a) = a 
type Element (Identity a) = a 
type Element (Vector a) = a 
type Element (NonEmpty a) = a 
type Element (Vector a) = a 
type Element (HashSet e) = e 
type Element (Vector a) = a 
type Element (Option a) = a 
type Element (DList a) = a 
type Element (r -> a) = a 
type Element (Either a b) = b 
type Element (a, b) = b 
type Element (Const m a) = a 
type Element (WrappedMonad m a) = a 
type Element (Map k v) = v 
type Element (MaybeT m a) = a 
type Element (ListT m a) = a 
type Element (IdentityT m a) = a 
type Element (HashMap k v) = v 
type Element (WrappedApplicative f a) = a 
type Element (MaybeApply f a) = a 
type Element (MinLen nat mono) = Element mono 
type Element (WrappedArrow a b c) = c 
type Element (WriterT w m a) = a 
type Element (WriterT w m a) = a 
type Element (StateT s m a) = a 
type Element (StateT s m a) = a 
type Element (ReaderT r m a) = a 
type Element (ErrorT e m a) = a 
type Element (ContT r m a) = a 
type Element (Compose f g a) = a 
type Element (Product f g a) = a 
type Element (Cokleisli w a b) = b 
type Element (Static f a b) = b 
type Element (RWST r w s m a) = a 
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

Instances

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

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.

ofoldr :: (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.

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_ :: (MonoFoldable mono, 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_ :: (MonoFoldable mono, Applicative f) => mono -> (Element mono -> f b) -> f () Source

ofor_ is otraverse_ with its arguments flipped.

omapM_ :: (MonoFoldable mono, Monad 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_ :: (MonoFoldable mono, Monad m) => mono -> (Element mono -> m ()) -> m () Source

oforM_ is omapM_ with its arguments flipped.

ofoldlM :: (MonoFoldable mono, 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.MinLen 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 ofoldr1Ex from Data.MinLen 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 ofoldl1Ex' from Data.MinLen 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.MinLen 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 'Data.MinLen.last from Data.MinLen 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.MinLen 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.MinLen for a total version of this function.

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

class (MonoFoldable mono, Monoid mono) => MonoFoldableMonoid mono where Source

A typeclass for monomorphic containers that are Monoids.

Minimal complete definition

Nothing

Methods

oconcatMap :: (Element mono -> mono) -> mono -> mono Source

Map a function over a monomorphic container and combine the results.

class (MonoFoldable mono, Eq (Element mono)) => MonoFoldableEq mono where Source

A typeclass for monomorphic containers whose elements are an instance of Eq.

Minimal complete definition

Nothing

Methods

oelem :: Element mono -> mono -> Bool Source

Checks if the monomorphic container includes the supplied element.

onotElem :: Element mono -> mono -> Bool Source

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

Instances

MonoFoldableEq ByteString 
MonoFoldableEq ByteString 
MonoFoldableEq IntSet 
MonoFoldableEq Text 
MonoFoldableEq Text 
Eq a => MonoFoldableEq [a] 
Eq a => MonoFoldableEq (Maybe a) 
Eq a => MonoFoldableEq (IntMap a) 
(Eq a, Ord a) => MonoFoldableEq (Set a) 
Eq a => MonoFoldableEq (Tree a) 
Eq a => MonoFoldableEq (Seq a) 
Eq a => MonoFoldableEq (ViewL a) 
Eq a => MonoFoldableEq (ViewR a) 
Eq a => MonoFoldableEq (Identity a) 
(Eq a, Storable a) => MonoFoldableEq (Vector a) 
Eq a => MonoFoldableEq (NonEmpty a) 
Eq a => MonoFoldableEq (Vector a) 
Eq a => MonoFoldableEq (HashSet a) 
(Eq a, Unbox a) => MonoFoldableEq (Vector a) 
Eq a => MonoFoldableEq (Option a) 
Eq a => MonoFoldableEq (DList a) 
Eq b => MonoFoldableEq (Either a b) 
Eq v => MonoFoldableEq (Map k v) 
Eq v => MonoFoldableEq (HashMap k v) 

class (MonoFoldable mono, Ord (Element mono)) => MonoFoldableOrd mono where Source

A typeclass for monomorphic containers whose elements are an instance of Ord.

Minimal complete definition

Nothing

Methods

maximumEx :: 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.MinLen for a total version of this function.

minimumEx :: 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.MinLen for a total version of this function.

Instances

MonoFoldableOrd ByteString 
MonoFoldableOrd ByteString 
MonoFoldableOrd IntSet 
MonoFoldableOrd Text 
MonoFoldableOrd Text 
Ord a => MonoFoldableOrd [a] 
Ord a => MonoFoldableOrd (Maybe a) 
Ord a => MonoFoldableOrd (IntMap a) 
Ord e => MonoFoldableOrd (Set e) 
Ord a => MonoFoldableOrd (Tree a) 
Ord a => MonoFoldableOrd (Seq a) 
Ord a => MonoFoldableOrd (ViewL a) 
Ord a => MonoFoldableOrd (ViewR a) 
Ord a => MonoFoldableOrd (Identity a) 
(Ord a, Storable a) => MonoFoldableOrd (Vector a) 
Ord a => MonoFoldableOrd (NonEmpty a) 
Ord a => MonoFoldableOrd (Vector a) 
Ord e => MonoFoldableOrd (HashSet e) 
(Unbox a, Ord a) => MonoFoldableOrd (Vector a) 
Ord a => MonoFoldableOrd (Option a) 
Ord b => MonoFoldableOrd (Either a b) 
Ord v => MonoFoldableOrd (Map k v) 
Ord v => MonoFoldableOrd (HashMap k v) 
MonoFoldableOrd mono => MonoFoldableOrd (MinLen nat mono) 

maximumMay :: MonoFoldableOrd 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 :: MonoFoldableOrd 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.

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.

omapM :: Monad 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.

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

ofor is otraverse with its arguments flipped.

oforM :: (MonoTraversable mono, Monad 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

Instances

MonoPointed ByteString 
MonoPointed ByteString 
MonoPointed IntSet 
MonoPointed Text 
MonoPointed Text 
MonoPointed [a] 
MonoPointed (Maybe a) 
MonoPointed (Set a) 
MonoPointed (Seq a) 
MonoPointed (Identity a) 
Storable a => MonoPointed (Vector a) 
MonoPointed (NonEmpty a) 
MonoPointed (Vector a) 
Hashable a => MonoPointed (HashSet a) 
Unbox a => MonoPointed (Vector a) 
MonoPointed (Option a) 
MonoPointed (DList a) 
MonoPointed (Either a b) 
MonoPointed mono => MonoPointed (MinLen (Succ Zero) mono) 
MonoPointed mono => MonoPointed (MinLen Zero mono)