Google Groups no longer supports new Usenet posts or subscriptions. Historical content remains viewable.
Dismiss

Non-comm

15 views
Skip to first unread message

Ersek_T...@mr.nawcad.navy.mil

unread,
Jul 23, 1998, 3:00:00 AM7/23/98
to

Isn't this built-in as a different type of multiplication?

In[5]:=
?NonCommutativeMultiply

"a ** b ** c is a general associative, but non-commutative, form of \
multiplication."

If you like you can use the Notation package to define a convention for
Input and/or Output that is more readable.


Ted Ersek

|
|It's OK to say that we should not remove attributes from fundemantal
ops |like Plus and Times. I agree, though for experimental purposes, I
like |the flexibility. Thanks for giving us that. |
|However there is one obvious and common case where the Orderless
|attribute doesn't apply, namely matrix math. The operation of
|multiplying matrices must not have the Orderless attribute. |
|Try writing out some matrix equations in Mathematica and asking the
|program to simplify or otherwise rearrange them. Unless you have
|actually constructed the matrices symbolically, it won't work. In
|other words, Mathematica does not allow any kind of shorthand for
|matrix math. You have to write out {{a[1,1],a[1,2]},{a[2,1],a[2,2]}}
|and can't just put A.
|
|There is one, and only one definition for a new symbol like "A": it
is, |by decree of Wolfram Research (:-/), a complex number. It can't
be a |real number, an integer, or -- a matrix. |
|In the field of control theory, the whole point of using matrix math is
|the shorthand notation, thus:
|
| x-dot = A.x + B.u (system state equation) | y = C.x + D.u
(system output equation) |
|where
|
| x = the n x 1 state vector for
| an nth-order system
| u = the m x 1 input vector for
| a system with m inputs | y = the p x 1 output vector
for | a system with p outputs | A = the n x n system
(or plant) matrix for an | nth-order system
| B = the n x m input matrix for an | nth-order system
with m inputs | C = the p x n output matrix for an |
nth-order system with p outputs | D = the p x m feed forward matrix
for a | system with p outputs and m inputs |
|In the past I tried to tinker with some Kalman filtering equations in
|Mathematica but got nowhere fast. The Kalman theory is derived from
|pure symbolic matrix mathematics. The dimensions of the matrices are
|irrelevant to the theory, but the fact that they are matrices is
|central.
|
|Sometimes you know the values of m,n,p but even in that case, in
|Mathematica you still have to write out the full matrices by hand. At
|other times, you want to leave m,n,p undefined. |
|I would say that WRI should take the task of writing the rule base for
|symbolic matrix math with the Orderless attribute removed. That's not
|a job for the users. I think that this example alone answers David
|Withoff's proposition:
|
|> A separate question is whether or not functions such as Expand could
or |> should somehow be modified, probably by invoking separate
algorithms, |> to handle operations in other algebras. That is an
interesting |> question, and one that many people have considered. |
|Yes, they should invoke separate algorithms for symbols declared as
|matrices, once we can make such declarations. |
|
|Best regards to the developers,
|
|Mark
|
|

MJE

unread,
Jul 24, 1998, 3:00:00 AM7/24/98
to
Hi Ted -

Regarding NonCommutativeMultiply:

This feature doesn't solve any of the problems I mentioned. As a
trivial example, write 'NonCommutativeMultiply[I,A]' where 'I' is meant
to represent the identity matrix. You can't tell Mathematica that I
and A are matrices, much less that I is the identity matrix, without
defining the full-blown forms. Mathematica assumes that I and A
represent complex numbers. So the matrix expression 'I A' will not
simplify under NonCommutativeMultiply.

Your comment about the Notation package is true in general terms, but
for common things like symbolic matrix math, WRI should write the rule
base, not every user on his own.

Mark

Tobias Oed

unread,
Jul 24, 1998, 3:00:00 AM7/24/98
to
I wrote a little package that works all right for me. It is actually
part of a much bigger project to do relativistic quantum mechanics
calculations.
What I needed was to have different linear spaces with symbols in them.
(Say Dirac and Isospin spaces). The solution I have here works in the
following way:

load the package

In[1]:= << ~/Tmp/mail.m

Declare different types

In[2]:= DefType[DiracOperator,DiracSpinor,IsospinOperator,IsoSpinor]

Declare objects of which type do not commute with objects of which
other types.

In[3]:=
SetNonCommutative[{DiracOperator,DiracSpinor},{IsospinOperator,IsoSpinor}]

Set the type of the symbols you use.

In[4]:= SetType[{DiracGamma,Slash,DiracOperator}]

In[5]:= SetType[{o1,o2,IsospinOperator}]

In[6]:=
SetType[{u,ubar,v,vbar,DiracSpinor},{xi,xidaggar,ksi,ksidaggar,IsoSpinor}]

and then you can play:

In[7]:= particle1=u xi; \
particle2=v ksi; \
particle3=ubar xidaggar; \
particle4=vbar ksidaggar;

