Copyright | (c) Erich Gut |
---|---|
License | BSD3 |
Maintainer | zerich.gut@gmail.com |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- class (Semiring (Scalar v), Commutative (Scalar v), Additive v) => Vectorial v where
- data Vec k
- class (ForgetfulFbr (s k), ForgetfulAdd (s k), Transformable (s k) (Vec k)) => ForgetfulVec k s
- class Vectorial v => Euclidean v where
Vectorial
class (Semiring (Scalar v), Commutative (Scalar v), Additive v) => Vectorial v where Source #
Additive
structures with a total defined scalar multiplication from the left
by a commutative semi ring. The entities of v
are called vector.
Properties Let v
b a Vectorial
structure, then holds:
- For all
s
in
andScalar
vv
inv
holds:s
is!
vvalid
and
.root
(s!
v)==
root
v - For all
v
inv
holds:0
.!
v==
zero
(root
v) - For all
s
in
andScalar
vr
in
holdsRoot
vs
.!
zero
r==
zero
r - For all
r
,s
in
andScalar
vv
inv
holds:(r
.+
s)!
v==
r!
v+
s!
v - For all
s
in
andScalar
vv
,w
inv
with
holds:root
v==
root
ws
.!
(v+
w)==
s!
v+
s!
w - For all
v
inv
holds:1
.!
v==
v - For all
r
,s
in
andScalar
vv
inv
holds:(r
.*
s)!
v==
r!
(s!
v)
Instances
Vectorial N Source # | |
Vectorial Q Source # | |
Vectorial Z Source # | |
Vectorial Integer Source # | |
Vectorial () Source # | |
Vectorial Int Source # | |
(Vectorial v, FibredOriented v) => Vectorial (Op v) Source # | |
(Vectorial x, FibredOriented x) => Vectorial (Matrix x) Source # | |
(Semiring r, Commutative r) => Vectorial (Vector r) Source # | |
Entity p => Vectorial (Orientation p) Source # | |
Defined in OAlg.Structure.Vectorial.Definition type Scalar (Orientation p) Source # (!) :: Scalar (Orientation p) -> Orientation p -> Orientation p Source # | |
(Fibred a, Ord a, Semiring r, Commutative r) => Vectorial (Sum r a) Source # | |
(Semiring r, Commutative r, Entity a, Ord a) => Vectorial (SumSymbol r a) Source # | |
(Distributive a, Vectorial a, Typeable t, Typeable n, Typeable m) => Vectorial (Transformation t n m a) Source # | |
Defined in OAlg.Entity.Diagram.Transformation type Scalar (Transformation t n m a) Source # (!) :: Scalar (Transformation t n m a) -> Transformation t n m a -> Transformation t n m a Source # |
type representing the class of k-
structures.Vectorial
Instances
ForgetfulVec k Vec Source # | |
Defined in OAlg.Structure.Vectorial.Definition | |
ForgetfulAdd (Vec k) Source # | |
Defined in OAlg.Structure.Vectorial.Definition | |
ForgetfulTyp (Vec k) Source # | |
Defined in OAlg.Structure.Vectorial.Definition | |
ForgetfulFbr (Vec k) Source # | |
Defined in OAlg.Structure.Vectorial.Definition | |
Transformable (Vec k) Ent Source # | |
Transformable (Vec k) Add Source # | |
Transformable (Vec k) Typ Source # | |
Transformable (Vec k) Fbr Source # | |
(Semiring r, Commutative r) => EmbeddableMorphism (HomSymbol r) (Vec r) Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
Transformable (Alg k) (Vec k) Source # | |
type Hom (Vec k) h Source # | |
Defined in OAlg.Hom.Vectorial | |
type Structure (Vec k) x Source # | |
Defined in OAlg.Structure.Vectorial.Definition |
class (ForgetfulFbr (s k), ForgetfulAdd (s k), Transformable (s k) (Vec k)) => ForgetfulVec k s Source #
transformable to k-
structure.Vectorial
Instances
ForgetfulVec k Alg Source # | |
Defined in OAlg.Structure.Algebraic.Definition | |
ForgetfulVec k Vec Source # | |
Defined in OAlg.Structure.Vectorial.Definition |
Euclidean
class Vectorial v => Euclidean v where Source #
Vectorial
structures with a partially defined scalar product.
Properties
- For all
v
,w
holds: if
thenroot
v==
root
wv
is<!>
wvalid
, otherwise aUndefinedScalarproduct
-exception will be thrown. - For all
u
holds:u
.<!>
zero
(root
u)==
rZero
- For all
u
,v
andw
with
androot
u==
root
w
holds:root
w==
root
vu
.<!>
(v+
w)==
u<!>
v+
u<!>
w - For all
w
holds:
.zero
(root
w)<!>
w==
rZero
- For all
u
,v
andw
with
androot
w==
root
u
holds:root
u==
root
v(u
.+
v)<!>
w==
u<!>
w+
v' !' w
Instances
Euclidean N Source # | |
Euclidean Q Source # | |
Euclidean Z Source # | |
(Semiring r, Commutative r) => Euclidean (Vector r) Source # | |
Entity p => Euclidean (Orientation p) Source # | |
Defined in OAlg.Structure.Vectorial.Definition (<!>) :: Orientation p -> Orientation p -> Scalar (Orientation p) Source # | |
(Semiring r, Commutative r, Entity a, Ord a) => Euclidean (SumSymbol r a) Source # | |