monoids-0.1.20: Monoids, specialized containers and a general map/reduce frameworkSource codeContentsIndex
Data.Ring.Module
Portabilitynon-portable (MPTCs)
Stabilityexperimental
Maintainerekmett@gmail.com
Description
Left- and right- modules over rings, semirings, and Seminearrings. To avoid a proliferation of classes. These only require that there be an addition and multiplication operation for the Ring
Synopsis
module Data.Ring
class (Monoid r, Multiplicative r, Monoid m) => LeftModule r m where
(*.) :: r -> m -> m
(*.) :: LeftModule r m => r -> m -> m
class (Monoid r, Multiplicative r, Monoid m) => RightModule r m where
(.*) :: m -> r -> m
(.*) :: RightModule r m => m -> r -> m
class (LeftModule r m, RightModule r m) => Module r m
Documentation
module Data.Ring
class (Monoid r, Multiplicative r, Monoid m) => LeftModule r m whereSource
 (x * y) *. m = x * (y *. m)
Methods
(*.) :: r -> m -> mSource
show/hide Instances
LeftModule Natural Ordering
LeftModule Natural Ordering
LeftModule Natural ()
LeftModule Natural ()
LeftModule Natural All
LeftModule Natural All
LeftModule Natural Any
LeftModule Natural Any
LeftModule Natural ([] a)
LeftModule Natural ([] a)
Monoid m => LeftModule Natural (Dual m)
Monoid m => LeftModule Natural (Dual m)
LeftModule Natural (Endo a)
LeftModule Natural (Endo a)
Num a => LeftModule Natural (Sum a)
Num a => LeftModule Natural (Sum a)
Num a => LeftModule Natural (Product a)
Num a => LeftModule Natural (Product a)
LeftModule Natural (First a)
LeftModule Natural (First a)
LeftModule Natural (Last a)
LeftModule Natural (Last a)
CharReducer m => LeftModule Natural (UTF8 m)
CharReducer m => LeftModule Natural (UTF8 m)
LeftModule Natural (SourcePosition f)
LeftModule Natural (SourcePosition f)
Monoid m => LeftModule Natural (Self m)
Monoid m => LeftModule Natural (Self m)
Monoid m => LeftModule Natural (FromString m)
Monoid m => LeftModule Natural (FromString m)
Multiplicative m => LeftModule Natural (Log m)
Multiplicative m => LeftModule Natural (Log m)
Applicative f => LeftModule Natural (Traversal f)
Applicative f => LeftModule Natural (Traversal f)
Monad f => LeftModule Natural (Action f)
Monad f => LeftModule Natural (Action f)
LeftModule Natural (Free a)
LeftModule Natural (Free a)
(LeftModule r m, LeftModule r n) => LeftModule r ((,) m n)
(LeftModule r m, Applicative f) => LeftModule r (App f m)
(LeftModule r m, Monad f) => LeftModule r (Mon f m)
Monoid m => LeftModule Natural (a -> m)
Monoid m => LeftModule Natural (a -> m)
Category k => LeftModule Natural (GEndo k a)
Category k => LeftModule Natural (GEndo k a)
Alternative f => LeftModule Natural (Alt f a)
Alternative f => LeftModule Natural (Alt f a)
MonadPlus f => LeftModule Natural (MonadSum f a)
MonadPlus f => LeftModule Natural (MonadSum f a)
Eq a => LeftModule Natural (RLE Seq a)
Eq a => LeftModule Natural (RLE Seq a)
(LeftModule r m, LeftModule r n, LeftModule r o) => LeftModule r ((,,) m n o)
Monoid m => LeftModule Natural (CMonoid m m m)
Monoid m => LeftModule Natural (CMonoid m m m)
(LeftModule r m, LeftModule r n, LeftModule r o, LeftModule r p) => LeftModule r ((,,,) m n o p)
(LeftModule r m, LeftModule r n, LeftModule r o, LeftModule r p, LeftModule r q) => LeftModule r ((,,,,) m n o p q)
(*.) :: LeftModule r m => r -> m -> mSource
class (Monoid r, Multiplicative r, Monoid m) => RightModule r m whereSource
 (m .* x) * y = m .* (x * y)
