@@ -145,15 +145,17 @@ PMMatrix class >> rows: nRows columns: nCols element: fillElement [
145145
146146]
147147
148- { #category : #' as yet unclassified ' }
149- PMMatrix class >> rows: rows columns: columns random: aMaxNumber [
148+ { #category : #' instance creation ' }
149+ PMMatrix class >> rows: aNumberOfRows columns: aNumberOfColumns random: aMaxNumber [
150150 " Answer a new Matrix of the given dimensions filled with random numbers"
151- |a b |
152- a: = (1 to: rows) collect: [:row |b: = PMVector new :columns .
153- 1 to: columns do: [:column |
154- b at: column put: (aMaxNumber random)].
155- b].
156- ^ PMMatrix rows: a
151+ | random rows |
152+ random := Random new .
153+
154+ rows := (1 to: aNumberOfRows) collect: [ :i |
155+ (1 to: aNumberOfColumns) collect: [ :j |
156+ random nextBetween: 0 and : aMaxNumber ] ].
157+
158+ ^ self rows: rows
157159]
158160
159161{ #category : #' instance creation' }
@@ -407,6 +409,12 @@ PMMatrix >> columnAt: anInteger [
407409 ^ rows collect: [ :each | each at: anInteger ]
408410]
409411
412+ { #category : #' cell accessing' }
413+ PMMatrix >> columnVectorAt: col size: dimension [
414+
415+ ^ (self columnAt: col) copyFrom: col to: dimension
416+ ]
417+
410418{ #category : #iterators }
411419PMMatrix >> columnsCollect: aBlock [
412420 " Perform the collect: operation on the rows of the receiver."
@@ -483,10 +491,12 @@ PMMatrix >> elementwiseProductWithMatrix: aMatrix [
483491
484492{ #category : #' as yet unclassified' }
485493PMMatrix >> equalsTo: aMatrix [
486- self rows
487- with: aMatrix rows
488- do: [:a :b | (a equalsTo: b) ifFalse: [ ^ false ] ].
489- ^ true
494+
495+ self
496+ deprecated: ' Use closeTo: instead'
497+ transformWith: ' `@rec equalsTo: `@arg' - > ' `@rec closeTo: `@arg' .
498+
499+ ^ self closeTo: aMatrix
490500]
491501
492502{ #category : #' as yet unclassified' }
@@ -650,6 +660,14 @@ PMMatrix >> lupInverse [
650660 ifNotNil: [ :i | ^ self class rows: i ]
651661]
652662
663+ { #category : #operation }
664+ PMMatrix >> minor: rowIndex and : columnIndex [
665+
666+ ^ PMMatrix rows:
667+ ((self rows allButFirst: columnIndex) collect: [ :aRow |
668+ aRow allButFirst: rowIndex ])
669+ ]
670+
653671{ #category : #' as yet unclassified' }
654672PMMatrix >> mpInverse [
655673 " Moore Penrose Inverse. "
@@ -746,35 +764,16 @@ PMMatrix >> productWithVector: aVector [
746764
747765{ #category : #' as yet unclassified' }
748766PMMatrix >> qrFactorization [
749- |identMat q r hh colSize i |
750- self numberOfRows < self numberOfColumns ifTrue: [ self error: ' numberOfRows<numberOfColumns' ].
751- r := PMMatrix rows: (rows deepCopy).
752- colSize := self numberOfRows.
753- q := PMSymmetricMatrix identity: colSize.
754- identMat := q deepCopy.
755- 1 to: self numberOfColumns do: [:col |
756- hh := ((r columnAt: col) copyFrom: col to: colSize) householder.
757- i := (PMVector new : col- 1withAll: 0 ) , (hh at: 2 ).
758- q := q* (identMat - ((hh at: 1 )* i tensorProduct: i ))." not really necessary, should be simplified"
759- i := PMMatrix rows: ( (r rows allButFirst: (col - 1 )) collect: [:aRow | aRow allButFirst: (col - 1 )] ).
760- i := i - ((hh at: 2 ) tensorProduct: ( (hh at: 1 )* (hh at: 2 )* i ) ) .
761- i rows withIndexDo: [ :aRow :index |
762- aRow withIndexDo: [ :n :c | r rowAt: (col + index - 1 ) columnAt: (col + c - 1 ) put: ((n equalsTo: 0 ) ifTrue: [0 ] ifFalse: [n] ) ] ] .
763- " col <colSize ifTrue: [i :=(hh at: 2) copyFrom: 2 to: colSize -col +1. i withIndexDo: [:n :index| r rowAt: col columnAt: index put: n ] ]" " and this part is not correct, dont uncomment before the bug is corrected! useful if q is not explicitely necessary" ].
764- " r rows allButFirst withIndexDo: [:aRow :ri|1 to: (ri min: self numberOfColumns ) do: [:ci|aRow at: ci put:0 ] ] " " not necessary with equalsTo:0"
765- i := 0 .
766- [(r rowAt: colSize) allSatisfy: [:n | n= 0 ] ]whileTrue: [i := i+ 1 .colSize := colSize - 1 ].
767- i> 0 ifTrue: [ r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
768- i := q numberOfColumns - i.
769- q := PMMatrix rows: ( q rows collect: [:row | row copyFrom: 1 to: i]) ].
770- ^ Array with: q with: r
767+
768+ ^ (PMQRDecomposition of: self ) decompose
771769]
772770
773771{ #category : #' as yet unclassified' }
774772PMMatrix >> qrFactorizationWithPivoting [
773+
775774 | identMat q r hh colSize i lengthArray rank mx pivot |
776- self numberOfRows < self numberOfColumns
777- ifTrue: [ self error: ' numberOfRows<numberOfColumns' ].
775+ self numberOfRows < self numberOfColumns ifTrue: [
776+ self error: ' numberOfRows<numberOfColumns' ].
778777 lengthArray := self columnsCollect: [ :col | col * col ].
779778 mx := lengthArray indexOf: lengthArray max.
780779 pivot := Array new : lengthArray size.
@@ -791,41 +790,41 @@ PMMatrix >> qrFactorizationWithPivoting [
791790 hh := ((r columnAt: rank) copyFrom: rank to: colSize) householder.
792791 i := (PMVector new : rank - 1 withAll: 0 ) , (hh at: 2 ).
793792 q := q * (identMat - ((hh at: 1 ) * i tensorProduct: i)).
794- i := PMMatrix rows: ((r rows allButFirst: rank - 1 ) collect: [ :aRow | aRow allButFirst: rank - 1 ]).
793+ i := PMMatrix rows:
794+ ((r rows allButFirst: rank - 1 ) collect: [ :aRow |
795+ aRow allButFirst: rank - 1 ]).
795796 i := i - ((hh at: 2 ) tensorProduct: (hh at: 1 ) * (hh at: 2 ) * i).
796- i rows
797- withIndexDo: [ :aRow :index |
798- aRow
799- withIndexDo: [ :n :c |
800- r
801- rowAt: rank + index - 1
802- columnAt: rank + c - 1
803- put:
804- ((n equalsTo: 0 )
805- ifTrue: [ 0 ]
806- ifFalse: [ n ]) ] ].
807- rank + 1 to: lengthArray size do: [ :ind | lengthArray at: ind put: (lengthArray at: ind) - (r rowAt: rank columnAt: ind) squared ].
797+ i rows withIndexDo: [ :aRow :index |
798+ aRow withIndexDo: [ :n :c |
799+ r
800+ rowAt: rank + index - 1
801+ columnAt: rank + c - 1
802+ put: ((n closeTo: 0 )
803+ ifTrue: [ 0 ]
804+ ifFalse: [ n ]) ] ].
805+ rank + 1 to: lengthArray size do: [ :ind |
806+ lengthArray
807+ at: ind
808+ put: (lengthArray at: ind) - (r rowAt: rank columnAt: ind) squared ].
808809 rank < lengthArray size
809810 ifTrue: [
810811 mx := (lengthArray copyFrom: rank + 1 to: lengthArray size) max.
811- (mx equalsTo: 0 )
812- ifTrue: [ mx := 0 ].
812+ (mx closeTo: 0 ) ifTrue: [ mx := 0 ].
813813 mx := mx > 0
814- ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
815- ifFalse: [ 0 ] ]
814+ ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
815+ ifFalse: [ 0 ] ]
816816 ifFalse: [ mx := 0 ].
817817 mx > 0 ] whileTrue.
818818 i := 0 .
819- [ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ]
820- whileTrue: [
821- i := i + 1 .
822- colSize := colSize - 1 ].
823- i > 0
824- ifTrue: [
825- r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
826- i := q numberOfColumns - i.
827- pivot := pivot copyFrom: 1 to: i.
828- q := PMMatrix rows: (q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
819+ [ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ] whileTrue: [
820+ i := i + 1 .
821+ colSize := colSize - 1 ].
822+ i > 0 ifTrue: [
823+ r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
824+ i := q numberOfColumns - i.
825+ pivot := pivot copyFrom: 1 to: i.
826+ q := PMMatrix rows:
827+ (q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
829828 ^ Array with: q with: r with: pivot
830829]
831830
@@ -892,6 +891,12 @@ PMMatrix >> rowsDo: aBlock [
892891 ^ rows do: aBlock
893892]
894893
894+ { #category : #iterators }
895+ PMMatrix >> rowsWithIndexDo: aBlock [
896+
897+ ^ rows withIndexDo: aBlock
898+ ]
899+
895900{ #category : #transformation }
896901PMMatrix >> scaleBy: aNumber [
897902
0 commit comments