In[8]:= particle1 ** DiracGamma[mu] ** particle3 ** \
particle2 ** (DiracGamma[mu]+Slash[k]) ** particle4

The package rearanges this expression by separating the multiplication
in Isospin space and the one in Dirac space

Out[8]= xi ** xidaggar ** ksi ** ksidaggar

> u ** DiracGamma[mu] ** ubar ** v ** (DiracGamma[mu] + Slash[k]) ** vbar

You have other a coupple more functions to manipulate the expressions

In[9]:= Factor[FullExpand[%]]

Out[10]= xi ** xidaggar ** ksi ** ksidaggar

> (u ** DiracGamma[mu] ** ubar ** v ** DiracGamma[mu] ** vbar +

> u ** DiracGamma[mu] ** ubar ** v ** Slash[k] ** vbar)

There is a type called MatrixOperator. Any symbol (like Matrix) carrying
this
type will not commute with any other typed object.

I hope this can help you , Tobias

(**** Non commutative multiply ****) (* (c) Tobias Oed and Old Dominion
University 23-7-98 *)

BeginPackage["RQMMultiply`"];

DefType::usage = "
DefType[t..] declates symbols t.. to be type identificators."
IsTypeQ::usage = "
IsTypeQ[t] is true if t is a type identificator"
SetNonCommutative::usage = "
SetNonCommutative[{t1..,t2..}..] declares the product of objects of
types t1.. by objects of
type t2.. to be non commutative.."
NonCommutative::usage = "
NonCommutative[t] is the list of types with wich an object of type t
does not commute."
SetType::usage = "
SetType[{a..,t}..] declares symbols a.. to be of type t.." Type::usage
= "
Type[expr] is the sequence of types involved in expr."

Commutator::usage = "
Commutator[expr1,expr2] is an expression with expr1 and expr2
interchanged (in a non
commutative product)."

CommuteQ::usage = "
CommuteQ[expr1,expr2] is true if expr1**expr2 is equal to
expr2**expr1."

ShouldCommuteQ::usage = "
SouldCommuteQ[expr1,expr2] is true if expr1**expr2 is equal to
expr2**expr1 and
expr2**expr1 is in the cannonical order"

NonCommutativeExpand::usage = "
NonCommutativeExpand[expr] distributes non commutative multiplications
over sums."
FullExpand::usage = "
FullExpand[expr] distributes commutative and non commutative
multiplications over sums."

NonCommutativeOrder::usage = "
NonCommutativeOrder[expr] orders noncommutative products.
NonCommutativeOrder[expr,{o1,o2..}] puts noncommutative products of
objects o1, o2... in the given order."

MatrixOperator::usage = "MatrixOperator is the Type of Matrices."
Matrix::usage = "Matrix[l1..] is a Matrix with lines l1.. Matrices do
not commute with objects of any other type."
MatrixMultiplication::usage = "MatrixMultiply[expr] effecutes matrix
multiplications in expr"
MatrixAdd::usage = "MatrixAdd[expr] Puts all multiplicative constants
that are in front of a matrix in it then it adds all matrices, and
finally it adds constants on the diagonal." ToExplicitMatrix::usage =
"ToExplicitMatrix[expr,t..] converts in expr everything to matrices
according to rules associated with objects of type t."
ToExplicitMatrixRules::usage = "ToExplicitMatrixRules[t]={Rules} sets
the matrix conversion rules for objects of type t." MatrixReduce

(****************************************************************************************)
Begin["`Private`"]
Clear[DefType,IsType,SetNonCommutative,NonCommutative,SetType,Type]
Clear[Commutator,CommuteQ,AutomaticNonCommutativeMultiply]
Clear[Matrix,MatrixMultiplication,MatrixAdd,ToExplicitMatrix,ToExplicitMatrixRules]

(****************************************************************************************)
(****
Type*******************************************************************************)

IsTypeQ[MatrixOperator]=True
NonCommutative[MatrixOperator]={MatrixOperator}
Type[Matrix|_Matrix]=MatrixOperator

