algebra-4.3: Constructive abstract algebra

Safe HaskellSafe
LanguageHaskell98

Numeric.Module.Class

Contents

Synopsis

Module over semirings

class (Semiring r, Additive m) => LeftModule r m where Source #

Minimal complete definition

(.*)

Methods

(.*) :: r -> m -> m infixl 7 Source #

Instances

LeftModule Integer Int Source # 

Methods

(.*) :: Integer -> Int -> Int Source #

LeftModule Integer Int8 Source # 

Methods

(.*) :: Integer -> Int8 -> Int8 Source #

LeftModule Integer Int16 Source # 

Methods

(.*) :: Integer -> Int16 -> Int16 Source #

LeftModule Integer Int32 Source # 

Methods

(.*) :: Integer -> Int32 -> Int32 Source #

LeftModule Integer Int64 Source # 

Methods

(.*) :: Integer -> Int64 -> Int64 Source #

LeftModule Integer Integer Source # 
LeftModule Integer Word Source # 

Methods

(.*) :: Integer -> Word -> Word Source #

LeftModule Integer Word8 Source # 

Methods

(.*) :: Integer -> Word8 -> Word8 Source #

LeftModule Integer Word16 Source # 

Methods

(.*) :: Integer -> Word16 -> Word16 Source #

LeftModule Integer Word32 Source # 

Methods

(.*) :: Integer -> Word32 -> Word32 Source #

LeftModule Integer Word64 Source # 

Methods

(.*) :: Integer -> Word64 -> Word64 Source #

LeftModule Integer Euclidean Source # 
Additive m => LeftModule () m Source # 

Methods

(.*) :: () -> m -> m Source #

Semiring r => LeftModule r () Source # 

Methods

(.*) :: r -> () -> () Source #

LeftModule Natural Bool Source # 

Methods

(.*) :: Natural -> Bool -> Bool Source #

LeftModule Natural Int Source # 

Methods

(.*) :: Natural -> Int -> Int Source #

LeftModule Natural Int8 Source # 

Methods

(.*) :: Natural -> Int8 -> Int8 Source #

LeftModule Natural Int16 Source # 

Methods

(.*) :: Natural -> Int16 -> Int16 Source #

LeftModule Natural Int32 Source # 

Methods

(.*) :: Natural -> Int32 -> Int32 Source #

LeftModule Natural Int64 Source # 

Methods

(.*) :: Natural -> Int64 -> Int64 Source #

LeftModule Natural Integer Source # 
LeftModule Natural Word Source # 

Methods

(.*) :: Natural -> Word -> Word Source #

LeftModule Natural Word8 Source # 

Methods

(.*) :: Natural -> Word8 -> Word8 Source #

LeftModule Natural Word16 Source # 

Methods

(.*) :: Natural -> Word16 -> Word16 Source #

LeftModule Natural Word32 Source # 

Methods

(.*) :: Natural -> Word32 -> Word32 Source #

LeftModule Natural Word64 Source # 

Methods

(.*) :: Natural -> Word64 -> Word64 Source #

LeftModule Natural Natural Source # 
LeftModule Natural Euclidean Source # 
GCDDomain d => LeftModule Integer (Fraction d) Source # 

Methods

(.*) :: Integer -> Fraction d -> Fraction d Source #

Division r => LeftModule Integer (Log r) Source # 

Methods

(.*) :: Integer -> Log r -> Log r Source #

(Abelian r, Group r) => LeftModule Integer (RngRing r) Source # 

Methods

(.*) :: Integer -> RngRing r -> RngRing r Source #

Group r => LeftModule Integer (ZeroRng r) Source # 

Methods

(.*) :: Integer -> ZeroRng r -> ZeroRng r Source #

LeftModule r s => LeftModule r (Complex s) Source # 

Methods

(.*) :: r -> Complex s -> Complex s Source #

LeftModule r s => LeftModule r (Dual s) Source # 

Methods

(.*) :: r -> Dual s -> Dual s Source #

