polynomial-algebra-0.1.0.1: Multivariate polynomial rings

Safe HaskellNone
LanguageHaskell2010

Math.Algebra.Polynomial.Monomial.Tensor

Contents

Description

Tensor product (that is, pairs) of monomials

Synopsis

Documentation

data Tensor (symbol :: Symbol) (a :: *) (b :: *) Source #

Elementary tensors (basically pairs). The phantom type parameter symbol is used to render an infix symbol when pretty-printing

Constructors

Tensor !a !b 
Instances
(Eq a, Eq b) => Eq (Tensor symbol a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Methods

(==) :: Tensor symbol a b -> Tensor symbol a b -> Bool #

(/=) :: Tensor symbol a b -> Tensor symbol a b -> Bool #

(Ord a, Ord b) => Ord (Tensor symbol a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Methods

compare :: Tensor symbol a b -> Tensor symbol a b -> Ordering #

(<) :: Tensor symbol a b -> Tensor symbol a b -> Bool #

(<=) :: Tensor symbol a b -> Tensor symbol a b -> Bool #

(>) :: Tensor symbol a b -> Tensor symbol a b -> Bool #

(>=) :: Tensor symbol a b -> Tensor symbol a b -> Bool #

max :: Tensor symbol a b -> Tensor symbol a b -> Tensor symbol a b #

min :: Tensor symbol a b -> Tensor symbol a b -> Tensor symbol a b #

(Show a, Show b) => Show (Tensor symbol a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Methods

showsPrec :: Int -> Tensor symbol a b -> ShowS #

show :: Tensor symbol a b -> String #

showList :: [Tensor symbol a b] -> ShowS #

(Semigroup a, Semigroup b) => Semigroup (Tensor sym a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Methods

(<>) :: Tensor sym a b -> Tensor sym a b -> Tensor sym a b #

sconcat :: NonEmpty (Tensor sym a b) -> Tensor sym a b #

stimes :: Integral b0 => b0 -> Tensor sym a b -> Tensor sym a b #

(Monoid a, Monoid b) => Monoid (Tensor sym a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Methods

mempty :: Tensor sym a b #

mappend :: Tensor sym a b -> Tensor sym a b -> Tensor sym a b #

mconcat :: [Tensor sym a b] -> Tensor sym a b #

(KnownSymbol sym, Pretty a, Pretty b) => Pretty (Tensor sym a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Methods

pretty :: Tensor sym a b -> String Source #

prettyInParens :: Tensor sym a b -> String Source #

(KnownSymbol sym, Monomial a, Monomial b) => Monomial (Tensor sym a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

Associated Types

type VarM (Tensor sym a b) :: Type Source #

Methods

normalizeM :: Tensor sym a b -> Tensor sym a b Source #

isNormalM :: Tensor sym a b -> Bool Source #

fromListM :: [(VarM (Tensor sym a b), Int)] -> Tensor sym a b Source #

toListM :: Tensor sym a b -> [(VarM (Tensor sym a b), Int)] Source #

emptyM :: Tensor sym a b Source #

isEmptyM :: Tensor sym a b -> Bool Source #

variableM :: VarM (Tensor sym a b) -> Tensor sym a b Source #

singletonM :: VarM (Tensor sym a b) -> Int -> Tensor sym a b Source #

mulM :: Tensor sym a b -> Tensor sym a b -> Tensor sym a b Source #

productM :: [Tensor sym a b] -> Tensor sym a b Source #

powM :: Tensor sym a b -> Int -> Tensor sym a b Source #

divM :: Tensor sym a b -> Tensor sym a b -> Maybe (Tensor sym a b) Source #

diffM :: Num c => VarM (Tensor sym a b) -> Int -> Tensor sym a b -> Maybe (Tensor sym a b, c) Source #

maxDegM :: Tensor sym a b -> Int Source #

totalDegM :: Tensor sym a b -> Int Source #

evalM :: Num c => (VarM (Tensor sym a b) -> c) -> Tensor sym a b -> c Source #

varSubsM :: (VarM (Tensor sym a b) -> VarM (Tensor sym a b)) -> Tensor sym a b -> Tensor sym a b Source #

termSubsM :: Num c => (VarM (Tensor sym a b) -> Maybe c) -> (Tensor sym a b, c) -> (Tensor sym a b, c) Source #

type VarM (Tensor sym a b) Source # 
Instance details

Defined in Math.Algebra.Polynomial.Monomial.Tensor

type VarM (Tensor sym a b) = Either (VarM a) (VarM b)

flip :: Tensor sym a b -> Tensor sym b a Source #

Injections

injLeft :: Monoid b => a -> Tensor sym a b Source #

injRight :: Monoid a => b -> Tensor sym a b Source #

Projections

projLeft :: Tensor sym a b -> a Source #

projRight :: Tensor sym a b -> b Source #

differentiation

diffTensor :: (Monomial a, Monomial b, Num c) => Either (VarM a) (VarM b) -> Int -> Tensor sym a b -> Maybe (Tensor sym a b, c) Source #

Helpers

distEither :: (Either a b, c) -> Either (a, c) (b, c) Source #