Methods
(.*) :: m -> r -> mSource
show/hide Instances
RightModule Natural Ordering
RightModule Natural Ordering
RightModule Natural ()
RightModule Natural ()
RightModule Natural All
RightModule Natural All
RightModule Natural Any
RightModule Natural Any
RightModule Natural ([] a)
RightModule Natural ([] a)
Monoid m => RightModule Natural (Dual m)
Monoid m => RightModule Natural (Dual m)
RightModule Natural (Endo a)
RightModule Natural (Endo a)
Num a => RightModule Natural (Sum a)
Num a => RightModule Natural (Sum a)
Num a => RightModule Natural (Product a)
Num a => RightModule Natural (Product a)
RightModule Natural (First a)
RightModule Natural (First a)
RightModule Natural (Last a)
RightModule Natural (Last a)
CharReducer m => RightModule Natural (UTF8 m)
CharReducer m => RightModule Natural (UTF8 m)
RightModule Natural (SourcePosition f)
RightModule Natural (SourcePosition f)
Monoid m => RightModule Natural (Self m)
Monoid m => RightModule Natural (Self m)
Monoid m => RightModule Natural (FromString m)
Monoid m => RightModule Natural (FromString m)
Multiplicative m => RightModule Natural (Log m)
Multiplicative m => RightModule Natural (Log m)
Applicative f => RightModule Natural (Traversal f)
Applicative f => RightModule Natural (Traversal f)
Monad f => RightModule Natural (Action f)
Monad f => RightModule Natural (Action f)
RightModule Natural (Free a)
RightModule Natural (Free a)
(RightModule r m, RightModule r n) => RightModule r ((,) m n)
(RightModule r m, Applicative f) => RightModule r (App f m)
(RightModule r m, Monad f) => RightModule r (Mon f m)
Monoid m => RightModule Natural (a -> m)
Monoid m => RightModule Natural (a -> m)
Category k => RightModule Natural (GEndo k a)
Category k => RightModule Natural (GEndo k a)
Alternative f => RightModule Natural (Alt f a)
Alternative f => RightModule Natural (Alt f a)
MonadPlus f => RightModule Natural (MonadSum f a)
MonadPlus f => RightModule Natural (MonadSum f a)
Eq a => RightModule Natural (RLE Seq a)
Eq a => RightModule Natural (RLE Seq a)
(RightModule r m, RightModule r n, RightModule r o) => RightModule r ((,,) m n o)
Monoid m => RightModule Natural (CMonoid m m m)
Monoid m => RightModule Natural (CMonoid m m m)
(RightModule r m, RightModule r n, RightModule r o, RightModule r p) => RightModule r ((,,,) m n o p)
(RightModule r m, RightModule r n, RightModule r o, RightModule r p, RightModule r q) => RightModule r ((,,,,) m n o p q)
(.*) :: RightModule r m => m -> r -> mSource
class (LeftModule r m, RightModule r m) => Module r m Source
 (x *. m) .* y = x *. (m .* y)
show/hide Instances
Module Natural Ordering
Module Natural Ordering
Module Natural ()
Module Natural ()
Module Natural All
Module Natural All
Module Natural Any
Module Natural Any
Module Natural ([] a)
Module Natural ([] a)
Monoid m => Module Natural (Dual m)
Monoid m => Module Natural (Dual m)
Module Natural (Endo a)
Module Natural (Endo a)
Num a => Module Natural (Sum a)
Num a => Module Natural (Sum a)
Num a => Module Natural (Product a)
Num a => Module Natural (Product a)
Module Natural (First a)
Module Natural (First a)
Module Natural (Last a)
Module Natural (Last a)
CharReducer m => Module Natural (UTF8 m)
CharReducer m => Module Natural (UTF8 m)
Module Natural (SourcePosition f)
Module Natural (SourcePosition f)
Monoid m => Module Natural (Self m)
Monoid m => Module Natural (Self m)
Monoid m => Module Natural (FromString m)
Monoid m => Module Natural (FromString m)
Multiplicative m => Module Natural (Log m)
Multiplicative m => Module Natural (Log m)
Applicative f => Module Natural (Traversal f)
Applicative f => Module Natural (Traversal f)
Monad f => Module Natural (Action f)
Monad f => Module Natural (Action f)
Module Natural (Free a)
Module Natural (Free a)
(Module r m, Module r n) => Module r ((,) m n)
(Module r m, Applicative f) => Module r (App f m)
(Module r m, Monad f) => Module r (Mon f m)
Monoid m => Module Natural (a -> m)
Monoid m => Module Natural (a -> m)
Category k => Module Natural (GEndo k a)
Category k => Module Natural (GEndo k a)
Alternative f => Module Natural (Alt f a)
Alternative f => Module Natural (Alt f a)
MonadPlus f => Module Natural (MonadSum f a)
MonadPlus f => Module Natural (MonadSum f a)
Eq a => Module Natural (RLE Seq a)
Eq a => Module Natural (RLE Seq a)
(Module r m, Module r n, Module r o) => Module r ((,,) m n o)
Monoid m => Module Natural (CMonoid m m m)
Monoid m => Module Natural (CMonoid m m m)
(Module r m, Module r n, Module r o, Module r p) => Module r ((,,,) m n o p)
(Module r m, Module r n, Module r o, Module r p, Module r q) => Module r ((,,,,) m n o p q)
Produced by Haddock version 2.4.1