DefType[t__]:=(
Scan[
If[MatchQ[#,_Symbol] && !IsTypeQ[#],
IsTypeQ[#]=True;
NonCommutative[#]={MatrixOperator,#};

NonCommutative[MatrixOperator]=Union[NonCommutative[MatrixOperator],{#}]
,
Print["Cannot define ",#," as a type identificator. It is not a
Symbol"];Abort[]
]
&,{t}]
)
IsTypeQ[_]=False;

SetNonCommutative[t_]:=(
Scan[
If[!IsTypeQ[#],Print[#,"Is not a type identificator in
SetNonCommutative[",t,"]"];Abort]
& ,t];
Scan[(NonCommutative[#]=Union[NonCommutative[#],t]) &,t] )
SetNonCommutative[a__]:=Scan[SetNonCommutative,{a}] NonCommutative[_]={}

SetType[{a__,t_}]:=(
If[IsTypeQ[t],
Scan[
If[MatchQ[#,_Symbol],
Type[#|Blank[#]]=t;
,
Print["Cannot set Type of ",a,". It is not a Symbol"]
]
&,{a}]
,
Print[t," Is not a type identificator"]
]
)
SetType[a__]:=Scan[SetType,{a}]
Type[(_)[x___]]:=Apply[Sequence,Union[Map[Type,{x}]]] Type[_]=Sequence[]

(****************************************************************************************)
(**** Commutator
************************************************************************)

Commutator[x_,x_]:=x**x
Commutator[x_,y_] /; CommuteQ[x,y] :=x y

Commutator[x_Plus,y_]:=Map[Commutator[#,y] &,x]
Commutator[x_,y_Plus]:=Map[Commutator[x,#] &,y]

(****************************************************************************************)
(**** Non Commutative Multiply
**********************************************************)

CommuteQ[expr1_,expr2_]:=(Intersection[{Type[expr1]},Apply[Union,Map[NonCommutative,{Type[expr2]}]]]==={})

ShouldCommuteQ[t1_,t2_]:=(
Intersection[t1,Apply[Union,Map[NonCommutative,t2]]]==={} &&
Order[First[t1],First[t2]]===-1
)

Unprotect[NonCommutativeMultiply]
ClearAll[NonCommutativeMultiply]
NonCommutativeMultiply[s___,a_Times,e___]:=
NonCommutativeMultiply[s,Apply[Sequence,a],e]
NonCommutativeMultiply[s___,a_NonCommutativeMultiply,e___]:=
NonCommutativeMultiply[s,Apply[Sequence,a],e]
NonCommutativeMultiply[s_]:=s
NonCommutativeMultiply[]:=1
NonCommutativeMultiply[s___,a_,e___] /; {Type[a]}==={} := a
NonCommutativeMultiply[s,e]
NonCommutativeMultiply[s___,a_,b_,e___] /;
ShouldCommuteQ[{Type[a]},{Type[b]}] := NonCommutativeMultiply[s,b,a,e]
NonCommutativeMultiply[s__,e__] /; CommuteQ[{s},{e}] :=
NonCommutativeMultiply[s] NonCommutativeMultiply[e]
Protect[NonCommutativeMultiply]

NonCommutativeOrder[expr_]:=(expr
//. HoldPattern[NonCommutativeMultiply[s___,b_,a_,e___] /;
OrderedQ[{a,b}]] :>
FullExpand[NonCommutativeMultiply[s,Commutator[b,a],e]] )

NonCommutativeOrder[expr_,o_]:=(expr //.
HoldPattern[NonCommutativeMultiply[s___,b_,a_,e___] /; MemberQ[o,a] &&
MemberQ[o,b] && (Position[o,a][[1,1]] < Position[o,b][[1,1]])]
:> FullExpand[NonCommutativeMultiply[s,Commutator[b,a],e]] )

(****************************************************************************************)
(**** Expand
****************************************************************************)

NonCommutativeExpand[expr_]:=expr /. x_NonCommutativeMultiply :>
Distribute[x]

FullExpand[expr_]:=expr //. {x:HoldPattern[___ ** _Plus ** ___] :>
Distribute[x],x:HoldPattern[___*_Plus*___]:> Expand[x]}

(****************************************************************************************)
(**** Matrix
****************************************************************************)

Matrix[{x_}]:=x

MatrixReduce[expr_]:=(expr //.
{
HoldPattern[NonCommutativeMultiply[s___,Matrix[m1__],Matrix[m2__],e___]]
/; Length[First[{m1}]]===Length[{m2}] :> s **
Apply[Matrix,Inner[NonCommutativeMultiply,{m1},{m2}]] ** e,
HoldPattern[NonCommutativeMultiply[s___,m1_Matrix,p_Plus,e___]] /;
MemberQ[{Type[p]},Matrix] :> s**m1**MatrixAdd[p]**e} )

MatrixMultiplication[expr_]:=(expr
//.
HoldPattern[NonCommutativeMultiply[s___,Matrix[m1__],Matrix[m2__],e___]]
/; Length[First[{m1}]]===Length[{m2}] :> s **
Apply[Matrix,Inner[NonCommutativeMultiply,{m1},{m2}]] ** e )

MatrixAdd[expr_]:=(expr
//. c__ Matrix[m1__] :> Apply[Matrix,c {m1}]
//. Matrix[m1__] + Matrix[m2__] :>
Apply[Matrix,MapThread[Plus,{{m1},{m2}}]]
//. c__ + Matrix[m1__] /; (!MemberQ[{Type[{c}]},Matrix] &&
Length[First[{m1}]]==Length[{m1}]) :> Apply[Matrix, Plus[c]
IdentityMatrix[Length[{m1}]] + {m1}] )

ToExplicitMatrix[expr_,r__]:=Fold[(#1 //. ToExplicitMatrixRules[#2])
&,expr,{r}]

ToExplicitMatrixRules[_]={}

End[]

EndPackage[];


0 new messages