algebra-4.3: Constructive abstract algebra

Safe HaskellSafe
LanguageHaskell98

Numeric.Algebra.Class

Contents

Synopsis

Multiplicative Semigroups

class Multiplicative r where Source #

A multiplicative semigroup

Minimal complete definition

(*)

Methods

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

pow1p :: r -> Natural -> r infixr 8 Source #

productWith1 :: Foldable1 f => (a -> r) -> f a -> r Source #

Instances

Multiplicative Bool Source # 

Methods

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

pow1p :: Bool -> Natural -> Bool Source #

productWith1 :: Foldable1 f => (a -> Bool) -> f a -> Bool Source #

Multiplicative Int Source # 

Methods

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

pow1p :: Int -> Natural -> Int Source #

productWith1 :: Foldable1 f => (a -> Int) -> f a -> Int Source #

Multiplicative Int8 Source # 

Methods

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

pow1p :: Int8 -> Natural -> Int8 Source #

productWith1 :: Foldable1 f => (a -> Int8) -> f a -> Int8 Source #

Multiplicative Int16 Source # 

Methods

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

pow1p :: Int16 -> Natural -> Int16 Source #

productWith1 :: Foldable1 f => (a -> Int16) -> f a -> Int16 Source #

Multiplicative Int32 Source # 

Methods

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

pow1p :: Int32 -> Natural -> Int32 Source #

productWith1 :: Foldable1 f => (a -> Int32) -> f a -> Int32 Source #

Multiplicative Int64 Source # 

Methods

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

pow1p :: Int64 -> Natural -> Int64 Source #

productWith1 :: Foldable1 f => (a -> Int64) -> f a -> Int64 Source #

Multiplicative Integer Source # 
Multiplicative Word Source # 

Methods

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

pow1p :: Word -> Natural -> Word Source #

productWith1 :: Foldable1 f => (a -> Word) -> f a -> Word Source #

Multiplicative Word8 Source # 

Methods

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

pow1p :: Word8 -> Natural -> Word8 Source #

productWith1 :: Foldable1 f => (a -> Word8) -> f a -> Word8 Source #

Multiplicative Word16 Source # 
Multiplicative Word32 Source # 
Multiplicative Word64 Source # 
Multiplicative () Source # 

Methods

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

pow1p :: () -> Natural -> () Source #

productWith1 :: Foldable1 f => (a -> ()) -> f a -> () Source #

Multiplicative Natural Source # 
Multiplicative Euclidean Source # 
GCDDomain d => Multiplicative (Fraction d) Source # 

Methods

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

pow1p :: Fraction d -> Natural -> Fraction d Source #

productWith1 :: Foldable1 f => (a -> Fraction d) -> f a -> Fraction d Source #

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

Methods

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

pow1p :: Complex r -> Natural -> Complex r Source #

productWith1 :: Foldable1 f => (a -> Complex r) -> f a -> Complex r Source #

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

Methods

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

pow1p :: Dual r -> Natural -> Dual r Source #

productWith1 :: Foldable1 f => (a -> Dual r) -> f a -> Dual r Source #

