Array variableSubclass: #DhbVector instanceVariableNames: '' classVariableNames: '' poolDictionaries: ''! Object subclass: #DhbLinearEquationSystem instanceVariableNames: 'rows solutions ' classVariableNames: '' poolDictionaries: 'SystemExceptions '! Object subclass: #DhbLUPDecomposition instanceVariableNames: 'rows permutation parity ' classVariableNames: '' poolDictionaries: ''! Object subclass: #DhbMatrix instanceVariableNames: 'rows lupDecomposition ' classVariableNames: '' poolDictionaries: ''! DhbMatrix subclass: #DhbSymmetricMatrix instanceVariableNames: '' classVariableNames: '' poolDictionaries: ''! SubApplication subclass: #DhbLinearAlgebra instanceVariableNames: '' classVariableNames: '' poolDictionaries: ''! !Collection publicMethods ! asVector "Convert the receiver to a vector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self convertToArrayedClass: DhbVector! ! !DhbLinearEquationSystem class publicMethods ! equations: anArrayOfArrays constant: anArray " (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self new initialize: anArrayOfArrays constants: (Array with: anArray)! equations: anArrayOfArrays constants: anArrayOfConstantArrays " (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self new initialize: anArrayOfArrays constants: anArrayOfConstantArrays! ! !DhbLinearEquationSystem publicMethods ! printOn: aStream "Append to the argument aStream, a sequence of characters that describes the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | first delimitingString n k | n := rows size. first := true. rows do: [ :row | first ifTrue: [ first := false] ifFalse:[ aStream cr]. delimitingString := '('. k := 0. row do: [ :each | aStream nextPutAll: delimitingString. each printOn: aStream. k := k + 1. delimitingString := k < n ifTrue: [ ' '] ifFalse: [ ' : ']. ]. aStream nextPut: $). ].! solution "Answers the solution corresponding to the first constant array. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " ^self solutionAt: 1! solutionAt: anInteger "Answer the solution corresponding to the anInteger-th constant array. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " solutions isNil ifTrue: [ [self solve] when: ExError do: [ :signal |solutions := 0. signal exitWith: nil.] ]. solutions = 0 ifTrue: [ ^nil]. ( solutions at: anInteger) isNil ifTrue: [ self backSubstitutionAt: anInteger]. ^solutions at: anInteger! ! !DhbLinearEquationSystem privateMethods ! backSubstitutionAt: anInteger "Private - Perform the back-substitution step corresponding to the anInteger-th constant array. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | size answer accumulator | size := rows size. answer := Array new: size. size to: 1 by: -1 do: [ :n | accumulator := (rows at: n) at: (anInteger + size). ( n + 1) to: size do: [ :m | accumulator := accumulator - ( ( answer at: m) * ( ( rows at: n) at: m))]. answer at: n put: ( accumulator / ( ( rows at: n) at: n)). ]. solutions at: anInteger put: answer.! initialize: anArrayOfArrays constants: anArrayOfConstantArrays "Private - Initialize the receiver with system's matrix in anArrayOfArrays and several constants. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. rows := anArrayOfArrays collect: [ :each | n := n + 1. each, ( anArrayOfConstantArrays collect: [ :c | c at: n])]. ^self! largestPivotFrom: anInteger "Private - Answers the largest pivot element in column anInteger, from position anInteger upward. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | valueOfMaximum indexOfMaximum | valueOfMaximum := ( rows at: anInteger) at: anInteger. indexOfMaximum := anInteger. ( anInteger + 2) to: rows size do: [ :n | ( ( rows at: n) at: anInteger) > valueOfMaximum ifTrue: [ valueOfMaximum := ( rows at: n) at: anInteger. indexOfMaximum := n. ]. ]. ^indexOfMaximum ! pivotAt: anInteger "Private - Performs pivot operation with pivot element at anInteger. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | inversePivot rowPivotValue row pivotRow | pivotRow := rows at: anInteger. inversePivot := 1 / ( pivotRow at: anInteger). ( anInteger + 1) to: rows size do: [ :n | row := rows at: n. rowPivotValue := ( row at: anInteger) * inversePivot. anInteger to: row size do: [ :m | row at: m put: ( ( row at: m) - (( pivotRow at: m) * rowPivotValue)). ]. ].! pivotStepAt: anInteger "Private - Performs an optimum pivot operation at anInteger. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " self swapRow: anInteger withRow: ( self largestPivotFrom: anInteger); pivotAt: anInteger.! solve "Private - Perform LU decomposition of the system. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " 1 to: rows size do: [ :n | self pivotStepAt: n]. solutions := Array new: ( (rows at: 1) size - rows size).! swapRow: anInteger1 withRow: anInteger2 "Private - Swap the rows indexed by the given integers. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | swappedRow | anInteger1 = anInteger2 ifFalse:[ swappedRow := rows at: anInteger1. rows at: anInteger1 put: ( rows at: anInteger2). rows at: anInteger2 put: swappedRow. ].! ! !DhbLUPDecomposition class publicMethods ! direct: anArrayOfArrays "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " ^self new initialize: anArrayOfArrays.! equations: anArrayOfArrays "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " ^self new initialize: ( anArrayOfArrays collect: [ :each | each deepCopy]).! ! !DhbLUPDecomposition publicMethods ! printOn: aStream "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " | first delimitingString n k | n := rows size. first := true. rows do: [ :row | first ifTrue: [ first := false] ifFalse:[ aStream cr]. delimitingString := '('. row do: [ :each | aStream nextPutAll: delimitingString. each printOn: aStream. delimitingString := ' '. ]. aStream nextPut: $). ].! solve: anArrayOrVector "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " permutation isNil ifTrue: [ self protectedDecomposition]. ^permutation = 0 ifTrue: [ nil] ifFalse:[ self backwardSubstitution: ( self forwardSubstitution: anArrayOrVector)]! ! !DhbLUPDecomposition privateMethods ! backwardSubstitution: anArray "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " | n sum answer| n := rows size. answer := DhbVector new: n. n to: 1 by: -1 do: [ :i | sum := anArray at: i. ( i + 1) to: n do: [ :j | sum := sum - ( ( ( rows at: i) at: j) * ( answer at: j))]. answer at: i put: sum / ( ( rows at: i) at: i). ]. ^answer! decompose "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " | n | n := rows size. permutation := (1 to: n) asArray. 1 to: ( n - 1) do: [ :k | self swapRow: k withRow: ( self largestPivotFrom: k); pivotAt: k. ].! forwardSubstitution: anArray "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " | n sum answer| answer := permutation collect: [ :each | anArray at: each]. n := rows size. 2 to: n do: [ :i | sum := answer at: i. 1 to: ( i - 1) do: [ :j | sum := sum - ( ( ( rows at: i) at: j) * ( answer at: j))]. answer at: i put: sum. ]. ^answer! initialize: anArrayOfArrays "Private - A copy of the original array is made. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " rows := anArrayOfArrays. parity := 1. ^self! largestPivotFrom: anInteger "Private - Answers the largest pivot element in column anInteger, from position anInteger upward. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " | valueOfMaximum indexOfMaximum value | valueOfMaximum := ( ( rows at: anInteger) at: anInteger) abs. indexOfMaximum := anInteger. ( anInteger + 1) to: rows size do: [ :n | value := ( ( rows at: n) at: anInteger) abs. value > valueOfMaximum ifTrue: [ valueOfMaximum := value. indexOfMaximum := n. ]. ]. ^indexOfMaximum ! pivotAt: anInteger "Private - (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " | inversePivot size k | inversePivot := 1 / ( ( rows at: anInteger) at: anInteger). size := rows size. k := anInteger + 1. k to: size do: [ :i | ( rows at: i) at: anInteger put: (( rows at: i) at: anInteger) * inversePivot. k to: size do: [ :j | ( rows at: i) at: j put: ( ( rows at: i) at: j) - ( (( rows at: i) at: anInteger) * (( rows at: anInteger) at: j)). ] ].! protectedDecomposition "Private - If decomposition fails, set permutation to 0. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " [ self decompose] when: ExAll do: [ :signal | permutation := 0. signal exitWith: nil].! swapRow: anInteger1 withRow: anInteger2 "Private - Swap the rows indexed by the given integers. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/2/99 " anInteger1 = anInteger2 ifFalse:[ | swappedRow | swappedRow := rows at: anInteger1. rows at: anInteger1 put: ( rows at: anInteger2). rows at: anInteger2 put: swappedRow. swappedRow := permutation at: anInteger1. permutation at: anInteger1 put: ( permutation at: anInteger2). permutation at: anInteger2 put: swappedRow. parity := parity negated. ].! ! !DhbMatrix class publicMethods ! new: anInteger "Create an empty square matrix of dimension anInteger. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self new initialize: anInteger! rows: anArrayOrVector "Create a new matrix with given components. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self new initializeRows: anArrayOrVector! ! !DhbMatrix publicMethods ! * aNumberOrMatrixOrVector "Answers the product of the receiver with the argument. The argument can be a number, matrix or vector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aNumberOrMatrixOrVector productWithMatrix: self! + aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix addWithRegularMatrix: self! - aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix subtractWithRegularMatrix: self! accumulate: aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. self rowsCollect: [ :each | n := n + 1. each accumulate: ( aMatrix rowAt: n)]! accumulateNegated: aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. self rowsCollect: [ :each | n := n + 1. each accumulateNegated: ( aMatrix rowAt: n)]! addWithMatrix: aMatrix class: aMatrixClass "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. ^aMatrixClass rows: ( self rowsCollect: [ :each | n := n + 1. each + ( aMatrix rowAt: n)])! addWithRegularMatrix: aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix addWithMatrix: self class: aMatrix class! addWithSymmetricMatrix: aMatrix "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/28/99 " ^aMatrix addWithMatrix: self class: self class! asSymmetricMatrix "Convert the receiver to a symmetric matrix (no check is made). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^DhbSymmetricMatrix rows: rows! columnAt: anInteger "Answers the anInteger-th column of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows collect: [ :each | each at: anInteger]! columnsCollect: aBlock "Perform the collect: operation on the rows of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. ^rows last collect: [ :each | n := n + 1. aBlock value: ( self columnAt: n)]! columnsDo: aBlock "Perform the collect: operation on the rows of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. ^rows last do: [ :each | n := n + 1. aBlock value: ( self columnAt: n)]! initialize: anInteger "Build empty components for a square matrix. No check is made: components are assumed to be orgainized in rows. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " rows := ( 1 to: anInteger) asVector collect: [ :each | DhbVector new: anInteger].! initializeRows: anArrayOrVector "Defines the components of the recevier. No check is made: components are assumed to be orgainized in rows. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " rows := anArrayOrVector asVector collect: [ :each | each asVector].! isSquare "Answers true if the number of rows is equal to the number of columns. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows size = rows last size! isSymmetric "Answers false because the receiver is not a symmetric matrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^false! lupDecomposition "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30/3/99 " lupDecomposition isNil ifTrue: [ lupDecomposition :=DhbLUPDecomposition equations: rows]. ^lupDecomposition! negate "Inverse the sign of all components of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " rows do: [ :each |each negate].! numberOfColumns "Answer the number of rows of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows last size! numberOfRows "Answer the number of rows of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows size! printOn: aStream "Append to the argument aStream, a sequence of characters that describes the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | first | first := true. rows do: [ :each | first ifTrue: [ first := false] ifFalse:[ aStream cr]. each printOn: aStream. ].! productWithMatrix: aMatrix "Answers the product of aMatrix with the receiver (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self productWithMatrixFinal: aMatrix! productWithMatrixFinal: aMatrix "Answers the product of aMatrix with the receiver (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self class rows: ( aMatrix rowsCollect: [ :row | self columnsCollect: [ :col | row * col]])! productWithSymmetricMatrix: aSymmetricMatrix "Answers the product of the receiver with aSymmetricMatrix (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self class rows: ( self rowsCollect: [ :row | aSymmetricMatrix columnsCollect: [ :col | row * col]])! productWithTransposeMatrix: aMatrix "Answers the product of the receiver with the transpose of aMatrix(in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self class rows: ( self rowsCollect: [ :row | aMatrix rowsCollect: [ :col | row * col]])! productWithVector: aVector "Answers the product of the receiver with aVector (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self columnsCollect: [ :each | each * aVector]! rowAt: anInteger "Answers the anInteger-th row of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows at: anInteger! rowsCollect: aBlock "Perform the collect: operation on the rows of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows collect: aBlock! rowsDo: aBlock "Perform the collect: operation on the rows of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^rows do: aBlock! scaleBy: aNumber "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/11/00 " rows do: [ :each | each scaleBy: aNumber].! squared "Answers the product of the transpose of the receiver with the receiver (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^DhbSymmetricMatrix rows: ( self columnsCollect: [ :col | self columnsCollect: [ :colT | col * colT]])! subtractWithMatrix: aMatrix class: aMatrixClass "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. ^aMatrixClass rows: ( self rowsCollect: [ :each | n := n + 1. each - ( aMatrix rowAt: n)])! subtractWithRegularMatrix: aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix subtractWithMatrix: self class: aMatrix class! subtractWithSymmetricMatrix: aMatrix "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 12/28/99 " ^aMatrix subtractWithMatrix: self class: self class! transpose "Answer a new matrix, transpose of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self class rows: ( self columnsCollect: [ :each | each])! transposeProductWithMatrix: aMatrix "Answers the product of the transpose of the receiver with aMatrix (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self class rows: ( self columnsCollect: [ :row | aMatrix columnsCollect: [ :col | row * col]])! ! !DhbSymmetricMatrix class publicMethods ! identity: anInteger "Create an identity matrix of dimension anInteger. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self new initializeIdentity: anInteger! ! !DhbSymmetricMatrix publicMethods ! + aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix addWithSymmetricMatrix: self! - aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix subtractWithSymmetricMatrix: self! addWithSymmetricMatrix: aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix addWithMatrix: self class: self class! clear "(c) Copyrights Didier BESSET, 2000, all rights reserved. Initial code: 2/11/00 " rows do: [ :each | each atAllPut: 0].! initializeIdentity: anInteger "Build components for an identity matrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " rows := ( 1 to: anInteger) asVector collect: [ :n | (DhbVector new: anInteger) atAllPut: 0; at: n put: 1; yourself].! isSquare "Answers true because a symmetric matrix is square. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^true! isSymmetric "Answers true because the receiver is a symmetric matrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^true! productWithMatrix: aMatrix "Answers the product of aMatrix with the receiver (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix productWithSymmetricMatrix: self! productWithSymmetricMatrix: aSymmetricMatrix "Answers the product of aMatrix with the receiver (in this order). (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aSymmetricMatrix productWithMatrixFinal: self! subtractWithSymmetricMatrix: aMatrix "Answers the sum of the receiver with aMatrix. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix subtractWithMatrix: self class: self class! ! !DhbVector publicMethods ! * aNumberOrMatrixOrVector "Answers the product of the receiver with the argument. The argument can be a number, matrix or vector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aNumberOrMatrixOrVector productWithVector: self! + aVector "Answers the sum of the receiver with aVector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | answer n | answer := self class new: self size. n := 0. self with: aVector do: [ :a :b | n := n + 1. answer at: n put: ( a + b). ]. ^answer! - aVector "Answers the difference of the receiver with aVector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | answer n | answer := self class new: self size. n := 0. self with: aVector do: [ :a :b | n := n + 1. answer at: n put: ( a - b). ]. ^answer! accumulate: aVectorOrAnArray " (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 8/3/99 " 1 to: self size do: [ :n | self at: n put: ( ( self at: n) + ( aVectorOrAnArray at: n))].! accumulateNegated: aVectorOrAnArray "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 8/3/99 " 1 to: self size do: [ :n | self at: n put: ( ( self at: n) - ( aVectorOrAnArray at: n))].! asVector "Answer self since the receiver is a vector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self! dimension "Answer the dimension of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^self size! negate "Inverse the sign of all components of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " 1 to: self size do: [ :n | self at: n put: (self at: n) negated].! norm "Answer the norm of the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^(self * self) sqrt! normalized "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 30-Dec-99 " ^(1 / self norm) * self! productWithMatrix: aMatrix "Answers the product of aMatrix with the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix rowsCollect: [ :each | each * self]! productWithVector: aVector "Answers the scalar product of aVector with the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " | n | n := 0. ^self inject: 0 into: [ :sum :each | n := n + 1. (aVector at: n) * each + sum]! scaleBy: aNumber "(c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 8/3/99 " 1 to: self size do: [ :n | self at: n put: ( ( self at: n) * aNumber)].! tensorProduct: aVector "Answers the tensor product of the receiver with aVector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " self dimension = aVector dimension ifFalse:[ ^self error: 'Vector dimensions mismatch to build tensor product']. ^DhbSymmetricMatrix rows: ( self collect: [ :a | aVector collect: [ :b | a * b]]) ! ! !Number publicMethods ! productWithMatrix: aMatrix "Answer a new matrix, product of aMatrix with the receiver. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aMatrix class rows: ( aMatrix rowsCollect: [ :each | each * self])! productWithVector: aVector "Answers a new vector product of the receiver with aVector. (c) Copyrights Didier BESSET, 1999, all rights reserved. Initial code: 11/2/99 " ^aVector collect: [ :each | each * self]! ! DhbVector initializeAfterLoad! DhbLinearEquationSystem initializeAfterLoad! DhbLUPDecomposition initializeAfterLoad! DhbMatrix initializeAfterLoad! DhbSymmetricMatrix initializeAfterLoad! DhbLinearAlgebra initializeAfterLoad!