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.Entity.Matrix.Dim

Description

dimension for matrices of x as a complete sequence of Point x.

Synopsis

Documentation

data Dim x p where Source #

dimension of x as a complete sequence of Point x.

Constructors

Dim :: CSequence (Point x) -> Dim x (Point x) 

Instances

Instances details
Sequence (Dim x) N p Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

graph :: p0 N -> Dim x p -> Graph N p Source #

list :: p0 N -> Dim x p -> [(p, N)] Source #

(??) :: Dim x p -> N -> Maybe p Source #

(Oriented x, Entity p) => PermutableSequence (Dim x) N p Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

permuteBy :: p0 N -> (w -> w -> Ordering) -> (p -> w) -> Dim x p -> (Dim x p, Permutation N) Source #

Entity p => Opr (Permutation N) (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

(<*) :: Dim x p -> Permutation N -> Dim x p Source #

(Oriented x, Entity p) => TotalOpr (Permutation N) (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Oriented x => Show (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

showsPrec :: Int -> Dim x p -> ShowS #

show :: Dim x p -> String #

showList :: [Dim x p] -> ShowS #

Oriented x => Eq (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

(==) :: Dim x p -> Dim x p -> Bool #

(/=) :: Dim x p -> Dim x p -> Bool #

(Oriented x, OrdPoint x) => Ord (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

compare :: Dim x p -> Dim x p -> Ordering #

(<) :: Dim x p -> Dim x p -> Bool #

(<=) :: Dim x p -> Dim x p -> Bool #

(>) :: Dim x p -> Dim x p -> Bool #

(>=) :: Dim x p -> Dim x p -> Bool #

max :: Dim x p -> Dim x p -> Dim x p #

min :: Dim x p -> Dim x p -> Dim x p #

LengthN (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

lengthN :: Dim x p -> N Source #

Oriented x => Validable (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

valid :: Dim x p -> Statement Source #

(Oriented x, () ~ Point x) => XStandard (Dim x ()) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

xStandard :: X (Dim x ()) Source #

(Oriented x, Typeable p) => Entity (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

(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 x, Typeable p, p ~ Point x) => Multiplicative (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

Methods

one :: Point (Dim x p) -> Dim x p Source #

(*) :: Dim x p -> Dim x p -> Dim x p Source #

npower :: Dim x p -> N -> Dim x p Source #

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

Defined in OAlg.Entity.Matrix.Dim

Associated Types

type Point (Dim x p) Source #

Methods

orientation :: Dim x p -> Orientation (Point (Dim x p)) Source #

start :: Dim x p -> Point (Dim x p) Source #

end :: Dim x p -> Point (Dim x p) Source #

Total (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

type Exponent (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

type Exponent (Dim x p) = N
type Point (Dim x p) Source # 
Instance details

Defined in OAlg.Entity.Matrix.Dim

type Point (Dim x p) = ()

type Dim' x = Dim x (Point x) Source #

abbreviation for Dim x (Point x).

fromDim :: Dim x p -> ProductSymbol p Source #

the underlying product.

dim :: (Entity p, p ~ Point x) => p -> Dim x p Source #

constructing a dimension form a point.

productDim :: (Entity p, p ~ Point x) => [p] -> Dim x p Source #

constructing a dimension from a list of points.

dimxs :: p ~ Point x => Dim x p -> [(p, N)] Source #

the indexed listing of the points.

dimwrd :: (Entity p, p ~ Point x) => Dim x p -> Word N p Source #

the underlying word.

dimMap :: (Entity q, q ~ Point y) => (p -> q) -> Dim x p -> Dim y q Source #

mapping a dimension.