algebra-0.5.0: Constructive abstract algebra

Numeric.Algebra

Contents

Synopsis

Additive

additive semigroups

class Additive r whereSource

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

Methods

(+) :: r -> r -> rSource

replicate1p :: Whole n => n -> r -> rSource

replicate1p n r = replicate (1 + n) r

sumWith1 :: Foldable1 f => (a -> r) -> f a -> rSource

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

additive Abelian semigroups

class Additive r => Abelian r Source

an additive abelian semigroup

a + b = b + a

additive idempotent semigroups

class Additive r => Idempotent r Source

An additive semigroup with idempotent addition.

 a + a = a

partitionable additive semigroups

class Additive m => Partitionable m whereSource

Methods

partitionWith :: (m -> m -> r) -> m -> NonEmpty rSource

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

additive monoids

class (LeftModule Natural m, RightModule Natural m) => Monoidal m whereSource

An additive monoid

 zero + a = a = a + zero

Methods

zero :: mSource

replicate :: Whole n => n -> m -> mSource

sumWith :: Foldable f => (a -> m) -> f a -> mSource

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

additive groups

class (LeftModule Integer r, RightModule Integer r, Monoidal r) => Group r whereSource

Methods

(-) :: r -> r -> rSource

negate :: r -> rSource

subtract :: r -> r -> rSource

times :: Integral n => n -> r -> rSource

Instances

Group Int 
Group Int8 
Group Int16 
Group Int32 
Group Int64 
Group Integer 
Group Word 
Group Word8 
Group Word16 
Group Word32 
Group Word64 
Group () 
Group Euclidean 
Division r => Group (Log r) 
Group r => Group (Complex r) 
Group r => Group (Quaternion r) 
Group r => Group (ZeroRng r) 
(Abelian r, Group r) => Group (RngRing r) 
Group r => Group (Opposite r) 
Group r => Group (End r) 
Group r => Group (e -> r) 
(Group a, Group b) => Group (a, b) 
Group s => Group (Covector s a) 
(Group a, Group b, Group c) => Group (a, b, c) 
Group s => Group (Map s b a) 
(Group a, Group b, Group c, Group d) => Group (a, b, c, d) 
(Group a, Group b, Group c, Group d, Group e) => Group (a, b, c, d, e) 

Multiplicative

multiplicative semigroups

commutative multiplicative semigroups

multiplicative monoids

class Multiplicative r => Unital r whereSource

Methods

one :: rSource

pow :: Whole n => r -> n -> rSource

productWith :: Foldable f => (a -> r) -> f a -> rSource

Instances

Unital Bool 
Unital Int 
Unital Int8 
Unital Int16 
Unital Int32 
Unital Int64 
Unital Integer 
Unital Word 
Unital Word8 
Unital Word16 
Unital Word32 
Unital Word64 
Unital () 
Unital Natural 
Unital Euclidean 
Monoidal r => Unital (Exp r) 
(Commutative r, Ring r) => Unital (Complex r) 
(TriviallyInvolutive r, Ring r) => Unital (Quaternion r) 
Rng r => Unital (RngRing r) 
Unital r => Unital (Opposite r) 
Unital (End r) 
Unital (Blade m) 
(Unital r, UnitalAlgebra r a) => Unital (a -> r) 
(Unital a, Unital b) => Unital (a, b) 
CounitalCoalgebra r m => Unital (Covector r m) 
(Unital a, Unital b, Unital c) => Unital (a, b, c) 
CounitalCoalgebra r m => Unital (Map r b m) 
(Unital a, Unital b, Unital c, Unital d) => Unital (a, b, c, d) 
(Unital a, Unital b, Unital c, Unital d, Unital e) => Unital (a, b, c, d, e) 

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

idempotent multiplicative semigroups

class Multiplicative r => Band r Source

An multiplicative semigroup with idempotent multiplication.

 a * a = a

Instances

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

pow1pBand :: Whole n => r -> n -> rSource

powBand :: (Unital r, Whole n) => r -> n -> rSource

multiplicative groups

class Unital r => Division r whereSource

Methods

recip :: r -> rSource

(/) :: r -> r -> rSource

(\\) :: r -> r -> rSource

(^) :: Integral n => r -> n -> rSource

Instances

Division () 
Group r => Division (Exp r) 
(Rng r, Division r) => Division (RngRing r) 
Division r => Division (Opposite r) 
(Unital r, DivisionAlgebra r a) => Division (a -> r) 
(Division a, Division b) => Division (a, b) 
(Division a, Division b, Division c) => Division (a, b, c) 
(Division a, Division b, Division c, Division d) => Division (a, b, c, d) 
(Division a, Division b, Division c, Division d, Division e) => Division (a, b, c, d, e) 

