| Copyright | (c) Erich Gut |
|---|---|
| License | BSD3 |
| Maintainer | zerich.gut@gmail.com |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
OAlg.Entity.Matrix.Vector
Synopsis
- newtype Vector r = Vector (PSequence N r)
- vecpsq :: Vector r -> PSequence N r
- cf :: Semiring r => Vector r -> N -> r
- cfsssy :: (Semiring r, Commutative r, Entity a, Ord a) => Set a -> Vector r -> SumSymbol r a
- ssycfs :: (Semiring r, Ord a) => Set a -> SumSymbol r a -> Vector r
- vecrc :: Vector r -> Row N (Col N r)
- vecAppl :: Semiring r => Matrix r -> Vector r -> Vector r
- data HomSymbol r x y where
- HomSymbol :: (Entity x, Ord x, Entity y, Ord y) => PSequence x (LinearCombination r y) -> HomSymbol r (SumSymbol r x) (SumSymbol r y)
- Cfs :: (Entity x, Ord x) => Set x -> HomSymbol r (SumSymbol r x) (Vector r)
- Ssy :: (Entity x, Ord x) => Set x -> HomSymbol r (Vector r) (SumSymbol r x)
- HomMatrix :: Matrix r -> HomSymbol r (Vector r) (Vector r)
- mtxHomSymbol :: Matrix r -> HomSymbol r (SumSymbol r N) (SumSymbol r N)
- repMatrix :: Representable r h x y -> Matrix r
- data Representable r h x y where
- mtxRepresentable :: (Semiring r, Commutative r) => Matrix r -> Representable r (HomSymbol r) (SumSymbol r N) (SumSymbol r N)
- prpRepMatrix :: (Semiring r, Commutative r) => Representable r h x y -> Vector r -> Statement
- prpRepMatrixZ :: N -> N -> Statement
- xVecN :: Semiring r => N -> X r -> X (Vector r)
Vector
vector with coefficients lying in a Semiring, indexd by N.
Definition Let v = be in Vector ris with Vector rr be a Semiring,
then v is valid iff
Instances
| Show r => Show (Vector r) Source # | |
| Eq r => Eq (Vector r) Source # | |
| Ord r => Ord (Vector r) Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
| Semiring r => Validable (Vector r) Source # | |
| Semiring r => Entity (Vector r) Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
| Ring r => Abelian (Vector r) Source # | |
| Semiring r => Additive (Vector r) Source # | |
| Semiring r => Fibred (Vector r) Source # | |
| (Semiring r, Commutative r) => Euclidean (Vector r) Source # | |
| (Semiring r, Commutative r) => Vectorial (Vector r) Source # | |
| type Root (Vector r) Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
| type Scalar (Vector r) Source # | |
Defined in OAlg.Entity.Matrix.Vector | |
cfsssy :: (Semiring r, Commutative r, Entity a, Ord a) => Set a -> Vector r -> SumSymbol r a Source #
Hom
data HomSymbol r x y where Source #
Constructors
| HomSymbol :: (Entity x, Ord x, Entity y, Ord y) => PSequence x (LinearCombination r y) -> HomSymbol r (SumSymbol r x) (SumSymbol r y) | |
| Cfs :: (Entity x, Ord x) => Set x -> HomSymbol r (SumSymbol r x) (Vector r) | |
| Ssy :: (Entity x, Ord x) => Set x -> HomSymbol r (Vector r) (SumSymbol r x) | |
| HomMatrix :: Matrix r -> HomSymbol r (Vector r) (Vector r) |
Instances
mtxHomSymbol :: Matrix r -> HomSymbol r (SumSymbol r N) (SumSymbol r N) Source #
the associated r-linear homomorphism.
Representation
repMatrix :: Representable r h x y -> Matrix r Source #
the associated representation matrix of the given r-homomorphism and the two symbol set.
Property Let p = be in Representable h xs ys
for a Representable r h x yCommutative Semiring r, then holds:
For all v in holds: Let Vector rh' = inHomMatrix (repMatrix p)
data Representable r h x y where Source #
Predicate for a r-linear homomorphisms between the free sums
and SumSymbol r x being representable for the given symbol sets.SumSymbol r y
Definition Let l be in and LinearCombination r xxs be a Set of symbols of
x, then l is called representable in xs iff all symbols of are elements
of lcs lxs.
Property Let h be a r-linear homomorphism between the free sums
and SumSymbol r x, SumSymbol r yxs a Set of symbols in x and
ys a Set of symbols in y, then holds: If for each symbol x in xs the associated
LinearCombination of h is representable in $ xys, then is
Representable h xs ysvalid.
Constructors
| Representable :: (Hom (Vec r) h, Entity x, Ord x, Entity y, Ord y) => h (SumSymbol r x) (SumSymbol r y) -> Set x -> Set y -> Representable r h (SumSymbol r x) (SumSymbol r y) |
Instances
| Show (Representable r h x y) Source # | |
Defined in OAlg.Entity.Matrix.Vector Methods showsPrec :: Int -> Representable r h x y -> ShowS # show :: Representable r h x y -> String # showList :: [Representable r h x y] -> ShowS # | |
| Validable (Representable r h x y) Source # | |
Defined in OAlg.Entity.Matrix.Vector Methods valid :: Representable r h x y -> Statement Source # | |
mtxRepresentable :: (Semiring r, Commutative r) => Matrix r -> Representable r (HomSymbol r) (SumSymbol r N) (SumSymbol r N) Source #
the associated representation of a matrix.
Propostion
prpRepMatrix :: (Semiring r, Commutative r) => Representable r h x y -> Vector r -> Statement Source #
validity of repMatrix for the given vector.