algebra-2.1: Constructive abstract algebra

Safe HaskellSafe-Infered

Numeric.Module.Class

Contents

Synopsis

Module over semirings

class (Semiring r, Additive m) => LeftModule r m whereSource

Methods

(.*) :: r -> m -> mSource

Instances

LeftModule Integer Int 
LeftModule Integer Int8 
LeftModule Integer Int16 
LeftModule Integer Int32 
LeftModule Integer Int64 
LeftModule Integer Integer 
LeftModule Integer Word 
LeftModule Integer Word8 
LeftModule Integer Word16 
LeftModule Integer Word32 
LeftModule Integer Word64 
LeftModule Integer Euclidean 
Additive m => LeftModule () m 
Semiring r => LeftModule r () 
LeftModule Natural Bool 
LeftModule Natural Int 
LeftModule Natural Int8 
LeftModule Natural Int16 
LeftModule Natural Int32 
LeftModule Natural Int64 
LeftModule Natural Integer 
LeftModule Natural Word 
LeftModule Natural Word8 
LeftModule Natural Word16 
LeftModule Natural Word32 
LeftModule Natural Word64 
LeftModule Natural Natural 
LeftModule Natural Euclidean 
Division r => LeftModule Integer (Log r) 
(Abelian r, Group r) => LeftModule Integer (RngRing r) 
Group r => LeftModule Integer (ZeroRng r) 
LeftModule r s => LeftModule r (Complex s) 
LeftModule r s => LeftModule r (Quaternion s) 
LeftModule r s => LeftModule r (Dual s) 
LeftModule r s => LeftModule r (Hyper' s) 
LeftModule r s => LeftModule r (Hyper s) 
LeftModule r s => LeftModule r (Dual' s) 
LeftModule r s => LeftModule r (Quaternion' s) 
LeftModule r s => LeftModule r (Trig s) 
LeftModule r m => LeftModule r (End m) 
RightModule r s => LeftModule r (Opposite s) 
LeftModule Natural (BasisCoblade m) 
Unital r => LeftModule Natural (Log r) 
(Abelian r, Monoidal r) => LeftModule Natural (RngRing r) 
Monoidal r => LeftModule Natural (ZeroRng r) 
(LeftModule r a, LeftModule r b) => LeftModule r (a, b) 
(HasTrie e, LeftModule r m) => LeftModule r (:->: e m) 
LeftModule r m => LeftModule r (e -> m) 
LeftModule r s => LeftModule r (Covector s m) 
(LeftModule r a, LeftModule r b, LeftModule r c) => LeftModule r (a, b, c) 
LeftModule r s => LeftModule r (Map s b m) 
(LeftModule r a, LeftModule r b, LeftModule r c, LeftModule r d) => LeftModule r (a, b, c, d) 
(LeftModule r a, LeftModule r b, LeftModule r c, LeftModule r d, LeftModule r e) => LeftModule r (a, b, c, d, e) 
(Commutative r, Rng r) => LeftModule (Complex r) (Complex r) 
(TriviallyInvolutive r, Rng r) => LeftModule (Quaternion r) (Quaternion r) 
(Commutative r, Rng r) => LeftModule (Dual r) (Dual r) 
(Commutative r, Semiring r) => LeftModule (Hyper' r) (Hyper' r) 
(Commutative r, Semiring r) => LeftModule (Hyper r) (Hyper r) 
(Commutative r, Rng r) => LeftModule (Dual' r) (Dual' r) 
(TriviallyInvolutive r, Rng r) => LeftModule (Quaternion' r) (Quaternion' r) 
(Commutative r, Rng r) => LeftModule (Trig r) (Trig r) 
(Monoidal m, Abelian m) => LeftModule (End m) (End m) 
Semiring r => LeftModule (Opposite r) (Opposite r) 
Rng s => LeftModule (RngRing s) (RngRing s) 
Coalgebra r m => LeftModule (Covector r m) (Covector r m) 
Coalgebra r m => LeftModule (Map r b m) (Map r b m) 

class (Semiring r, Additive m) => RightModule r m whereSource

Methods

(*.) :: m -> r -> mSource

Instances

RightModule Integer Int 
RightModule Integer Int8 
RightModule Integer Int16 
RightModule Integer Int32 
RightModule Integer Int64 
RightModule Integer Integer 
RightModule Integer Word 
RightModule Integer Word8 
RightModule Integer Word16 
RightModule Integer Word32 
RightModule Integer Word64 
RightModule Integer Euclidean 
Additive m => RightModule () m 
Semiring r => RightModule r () 
RightModule Natural Bool 
RightModule Natural Int 
RightModule Natural Int8 
RightModule Natural Int16 
RightModule Natural Int32 
RightModule Natural Int64 
RightModule Natural Integer 
RightModule Natural Word 
RightModule Natural Word8 
RightModule Natural Word16 
RightModule Natural Word32 
RightModule Natural Word64 
RightModule Natural Natural 
RightModule Natural Euclidean 
Division r => RightModule Integer (Log r) 
(Abelian r, Group r) => RightModule Integer (RngRing r) 
Group r => RightModule Integer (ZeroRng r) 
RightModule r s => RightModule r (Complex s) 
RightModule r s => RightModule r (Quaternion s) 
RightModule r s => RightModule r (Dual s) 
RightModule r s => RightModule r (Hyper' s) 
RightModule r s => RightModule r (Hyper s) 
RightModule r s => RightModule r (Dual' s) 
RightModule r s => RightModule r (Quaternion' s) 
RightModule r s => RightModule r (Trig s) 
RightModule r m => RightModule r (End m) 
LeftModule r s => RightModule r (Opposite s) 
RightModule Natural (BasisCoblade m) 
Unital r => RightModule Natural (Log r) 
(Abelian r, Monoidal r) => RightModule Natural (RngRing r) 
Monoidal r => RightModule Natural (ZeroRng r) 
(RightModule r a, RightModule r b) => RightModule r (a, b) 
(HasTrie e, RightModule r m) => RightModule r (:->: e m) 
RightModule r m => RightModule r (e -> m) 
RightModule r s => RightModule r (Covector s m) 
(RightModule r a, RightModule r b, RightModule r c) => RightModule r (a, b, c) 
RightModule r s => RightModule r (Map s b m) 
(RightModule r a, RightModule r b, RightModule r c, RightModule r d) => RightModule r (a, b, c, d) 
(RightModule r a, RightModule r b, RightModule r c, RightModule r d, RightModule r e) => RightModule r (a, b, c, d, e) 
(Commutative r, Rng r) => RightModule (Complex r) (Complex r) 
(TriviallyInvolutive r, Rng r) => RightModule (Quaternion r) (Quaternion r) 
(Commutative r, Rng r) => RightModule (Dual r) (Dual r) 
(Commutative r, Semiring r) => RightModule (Hyper' r) (Hyper' r) 
(Commutative r, Semiring r) => RightModule (Hyper r) (Hyper r) 
(Commutative r, Rng r) => RightModule (Dual' r) (Dual' r) 
(TriviallyInvolutive r, Rng r) => RightModule (Quaternion' r) (Quaternion' r) 
(Commutative r, Rng r) => RightModule (Trig r) (Trig r) 
(Monoidal m, Abelian m) => RightModule (End m) (End m) 
Semiring r => RightModule (Opposite r) (Opposite r) 
Rng s => RightModule (RngRing s) (RngRing s) 
Coalgebra r m => RightModule (Covector r m) (Covector r m) 
Coalgebra r m => RightModule (Map r b m) (Map r b m) 

class (LeftModule r m, RightModule r m) => Module r m Source

Instances

(LeftModule r m, RightModule r m) => Module r m