algebra-4.3.1: Constructive abstract algebra

Safe HaskellNone
LanguageHaskell98

Numeric.Algebra

Contents

Synopsis

Additive

additive semigroups

class Additive r where Source #

(a + b) + c = a + (b + c)
sinnum 1 a = a
sinnum (2 * n) a = sinnum n a + sinnum n a
sinnum (2 * n + 1) a = sinnum n a + sinnum n a + a

Minimal complete definition

(+)

Methods

(+) :: r -> r -> r infixl 6 Source #

sinnum1p :: Natural -> r -> r Source #

sinnum1p n r = sinnum (1 + n) r

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

Instances

Additive Bool Source # 

Methods

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

sinnum1p :: Natural -> Bool -> Bool Source #

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

Additive Int Source # 

Methods

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

sinnum1p :: Natural -> Int -> Int Source #

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

Additive Int8 Source # 

Methods

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

sinnum1p :: Natural -> Int8 -> Int8 Source #

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

Additive Int16 Source # 

Methods

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

sinnum1p :: Natural -> Int16 -> Int16 Source #

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

Additive Int32 Source # 

Methods

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

sinnum1p :: Natural -> Int32 -> Int32 Source #

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

Additive Int64 Source # 

Methods

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

sinnum1p :: Natural -> Int64 -> Int64 Source #

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

Additive Integer Source # 
Additive Natural Source # 
Additive Word Source # 

Methods

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

sinnum1p :: Natural -> Word -> Word Source #

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

Additive Word8 Source # 

Methods

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

sinnum1p :: Natural -> Word8 -> Word8 Source #

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

Additive Word16 Source # 
Additive Word32 Source # 
Additive Word64 Source # 
Additive () Source # 

Methods

(+) :: () -> () -> () Source #

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

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

Additive Euclidean Source # 
Additive r => Additive (ZeroRng r) Source # 

Methods

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

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

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

Abelian r => Additive (RngRing r) Source # 

Methods

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

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

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

Additive r => Additive (Opposite r) Source # 

Methods

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

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

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

Additive r => Additive (End r) Source # 

Methods

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

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

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

Multiplicative r => Additive (Log r) Source # 

Methods

(+) :: Log r -> Log r -> Log r Source #

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

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

Additive r => Additive (Trig r) Source # 

Methods

(+) :: Trig r -> Trig r -> Trig r Source #

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

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

