algebra-4.3.1: Constructive abstract algebra

Safe HaskellSafe
LanguageHaskell98

Numeric.Algebra.Unital

Contents

Synopsis

Unital Multiplication (Multiplicative monoid)

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 #

Unital Associative Algebra

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 #

Unital Coassociative Coalgebra

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 #

Bialgebra

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.