factorable multiplicative semigroups

class Multiplicative m => Factorable m whereSource

`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.

Methods

factorWith :: (m -> m -> r) -> m -> NonEmpty rSource

Instances

involutive multiplicative semigroups

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.

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

Instances

(Semiring r, Idempotent r) => Dioid r 

Rngs

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

A Ring without an identity.

Instances

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

Rigs

class (Semiring r, Unital r, Monoidal r) => Rig r whereSource

A Ring without (n)egation

Methods

fromNatural :: Natural -> rSource

Instances

Rig Bool 
Rig Int 
Rig Int8 
Rig Int16 
Rig Int32 
Rig Int64 
Rig Integer 
Rig Word 
Rig Word8 
Rig Word16 
Rig Word32 
Rig Word64 
Rig () 
Rig Natural 
Rig Euclidean 
(Commutative r, Ring r) => Rig (Complex r) 
(TriviallyInvolutive r, Ring r) => Rig (Quaternion r) 
Rng r => Rig (RngRing r) 
Rig r => Rig (Opposite r) 
(Abelian r, Monoidal r) => Rig (End r) 
Rig (Blade m) 
(Rig a, Rig b) => Rig (a, b) 
(Rig r, CounitalCoalgebra r m) => Rig (Covector r m) 
(Rig a, Rig b, Rig c) => Rig (a, b, c) 
(Rig r, CounitalCoalgebra r m) => Rig (Map r b m) 
(Rig a, Rig b, Rig c, Rig d) => Rig (a, b, c, d) 
(Rig a, Rig b, Rig c, Rig d, Rig e) => Rig (a, b, c, d, e) 

Rings

class (Rig r, Rng r) => Ring r whereSource

Methods

fromInteger :: Integer -> rSource

Instances

Ring Int 
Ring Int8 
Ring Int16 
Ring Int32 
Ring Int64 
Ring Integer 
Ring Word 
Ring Word8 
Ring Word16 
Ring Word32 
Ring Word64 
Ring () 
Ring Euclidean 
(Commutative r, Ring r) => Ring (Complex r) 
(TriviallyInvolutive r, Ring r) => Ring (Quaternion r) 
Rng r => Ring (RngRing r) 
Ring r => Ring (Opposite r) 
(Abelian r, Group r) => Ring (End r) 
(Ring a, Ring b) => Ring (a, b) 
(Ring r, CounitalCoalgebra r m) => Ring (Covector r m) 
(Ring a, Ring b, Ring c) => Ring (a, b, c) 
(Ring r, CounitalCoalgebra r m) => Ring (Map r a m) 
(Ring a, Ring b, Ring c, Ring d) => Ring (a, b, c, d) 
(Ring a, Ring b, Ring c, Ring d, Ring e) => Ring (a, b, c, d, e) 

Modules

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

Methods

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

Instances

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

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

Methods

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

Instances

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

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

Instances

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

Algebras

associative algebras over (non-commutative) semirings

class Semiring r => Algebra r a whereSource

An associative algebra built with a free module over a semiring

Methods

mult :: (a -> a -> r) -> a -> rSource

Instances

Algebra () a 
Semiring r => Algebra r IntSet 
Semiring r => Algebra r () 
Rng k => Algebra k ComplexBasis 
(TriviallyInvolutive r, Rng r) => Algebra r QuaternionBasis 
(Semiring r, Monoidal r, Partitionable a) => Algebra r (IntMap a) 
(Semiring r, Ord a) => Algebra r (Set a) 
Semiring r => Algebra r (Seq a)

The tensor algebra

Semiring r => Algebra r [a]

The tensor algebra

(Algebra r a, Algebra r b) => Algebra r (a, b) 
(Semiring r, Monoidal r, Ord a, Partitionable b) => Algebra r (Map a b) 
(Algebra r a, Algebra r b, Algebra r c) => Algebra r (a, b, c) 
(Algebra r a, Algebra r b, Algebra r c, Algebra r d) => Algebra r (a, b, c, d) 
(Algebra r a, Algebra r b, Algebra r c, Algebra r d, Algebra r e) => Algebra r (a, b, c, d, e) 

class Semiring r => Coalgebra r c whereSource

Methods

comult :: (c -> r) -> c -> c -> rSource

Instances

Semiring r => Coalgebra r IntSet

the free commutative band coalgebra over Int

Semiring r => Coalgebra r () 
Rng k => Coalgebra k ComplexBasis 
(TriviallyInvolutive r, Rng r) => Coalgebra r QuaternionBasis 
(Semiring r, Additive b) => Coalgebra r (IntMap b)

the free commutative coalgebra over a set and Int

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

the free commutative band coalgebra

Semiring r => Coalgebra r (Seq a)

The tensor Hopf algebra

Semiring r => Coalgebra r [a]

The tensor Hopf algebra

Eigenmetric r m => Coalgebra r (Blade m) 
(Semiring r, Ord a, Additive b) => Coalgebra r (Map a b)

the free commutative coalgebra over a set and a given semigroup

(Coalgebra r a, Coalgebra r b) => Coalgebra r (a, b) 
Algebra r m => Coalgebra r (m -> r)

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.

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

unital algebras

class Algebra r a => UnitalAlgebra r a whereSource

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

Methods

unit :: r -> a -> rSource

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.

Instances

Semiring r => Bialgebra r () 
Rng k => Bialgebra k ComplexBasis 
(TriviallyInvolutive r, Rng r) => Bialgebra r QuaternionBasis 
(Monoidal r, Semiring r) => Bialgebra r (Seq a) 
(Monoidal r, Semiring r) => Bialgebra r [a] 
(Bialgebra r a, Bialgebra r b) => Bialgebra r (a, b) 
(Bialgebra r a, Bialgebra r b, Bialgebra r c) => Bialgebra r (a, b, c) 
(Bialgebra r a, Bialgebra r b, Bialgebra r c, Bialgebra r d) => Bialgebra r (a, b, c, d) 
(Bialgebra r a, Bialgebra r b, Bialgebra r c, Bialgebra r d, Bialgebra r e) => Bialgebra r (a, b, c, d, e) 

involutive algebras

idempotent algebras

class (Bialgebra r h, IdempotentAlgebra r h, IdempotentCoalgebra r h) => IdempotentBialgebra r h Source

Instances

(Bialgebra r h, IdempotentAlgebra r h, IdempotentCoalgebra r h) => IdempotentBialgebra r h 

commutative algebras

division algebras

class UnitalAlgebra r a => DivisionAlgebra r a whereSource

Methods

recipriocal :: (a -> r) -> a -> rSource

Hopf alegebras

class Bialgebra r h => HopfAlgebra r h whereSource

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

Methods

antipode :: (h -> r) -> h -> rSource

Instances

Rng k => HopfAlgebra k ComplexBasis 
(TriviallyInvolutive r, Rng r) => HopfAlgebra r QuaternionBasis 
(HopfAlgebra r a, HopfAlgebra r b) => HopfAlgebra r (a, b) 
(HopfAlgebra r a, HopfAlgebra r b, HopfAlgebra r c) => HopfAlgebra r (a, b, c) 
(HopfAlgebra r a, HopfAlgebra r b, HopfAlgebra r c, HopfAlgebra r d) => HopfAlgebra r (a, b, c, d) 
(HopfAlgebra r a, HopfAlgebra r b, HopfAlgebra r c, HopfAlgebra r d, HopfAlgebra r e) => HopfAlgebra r (a, b, c, d, e) 

Ring Properties

Characteristic

charInt :: (Integral s, Bounded s) => proxy s -> NaturalSource

charWord :: (Whole s, Bounded s) => proxy s -> NaturalSource

Order

class Order a whereSource

Methods

(<~) :: a -> a -> BoolSource

(<) :: a -> a -> BoolSource

(>~) :: a -> a -> BoolSource

(>) :: a -> a -> BoolSource

(~~) :: a -> a -> BoolSource

(/~) :: a -> a -> BoolSource

order :: a -> a -> Maybe OrderingSource

comparable :: a -> a -> BoolSource

Instances

Order Bool 
Order Int 
Order Int8 
Order Int16 
Order Int32 
Order Int64 
Order Integer 
Order Word 
Order Word8 
Order Word16 
Order Word32 
Order Word64 
Order () 
Order Natural 
(Order a, Order b) => Order (a, b) 
(Order a, Order b, Order c) => Order (a, b, c) 
(Order a, Order b, Order c, Order d) => Order (a, b, c, d) 
(Order a, Order b, Order c, Order d, Order e) => Order (a, b, c, d, e) 

Natural numbers

data Natural Source

Instances

Enum Natural 
Eq Natural 
Integral Natural 
Num Natural 
Ord Natural 
Read Natural 
Real Natural 
Show Natural 
Whole Natural 
Order Natural 
Abelian Natural 
Partitionable Natural 
Additive Natural 
Monoidal Natural 
Semiring Natural 
Multiplicative Natural 
Unital Natural 
DecidableAssociates Natural 
DecidableUnits Natural 
DecidableZero Natural 
Rig Natural 
Characteristic Natural 
IntegralSemiring Natural 
Commutative Natural 
TriviallyInvolutive Natural 
InvolutiveSemiring Natural 
InvolutiveMultiplication Natural 
AdditiveOrder Natural 
OrderedRig Natural 
RightModule Natural Bool 
RightModule Natural Int 
RightModule Natural Int8 
RightModule Natural Int16 
RightModule Natural Int32 
RightModule Natural Int64 
RightModule Natural Integer 
RightModule Natural Word 
RightModule Natural Word8 
RightModule Natural Word16 
RightModule Natural Word32 
RightModule Natural Word64 
RightModule Natural Natural 
RightModule Natural Euclidean 
LeftModule Natural Bool 
LeftModule Natural Int 
LeftModule Natural Int8 
LeftModule Natural Int16 
LeftModule Natural Int32 
LeftModule Natural Int64 
LeftModule Natural Integer 
LeftModule Natural Word 
LeftModule Natural Word8 
LeftModule Natural Word16 
LeftModule Natural Word32 
LeftModule Natural Word64 
LeftModule Natural Natural 
LeftModule Natural Euclidean 
Rig r => Quadrance r Natural 
Unital r => RightModule Natural (Log r) 
Monoidal r => RightModule Natural (ZeroRng r) 
(Abelian r, Monoidal r) => RightModule Natural (RngRing r) 
RightModule Natural (Blade m) 
Unital r => LeftModule Natural (Log r) 
Monoidal r => LeftModule Natural (ZeroRng r) 
(Abelian r, Monoidal r) => LeftModule Natural (RngRing r) 
LeftModule Natural (Blade m) 

Representable Additive

addRep :: (Zip m, Additive r) => m r -> m r -> m rSource

`Additive.(+)` default definition

replicate1pRep :: (Whole n, Functor m, Additive r) => n -> m r -> m rSource

Additive.replicate1p default definition

Representable Monoidal

zeroRep :: (Applicative m, Monoidal r) => m rSource

Monoidal.zero default definition

replicateRep :: (Whole n, Functor m, Monoidal r) => n -> m r -> m rSource

Monoidal.replicate default definition

Representable Group

negateRep :: (Functor m, Group r) => m r -> m rSource

Group.negate default definition

minusRep :: (Zip m, Group r) => m r -> m r -> m rSource

`Group.(-)` default definition

subtractRep :: (Zip m, Group r) => m r -> m r -> m rSource

Group.subtract default definition

timesRep :: (Integral n, Functor m, Group r) => n -> m r -> m rSource

Group.times default definition

Representable Multiplicative (via Algebra)

mulRep :: (Representable m, Algebra r (Key m)) => m r -> m r -> m rSource

`Multiplicative.(*)` default definition

Representable Unital (via UnitalAlgebra)

oneRep :: (Representable m, Unital r, UnitalAlgebra r (Key m)) => m rSource

Unital.one default definition

Representable Rig (via Algebra)

fromNaturalRep :: (UnitalAlgebra r (Key m), Representable m, Rig r) => Natural -> m rSource

Rig.fromNatural default definition

Representable Ring (via Algebra)

fromIntegerRep :: (UnitalAlgebra r (Key m), Representable m, Ring r) => Integer -> m rSource

Ring.fromInteger default definition

Norm

class Additive r => Quadrance r m whereSource

Methods

quadrance :: m -> rSource

Instances

Quadrance () a 
Rig r => Quadrance r Word64 
Rig r => Quadrance r Word32 
Rig r => Quadrance r Word16 
Rig r => Quadrance r Word8 
Rig r => Quadrance r Int64 
Rig r => Quadrance r Int32 
Rig r => Quadrance r Int16 
Rig r => Quadrance r Int8 
Rig r => Quadrance r Integer 
Rig r => Quadrance r Natural 
Rig r => Quadrance r Word 
Rig r => Quadrance r Int 
Rig r => Quadrance r Bool 
Monoidal r => Quadrance r () 
(Quadrance r a, Quadrance r b) => Quadrance r (a, b) 
(Quadrance r a, Quadrance r b, Quadrance r c) => Quadrance r (a, b, c) 
(Quadrance r a, Quadrance r b, Quadrance r c, Quadrance r d) => Quadrance r (a, b, c, d) 
(Quadrance r a, Quadrance r b, Quadrance r c, Quadrance r d, Quadrance r e) => Quadrance r (a, b, c, d, e) 

Covectors

newtype Covector r a Source

Linear functionals from elements of an (infinite) free module to a scalar

Constructors

Covector ((a -> r) -> r) 

Covectors as linear functionals

comultM :: Algebra r a => a -> Covector r (a, a)Source

multM :: Coalgebra r c => c -> c -> Covector r cSource

antipodeM :: HopfAlgebra r h => h -> Covector r hSource

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 aSource

memoM :: HasTrie a => a -> Covector s aSource