Additive r => Additive (Quaternion' r) Source # 
Additive r => Additive (Hyper r) Source # 

Methods

(+) :: Hyper r -> Hyper r -> Hyper r Source #

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

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

Additive (BasisCoblade m) Source # 
Additive r => Additive (Dual' r) Source # 

Methods

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

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

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

Additive r => Additive (Quaternion r) Source # 
Additive r => Additive (Hyper' r) Source # 

Methods

(+) :: Hyper' r -> Hyper' r -> Hyper' r Source #

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

sumWith1 :: Foldable1 f => (a -> Hyper' r) -> f a -> Hyper' r Source #

Additive r => Additive (Dual r) Source # 

Methods

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

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

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

Additive r => Additive (Complex r) Source # 

Methods

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

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

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

GCDDomain d => Additive (Fraction d) Source # 

Methods

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

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

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

Additive r => Additive (b -> r) Source # 

Methods

(+) :: (b -> r) -> (b -> r) -> b -> r Source #

sinnum1p :: Natural -> (b -> r) -> b -> r Source #

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

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

Methods

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

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

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

Additive r => Additive (Covector r a) Source # 

Methods

(+) :: Covector r a -> Covector r a -> Covector r a Source #

sinnum1p :: Natural -> Covector r a -> Covector r a Source #

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

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

Methods

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

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

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

Additive r => Additive (Map r b a) Source # 

Methods

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

sinnum1p :: Natural -> Map r b a -> Map r b a Source #

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

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

Methods

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

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

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

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

Methods

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

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

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

sum1 :: (Foldable1 f, Additive r) => f r -> r Source #

additive Abelian semigroups

class Additive r => Abelian r Source #

an additive abelian semigroup

a + b = b + a

additive idempotent semigroups

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

partitionable additive semigroups

class Additive m => Partitionable m where Source #

Minimal complete definition

partitionWith

Methods

partitionWith :: (m -> m -> r) -> m -> NonEmpty r Source #

partitionWith f c returns a list containing f a b for each a b such that a + b = c,

Instances

Partitionable Bool Source # 

Methods

partitionWith :: (Bool -> Bool -> r) -> Bool -> NonEmpty r Source #

Partitionable Natural Source # 

Methods

partitionWith :: (Natural -> Natural -> r) -> Natural -> NonEmpty r Source #

Partitionable () Source # 

Methods

partitionWith :: (() -> () -> r) -> () -> NonEmpty r Source #

Factorable r => Partitionable (Log r) Source # 

Methods

partitionWith :: (Log r -> Log r -> r) -> Log r -> NonEmpty r Source #

Partitionable r => Partitionable (Trig r) Source # 

Methods

partitionWith :: (Trig r -> Trig r -> r) -> Trig r -> NonEmpty r Source #

Partitionable r => Partitionable (Quaternion' r) Source # 
Partitionable r => Partitionable (Hyper r) Source # 

Methods

partitionWith :: (Hyper r -> Hyper r -> r) -> Hyper r -> NonEmpty r Source #

Partitionable r => Partitionable (Dual' r) Source # 

Methods

partitionWith :: (Dual' r -> Dual' r -> r) -> Dual' r -> NonEmpty r Source #

Partitionable r => Partitionable (Quaternion r) Source # 

Methods

partitionWith :: (Quaternion r -> Quaternion r -> r) -> Quaternion r -> NonEmpty r Source #

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

Methods

partitionWith :: (Hyper' r -> Hyper' r -> r) -> Hyper' r -> NonEmpty r Source #

Partitionable r => Partitionable (Dual r) Source # 

Methods

partitionWith :: (Dual r -> Dual r -> r) -> Dual r -> NonEmpty r Source #

Partitionable r => Partitionable (Complex r) Source # 

Methods

partitionWith :: (Complex r -> Complex r -> r) -> Complex r -> NonEmpty r Source #

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

Methods

partitionWith :: ((a, b) -> (a, b) -> r) -> (a, b) -> NonEmpty r Source #

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

Methods

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

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

Methods

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

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

Methods

partitionWith :: ((a, b, c, d, e) -> (a, b, c, d, e) -> r) -> (a, b, c, d, e) -> NonEmpty r 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 Natural 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 Euclidean 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 #

(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 (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 #

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 #

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 (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 #

Monoidal r => Monoidal (Quaternion' 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 (BasisCoblade m) 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 (Quaternion 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 (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 (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 #

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 (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 #

additive groups

class (LeftModule Integer r, RightModule Integer r, Monoidal r) => Group r where Source #

Methods

(-) :: r -> r -> r infixl 6 Source #

negate :: r -> r Source #

subtract :: r -> r -> r Source #

times :: Integral n => n -> r -> r infixl 7 Source #

Instances

Group Int Source # 

Methods

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

negate :: Int -> Int Source #

subtract :: Int -> Int -> Int Source #

times :: Integral n => n -> Int -> Int Source #

Group Int8 Source # 

Methods

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

negate :: Int8 -> Int8 Source #

subtract :: Int8 -> Int8 -> Int8 Source #

times :: Integral n => n -> Int8 -> Int8 Source #

Group Int16 Source # 
Group Int32 Source # 
Group Int64 Source # 
Group Integer Source # 
Group Word Source # 

Methods

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

negate :: Word -> Word Source #

subtract :: Word -> Word -> Word Source #

times :: Integral n => n -> Word -> Word Source #

Group Word8 Source # 
Group Word16 Source # 
Group Word32 Source # 
Group Word64 Source # 
Group () Source # 

Methods

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

negate :: () -> () Source #

subtract :: () -> () -> () Source #

times :: Integral n => n -> () -> () Source #

Group Euclidean Source # 
Group r => Group (ZeroRng r) Source # 

Methods

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

negate :: ZeroRng r -> ZeroRng r Source #

subtract :: ZeroRng r -> ZeroRng r -> ZeroRng r Source #

times :: Integral n => n -> ZeroRng r -> ZeroRng r Source #

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

Methods

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

negate :: RngRing r -> RngRing r Source #

subtract :: RngRing r -> RngRing r -> RngRing r Source #

times :: Integral n => n -> RngRing r -> RngRing r Source #

Group r => Group (Opposite r) Source # 
Group r => Group (End r) Source # 

Methods

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

negate :: End r -> End r Source #

subtract :: End r -> End r -> End r Source #

times :: Integral n => n -> End r -> End r Source #

Division r => Group (Log r) Source # 

Methods

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

negate :: Log r -> Log r Source #

subtract :: Log r -> Log r -> Log r Source #

times :: Integral n => n -> Log r -> Log r Source #

Group r => Group (Trig r) Source # 

Methods

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

negate :: Trig r -> Trig r Source #

subtract :: Trig r -> Trig r -> Trig r Source #

times :: Integral n => n -> Trig r -> Trig r Source #

Group r => Group (Quaternion' r) Source # 
Group r => Group (Hyper r) Source # 

Methods

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

negate :: Hyper r -> Hyper r Source #

subtract :: Hyper r -> Hyper r -> Hyper r Source #

times :: Integral n => n -> Hyper r -> Hyper r Source #

Group r => Group (Dual' r) Source # 

Methods

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

negate :: Dual' r -> Dual' r Source #

subtract :: Dual' r -> Dual' r -> Dual' r Source #

times :: Integral n => n -> Dual' r -> Dual' r Source #

Group r => Group (Quaternion r) Source # 
Group r => Group (Hyper' r) Source # 

Methods

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

negate :: Hyper' r -> Hyper' r Source #

subtract :: Hyper' r -> Hyper' r -> Hyper' r Source #

times :: Integral n => n -> Hyper' r -> Hyper' r Source #

Group r => Group (Dual r) Source # 

Methods

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

negate :: Dual r -> Dual r Source #

subtract :: Dual r -> Dual r -> Dual r Source #

times :: Integral n => n -> Dual r -> Dual r Source #

Group r => Group (Complex r) Source # 

Methods

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

negate :: Complex r -> Complex r Source #

subtract :: Complex r -> Complex r -> Complex r Source #

times :: Integral n => n -> Complex r -> Complex r Source #

GCDDomain d => Group (Fraction d) Source # 
Group r => Group (e -> r) Source # 

Methods

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

negate :: (e -> r) -> e -> r Source #

subtract :: (e -> r) -> (e -> r) -> e -> r Source #

times :: Integral n => n -> (e -> r) -> e -> r Source #

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

Methods

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

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

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

times :: Integral n => n -> (a, b) -> (a, b) Source #

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

Methods

(-) :: Covector s a -> Covector s a -> Covector s a Source #

negate :: Covector s a -> Covector s a Source #

subtract :: Covector s a -> Covector s a -> Covector s a Source #

times :: Integral n => n -> Covector s a -> Covector s a Source #

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

Methods

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

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

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

times :: Integral n => n -> (a, b, c) -> (a, b, c) Source #

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

Methods

(-) :: Map s b a -> Map s b a -> Map s b a Source #

negate :: Map s b a -> Map s b a Source #

subtract :: Map s b a -> Map s b a -> Map s b a Source #

times :: Integral n => n -> Map s b a -> Map s b a Source #

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

Methods

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

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

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

times :: Integral n => n -> (a, b, c, d) -> (a, b, c, d) Source #

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

Methods

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

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

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

times :: Integral n => n -> (a, b, c, d, e) -> (a, b, c, d, e) Source #

Multiplicative

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 Natural 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 Euclidean 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 #

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 #

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 #

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 #

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 #

(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 #

(TriviallyInvolutive r, Semiring r) => Multiplicative (Quaternion' 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 #

Multiplicative (BasisCoblade m) 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 #

(TriviallyInvolutive r, Rng r) => Multiplicative (Quaternion 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 #

(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 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 #

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 #

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 #

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

commutative multiplicative semigroups

class Multiplicative r => Commutative r Source #

A commutative multiplicative semigroup

Instances

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

multiplicative monoids

class Multiplicative r => Unital r where Source #

Minimal complete definition

one

Methods

one :: r Source #

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

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

Instances

Unital Bool Source # 

Methods

one :: Bool Source #

pow :: Bool -> Natural -> Bool Source #

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

Unital Int Source # 

Methods

one :: Int Source #

pow :: Int -> Natural -> Int Source #

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

Unital Int8 Source # 

Methods

one :: Int8 Source #

pow :: Int8 -> Natural -> Int8 Source #

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

Unital Int16 Source # 

Methods

one :: Int16 Source #

pow :: Int16 -> Natural -> Int16 Source #

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

Unital Int32 Source # 

Methods

one :: Int32 Source #

pow :: Int32 -> Natural -> Int32 Source #

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

Unital Int64 Source # 

Methods

one :: Int64 Source #

pow :: Int64 -> Natural -> Int64 Source #

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

Unital Integer Source # 
Unital Natural Source # 
Unital Word Source # 

Methods

one :: Word Source #

pow :: Word -> Natural -> Word Source #

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

Unital Word8 Source # 

Methods

one :: Word8 Source #

pow :: Word8 -> Natural -> Word8 Source #

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

Unital Word16 Source # 

Methods

one :: Word16 Source #

pow :: Word16 -> Natural -> Word16 Source #

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

Unital Word32 Source # 

Methods

one :: Word32 Source #

pow :: Word32 -> Natural -> Word32 Source #

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

Unital Word64 Source # 

Methods

one :: Word64 Source #

pow :: Word64 -> Natural -> Word64 Source #

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

Unital () Source # 

Methods

one :: () Source #

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

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

Unital Euclidean Source # 
Rng r => Unital (RngRing r) Source # 

Methods

one :: RngRing r Source #

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

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

Unital r => Unital (Opposite r) Source # 

Methods

one :: Opposite r Source #

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

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

Unital (End r) Source # 

Methods

one :: End r Source #

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

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

Monoidal r => Unital (Exp r) Source # 

Methods

one :: Exp r Source #

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

productWith :: Foldable f => (a -> Exp r) -> f a -> Exp r Source #

(Commutative k, Ring k) => Unital (Trig k) Source # 

Methods

one :: Trig k Source #

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

productWith :: Foldable f => (a -> Trig k) -> f a -> Trig k Source #

(TriviallyInvolutive r, Ring r) => Unital (Quaternion' r) Source # 
(Commutative k, Rig k) => Unital (Hyper k) Source # 

Methods

one :: Hyper k Source #

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

productWith :: Foldable f => (a -> Hyper k) -> f a -> Hyper k Source #

Unital (BasisCoblade m) Source # 
(Commutative r, Ring r) => Unital (Dual' r) Source # 

Methods

one :: Dual' r Source #

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

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

(TriviallyInvolutive r, Ring r) => Unital (Quaternion r) Source # 
(Commutative k, Rig k) => Unital (Hyper' k) Source # 

Methods

one :: Hyper' k Source #

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

productWith :: Foldable f => (a -> Hyper' k) -> f a -> Hyper' k Source #

(Commutative r, Ring r) => Unital (Dual r) Source # 

Methods

one :: Dual r Source #

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

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

(Commutative r, Ring r) => Unital (Complex r) Source # 

Methods

one :: Complex r Source #

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

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

GCDDomain d => Unital (Fraction d) Source # 

Methods

one :: Fraction d Source #

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

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

(Unital r, UnitalAlgebra r a) => Unital (a -> r) Source # 

Methods

one :: a -> r Source #

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

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

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

Methods

one :: (a, b) Source #

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

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

CounitalCoalgebra r m => Unital (Covector r m) Source # 

Methods

one :: Covector r m Source #

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

productWith :: Foldable f => (a -> Covector r m) -> f a -> Covector r m Source #

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

Methods

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

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

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

CounitalCoalgebra r m => Unital (Map r b m) Source # 

Methods

one :: Map r b m Source #

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

productWith :: Foldable f => (a -> Map r b m) -> f a -> Map r b m Source #

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

Methods

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

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

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

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

Methods

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

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

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

product :: (Foldable f, Unital r) => f r -> r Source #

idempotent multiplicative semigroups

class Multiplicative r => Band r Source #

An multiplicative semigroup with idempotent multiplication.

a * a = a

Instances

Band Bool Source # 
Band () Source # 
Band r => Band (Opposite r) Source # 
Idempotent r => Band (Exp r) Source # 
(Band a, Band b) => Band (a, b) Source # 
Band (Rect i j) Source # 
(Idempotent r, IdempotentCoalgebra r a) => Band (Covector r a) Source # 
(Band a, Band b, Band c) => Band (a, b, c) Source # 
(Band a, Band b, Band c, Band d) => Band (a, b, c, d) Source # 
(Band a, Band b, Band c, Band d, Band e) => Band (a, b, c, d, e) Source # 

pow1pBand :: r -> Natural -> r Source #

powBand :: Unital r => r -> Natural -> r Source #

multiplicative groups

class Unital r => Division r where Source #

Methods

recip :: r -> r Source #

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

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

(^) :: Integral n => r -> n -> r infixr 8 Source #

Instances

Division () Source # 

Methods

recip :: () -> () Source #

(/) :: () -> () -> () Source #

(\\) :: () -> () -> () Source #

(^) :: Integral n => () -> n -> () Source #

(Rng r, Division r) => Division (RngRing r) Source # 

Methods

recip :: RngRing r -> RngRing r Source #

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

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

(^) :: Integral n => RngRing r -> n -> RngRing r Source #

Division r => Division (Opposite r) Source # 
Group r => Division (Exp r) Source # 

Methods

recip :: Exp r -> Exp r Source #

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

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

(^) :: Integral n => Exp r -> n -> Exp r Source #

(TriviallyInvolutive r, Ring r, Division r) => Division (Quaternion' r) Source # 
(Commutative r, InvolutiveSemiring r, DivisionRing r) => Division (Dual' r) Source # 

Methods

recip :: Dual' r -> Dual' r Source #

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

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

(^) :: Integral n => Dual' r -> n -> Dual' r Source #

(TriviallyInvolutive r, Ring r, Division r) => Division (Quaternion r) Source # 
(Commutative r, InvolutiveSemiring r, DivisionRing r) => Division (Hyper' r) Source # 

Methods

recip :: Hyper' r -> Hyper' r Source #

(/) :: Hyper' r -> Hyper' r -> Hyper' r Source #

(\\) :: Hyper' r -> Hyper' r -> Hyper' r Source #

(^) :: Integral n => Hyper' r -> n -> Hyper' r Source #

(Commutative r, InvolutiveSemiring r, DivisionRing r) => Division (Dual r) Source # 

Methods

recip :: Dual r -> Dual r Source #

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

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

(^) :: Integral n => Dual r -> n -> Dual r Source #

(Commutative r, InvolutiveSemiring r, DivisionRing r) => Division (Complex r) Source # 

Methods

recip :: Complex r -> Complex r Source #

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

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

(^) :: Integral n => Complex r -> n -> Complex r Source #

GCDDomain d => Division (Fraction d) Source # 
(Unital r, DivisionAlgebra r a) => Division (a -> r) Source # 

Methods

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

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

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

(^) :: Integral n => (a -> r) -> n -> a -> r Source #

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

Methods

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

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

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

(^) :: Integral n => (a, b) -> n -> (a, b) Source #

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

Methods

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

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

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

(^) :: Integral n => (a, b, c) -> n -> (a, b, c) Source #

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

Methods

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

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

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

(^) :: Integral n => (a, b, c, d) -> n -> (a, b, c, d) Source #

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

Methods

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

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

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

(^) :: Integral n => (a, b, c, d, e) -> n -> (a, b, c, d, e) Source #

factorable multiplicative semigroups

class Multiplicative m => Factorable m where Source #

`factorWith f c` returns a non-empty list containing `f a b` for all `a, b` such that `a * b = c`.

Results of factorWith f 0 are undefined and may result in either an error or an infinite list.

Minimal complete definition

factorWith

Methods

factorWith :: (m -> m -> r) -> m -> NonEmpty r Source #

Instances

Factorable Bool Source # 

Methods

factorWith :: (Bool -> Bool -> r) -> Bool -> NonEmpty r Source #

Factorable () Source # 

Methods

factorWith :: (() -> () -> r) -> () -> NonEmpty r Source #

Partitionable r => Factorable (Exp r) Source # 

Methods

factorWith :: (Exp r -> Exp r -> r) -> Exp r -> NonEmpty r Source #

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

Methods

factorWith :: ((a, b) -> (a, b) -> r) -> (a, b) -> NonEmpty r Source #

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

Methods

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

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

Methods

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

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

Methods

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

involutive multiplicative semigroups

class Multiplicative r => InvolutiveMultiplication r where Source #

An semigroup with involution

adjoint a * adjoint b = adjoint (b * a)

Minimal complete definition

adjoint

Methods

adjoint :: r -> r Source #

Instances

InvolutiveMultiplication Bool Source # 

Methods

adjoint :: Bool -> Bool Source #

InvolutiveMultiplication Int Source # 

Methods

adjoint :: Int -> Int Source #

InvolutiveMultiplication Int8 Source # 

Methods

adjoint :: Int8 -> Int8 Source #

InvolutiveMultiplication Int16 Source # 

Methods

adjoint :: Int16 -> Int16 Source #

InvolutiveMultiplication Int32 Source # 

Methods

adjoint :: Int32 -> Int32 Source #

InvolutiveMultiplication Int64 Source # 

Methods

adjoint :: Int64 -> Int64 Source #

InvolutiveMultiplication Integer Source # 
InvolutiveMultiplication Natural Source # 
InvolutiveMultiplication Word Source # 

Methods

adjoint :: Word -> Word Source #

InvolutiveMultiplication Word8 Source # 

Methods

adjoint :: Word8 -> Word8 Source #

InvolutiveMultiplication Word16 Source # 
InvolutiveMultiplication Word32 Source # 
InvolutiveMultiplication Word64 Source # 
InvolutiveMultiplication () Source # 

Methods

adjoint :: () -> () Source #

InvolutiveMultiplication Euclidean Source # 
(Commutative r, Rng r, InvolutiveMultiplication r) => InvolutiveMultiplication (Trig r) Source # 

Methods

adjoint :: Trig r -> Trig r Source #

(TriviallyInvolutive r, Rng r) => InvolutiveMultiplication (Quaternion' r) Source # 
(Commutative r, Group r, InvolutiveSemiring r) => InvolutiveMultiplication (Hyper r) Source # 

Methods

adjoint :: Hyper r -> Hyper r Source #

(Commutative r, Rng r, InvolutiveSemiring r) => InvolutiveMultiplication (Dual' r) Source # 

Methods

adjoint :: Dual' r -> Dual' r Source #

(TriviallyInvolutive r, Rng r) => InvolutiveMultiplication (Quaternion r) Source # 
(Commutative r, InvolutiveSemiring r, Rng r) => InvolutiveMultiplication (Hyper' r) Source # 

Methods

adjoint :: Hyper' r -> Hyper' r Source #

(Commutative r, Rng r, InvolutiveSemiring r) => InvolutiveMultiplication (Dual r) Source # 

Methods

adjoint :: Dual r -> Dual r Source #

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

Methods

adjoint :: Complex r -> Complex r Source #

InvolutiveAlgebra r h => InvolutiveMultiplication (h -> r) Source # 

Methods

adjoint :: (h -> r) -> h -> r Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

Ring-Structures

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 Natural Source # 
Semiring Word Source # 
Semiring Word8 Source # 
Semiring Word16 Source # 
Semiring Word32 Source # 
Semiring Word64 Source # 
Semiring () Source # 
Semiring Euclidean Source # 
(Monoidal r, Abelian r) => Semiring (ZeroRng r) Source # 
Rng r => Semiring (RngRing r) Source # 
Semiring r => Semiring (Opposite r) Source # 
(Abelian r, Monoidal r) => Semiring (End r) Source # 
(Commutative k, Rng k) => Semiring (Trig k) Source # 
(TriviallyInvolutive r, Semiring r) => Semiring (Quaternion' r) Source # 
(Commutative k, Semiring k) => Semiring (Hyper k) Source # 
Semiring (BasisCoblade m) Source # 
(Commutative r, Rng r) => Semiring (Dual' r) Source # 
(TriviallyInvolutive r, Rng r) => Semiring (Quaternion r) Source # 
(Commutative k, Semiring k) => Semiring (Hyper' k) Source # 
(Commutative r, Rng r) => Semiring (Dual r) Source # 
(Commutative r, Rng r) => Semiring (Complex r) Source # 
GCDDomain d => Semiring (Fraction d) 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 # 

class (Semiring r, InvolutiveMultiplication r) => InvolutiveSemiring r Source #

adjoint (x + y) = adjoint x + adjoint y

Instances

InvolutiveSemiring Bool Source # 
InvolutiveSemiring Int Source # 
InvolutiveSemiring Int8 Source # 
InvolutiveSemiring Int16 Source # 
InvolutiveSemiring Int32 Source # 
InvolutiveSemiring Int64 Source # 
InvolutiveSemiring Integer Source # 
InvolutiveSemiring Natural Source # 
InvolutiveSemiring Word Source # 
InvolutiveSemiring Word8 Source # 
InvolutiveSemiring Word16 Source # 
InvolutiveSemiring Word32 Source # 
InvolutiveSemiring Word64 Source # 
InvolutiveSemiring () Source # 
InvolutiveSemiring Euclidean Source # 
(Commutative r, Rng r, InvolutiveSemiring r) => InvolutiveSemiring (Trig r) Source # 
(Commutative r, Group r, InvolutiveSemiring r) => InvolutiveSemiring (Hyper r) Source # 
(Commutative r, Rng r, InvolutiveSemiring r) => InvolutiveSemiring (Dual' r) Source # 
(Commutative r, InvolutiveSemiring r, Rng r) => InvolutiveSemiring (Hyper' r) Source # 
(Commutative r, Rng r, InvolutiveSemiring r) => InvolutiveSemiring (Dual r) Source # 
(Commutative r, Rng r, InvolutiveSemiring r) => InvolutiveSemiring (Complex r) Source # 
(InvolutiveSemiring a, InvolutiveSemiring b) => InvolutiveSemiring (a, b) Source # 
(InvolutiveSemiring a, InvolutiveSemiring b, InvolutiveSemiring c) => InvolutiveSemiring (a, b, c) Source # 
(InvolutiveSemiring a, InvolutiveSemiring b, InvolutiveSemiring c, InvolutiveSemiring d) => InvolutiveSemiring (a, b, c, d) Source # 
(InvolutiveSemiring a, InvolutiveSemiring b, InvolutiveSemiring c, InvolutiveSemiring d, InvolutiveSemiring e) => InvolutiveSemiring (a, b, c, d, e) Source # 

class (Semiring r, Idempotent r) => Dioid r Source #

Instances

Rngs

class (Group r, Semiring r) => Rng r Source #

A Ring without an identity.

Instances

(Group r, Semiring r) => Rng r Source # 
(Group r, Abelian r) => Rng (ZeroRng r) Source # 

Rigs

class (Semiring r, Unital r, Monoidal r) => Rig r where Source #

A Ring without (n)egation

Methods

fromNatural :: Natural -> r Source #

Instances

Rig Bool Source # 
Rig Int Source # 
Rig Int8 Source # 
Rig Int16 Source # 
Rig Int32 Source # 
Rig Int64 Source # 
Rig Integer Source # 
Rig Natural Source # 
Rig Word Source # 
Rig Word8 Source # 
Rig Word16 Source # 
Rig Word32 Source # 
Rig Word64 Source # 
Rig () Source # 

Methods

fromNatural :: Natural -> () Source #

Rig Euclidean Source # 
Rng r => Rig (RngRing r) Source # 
Rig r => Rig (Opposite r) Source # 
(Abelian r, Monoidal r) => Rig (End r) Source # 

Methods

fromNatural :: Natural -> End r Source #

(Commutative r, Ring r) => Rig (Trig r) Source # 
(TriviallyInvolutive r, Ring r) => Rig (Quaternion' r) Source # 
(Commutative r, Rig r) => Rig (Hyper r) Source # 
Rig (BasisCoblade m) Source # 
(Commutative r, Ring r) => Rig (Dual' r) Source # 
(TriviallyInvolutive r, Ring r) => Rig (Quaternion r) Source # 
(Commutative r, Rig r) => Rig (Hyper' r) Source # 
(Commutative r, Ring r) => Rig (Dual r) Source # 
(Commutative r, Ring r) => Rig (Complex r) Source # 
GCDDomain d => Rig (Fraction d) Source # 
(Rig a, Rig b) => Rig (a, b) Source # 

Methods

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

(Rig r, CounitalCoalgebra r m) => Rig (Covector r m) Source # 
(Rig a, Rig b, Rig c) => Rig (a, b, c) Source # 

Methods

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

(Rig r, CounitalCoalgebra r m) => Rig (Map r b m) Source # 

Methods

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

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

Methods

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

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

Methods

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

Rings

class (Rig r, Rng r) => Ring r where Source #

Methods

fromInteger :: Integer -> r Source #

Instances

Ring Int Source # 
Ring Int8 Source # 
Ring Int16 Source # 
Ring Int32 Source # 
Ring Int64 Source # 
Ring Integer Source # 
Ring Word Source # 
Ring Word8 Source # 
Ring Word16 Source # 
Ring Word32 Source # 
Ring Word64 Source # 
Ring () Source # 

Methods

fromInteger :: Integer -> () Source #

Ring Euclidean Source # 
Rng r => Ring (RngRing r) Source # 
Ring r => Ring (Opposite r) Source # 
(Abelian r, Group r) => Ring (End r) Source # 

Methods

fromInteger :: Integer -> End r Source #

(Commutative r, Ring r) => Ring (Trig r) Source # 
(TriviallyInvolutive r, Ring r) => Ring (Quaternion' r) Source # 
(Commutative r, Ring r) => Ring (Hyper r) Source # 
(Commutative r, Ring r) => Ring (Dual' r) Source # 
(TriviallyInvolutive r, Ring r) => Ring (Quaternion r) Source # 
(Commutative r, Ring r) => Ring (Hyper' r) Source # 
(Commutative r, Ring r) => Ring (Dual r) Source # 
(Commutative r, Ring r) => Ring (Complex r) Source # 
GCDDomain d => Ring (Fraction d) Source # 
(Ring a, Ring b) => Ring (a, b) Source # 

Methods

fromInteger :: Integer -> (a, b) Source #

(Ring r, CounitalCoalgebra r m) => Ring (Covector r m) Source # 
(Ring a, Ring b, Ring c) => Ring (a, b, c) Source # 

Methods

fromInteger :: Integer -> (a, b, c) Source #

(Ring r, CounitalCoalgebra r m) => Ring (Map r a m) Source # 

Methods

fromInteger :: Integer -> Map r a m Source #

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

Methods

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

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

Methods

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

Division Rings

class Ring r => LocalRing r Source #

class (Division r, Ring r) => DivisionRing r Source #

Instances

class (Euclidean d, Division d) => Field d Source #

Instances

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 # 
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 Natural 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 Euclidean Source # 
Additive m => LeftModule () m Source # 

Methods

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

Semiring r => LeftModule r () Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

(.*) :: r -> Complex s -> Complex s 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 #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

(.*) :: Complex r -> Complex r -> Complex r 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 # 
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 Natural 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 Euclidean Source # 
Additive m => RightModule () m Source # 

Methods

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

Semiring r => RightModule r () Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

(*.) :: Complex s -> r -> Complex s 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 #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

(*.) :: Complex r -> Complex r -> Complex r 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 # 

Algebras

associative algebras over (non-commutative) semirings

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 #

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

Methods

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

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

the trivial diagonal algebra

Semiring k => Algebra k HyperBasis Source #

the trivial diagonal algebra

Methods

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

Semiring k => Algebra k DualBasis' Source # 

Methods

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

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

the quaternion algebra

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

Methods

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

Rng k => Algebra k DualBasis Source # 

Methods

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

Rng k => Algebra k ComplexBasis Source # 

Methods

mult :: (ComplexBasis -> ComplexBasis -> k) -> ComplexBasis -> 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 #

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 #

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

Methods

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

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

dual quaternion comultiplication

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

the hyperbolic trigonometric coalgebra

Methods

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

Rng k => Coalgebra k DualBasis' Source # 

Methods

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

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

the trivial diagonal coalgebra

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

Methods

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

Rng k => Coalgebra k DualBasis Source # 

Methods

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

Rng k => Coalgebra k ComplexBasis Source # 

Methods

comult :: (ComplexBasis -> k) -> ComplexBasis -> ComplexBasis -> 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 #

unital algebras

class Algebra r a => UnitalAlgebra r a where Source #

An associative unital algebra over a semiring, built using a free module

Minimal complete definition

unit

Methods

unit :: r -> a -> r Source #

Instances

Semiring r => UnitalAlgebra r () Source # 

Methods

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

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

Methods

unit :: k -> TrigBasis -> k Source #

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

Methods

unit :: r -> QuaternionBasis' -> r Source #

Semiring k => UnitalAlgebra k HyperBasis Source # 

Methods

unit :: k -> HyperBasis -> k Source #

Semiring k => UnitalAlgebra k DualBasis' Source # 

Methods

unit :: k -> DualBasis' -> k Source #

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

Methods

unit :: r -> QuaternionBasis -> r Source #

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

Methods

unit :: k -> HyperBasis' -> k Source #

Rng k => UnitalAlgebra k DualBasis Source # 

Methods

unit :: k -> DualBasis -> k Source #

Rng k => UnitalAlgebra k ComplexBasis Source # 

Methods

unit :: k -> ComplexBasis -> k Source #

(Monoidal r, Semiring r) => UnitalAlgebra r (Seq a) Source # 

Methods

unit :: r -> Seq a -> r Source #

(Monoidal r, Semiring r) => UnitalAlgebra r [a] Source # 

Methods

unit :: r -> [a] -> r Source #

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

Methods

unit :: r -> Interval a -> r Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class Coalgebra r c => CounitalCoalgebra r c where Source #

Minimal complete definition

counit

Methods

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

Instances

Semiring r => CounitalCoalgebra r () Source # 

Methods

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

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

Methods

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

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

Methods

counit :: (QuaternionBasis' -> r) -> r Source #

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

Methods

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

Rng k => CounitalCoalgebra k DualBasis' Source # 

Methods

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

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

Methods

counit :: (QuaternionBasis -> r) -> r Source #

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

Methods

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

Rng k => CounitalCoalgebra k DualBasis Source # 

Methods

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

Rng k => CounitalCoalgebra k ComplexBasis Source # 

Methods

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

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

Methods

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

Semiring r => CounitalCoalgebra r [a] Source # 

Methods

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

(Commutative r, Monoidal r, Semiring r, PartialMonoid a) => CounitalCoalgebra r (Morphism a) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

(Unital r, UnitalAlgebra r m) => CounitalCoalgebra r (m -> r) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class (UnitalAlgebra r a, CounitalCoalgebra r a) => Bialgebra r a Source #

A bialgebra is both a unital algebra and counital coalgebra where the mult and unit are compatible in some sense with the comult and counit. That is to say that mult and unit are a coalgebra homomorphisms or (equivalently) that comult and counit are an algebra homomorphisms.

involutive algebras

class (InvolutiveSemiring r, Algebra r a) => InvolutiveAlgebra r a where Source #

Minimal complete definition

inv

Methods

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

Instances

InvolutiveSemiring r => InvolutiveAlgebra r () Source # 

Methods

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

(Commutative k, Group k, InvolutiveSemiring k) => InvolutiveAlgebra k TrigBasis Source # 

Methods

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

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

Methods

inv :: (QuaternionBasis' -> r) -> QuaternionBasis' -> r Source #

(Commutative k, Group k, InvolutiveSemiring k) => InvolutiveAlgebra k HyperBasis Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => InvolutiveAlgebra k DualBasis' Source # 

Methods

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

(TriviallyInvolutive r, InvolutiveSemiring r, Rng r) => InvolutiveAlgebra r QuaternionBasis Source # 

Methods

inv :: (QuaternionBasis -> r) -> QuaternionBasis -> r Source #

(Commutative k, Group k, InvolutiveSemiring k) => InvolutiveAlgebra k HyperBasis' Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => InvolutiveAlgebra k DualBasis Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => InvolutiveAlgebra k ComplexBasis Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

class (InvolutiveSemiring r, Coalgebra r c) => InvolutiveCoalgebra r c where Source #

Minimal complete definition

coinv

Methods

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

Instances

InvolutiveSemiring r => InvolutiveCoalgebra r () Source # 

Methods

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

(Commutative k, Group k, InvolutiveSemiring k) => InvolutiveCoalgebra k TrigBasis Source # 

Methods

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

(TriviallyInvolutive r, InvolutiveSemiring r, Rng r) => InvolutiveCoalgebra r QuaternionBasis' Source # 
(Commutative k, Group k, InvolutiveSemiring k) => InvolutiveCoalgebra k HyperBasis Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => InvolutiveCoalgebra k DualBasis' Source # 

Methods

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

(TriviallyInvolutive r, InvolutiveSemiring r, Rng r) => InvolutiveCoalgebra r QuaternionBasis Source # 

Methods

coinv :: (QuaternionBasis -> r) -> QuaternionBasis -> r Source #

(Commutative k, Group k, InvolutiveSemiring k) => InvolutiveCoalgebra k HyperBasis' Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => InvolutiveCoalgebra k DualBasis Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => InvolutiveCoalgebra k ComplexBasis Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

idempotent algebras

commutative algebras

division algebras

class UnitalAlgebra r a => DivisionAlgebra r a where Source #

Minimal complete definition

recipriocal

Methods

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

Hopf alegebras

class Bialgebra r h => HopfAlgebra r h where Source #

A HopfAlgebra algebra on a semiring, where the module is free.

When antipode . antipode = id and antipode is an antihomomorphism then we are an InvolutiveBialgebra with inv = antipode as well

Minimal complete definition

antipode

Methods

antipode :: (h -> r) -> h -> r Source #

Instances

(Commutative k, Group k, InvolutiveSemiring k) => HopfAlgebra k TrigBasis Source # 

Methods

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

(TriviallyInvolutive r, InvolutiveSemiring r, Rng r) => HopfAlgebra r QuaternionBasis' Source # 
(Commutative k, Group k, InvolutiveSemiring k) => HopfAlgebra k HyperBasis Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => HopfAlgebra k DualBasis' Source # 

Methods

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

(TriviallyInvolutive r, InvolutiveSemiring r, Rng r) => HopfAlgebra r QuaternionBasis Source # 
(Commutative k, Group k, InvolutiveSemiring k) => HopfAlgebra k HyperBasis' Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => HopfAlgebra k DualBasis Source # 

Methods

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

(InvolutiveSemiring k, Rng k) => HopfAlgebra k ComplexBasis Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

Ring Properties

Characteristic

class Rig r => Characteristic r where Source #

Minimal complete definition

char

Methods

char :: proxy r -> Natural Source #

Instances

Characteristic Bool Source #

NB: we're using the boolean semiring, not the boolean ring

Methods

char :: proxy Bool -> Natural Source #

Characteristic Int Source # 

Methods

char :: proxy Int -> Natural Source #

Characteristic Int8 Source # 

Methods

char :: proxy Int8 -> Natural Source #

Characteristic Int16 Source # 

Methods

char :: proxy Int16 -> Natural Source #

Characteristic Int32 Source # 

Methods

char :: proxy Int32 -> Natural Source #

Characteristic Int64 Source # 

Methods

char :: proxy Int64 -> Natural Source #

Characteristic Integer Source # 

Methods

char :: proxy Integer -> Natural Source #

Characteristic Natural Source # 

Methods

char :: proxy Natural -> Natural Source #

Characteristic Word Source # 

Methods

char :: proxy Word -> Natural Source #

Characteristic Word8 Source # 

Methods

char :: proxy Word8 -> Natural Source #

Characteristic Word16 Source # 

Methods

char :: proxy Word16 -> Natural Source #

Characteristic Word32 Source # 

Methods

char :: proxy Word32 -> Natural Source #

Characteristic Word64 Source # 

Methods

char :: proxy Word64 -> Natural Source #

Characteristic () Source # 

Methods

char :: proxy () -> Natural Source #

(Characteristic d, GCDDomain d) => Characteristic (Fraction d) Source # 

Methods

char :: proxy (Fraction d) -> Natural Source #

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

Methods

char :: proxy (a, b) -> Natural Source #

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

Methods

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

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

Methods

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

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

Methods

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

charInt :: (Integral s, Bounded s) => proxy s -> Natural Source #

charWord :: (Integral s, Bounded s) => proxy s -> Natural Source #

Order

class Order a where Source #

Methods

(<~) :: a -> a -> Bool Source #

(<) :: a -> a -> Bool Source #

(>~) :: a -> a -> Bool Source #

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

(~~) :: a -> a -> Bool Source #

(/~) :: a -> a -> Bool Source #

order :: a -> a -> Maybe Ordering Source #

comparable :: a -> a -> Bool Source #

Instances

Order Bool Source # 
Order Int Source # 
Order Int8 Source # 
Order Int16 Source # 
Order Int32 Source # 
Order Int64 Source # 
Order Integer Source # 
Order Natural Source # 
Order Word Source # 
Order Word8 Source # 
Order Word16 Source # 
Order Word32 Source # 
Order Word64 Source # 
Order () Source # 

Methods

(<~) :: () -> () -> Bool Source #

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

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

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

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

(/~) :: () -> () -> Bool Source #

order :: () -> () -> Maybe Ordering Source #

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

Ord a => Order (Set a) Source # 

Methods

(<~) :: Set a -> Set a -> Bool Source #

(<) :: Set a -> Set a -> Bool Source #

(>~) :: Set a -> Set a -> Bool Source #

(>) :: Set a -> Set a -> Bool Source #

(~~) :: Set a -> Set a -> Bool Source #

(/~) :: Set a -> Set a -> Bool Source #

order :: Set a -> Set a -> Maybe Ordering Source #

comparable :: Set a -> Set a -> Bool Source #

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

Methods

(<~) :: (a, b) -> (a, b) -> Bool Source #

(<) :: (a, b) -> (a, b) -> Bool Source #

(>~) :: (a, b) -> (a, b) -> Bool Source #

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

(~~) :: (a, b) -> (a, b) -> Bool Source #

(/~) :: (a, b) -> (a, b) -> Bool Source #

order :: (a, b) -> (a, b) -> Maybe Ordering Source #

comparable :: (a, b) -> (a, b) -> Bool Source #

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

Methods

(<~) :: (a, b, c) -> (a, b, c) -> Bool Source #

(<) :: (a, b, c) -> (a, b, c) -> Bool Source #

(>~) :: (a, b, c) -> (a, b, c) -> Bool Source #

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

(~~) :: (a, b, c) -> (a, b, c) -> Bool Source #

(/~) :: (a, b, c) -> (a, b, c) -> Bool Source #

order :: (a, b, c) -> (a, b, c) -> Maybe Ordering Source #

comparable :: (a, b, c) -> (a, b, c) -> Bool Source #

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

Methods

(<~) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

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

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

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

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

(/~) :: (a, b, c, d) -> (a, b, c, d) -> Bool Source #

order :: (a, b, c, d) -> (a, b, c, d) -> Maybe Ordering Source #

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

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

Methods

(<~) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

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

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

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

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

(/~) :: (a, b, c, d, e) -> (a, b, c, d, e) -> Bool Source #

order :: (a, b, c, d, e) -> (a, b, c, d, e) -> Maybe Ordering Source #

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

class Order a => LocallyFiniteOrder a Source #

Minimal complete definition

range, rangeSize

Instances

LocallyFiniteOrder Bool Source # 
LocallyFiniteOrder Int Source # 

Methods

range :: Int -> Int -> [Int] Source #

rangeSize :: Int -> Int -> Natural Source #

moebiusInversion :: Ring r => Int -> Int -> r Source #

LocallyFiniteOrder Int8 Source # 
LocallyFiniteOrder Int16 Source # 
LocallyFiniteOrder Int32 Source # 
LocallyFiniteOrder Int64 Source # 
LocallyFiniteOrder Integer Source # 
LocallyFiniteOrder Natural Source # 
LocallyFiniteOrder Word Source # 
LocallyFiniteOrder Word8 Source # 
LocallyFiniteOrder Word16 Source # 
LocallyFiniteOrder Word32 Source # 
LocallyFiniteOrder Word64 Source # 
LocallyFiniteOrder () Source # 

Methods

range :: () -> () -> [()] Source #

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

moebiusInversion :: Ring r => () -> () -> r Source #

Ord a => LocallyFiniteOrder (Set a) Source # 

Methods

range :: Set a -> Set a -> [Set a] Source #

rangeSize :: Set a -> Set a -> Natural Source #

moebiusInversion :: Ring r => Set a -> Set a -> r Source #

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

Methods

range :: (a, b) -> (a, b) -> [(a, b)] Source #

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

moebiusInversion :: Ring r => (a, b) -> (a, b) -> r Source #

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

Methods

range :: (a, b, c) -> (a, b, c) -> [(a, b, c)] Source #

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

moebiusInversion :: Ring r => (a, b, c) -> (a, b, c) -> r Source #

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

Methods

range :: (a, b, c, d) -> (a, b, c, d) -> [(a, b, c, d)] Source #

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

moebiusInversion :: Ring r => (a, b, c, d) -> (a, b, c, d) -> r Source #

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

Methods

range :: (a, b, c, d, e) -> (a, b, c, d, e) -> [(a, b, c, d, e)] Source #

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

moebiusInversion :: Ring r => (a, b, c, d, e) -> (a, b, c, d, e) -> r Source #

class Monoidal r => DecidableZero r Source #

Minimal complete definition

isZero

Instances

DecidableZero Bool Source # 

Methods

isZero :: Bool -> Bool Source #

DecidableZero Int Source # 

Methods

isZero :: Int -> Bool Source #

DecidableZero Int8 Source # 

Methods

isZero :: Int8 -> Bool Source #

DecidableZero Int16 Source # 

Methods

isZero :: Int16 -> Bool Source #

DecidableZero Int32 Source # 

Methods

isZero :: Int32 -> Bool Source #

DecidableZero Int64 Source # 

Methods

isZero :: Int64 -> Bool Source #

DecidableZero Integer Source # 

Methods

isZero :: Integer -> Bool Source #

DecidableZero Natural Source # 

Methods

isZero :: Natural -> Bool Source #

DecidableZero Word Source # 

Methods

isZero :: Word -> Bool Source #

DecidableZero Word8 Source # 

Methods

isZero :: Word8 -> Bool Source #

DecidableZero Word16 Source # 

Methods

isZero :: Word16 -> Bool Source #

DecidableZero Word32 Source # 

Methods

isZero :: Word32 -> Bool Source #

DecidableZero Word64 Source # 

Methods

isZero :: Word64 -> Bool Source #

DecidableZero () Source # 

Methods

isZero :: () -> Bool Source #

DecidableZero r => DecidableZero (Opposite r) Source # 

Methods

isZero :: Opposite r -> Bool Source #

DecidableZero (BasisCoblade m) Source # 
GCDDomain d => DecidableZero (Fraction d) Source # 

Methods

isZero :: Fraction d -> Bool Source #

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

Methods

isZero :: (a, b) -> Bool Source #

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

Methods

isZero :: (a, b, c) -> Bool Source #

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

Methods

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

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

Methods

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

class Unital r => DecidableUnits r Source #

Minimal complete definition

recipUnit

Instances

DecidableUnits Bool Source # 
DecidableUnits Int Source # 
DecidableUnits Int8 Source # 
DecidableUnits Int16 Source # 
DecidableUnits Int32 Source # 
DecidableUnits Int64 Source # 
DecidableUnits Integer Source # 
DecidableUnits Natural Source # 
DecidableUnits Word Source # 
DecidableUnits Word8 Source # 
DecidableUnits Word16 Source # 
DecidableUnits Word32 Source # 
DecidableUnits Word64 Source # 
DecidableUnits () Source # 

Methods

recipUnit :: () -> Maybe () Source #

isUnit :: () -> Bool Source #

(^?) :: Integral n => () -> n -> Maybe () Source #

DecidableUnits r => DecidableUnits (Opposite r) Source # 
DecidableUnits (BasisCoblade m) Source # 
GCDDomain d => DecidableUnits (Fraction d) Source # 
(DecidableUnits a, DecidableUnits b) => DecidableUnits (a, b) Source # 

Methods

recipUnit :: (a, b) -> Maybe (a, b) Source #

isUnit :: (a, b) -> Bool Source #

(^?) :: Integral n => (a, b) -> n -> Maybe (a, b) Source #

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

Methods

recipUnit :: (a, b, c) -> Maybe (a, b, c) Source #

isUnit :: (a, b, c) -> Bool Source #

(^?) :: Integral n => (a, b, c) -> n -> Maybe (a, b, c) Source #

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

Methods

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

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

(^?) :: Integral n => (a, b, c, d) -> n -> Maybe (a, b, c, d) Source #

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

Methods

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

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

(^?) :: Integral n => (a, b, c, d, e) -> n -> Maybe (a, b, c, d, e) Source #

class Unital r => DecidableAssociates r Source #

Minimal complete definition

isAssociate

Instances

DecidableAssociates Bool Source # 

Methods

isAssociate :: Bool -> Bool -> Bool Source #

DecidableAssociates Int Source # 

Methods

isAssociate :: Int -> Int -> Bool Source #

DecidableAssociates Int8 Source # 

Methods

isAssociate :: Int8 -> Int8 -> Bool Source #

DecidableAssociates Int16 Source # 
DecidableAssociates Int32 Source # 
DecidableAssociates Int64 Source # 
DecidableAssociates Integer Source # 
DecidableAssociates Natural Source # 
DecidableAssociates Word Source # 

Methods

isAssociate :: Word -> Word -> Bool Source #

DecidableAssociates Word8 Source # 
DecidableAssociates Word16 Source # 
DecidableAssociates Word32 Source # 
DecidableAssociates Word64 Source # 
DecidableAssociates () Source # 

Methods

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

DecidableAssociates r => DecidableAssociates (Opposite r) Source # 
DecidableAssociates (BasisCoblade m) Source # 
GCDDomain d => DecidableAssociates (Fraction d) Source # 
(DecidableAssociates a, DecidableAssociates b) => DecidableAssociates (a, b) Source # 

Methods

isAssociate :: (a, b) -> (a, b) -> Bool Source #

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

Methods

isAssociate :: (a, b, c) -> (a, b, c) -> Bool Source #

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

Methods

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

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

Methods

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

Natural numbers

data Natural :: * #

Type representing arbitrary-precision non-negative integers.

Operations whose result would be negative throw (Underflow :: ArithException).

Since: 4.8.0.0

Instances

Enum Natural

Since: 4.8.0.0

Eq Natural 

Methods

(==) :: Natural -> Natural -> Bool #

(/=) :: Natural -> Natural -> Bool #

Integral Natural

Since: 4.8.0.0

Data Natural

Since: 4.8.0.0

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Natural -> c Natural #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Natural #

toConstr :: Natural -> Constr #

dataTypeOf :: Natural -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Natural) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Natural) #

gmapT :: (forall b. Data b => b -> b) -> Natural -> Natural #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Natural -> r #

gmapQ :: (forall d. Data d => d -> u) -> Natural -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Natural -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Natural -> m Natural #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Natural -> m Natural #

Num Natural

Since: 4.8.0.0

Ord Natural 
Read Natural

Since: 4.8.0.0

Real Natural

Since: 4.8.0.0

Show Natural

Since: 4.8.0.0

Ix Natural

Since: 4.8.0.0

Bits Natural

Since: 4.8.0.0

Hashable Natural 

Methods

hashWithSalt :: Int -> Natural -> Int #

hash :: Natural -> Int #

Abelian Natural Source # 
Partitionable Natural Source # 

Methods

partitionWith :: (Natural -> Natural -> r) -> Natural -> NonEmpty r Source #

Additive Natural Source # 
Monoidal Natural Source # 
Semiring Natural Source # 
Multiplicative Natural Source # 
Unital Natural Source # 
Commutative Natural Source # 
TriviallyInvolutive Natural Source # 
InvolutiveSemiring Natural Source # 
InvolutiveMultiplication Natural Source # 
DecidableAssociates Natural Source # 
DecidableUnits Natural Source # 
DecidableZero Natural Source # 

Methods

isZero :: Natural -> Bool Source #

Order Natural Source # 
AdditiveOrder Natural Source # 
PartialSemigroup Natural Source # 
PartialMonoid Natural Source # 

Methods

pzero :: Natural Source #

PartialGroup Natural Source # 
Rig Natural Source # 
Characteristic Natural Source # 

Methods

char :: proxy Natural -> Natural Source #

OrderedRig Natural Source # 
LocallyFiniteOrder Natural Source # 
ZeroProductSemiring Natural Source # 
DecidableNilpotent Natural 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 Natural 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 Euclidean 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 Natural 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 Euclidean Source # 
Rig r => Quadrance r Natural Source # 

Methods

quadrance :: Natural -> r Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

Representable Additive

addRep :: (Applicative m, Additive r) => m r -> m r -> m r Source #

`Additive.(+)` default definition

sinnum1pRep :: (Functor m, Additive r) => Natural -> m r -> m r Source #

sinnum1p default definition

Representable Monoidal

zeroRep :: (Applicative m, Monoidal r) => m r Source #

zero default definition

sinnumRep :: (Functor m, Monoidal r) => Natural -> m r -> m r Source #

sinnum default definition

Representable Group

negateRep :: (Functor m, Group r) => m r -> m r Source #

negate default definition

minusRep :: (Applicative m, Group r) => m r -> m r -> m r Source #

`Group.(-)` default definition

subtractRep :: (Applicative m, Group r) => m r -> m r -> m r Source #

subtract default definition

timesRep :: (Integral n, Functor m, Group r) => n -> m r -> m r Source #

times default definition

Representable Multiplicative (via Algebra)

mulRep :: (Representable m, Algebra r (Rep m)) => m r -> m r -> m r Source #

`Multiplicative.(*)` default definition

Representable Unital (via UnitalAlgebra)

oneRep :: (Representable m, Unital r, UnitalAlgebra r (Rep m)) => m r Source #

one default definition

Representable Rig (via Algebra)

fromNaturalRep :: (UnitalAlgebra r (Rep m), Representable m, Rig r) => Natural -> m r Source #

fromNatural default definition

Representable Ring (via Algebra)

fromIntegerRep :: (UnitalAlgebra r (Rep m), Representable m, Ring r) => Integer -> m r Source #

fromInteger default definition

Norm

class Additive r => Quadrance r m where Source #

Minimal complete definition

quadrance

Methods

quadrance :: m -> r Source #

Instances

Quadrance () a Source # 

Methods

quadrance :: a -> () Source #

Rig r => Quadrance r Word64 Source # 

Methods

quadrance :: Word64 -> r Source #

Rig r => Quadrance r Word32 Source # 

Methods

quadrance :: Word32 -> r Source #

Rig r => Quadrance r Word16 Source # 

Methods

quadrance :: Word16 -> r Source #

Rig r => Quadrance r Word8 Source # 

Methods

quadrance :: Word8 -> r Source #

Rig r => Quadrance r Int64 Source # 

Methods

quadrance :: Int64 -> r Source #

Rig r => Quadrance r Int32 Source # 

Methods

quadrance :: Int32 -> r Source #

Rig r => Quadrance r Int16 Source # 

Methods

quadrance :: Int16 -> r Source #

Rig r => Quadrance r Int8 Source # 

Methods

quadrance :: Int8 -> r Source #

Rig r => Quadrance r Integer Source # 

Methods

quadrance :: Integer -> r Source #

Rig r => Quadrance r Natural Source # 

Methods

quadrance :: Natural -> r Source #

Rig r => Quadrance r Word Source # 

Methods

quadrance :: Word -> r Source #

Rig r => Quadrance r Int Source # 

Methods

quadrance :: Int -> r Source #

Rig r => Quadrance r Bool Source # 

Methods

quadrance :: Bool -> r Source #

(Additive r, Monoidal r) => Quadrance r () Source # 

Methods

quadrance :: () -> r Source #

(TriviallyInvolutive r, Rng r) => Quadrance r (Quaternion' r) Source # 

Methods

quadrance :: Quaternion' r -> r Source #

(Commutative r, Rng r, InvolutiveSemiring r) => Quadrance r (Dual' r) Source # 

Methods

quadrance :: Dual' r -> r Source #

(TriviallyInvolutive r, Rng r) => Quadrance r (Quaternion r) Source # 

Methods

quadrance :: Quaternion r -> r Source #

(Commutative r, InvolutiveSemiring r, Rng r) => Quadrance r (Hyper' r) Source # 

Methods

quadrance :: Hyper' r -> r Source #

(Commutative r, Rng r, InvolutiveSemiring r) => Quadrance r (Dual r) Source # 

Methods

quadrance :: Dual r -> r Source #

(Commutative r, Rng r, InvolutiveSemiring r) => Quadrance r (Complex r) Source # 

Methods

quadrance :: Complex r -> r Source #

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

Covectors

newtype Covector r a Source #

Linear functionals from elements of an (infinite) free module to a scalar

Constructors

Covector 

Fields

  • ($*) :: (a -> r) -> r
     

Instances

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

Methods

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

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

Methods

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

Monad (Covector r) Source # 

Methods

(>>=) :: Covector r a -> (a -> Covector r b) -> Covector r b #

(>>) :: Covector r a -> Covector r b -> Covector r b #

return :: a -> Covector r a #

fail :: String -> Covector r a #

Functor (Covector r) Source # 

Methods

fmap :: (a -> b) -> Covector r a -> Covector r b #

(<$) :: a -> Covector r b -> Covector r a #

Applicative (Covector r) Source # 

Methods

pure :: a -> Covector r a #

(<*>) :: Covector r (a -> b) -> Covector r a -> Covector r b #

liftA2 :: (a -> b -> c) -> Covector r a -> Covector r b -> Covector r c #

(*>) :: Covector r a -> Covector r b -> Covector r b #

(<*) :: Covector r a -> Covector r b -> Covector r a #

Monoidal r => Alternative (Covector r) Source # 

Methods

empty :: Covector r a #

(<|>) :: Covector r a -> Covector r a -> Covector r a #

some :: Covector r a -> Covector r [a] #

many :: Covector r a -> Covector r [a] #

Monoidal r => MonadPlus (Covector r) Source # 

Methods

mzero :: Covector r a #

mplus :: Covector r a -> Covector r a -> Covector r a #

Monoidal r => Plus (Covector r) Source # 

Methods

zero :: Covector r a #

Additive r => Alt (Covector r) Source # 

Methods

(<!>) :: Covector r a -> Covector r a -> Covector r a #

some :: Applicative (Covector r) => Covector r a -> Covector r [a] #

many :: Applicative (Covector r) => Covector r a -> Covector r [a] #

Apply (Covector r) Source # 

Methods

(<.>) :: Covector r (a -> b) -> Covector r a -> Covector r b #

(.>) :: Covector r a -> Covector r b -> Covector r b #

(<.) :: Covector r a -> Covector r b -> Covector r a #

Bind (Covector r) Source # 

Methods

(>>-) :: Covector r a -> (a -> Covector r b) -> Covector r b #

join :: Covector r (Covector r a) -> Covector r a #

Idempotent r => Idempotent (Covector r a) Source # 
Abelian s => Abelian (Covector s a) Source # 
Additive r => Additive (Covector r a) Source # 

Methods

(+) :: Covector r a -> Covector r a -> Covector r a Source #

sinnum1p :: Natural -> Covector r a -> Covector r a Source #

sumWith1 :: Foldable1 f => (a -> Covector r a) -> f a -> Covector r a 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 #

Coalgebra r m => Semiring (Covector r m) 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 #

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

Methods

(-) :: Covector s a -> Covector s a -> Covector s a Source #

negate :: Covector s a -> Covector s a Source #

subtract :: Covector s a -> Covector s a -> Covector s a Source #

times :: Integral n => n -> Covector s a -> Covector s a Source #

CounitalCoalgebra r m => Unital (Covector r m) Source # 

Methods

one :: Covector r m Source #

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

productWith :: Foldable f => (a -> Covector r m) -> f a -> Covector r m Source #

(Idempotent r, IdempotentCoalgebra r a) => Band (Covector r a) Source # 
(Commutative m, Coalgebra r m) => Commutative (Covector r m) Source # 
(Rig r, CounitalCoalgebra r m) => Rig (Covector r m) Source # 
(Ring r, CounitalCoalgebra r m) => Ring (Covector r m) Source # 
Trigonometric a => Trigonometric (Covector r a) Source # 

Methods

cos :: Covector r a Source #

sin :: Covector r a Source #

Hyperbolic a => Hyperbolic (Covector r a) Source # 

Methods

cosh :: Covector r a Source #

sinh :: Covector r a Source #

Distinguished a => Distinguished (Covector r a) Source # 

Methods

e :: Covector r a Source #

Infinitesimal a => Infinitesimal (Covector r a) Source # 

Methods

d :: Covector r a Source #

Complicated a => Complicated (Covector r a) Source # 

Methods

i :: Covector r a Source #

Hamiltonian a => Hamiltonian (Covector r a) Source # 

Methods

j :: Covector r a Source #

k :: Covector r a 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 => LeftModule (Covector r m) (Covector r m) Source # 

Methods

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

Covectors as linear functionals

counitM :: UnitalAlgebra r a => a -> Covector r () Source #

comultM :: Algebra r a => a -> Covector r (a, a) Source #

multM :: Coalgebra r c => c -> c -> Covector r c Source #

antipodeM :: HopfAlgebra r h => h -> Covector r h Source #

convolveM antipodeM return = convolveM return antipodeM = comultM >=> uncurry joinM

convolveM :: (Algebra r c, Coalgebra r a) => (c -> Covector r a) -> (c -> Covector r a) -> c -> Covector r a Source #