algebra-4.3.1: Constructive abstract algebra

Safe HaskellSafe
LanguageHaskell98

Numeric.Algebra.Involutive

Contents

Synopsis

Involution

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 #

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 # 

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 #

Trivial Involution