oalg-base-1.1.4.0: Algebraic structures on oriented entities and limits as a tool kit to solve algebraic problems.
Copyright(c) Erich Gut
LicenseBSD3
Maintainerzerich.gut@gmail.com
Safe HaskellSafe-Inferred
LanguageHaskell2010

OAlg.Structure.Exponential

Description

Multiplicative structures with a power function (^).

Synopsis

Exponential

class (Multiplicative f, Number (Exponent f)) => Exponential f where Source #

Multiplicative structures with a partially defined power function with numbers as exponents.

Properties

  1. For all f and a holds:

    1. If start f == end f or a is an element of [-1,1] then f^a is valid.
    2. If start f /= end f and a is not an element of [-1,1] then f^a is not valid and its evaluation will end up in a NotExponential-exception.
  2. For all f holds: f^1 == f.
  3. For all f holds: f^(-1) == invert f.
  4. For all f and a with start f == end f and a not in [-1,1] holds: start (f^a) == start f and end (f^a) == end f.
  5. For all f, a and b with start f == end f holds: f^(a*b) == (f^a)^ b.
  6. For all f with start f == end f holds: f^0 == one (end f).
  7. For all f, a and b with start f == end f holds: f^(a + b) == f^a * f^b.
  8. For all a and p holds: (one p)^a == one p.
  9. For all f, g and a with start f == end f, start g == end g start f == start g and f * g == g * f holds: (f * g)^a == f^a * g^a.

Note

  1. The phrase ..a is an element of [-1,1].. for the properties of ^ is meant to be: isOne a or isMinusOne a.
  2. If -1 is an instance of Exponent f (see minusOne) then f has to be Cayleyan.

Associated Types

type Exponent f Source #

the exponent.

Methods

(^) :: f -> Exponent f -> f infixl 9 Source #

the power of a factor to an exponent.

Instances

Instances details
Galoisian x => Exponential (GL2 x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Exponent (GL2 x) Source #

Methods

(^) :: GL2 x -> Exponent (GL2 x) -> GL2 x Source #

Oriented x => Exponential (GLT x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.GeneralLinearGroup

Associated Types

type Exponent (GLT x) Source #

Methods

(^) :: GLT x -> Exponent (GLT x) -> GLT x Source #

Oriented x => Exponential (ColTrafo x) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Exponent (ColTrafo x) Source #

Methods

(^) :: ColTrafo x -> Exponent (ColTrafo x) -> ColTrafo x Source #

Oriented a => Exponential (RowTrafo a) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Transformation

Associated Types

type Exponent (RowTrafo a) Source #

Methods

(^) :: RowTrafo a -> Exponent (RowTrafo a) -> RowTrafo a Source #

Entity x => Exponential (ProductSymbol x) Source # 
Instance details

Defined in OAlg.Entity.Product.ProductSymbol

Associated Types

type Exponent (ProductSymbol x) Source #

(Entity i, Ord i) => Exponential (Permutation i) Source # 
Instance details

Defined in OAlg.Entity.Sequence.Permutation

Associated Types

type Exponent (Permutation i) Source #

Multiplicative c => Exponential (Inv c) Source # 
Instance details

Defined in OAlg.Structure.Exponential

Associated Types

type Exponent (Inv c) Source #

Methods

(^) :: Inv c -> Exponent (Inv c) -> Inv c Source #

(Oriented x, Typeable p, p ~ Point x) => Exponential (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Associated Types

type Exponent (Dim x p) Source #

Methods

(^) :: Dim x p -> Exponent (Dim x p) -> Dim x p Source #

(Oriented a, Integral r) => Exponential (Product r a) Source # 
Instance details

Defined in OAlg.Entity.Product.Definition

Associated Types

type Exponent (Product r a) Source #

Methods

(^) :: Product r a -> Exponent (Product r a) -> Product r a Source #

opower :: (Entity p, Number r) => Orientation p -> r -> Orientation p Source #

the power of an orientation by an number.

Note opower fulfill the properties of Exponential for any number structure.

Real

class Multiplicative f => Real f where Source #

reals.

Methods

power :: Number r => f -> r -> f Source #

Instances

Instances details
Entity p => Real (Orientation p) Source # 
Instance details

Defined in OAlg.Structure.Exponential

Methods

power :: Number r => Orientation p -> r -> Orientation p Source #