LeftModule r s => LeftModule r (Hyper' s) Source # 

Methods

(.*) :: r -> Hyper' s -> Hyper' s Source #

LeftModule r s => LeftModule r (Quaternion s) Source # 

Methods

(.*) :: r -> Quaternion s -> Quaternion s Source #

LeftModule r s => LeftModule r (Dual' s) Source # 

Methods

(.*) :: r -> Dual' s -> Dual' s Source #

LeftModule r s => LeftModule r (Hyper s) Source # 

Methods

(.*) :: r -> Hyper s -> Hyper s Source #

LeftModule r s => LeftModule r (Quaternion' s) Source # 

Methods

(.*) :: r -> Quaternion' s -> Quaternion' s Source #

LeftModule r s => LeftModule r (Trig s) Source # 

Methods

(.*) :: r -> Trig s -> Trig s Source #

LeftModule r m => LeftModule r (End m) Source # 

Methods

(.*) :: r -> End m -> End m Source #

RightModule r s => LeftModule r (Opposite s) Source # 

Methods

(.*) :: r -> Opposite s -> Opposite s Source #

GCDDomain d => LeftModule Natural (Fraction d) Source # 

Methods

(.*) :: Natural -> Fraction d -> Fraction d Source #

LeftModule Natural (BasisCoblade m) Source # 
Unital r => LeftModule Natural (Log r) Source # 

Methods

(.*) :: Natural -> Log r -> Log r Source #

(Abelian r, Monoidal r) => LeftModule Natural (RngRing r) Source # 

Methods

(.*) :: Natural -> RngRing r -> RngRing r Source #

Monoidal r => LeftModule Natural (ZeroRng r) Source # 

Methods

(.*) :: Natural -> ZeroRng r -> ZeroRng r Source #

(LeftModule r a, LeftModule r b) => LeftModule r (a, b) Source # 

Methods

(.*) :: r -> (a, b) -> (a, b) Source #

LeftModule r m => LeftModule r (e -> m) Source # 

Methods

(.*) :: r -> (e -> m) -> e -> m Source #

LeftModule r s => LeftModule r (Covector s m) Source # 

Methods

(.*) :: r -> Covector s m -> Covector s m Source #

(LeftModule r a, LeftModule r b, LeftModule r c) => LeftModule r (a, b, c) Source # 

Methods

(.*) :: r -> (a, b, c) -> (a, b, c) Source #

LeftModule r s => LeftModule r (Map s b m) Source # 

Methods

(.*) :: r -> Map s b m -> Map s b m Source #

(LeftModule r a, LeftModule r b, LeftModule r c, LeftModule r d) => LeftModule r (a, b, c, d) Source # 

Methods

(.*) :: r -> (a, b, c, d) -> (a, b, c, d) Source #

(LeftModule r a, LeftModule r b, LeftModule r c, LeftModule r d, LeftModule r e) => LeftModule r (a, b, c, d, e) Source # 

Methods

(.*) :: r -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

(Commutative r, Rng r) => LeftModule (Complex r) (Complex r) Source # 

Methods

(.*) :: Complex r -> Complex r -> Complex r Source #

(Commutative r, Rng r) => LeftModule (Dual r) (Dual r) Source # 

Methods

(.*) :: Dual r -> Dual r -> Dual r Source #

(Commutative r, Semiring r) => LeftModule (Hyper' r) (Hyper' r) Source # 

Methods

(.*) :: Hyper' r -> Hyper' r -> Hyper' r Source #

(TriviallyInvolutive r, Rng r) => LeftModule (Quaternion r) (Quaternion r) Source # 
(Commutative r, Rng r) => LeftModule (Dual' r) (Dual' r) Source # 

Methods

(.*) :: Dual' r -> Dual' r -> Dual' r Source #

(Commutative r, Semiring r) => LeftModule (Hyper r) (Hyper r) Source # 

Methods

(.*) :: Hyper r -> Hyper r -> Hyper r Source #

(TriviallyInvolutive r, Rng r) => LeftModule (Quaternion' r) (Quaternion' r) Source # 
(Commutative r, Rng r) => LeftModule (Trig r) (Trig r) Source # 

Methods

(.*) :: Trig r -> Trig r -> Trig r Source #

(Monoidal m, Abelian m) => LeftModule (End m) (End m) Source # 

Methods

(.*) :: End m -> End m -> End m Source #

Semiring r => LeftModule (Opposite r) (Opposite r) Source # 

Methods

(.*) :: Opposite r -> Opposite r -> Opposite r Source #

Rng s => LeftModule (RngRing s) (RngRing s) Source # 

Methods

(.*) :: RngRing s -> RngRing s -> RngRing s Source #

Coalgebra r m => LeftModule (Covector r m) (Covector r m) Source # 

Methods

(.*) :: Covector r m -> Covector r m -> Covector r m Source #

Coalgebra r m => LeftModule (Map r b m) (Map r b m) Source # 

Methods

(.*) :: Map r b m -> Map r b m -> Map r b m Source #

class (Semiring r, Additive m) => RightModule r m where Source #

Minimal complete definition

(*.)

Methods

(*.) :: m -> r -> m infixl 7 Source #

Instances

RightModule Integer Int Source # 

Methods

(*.) :: Int -> Integer -> Int Source #

RightModule Integer Int8 Source # 

Methods

(*.) :: Int8 -> Integer -> Int8 Source #

RightModule Integer Int16 Source # 

Methods

(*.) :: Int16 -> Integer -> Int16 Source #

RightModule Integer Int32 Source # 

Methods

(*.) :: Int32 -> Integer -> Int32 Source #

RightModule Integer Int64 Source # 

Methods

(*.) :: Int64 -> Integer -> Int64 Source #

RightModule Integer Integer Source # 
RightModule Integer Word Source # 

Methods

(*.) :: Word -> Integer -> Word Source #

RightModule Integer Word8 Source # 

Methods

(*.) :: Word8 -> Integer -> Word8 Source #

RightModule Integer Word16 Source # 

Methods

(*.) :: Word16 -> Integer -> Word16 Source #

RightModule Integer Word32 Source # 

Methods

(*.) :: Word32 -> Integer -> Word32 Source #

RightModule Integer Word64 Source # 

Methods

(*.) :: Word64 -> Integer -> Word64 Source #

RightModule Integer Euclidean Source # 
Additive m => RightModule () m Source # 

Methods

(*.) :: m -> () -> m Source #

Semiring r => RightModule r () Source # 

Methods

(*.) :: () -> r -> () Source #

RightModule Natural Bool Source # 

Methods

(*.) :: Bool -> Natural -> Bool Source #

RightModule Natural Int Source # 

Methods

(*.) :: Int -> Natural -> Int Source #

RightModule Natural Int8 Source # 

Methods

(*.) :: Int8 -> Natural -> Int8 Source #

RightModule Natural Int16 Source # 

Methods

(*.) :: Int16 -> Natural -> Int16 Source #

RightModule Natural Int32 Source # 

Methods

(*.) :: Int32 -> Natural -> Int32 Source #

RightModule Natural Int64 Source # 

Methods

(*.) :: Int64 -> Natural -> Int64 Source #

RightModule Natural Integer Source # 
RightModule Natural Word Source # 

Methods

(*.) :: Word -> Natural -> Word Source #

RightModule Natural Word8 Source # 

Methods

(*.) :: Word8 -> Natural -> Word8 Source #

RightModule Natural Word16 Source # 

Methods

(*.) :: Word16 -> Natural -> Word16 Source #

RightModule Natural Word32 Source # 

Methods

(*.) :: Word32 -> Natural -> Word32 Source #

RightModule Natural Word64 Source # 

Methods

(*.) :: Word64 -> Natural -> Word64 Source #

RightModule Natural Natural Source # 
RightModule Natural Euclidean Source # 
GCDDomain d => RightModule Integer (Fraction d) Source # 

Methods

(*.) :: Fraction d -> Integer -> Fraction d Source #

Division r => RightModule Integer (Log r) Source # 

Methods

(*.) :: Log r -> Integer -> Log r Source #

(Abelian r, Group r) => RightModule Integer (RngRing r) Source # 

Methods

(*.) :: RngRing r -> Integer -> RngRing r Source #

Group r => RightModule Integer (ZeroRng r) Source # 

Methods

(*.) :: ZeroRng r -> Integer -> ZeroRng r Source #

RightModule r s => RightModule r (Complex s) Source # 

Methods

(*.) :: Complex s -> r -> Complex s Source #

RightModule r s => RightModule r (Dual s) Source # 

Methods

(*.) :: Dual s -> r -> Dual s Source #

RightModule r s => RightModule r (Hyper' s) Source # 

Methods

(*.) :: Hyper' s -> r -> Hyper' s Source #

RightModule r s => RightModule r (Quaternion s) Source # 

Methods

(*.) :: Quaternion s -> r -> Quaternion s Source #

RightModule r s => RightModule r (Dual' s) Source # 

Methods

(*.) :: Dual' s -> r -> Dual' s Source #

RightModule r s => RightModule r (Hyper s) Source # 

Methods

(*.) :: Hyper s -> r -> Hyper s Source #

RightModule r s => RightModule r (Quaternion' s) Source # 

Methods

(*.) :: Quaternion' s -> r -> Quaternion' s Source #

RightModule r s => RightModule r (Trig s) Source # 

Methods

(*.) :: Trig s -> r -> Trig s Source #

RightModule r m => RightModule r (End m) Source # 

Methods

(*.) :: End m -> r -> End m Source #

LeftModule r s => RightModule r (Opposite s) Source # 

Methods

(*.) :: Opposite s -> r -> Opposite s Source #

GCDDomain d => RightModule Natural (Fraction d) Source # 

Methods

(*.) :: Fraction d -> Natural -> Fraction d Source #

RightModule Natural (BasisCoblade m) Source # 
Unital r => RightModule Natural (Log r) Source # 

Methods

(*.) :: Log r -> Natural -> Log r Source #

(Abelian r, Monoidal r) => RightModule Natural (RngRing r) Source # 

Methods

(*.) :: RngRing r -> Natural -> RngRing r Source #

Monoidal r => RightModule Natural (ZeroRng r) Source # 

Methods

(*.) :: ZeroRng r -> Natural -> ZeroRng r Source #

(RightModule r a, RightModule r b) => RightModule r (a, b) Source # 

Methods

(*.) :: (a, b) -> r -> (a, b) Source #

RightModule r m => RightModule r (e -> m) Source # 

Methods

(*.) :: (e -> m) -> r -> e -> m Source #

RightModule r s => RightModule r (Covector s m) Source # 

Methods

(*.) :: Covector s m -> r -> Covector s m Source #

(RightModule r a, RightModule r b, RightModule r c) => RightModule r (a, b, c) Source # 

Methods

(*.) :: (a, b, c) -> r -> (a, b, c) Source #

RightModule r s => RightModule r (Map s b m) Source # 

Methods

(*.) :: Map s b m -> r -> Map s b m Source #

(RightModule r a, RightModule r b, RightModule r c, RightModule r d) => RightModule r (a, b, c, d) Source # 

Methods

(*.) :: (a, b, c, d) -> r -> (a, b, c, d) Source #

(RightModule r a, RightModule r b, RightModule r c, RightModule r d, RightModule r e) => RightModule r (a, b, c, d, e) Source # 

Methods

(*.) :: (a, b, c, d, e) -> r -> (a, b, c, d, e) Source #

(Commutative r, Rng r) => RightModule (Complex r) (Complex r) Source # 

Methods

(*.) :: Complex r -> Complex r -> Complex r Source #

(Commutative r, Rng r) => RightModule (Dual r) (Dual r) Source # 

Methods

(*.) :: Dual r -> Dual r -> Dual r Source #

(Commutative r, Semiring r) => RightModule (Hyper' r) (Hyper' r) Source # 

Methods

(*.) :: Hyper' r -> Hyper' r -> Hyper' r Source #

(TriviallyInvolutive r, Rng r) => RightModule (Quaternion r) (Quaternion r) Source # 
(Commutative r, Rng r) => RightModule (Dual' r) (Dual' r) Source # 

Methods

(*.) :: Dual' r -> Dual' r -> Dual' r Source #

(Commutative r, Semiring r) => RightModule (Hyper r) (Hyper r) Source # 

Methods

(*.) :: Hyper r -> Hyper r -> Hyper r Source #

(TriviallyInvolutive r, Rng r) => RightModule (Quaternion' r) (Quaternion' r) Source # 
(Commutative r, Rng r) => RightModule (Trig r) (Trig r) Source # 

Methods

(*.) :: Trig r -> Trig r -> Trig r Source #

(Monoidal m, Abelian m) => RightModule (End m) (End m) Source # 

Methods

(*.) :: End m -> End m -> End m Source #

Semiring r => RightModule (Opposite r) (Opposite r) Source # 

Methods

(*.) :: Opposite r -> Opposite r -> Opposite r Source #

Rng s => RightModule (RngRing s) (RngRing s) Source # 

Methods

(*.) :: RngRing s -> RngRing s -> RngRing s Source #

Coalgebra r m => RightModule (Covector r m) (Covector r m) Source # 

Methods

(*.) :: Covector r m -> Covector r m -> Covector r m Source #

Coalgebra r m => RightModule (Map r b m) (Map r b m) Source # 

Methods

(*.) :: Map r b m -> Map r b m -> Map r b m Source #

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

Instances

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