Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Type-classes mirroring type-classes from Key
, 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 type-classes like Keyed
, Indexable
,
and FoldableWithKey
, since they are monomorphic structures. This module
allows both monomorphic and polymorphic data types to be instances of the
same type-classes.
All of the laws for the polymorphic type-classes apply to their monomorphic cousins.
Note that all type-classes have been prefixed with Mono
, and functions have
been prefixed with o
. The mnemonic is inherited from MonoTraversable
.
Synopsis
- type family MonoKey key
- class MonoFunctor mono => MonoKeyed mono where
- omapWithKey :: (MonoKey mono -> Element mono -> Element mono) -> mono -> mono
- class MonoFoldable mono => MonoFoldableWithKey mono where
- otoKeyedList :: mono -> [(MonoKey mono, Element mono)]
- ofoldMapWithKey :: Monoid m => (MonoKey mono -> Element mono -> m) -> mono -> m
- ofoldrWithKey :: (MonoKey mono -> Element mono -> a -> a) -> a -> mono -> a
- ofoldlWithKey :: (a -> MonoKey mono -> Element mono -> a) -> a -> mono -> a
- class (MonoKeyed mono, MonoFoldableWithKey mono, MonoTraversable mono) => MonoTraversableWithKey mono where
- otraverseWithKey :: Applicative f => (MonoKey mono -> Element mono -> f (Element mono)) -> mono -> f mono
- omapWithKeyM :: Monad m => (MonoKey mono -> Element mono -> m (Element mono)) -> mono -> m mono
- class MonoFunctor mono => MonoAdjustable mono where
- class MonoFunctor mono => MonoZip mono where
- class (MonoKeyed mono, MonoZip mono) => MonoZipWithKey mono where
- ozipWithKey :: (MonoKey mono -> Element mono -> Element mono -> Element mono) -> mono -> mono -> mono
- class MonoLookup mono => MonoIndexable mono where
- class MonoLookup mono where
- ofoldlWithKeyUnwrap :: MonoFoldableWithKey mono => (x -> Element mono -> x) -> x -> (x -> b) -> mono -> b
- ofoldWithKeyMUnwrap :: (Monad m, MonoFoldableWithKey mono) => (x -> Element mono -> m x) -> m x -> (x -> m b) -> mono -> m b
Documentation
type family MonoKey key Source #
Type family for getting the type of the key of a monomorphic container.
Instances
Keyed Monomorphic Structures
class MonoFunctor mono => MonoKeyed mono where Source #
Monomorphic containers that can be mapped over.
Nothing
omapWithKey :: (MonoKey mono -> Element mono -> Element mono) -> mono -> mono Source #
Map over a monomorphic container
Instances
class MonoFoldable mono => MonoFoldableWithKey mono where Source #
Monomorphic containers that can be folded over thier pairs of elements and corresponding keys.
otoKeyedList :: mono -> [(MonoKey mono, Element mono)] Source #
ofoldMapWithKey :: Monoid m => (MonoKey mono -> Element mono -> m) -> mono -> m Source #
ofoldrWithKey :: (MonoKey mono -> Element mono -> a -> a) -> a -> mono -> a Source #
ofoldlWithKey :: (a -> MonoKey mono -> Element mono -> a) -> a -> mono -> a Source #
Instances
class (MonoKeyed mono, MonoFoldableWithKey mono, MonoTraversable mono) => MonoTraversableWithKey mono where Source #
Monomorphic containers that can be traversed from left to right over thier pairs of elements and corresponding keys.
otraverseWithKey :: Applicative f => (MonoKey mono -> Element mono -> f (Element mono)) -> mono -> f mono Source #
Map each key-element pair of a monomorphic container to an action, evaluate these actions from left to right, and collect the results. {-# INLINE otraverseWithKey #-}
default otraverseWithKey :: (Applicative f, TraversableWithKey t, Element (t a) ~ a, MonoKey (t a) ~ Key t, t a ~ mono) => (MonoKey mono -> Element mono -> f (Element mono)) -> mono -> f mono Source #
omapWithKeyM :: Monad m => (MonoKey mono -> Element mono -> m (Element mono)) -> mono -> m mono Source #
Like otraverse
but with a Monad constraint.
Instances
Adjustable Monomorphic Structures
class MonoFunctor mono => MonoAdjustable mono where Source #
Monomorphic container that can adjust elements "in place."
oadjust :: (Element mono -> Element mono) -> MonoKey mono -> mono -> mono Source #
default oadjust :: (Adjustable f, Element (f a) ~ a, MonoKey (f a) ~ Key f, f a ~ mono) => (Element mono -> Element mono) -> MonoKey mono -> mono -> mono Source #
oreplace :: MonoKey mono -> Element mono -> mono -> mono Source #
Instances
Zippable Monomorphic Structures
class MonoFunctor mono => MonoZip mono where Source #
Monomorphic container that can be zipped together, merging thier elements.
Laws:
ozipWith
const u u ===ozipWith
(flip const) u u === uozipWith
(flip
f) x y ===ozipWith
f y xozipWith
(a b -> f (g a) (h b)) x y ===ozipWith
f (omap
g x) (omap
h y)
Instances
class (MonoKeyed mono, MonoZip mono) => MonoZipWithKey mono where Source #
Monomorphic container that can be zipped together, merging thier pairs of elements and corresponding keys.
ozipWithKey :: (MonoKey mono -> Element mono -> Element mono -> Element mono) -> mono -> mono -> mono Source #
Instances
Monomorphic Indexing / Querries
class MonoLookup mono => MonoIndexable mono where Source #
Monomorphic container that can be indexed by a key for an element.
Instances
class MonoLookup mono where Source #
Monomorphic container that can be querried by a key for an element.
Instances
Monomorphic unwrapping with key
ofoldlWithKeyUnwrap :: MonoFoldableWithKey mono => (x -> Element mono -> x) -> x -> (x -> b) -> mono -> b Source #
ofoldWithKeyMUnwrap :: (Monad m, MonoFoldableWithKey mono) => (x -> Element mono -> m x) -> m x -> (x -> m b) -> mono -> m b Source #