(Commutative k, Semiring k) => Multiplicative (Hyper' k) Source # 

Methods

(*) :: Hyper' k -> Hyper' k -> Hyper' k Source #

pow1p :: Hyper' k -> Natural -> Hyper' k Source #

productWith1 :: Foldable1 f => (a -> Hyper' k) -> f a -> Hyper' k Source #

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

Methods

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

pow1p :: Dual' r -> Natural -> Dual' r Source #

productWith1 :: Foldable1 f => (a -> Dual' r) -> f a -> Dual' r Source #

Multiplicative (BasisCoblade m) Source # 
(Commutative k, Semiring k) => Multiplicative (Hyper k) Source # 

Methods

(*) :: Hyper k -> Hyper k -> Hyper k Source #

pow1p :: Hyper k -> Natural -> Hyper k Source #

productWith1 :: Foldable1 f => (a -> Hyper k) -> f a -> Hyper k Source #

(TriviallyInvolutive r, Semiring r) => Multiplicative (Quaternion' r) Source # 
(Commutative k, Rng k) => Multiplicative (Trig k) Source # 

Methods

(*) :: Trig k -> Trig k -> Trig k Source #

pow1p :: Trig k -> Natural -> Trig k Source #

productWith1 :: Foldable1 f => (a -> Trig k) -> f a -> Trig k Source #

Additive r => Multiplicative (Exp r) Source # 

Methods

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

pow1p :: Exp r -> Natural -> Exp r Source #

productWith1 :: Foldable1 f => (a -> Exp r) -> f a -> Exp r Source #

Multiplicative (End r) Source # 

Methods

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

pow1p :: End r -> Natural -> End r Source #

productWith1 :: Foldable1 f => (a -> End r) -> f a -> End r Source #

Multiplicative r => Multiplicative (Opposite r) Source # 

Methods

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

pow1p :: Opposite r -> Natural -> Opposite r Source #

productWith1 :: Foldable1 f => (a -> Opposite r) -> f a -> Opposite r Source #

Rng r => Multiplicative (RngRing r) Source # 

Methods

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

pow1p :: RngRing r -> Natural -> RngRing r Source #

productWith1 :: Foldable1 f => (a -> RngRing r) -> f a -> RngRing r Source #

Monoidal r => Multiplicative (ZeroRng r) Source # 

Methods

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

pow1p :: ZeroRng r -> Natural -> ZeroRng r Source #

productWith1 :: Foldable1 f => (a -> ZeroRng r) -> f a -> ZeroRng r Source #

Algebra r a => Multiplicative (a -> r) Source # 

Methods

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

pow1p :: (a -> r) -> Natural -> a -> r Source #

productWith1 :: Foldable1 f => (a -> a -> r) -> f a -> a -> r Source #

(Multiplicative a, Multiplicative b) => Multiplicative (a, b) Source # 

Methods

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

pow1p :: (a, b) -> Natural -> (a, b) Source #

productWith1 :: Foldable1 f => (a -> (a, b)) -> f a -> (a, b) Source #

Multiplicative (Rect i j) Source # 

Methods

(*) :: Rect i j -> Rect i j -> Rect i j Source #

pow1p :: Rect i j -> Natural -> Rect i j Source #

productWith1 :: Foldable1 f => (a -> Rect i j) -> f a -> Rect i j Source #

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

Methods

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

pow1p :: Covector r m -> Natural -> Covector r m Source #

productWith1 :: Foldable1 f => (a -> Covector r m) -> f a -> Covector r m Source #

(Multiplicative a, Multiplicative b, Multiplicative c) => Multiplicative (a, b, c) Source # 

Methods

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

pow1p :: (a, b, c) -> Natural -> (a, b, c) Source #

productWith1 :: Foldable1 f => (a -> (a, b, c)) -> f a -> (a, b, c) Source #

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

Methods

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

pow1p :: Map r b m -> Natural -> Map r b m Source #

productWith1 :: Foldable1 f => (a -> Map r b m) -> f a -> Map r b m Source #

(Multiplicative a, Multiplicative b, Multiplicative c, Multiplicative d) => Multiplicative (a, b, c, d) Source # 

Methods

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

pow1p :: (a, b, c, d) -> Natural -> (a, b, c, d) Source #

productWith1 :: Foldable1 f => (a -> (a, b, c, d)) -> f a -> (a, b, c, d) Source #

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

Methods

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

pow1p :: (a, b, c, d, e) -> Natural -> (a, b, c, d, e) Source #

productWith1 :: Foldable1 f => (a -> (a, b, c, d, e)) -> f a -> (a, b, c, d, e) Source #

pow1pIntegral :: (Integral r, Integral n) => r -> n -> r Source #

product1 :: (Foldable1 f, Multiplicative r) => f r -> r Source #

Semirings

class (Additive r, Abelian r, Multiplicative r) => Semiring r Source #

A pair of an additive abelian semigroup, and a multiplicative semigroup, with the distributive laws:

a(b + c) = ab + ac -- left distribution (we are a LeftNearSemiring)
(a + b)c = ac + bc -- right distribution (we are a [Right]NearSemiring)

Common notation includes the laws for additive and multiplicative identity in semiring.

If you want that, look at Rig instead.

Ideally we'd use the cyclic definition:

class (LeftModule r r, RightModule r r, Additive r, Abelian r, Multiplicative r) => Semiring r

to enforce that every semiring r is an r-module over itself, but Haskell doesn't like that.

Instances

Semiring Bool Source # 
Semiring Int Source # 
Semiring Int8 Source # 
Semiring Int16 Source # 
Semiring Int32 Source # 
Semiring Int64 Source # 
Semiring Integer Source # 
Semiring Word Source # 
Semiring Word8 Source # 
Semiring Word16 Source # 
Semiring Word32 Source # 
Semiring Word64 Source # 
Semiring () Source # 
Semiring Natural Source # 
Semiring Euclidean Source # 
GCDDomain d => Semiring (Fraction d) Source # 
(Commutative r, Rng r) => Semiring (Complex r) Source # 
(Commutative r, Rng r) => Semiring (Dual r) Source # 
(Commutative k, Semiring k) => Semiring (Hyper' k) Source # 
(TriviallyInvolutive r, Rng r) => Semiring (Quaternion r) Source # 
(Commutative r, Rng r) => Semiring (Dual' r) Source # 
Semiring (BasisCoblade m) Source # 
(Commutative k, Semiring k) => Semiring (Hyper k) Source # 
(TriviallyInvolutive r, Semiring r) => Semiring (Quaternion' r) Source # 
(Commutative k, Rng k) => Semiring (Trig k) Source # 
(Abelian r, Monoidal r) => Semiring (End r) Source # 
Semiring r => Semiring (Opposite r) Source # 
Rng r => Semiring (RngRing r) Source # 
(Monoidal r, Abelian r) => Semiring (ZeroRng r) Source # 
Algebra r a => Semiring (a -> r) Source # 
(Semiring a, Semiring b) => Semiring (a, b) Source # 
Coalgebra r m => Semiring (Covector r m) Source # 
(Semiring a, Semiring b, Semiring c) => Semiring (a, b, c) Source # 
Coalgebra r m => Semiring (Map r b m) Source # 
(Semiring a, Semiring b, Semiring c, Semiring d) => Semiring (a, b, c, d) Source # 
(Semiring a, Semiring b, Semiring c, Semiring d, Semiring e) => Semiring (a, b, c, d, e) Source # 

Left and Right Modules

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 # 

Additive Monoids

class (LeftModule Natural m, RightModule Natural m) => Monoidal m where Source #

An additive monoid

zero + a = a = a + zero

Minimal complete definition

zero

Methods

zero :: m Source #

sinnum :: Natural -> m -> m Source #

sumWith :: Foldable f => (a -> m) -> f a -> m Source #

Instances

Monoidal Bool Source # 

Methods

zero :: Bool Source #

sinnum :: Natural -> Bool -> Bool Source #

sumWith :: Foldable f => (a -> Bool) -> f a -> Bool Source #

Monoidal Int Source # 

Methods

zero :: Int Source #

sinnum :: Natural -> Int -> Int Source #

sumWith :: Foldable f => (a -> Int) -> f a -> Int Source #

Monoidal Int8 Source # 

Methods

zero :: Int8 Source #

sinnum :: Natural -> Int8 -> Int8 Source #

sumWith :: Foldable f => (a -> Int8) -> f a -> Int8 Source #

Monoidal Int16 Source # 

Methods

zero :: Int16 Source #

sinnum :: Natural -> Int16 -> Int16 Source #

sumWith :: Foldable f => (a -> Int16) -> f a -> Int16 Source #

Monoidal Int32 Source # 

Methods

zero :: Int32 Source #

sinnum :: Natural -> Int32 -> Int32 Source #

sumWith :: Foldable f => (a -> Int32) -> f a -> Int32 Source #

Monoidal Int64 Source # 

Methods

zero :: Int64 Source #

sinnum :: Natural -> Int64 -> Int64 Source #

sumWith :: Foldable f => (a -> Int64) -> f a -> Int64 Source #

Monoidal Integer Source # 
Monoidal Word Source # 

Methods

zero :: Word Source #

sinnum :: Natural -> Word -> Word Source #

sumWith :: Foldable f => (a -> Word) -> f a -> Word Source #

Monoidal Word8 Source # 

Methods

zero :: Word8 Source #

sinnum :: Natural -> Word8 -> Word8 Source #

sumWith :: Foldable f => (a -> Word8) -> f a -> Word8 Source #

Monoidal Word16 Source # 

Methods

zero :: Word16 Source #

sinnum :: Natural -> Word16 -> Word16 Source #

sumWith :: Foldable f => (a -> Word16) -> f a -> Word16 Source #

Monoidal Word32 Source # 

Methods

zero :: Word32 Source #

sinnum :: Natural -> Word32 -> Word32 Source #

sumWith :: Foldable f => (a -> Word32) -> f a -> Word32 Source #

Monoidal Word64 Source # 

Methods

zero :: Word64 Source #

sinnum :: Natural -> Word64 -> Word64 Source #

sumWith :: Foldable f => (a -> Word64) -> f a -> Word64 Source #

Monoidal () Source # 

Methods

zero :: () Source #

sinnum :: Natural -> () -> () Source #

sumWith :: Foldable f => (a -> ()) -> f a -> () Source #

Monoidal Natural Source # 
Monoidal Euclidean Source # 
GCDDomain d => Monoidal (Fraction d) Source # 

Methods

zero :: Fraction d Source #

sinnum :: Natural -> Fraction d -> Fraction d Source #

sumWith :: Foldable f => (a -> Fraction d) -> f a -> Fraction d Source #

Monoidal r => Monoidal (Complex r) Source # 

Methods

zero :: Complex r Source #

sinnum :: Natural -> Complex r -> Complex r Source #

sumWith :: Foldable f => (a -> Complex r) -> f a -> Complex r Source #

Monoidal r => Monoidal (Dual r) Source # 

Methods

zero :: Dual r Source #

sinnum :: Natural -> Dual r -> Dual r Source #

sumWith :: Foldable f => (a -> Dual r) -> f a -> Dual r Source #

Monoidal r => Monoidal (Hyper' r) Source # 

Methods

zero :: Hyper' r Source #

sinnum :: Natural -> Hyper' r -> Hyper' r Source #

sumWith :: Foldable f => (a -> Hyper' r) -> f a -> Hyper' r Source #

Monoidal r => Monoidal (Quaternion r) Source # 
Monoidal r => Monoidal (Dual' r) Source # 

Methods

zero :: Dual' r Source #

sinnum :: Natural -> Dual' r -> Dual' r Source #

sumWith :: Foldable f => (a -> Dual' r) -> f a -> Dual' r Source #

Monoidal (BasisCoblade m) Source # 
Monoidal r => Monoidal (Hyper r) Source # 

Methods

zero :: Hyper r Source #

sinnum :: Natural -> Hyper r -> Hyper r Source #

sumWith :: Foldable f => (a -> Hyper r) -> f a -> Hyper r Source #

Monoidal r => Monoidal (Quaternion' r) Source # 
Monoidal r => Monoidal (Trig r) Source # 

Methods

zero :: Trig r Source #

sinnum :: Natural -> Trig r -> Trig r Source #

sumWith :: Foldable f => (a -> Trig r) -> f a -> Trig r Source #

Unital r => Monoidal (Log r) Source # 

Methods

zero :: Log r Source #

sinnum :: Natural -> Log r -> Log r Source #

sumWith :: Foldable f => (a -> Log r) -> f a -> Log r Source #

Monoidal r => Monoidal (End r) Source # 

Methods

zero :: End r Source #

sinnum :: Natural -> End r -> End r Source #

sumWith :: Foldable f => (a -> End r) -> f a -> End r Source #

Monoidal r => Monoidal (Opposite r) Source # 

Methods

zero :: Opposite r Source #

sinnum :: Natural -> Opposite r -> Opposite r Source #

sumWith :: Foldable f => (a -> Opposite r) -> f a -> Opposite r Source #

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

Methods

zero :: RngRing r Source #

sinnum :: Natural -> RngRing r -> RngRing r Source #

sumWith :: Foldable f => (a -> RngRing r) -> f a -> RngRing r Source #

Monoidal r => Monoidal (ZeroRng r) Source # 

Methods

zero :: ZeroRng r Source #

sinnum :: Natural -> ZeroRng r -> ZeroRng r Source #

sumWith :: Foldable f => (a -> ZeroRng r) -> f a -> ZeroRng r Source #

Monoidal r => Monoidal (e -> r) Source # 

Methods

zero :: e -> r Source #

sinnum :: Natural -> (e -> r) -> e -> r Source #

sumWith :: Foldable f => (a -> e -> r) -> f a -> e -> r Source #

(Monoidal a, Monoidal b) => Monoidal (a, b) Source # 

Methods

zero :: (a, b) Source #

sinnum :: Natural -> (a, b) -> (a, b) Source #

sumWith :: Foldable f => (a -> (a, b)) -> f a -> (a, b) Source #

Monoidal s => Monoidal (Covector s a) Source # 

Methods

zero :: Covector s a Source #

sinnum :: Natural -> Covector s a -> Covector s a Source #

sumWith :: Foldable f => (a -> Covector s a) -> f a -> Covector s a Source #

(Monoidal a, Monoidal b, Monoidal c) => Monoidal (a, b, c) Source # 

Methods

zero :: (a, b, c) Source #

sinnum :: Natural -> (a, b, c) -> (a, b, c) Source #

sumWith :: Foldable f => (a -> (a, b, c)) -> f a -> (a, b, c) Source #

Monoidal s => Monoidal (Map s b a) Source # 

Methods

zero :: Map s b a Source #

sinnum :: Natural -> Map s b a -> Map s b a Source #

sumWith :: Foldable f => (a -> Map s b a) -> f a -> Map s b a Source #

(Monoidal a, Monoidal b, Monoidal c, Monoidal d) => Monoidal (a, b, c, d) Source # 

Methods

zero :: (a, b, c, d) Source #

sinnum :: Natural -> (a, b, c, d) -> (a, b, c, d) Source #

sumWith :: Foldable f => (a -> (a, b, c, d)) -> f a -> (a, b, c, d) Source #

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

Methods

zero :: (a, b, c, d, e) Source #

sinnum :: Natural -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

sumWith :: Foldable f => (a -> (a, b, c, d, e)) -> f a -> (a, b, c, d, e) Source #

sum :: (Foldable f, Monoidal m) => f m -> m Source #

sinnumIdempotent :: (Integral n, Idempotent r, Monoidal r) => n -> r -> r Source #

Associative algebras

class Semiring r => Algebra r a where Source #

An associative algebra built with a free module over a semiring

Minimal complete definition

mult

Methods

mult :: (a -> a -> r) -> a -> r Source #

Instances

Algebra () a Source # 

Methods

mult :: (a -> a -> ()) -> a -> () Source #

Semiring r => Algebra r IntSet Source # 

Methods

mult :: (IntSet -> IntSet -> r) -> IntSet -> r Source #

Semiring r => Algebra r () Source # 

Methods

mult :: (() -> () -> r) -> () -> r Source #

Rng k => Algebra k ComplexBasis Source # 

Methods

mult :: (ComplexBasis -> ComplexBasis -> k) -> ComplexBasis -> k Source #

Rng k => Algebra k DualBasis Source # 

Methods

mult :: (DualBasis -> DualBasis -> k) -> DualBasis -> k Source #

(Commutative k, Semiring k) => Algebra k HyperBasis' Source # 

Methods

mult :: (HyperBasis' -> HyperBasis' -> k) -> HyperBasis' -> k Source #

(TriviallyInvolutive r, Rng r) => Algebra r QuaternionBasis Source #

the quaternion algebra

Semiring k => Algebra k DualBasis' Source # 

Methods

mult :: (DualBasis' -> DualBasis' -> k) -> DualBasis' -> k Source #

Semiring k => Algebra k HyperBasis Source #

the trivial diagonal algebra

Methods

mult :: (HyperBasis -> HyperBasis -> k) -> HyperBasis -> k Source #

(TriviallyInvolutive r, Semiring r) => Algebra r QuaternionBasis' Source #

the trivial diagonal algebra

(Commutative k, Rng k) => Algebra k TrigBasis Source # 

Methods

mult :: (TrigBasis -> TrigBasis -> k) -> TrigBasis -> k Source #

(Semiring r, Ord a) => Algebra r (Set a) Source # 

Methods

mult :: (Set a -> Set a -> r) -> Set a -> r Source #

Semiring r => Algebra r (Seq a) Source #

The tensor algebra

Methods

mult :: (Seq a -> Seq a -> r) -> Seq a -> r Source #

Semiring r => Algebra r [a] Source #

The tensor algebra

Methods

mult :: ([a] -> [a] -> r) -> [a] -> r Source #

(Commutative r, Monoidal r, Semiring r, LocallyFiniteOrder a) => Algebra r (Interval a) Source # 

Methods

mult :: (Interval a -> Interval a -> r) -> Interval a -> r Source #

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

Methods

mult :: ((a, b) -> (a, b) -> r) -> (a, b) -> r Source #

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

Methods

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

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

Methods

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

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

Methods

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

Coassociative coalgebras

class Semiring r => Coalgebra r c where Source #

Minimal complete definition

comult

Methods

comult :: (c -> r) -> c -> c -> r Source #

Instances

Semiring r => Coalgebra r IntSet Source #

the free commutative band coalgebra over Int

Methods

comult :: (IntSet -> r) -> IntSet -> IntSet -> r Source #

Semiring r => Coalgebra r () Source # 

Methods

comult :: (() -> r) -> () -> () -> r Source #

Rng k => Coalgebra k ComplexBasis Source # 

Methods

comult :: (ComplexBasis -> k) -> ComplexBasis -> ComplexBasis -> k Source #

Rng k => Coalgebra k DualBasis Source # 

Methods

comult :: (DualBasis -> k) -> DualBasis -> DualBasis -> k Source #

(Commutative k, Monoidal k, Semiring k) => Coalgebra k HyperBasis' Source # 

Methods

comult :: (HyperBasis' -> k) -> HyperBasis' -> HyperBasis' -> k Source #

(TriviallyInvolutive r, Rng r) => Coalgebra r QuaternionBasis Source #

the trivial diagonal coalgebra

Rng k => Coalgebra k DualBasis' Source # 

Methods

comult :: (DualBasis' -> k) -> DualBasis' -> DualBasis' -> k Source #

(Commutative k, Semiring k) => Coalgebra k HyperBasis Source #

the hyperbolic trigonometric coalgebra

Methods

comult :: (HyperBasis -> k) -> HyperBasis -> HyperBasis -> k Source #

(TriviallyInvolutive r, Rng r) => Coalgebra r QuaternionBasis' Source #

dual quaternion comultiplication

(Commutative k, Rng k) => Coalgebra k TrigBasis Source # 

Methods

comult :: (TrigBasis -> k) -> TrigBasis -> TrigBasis -> k Source #

(Semiring r, Additive b) => Coalgebra r (IntMap b) Source #

the free commutative coalgebra over a set and Int

Methods

comult :: (IntMap b -> r) -> IntMap b -> IntMap b -> r Source #

(Semiring r, Ord a) => Coalgebra r (Set a) Source #

the free commutative band coalgebra

Methods

comult :: (Set a -> r) -> Set a -> Set a -> r Source #

Semiring r => Coalgebra r (Seq a) Source #

The tensor Hopf algebra

Methods

comult :: (Seq a -> r) -> Seq a -> Seq a -> r Source #

Semiring r => Coalgebra r [a] Source #

The tensor Hopf algebra

Methods

comult :: ([a] -> r) -> [a] -> [a] -> r Source #

(Commutative r, Monoidal r, Semiring r, PartialSemigroup a) => Coalgebra r (Morphism a) Source # 

Methods

comult :: (Morphism a -> r) -> Morphism a -> Morphism a -> r Source #

(Eq a, Commutative r, Monoidal r, Semiring r) => Coalgebra r (Interval' a) Source # 

Methods

comult :: (Interval' a -> r) -> Interval' a -> Interval' a -> r Source #

Eigenmetric r m => Coalgebra r (BasisCoblade m) Source # 

Methods

comult :: (BasisCoblade m -> r) -> BasisCoblade m -> BasisCoblade m -> r Source #

(Semiring r, Ord a, Additive b) => Coalgebra r (Map a b) Source #

the free commutative coalgebra over a set and a given semigroup

Methods

comult :: (Map a b -> r) -> Map a b -> Map a b -> r Source #

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

Methods

comult :: ((a, b) -> r) -> (a, b) -> (a, b) -> r Source #

Algebra r m => Coalgebra r (m -> r) Source #

Every coalgebra gives rise to an algebra by vector space duality classically. Sadly, it requires vector space duality, which we cannot use constructively. The dual argument only relies in the fact that any constructive coalgebra can only inspect a finite number of coefficients, which we CAN exploit.

Methods

comult :: ((m -> r) -> r) -> (m -> r) -> (m -> r) -> r Source #

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

Methods

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

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

Methods

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

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

Methods

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