Skip to content

Commit 37577d1

Browse files
authored
Merge branch 'master' into 269-Remove-random-methods
2 parents 50ac44e + ad0cfc0 commit 37577d1

File tree

42 files changed

+767
-724
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

42 files changed

+767
-724
lines changed

src/Math-AutomaticDifferenciation/PMDualNumber.class.st

Lines changed: 13 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -133,6 +133,13 @@ PMDualNumber >> asInteger [
133133
^ value asInteger
134134
]
135135

136+
{ #category : #comparing }
137+
PMDualNumber >> closeTo: aDualNumber [
138+
139+
^ (value closeTo: aDualNumber value) and: [
140+
eps closeTo: aDualNumber eps ]
141+
]
142+
136143
{ #category : #'mathematical functions' }
137144
PMDualNumber >> conjugated [
138145
^ self class
@@ -157,7 +164,12 @@ PMDualNumber >> eps: aNumber [
157164

158165
{ #category : #comparing }
159166
PMDualNumber >> equalsTo: aDualNumber [
160-
^ (value equalsTo: aDualNumber value) and: [ eps equalsTo: aDualNumber eps ]
167+
168+
self
169+
deprecated: 'Use closeTo: instead'
170+
transformWith: '`@rec equalsTo: `@arg' -> '`@rec closeTo: `@arg'.
171+
172+
^ self closeTo: aDualNumber
161173
]
162174

163175
{ #category : #testing }

src/Math-AutomaticDifferenciation/PMHyperDualNumber.class.st

Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -96,6 +96,14 @@ PMHyperDualNumber >> arcTan [
9696
yourself
9797
]
9898

99+
{ #category : #comparing }
100+
PMHyperDualNumber >> closeTo: aHyperDualNumber [
101+
102+
^ (super closeTo: aHyperDualNumber) and: [
103+
(eps2 closeTo: aHyperDualNumber eps2) and: [
104+
eps1eps2 closeTo: aHyperDualNumber eps1eps2 ] ]
105+
]
106+
99107
{ #category : #'mathematical functions' }
100108
PMHyperDualNumber >> cos [
101109
^ super cos
@@ -126,9 +134,12 @@ PMHyperDualNumber >> eps2: anEps2 [
126134

127135
{ #category : #comparing }
128136
PMHyperDualNumber >> equalsTo: aHyperDualNumber [
129-
^ (super equalsTo: aHyperDualNumber)
130-
and: [ (eps2 equalsTo: aHyperDualNumber eps2)
131-
and: [ eps1eps2 equalsTo: aHyperDualNumber eps1eps2 ] ]
137+
138+
self
139+
deprecated: 'Use closeTo: instead'
140+
transformWith: '`@rec equalsTo: `@arg' -> '`@rec closeTo: `@arg'.
141+
142+
^ self closeTo: aHyperDualNumber
132143
]
133144

134145
{ #category : #'mathematical functions' }

src/Math-Numerical/Collection.extension.st renamed to src/Math-Core/Collection.extension.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
Extension { #name : #Collection }
22

3-
{ #category : #'*Math-Numerical' }
3+
{ #category : #'*Math-Core' }
44
Collection >> asPMVector [
55

66
| aVector index |

src/Math-Core/Number.extension.st

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,3 +11,9 @@ Number >> addWithVector: aVector [
1111
"Adds itself to each element of the vector"
1212
^ aVector collect: [ :each | each + self ]
1313
]
14+
15+
{ #category : #'*Math-Core' }
16+
Number >> productWithVector: aVector [
17+
"Answers a new vector product of the receiver with aVector."
18+
^aVector collect: [ :each | each * self]
19+
]
Lines changed: 14 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,20 @@
11
Extension { #name : #SequenceableCollection }
22

3+
{ #category : #'*Math-Core' }
4+
SequenceableCollection >> closeTo: aSequenceableCollection [
5+
6+
self
7+
with: aSequenceableCollection
8+
do: [ :a :b | (a closeTo: b) ifFalse: [ ^ false ] ].
9+
^ true
10+
]
11+
312
{ #category : #'*Math-Core' }
413
SequenceableCollection >> equalsTo: aSequenceableCollection [
14+
15+
self
16+
deprecated: 'Use closeTo: instead'
17+
transformWith: '`@rec equalsTo: `@arg' -> '`@rec closeTo: `@arg'.
518

6-
"^ self = aSequenceableCollection "
7-
self with: aSequenceableCollection do: [:a :b| (a equalsTo: b) ifFalse: [^false] ].
8-
^true
19+
^ self closeTo: aSequenceableCollection
920
]

src/Math-FunctionFit/PMFunctionFit.class.st

Lines changed: 7 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ fit result parameters . ---> #(1.9999999999999998 0.39999999999999863)
99
Class {
1010
#name : #PMFunctionFit,
1111
#superclass : #PMLeastSquareFit,
12-
#category : 'Math-FunctionFit'
12+
#category : #'Math-FunctionFit'
1313
}
1414

1515
{ #category : #creation }
@@ -78,9 +78,12 @@ PMFunctionFit >> parameters [
7878

7979
{ #category : #initialization }
8080
PMFunctionFit >> parameters: indexableCollection [
81-
indexableCollection do:[ :e|(e equalsTo: 0.0)ifTrue: [ self error:'parameters shouldnt be set to practically zero' ] ].
82-
result parameters: indexableCollection.
83-
self finalizeIterations .
81+
82+
indexableCollection do: [ :e |
83+
(e closeTo: 0.0) ifTrue: [
84+
self error: 'parameters shouldnt be set to practically zero' ] ].
85+
result parameters: indexableCollection.
86+
self finalizeIterations
8487
]
8588

8689
{ #category : #printing }
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
Extension { #name : #Number }
2+
3+
{ #category : #'*Math-Matrix' }
4+
Number >> productWithMatrix: aMatrix [
5+
^aMatrix class rows: (aMatrix rowsCollect: [:r| self productWithVector: r])
6+
]

src/Math-Matrix/PMMatrix.class.st

Lines changed: 69 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -485,10 +485,12 @@ PMMatrix >> elementwiseProductWithMatrix: aMatrix [
485485

486486
{ #category : #'as yet unclassified' }
487487
PMMatrix >> equalsTo: aMatrix [
488-
self rows
489-
with: aMatrix rows
490-
do: [:a :b| (a equalsTo: b) ifFalse: [ ^false ] ].
491-
^ true
488+
489+
self
490+
deprecated: 'Use closeTo: instead'
491+
transformWith: '`@rec equalsTo: `@arg' -> '`@rec closeTo: `@arg'.
492+
493+
^ self closeTo: aMatrix
492494
]
493495

494496
{ #category : #'as yet unclassified' }
@@ -748,35 +750,50 @@ PMMatrix >> productWithVector: aVector [
748750

749751
{ #category : #'as yet unclassified' }
750752
PMMatrix >> qrFactorization [
751-
|identMat q r hh colSize i|
752-
self numberOfRows < self numberOfColumns ifTrue:[ self error: 'numberOfRows<numberOfColumns' ].
753-
r :=PMMatrix rows: (rows deepCopy).
753+
754+
| identMat q r hh colSize i |
755+
self numberOfRows < self numberOfColumns ifTrue: [
756+
self error: 'numberOfRows<numberOfColumns' ].
757+
r := PMMatrix rows: rows deepCopy.
754758
colSize := self numberOfRows.
755-
q := PMSymmetricMatrix identity: colSize.
759+
q := PMSymmetricMatrix identity: colSize.
756760
identMat := q deepCopy.
757-
1 to: self numberOfColumns do: [:col|
761+
1 to: self numberOfColumns do: [ :col |
758762
hh := ((r columnAt: col) copyFrom: col to: colSize) householder.
759-
i := (PMVector new: col-1withAll: 0) , (hh at:2 ).
760-
q := q* (identMat - ((hh at: 1)*i tensorProduct: i ))."not really necessary, should be simplified"
761-
i := PMMatrix rows: ( (r rows allButFirst: (col -1)) collect: [:aRow| aRow allButFirst: (col -1)] ).
762-
i := i - ((hh at: 2) tensorProduct: ( (hh at: 1)*(hh at: 2)*i ) ) .
763-
i rows withIndexDo: [ :aRow :index |
764-
aRow withIndexDo: [ :n :c| r rowAt: (col + index -1) columnAt: (col +c -1) put: ((n equalsTo: 0) ifTrue: [0] ifFalse: [n] ) ] ] .
765-
"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" ].
766-
"r rows allButFirst withIndexDo: [:aRow :ri|1 to: (ri min: self numberOfColumns ) do: [:ci|aRow at: ci put:0 ] ] ""not necessary with equalsTo:0"
767-
i :=0.
768-
[(r rowAt: colSize) allSatisfy: [:n| n=0] ]whileTrue: [i :=i+1.colSize :=colSize -1].
769-
i>0 ifTrue: [ r :=PMMatrix rows: (r rows copyFrom: 1 to: colSize).
770-
i := q numberOfColumns - i.
771-
q := PMMatrix rows: ( q rows collect: [:row| row copyFrom: 1 to: i]) ].
772-
^Array with: q with: r
763+
i := (PMVector new: col - 1 withAll: 0) , (hh at: 2).
764+
q := q * (identMat - ((hh at: 1) * i tensorProduct: i)). "not really necessary, should be simplified"
765+
i := PMMatrix rows:
766+
((r rows allButFirst: col - 1) collect: [ :aRow |
767+
aRow allButFirst: col - 1 ]).
768+
i := i - ((hh at: 2) tensorProduct: (hh at: 1) * (hh at: 2) * i).
769+
i rows withIndexDo: [ :aRow :index |
770+
aRow withIndexDo: [ :n :c |
771+
r
772+
rowAt: col + index - 1
773+
columnAt: col + c - 1
774+
put: ((n closeTo: 0)
775+
ifTrue: [ 0 ]
776+
ifFalse: [ n ]) ] ]
777+
"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" ].
778+
"r rows allButFirst withIndexDo: [:aRow :ri|1 to: (ri min: self numberOfColumns ) do: [:ci|aRow at: ci put:0 ] ] ""not necessary with equalsTo:0"
779+
i := 0.
780+
[ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ] whileTrue: [
781+
i := i + 1.
782+
colSize := colSize - 1 ].
783+
i > 0 ifTrue: [
784+
r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
785+
i := q numberOfColumns - i.
786+
q := PMMatrix rows:
787+
(q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
788+
^ Array with: q with: r
773789
]
774790

775791
{ #category : #'as yet unclassified' }
776792
PMMatrix >> qrFactorizationWithPivoting [
793+
777794
| identMat q r hh colSize i lengthArray rank mx pivot |
778-
self numberOfRows < self numberOfColumns
779-
ifTrue: [ self error: 'numberOfRows<numberOfColumns' ].
795+
self numberOfRows < self numberOfColumns ifTrue: [
796+
self error: 'numberOfRows<numberOfColumns' ].
780797
lengthArray := self columnsCollect: [ :col | col * col ].
781798
mx := lengthArray indexOf: lengthArray max.
782799
pivot := Array new: lengthArray size.
@@ -793,41 +810,41 @@ PMMatrix >> qrFactorizationWithPivoting [
793810
hh := ((r columnAt: rank) copyFrom: rank to: colSize) householder.
794811
i := (PMVector new: rank - 1 withAll: 0) , (hh at: 2).
795812
q := q * (identMat - ((hh at: 1) * i tensorProduct: i)).
796-
i := PMMatrix rows: ((r rows allButFirst: rank - 1) collect: [ :aRow | aRow allButFirst: rank - 1 ]).
813+
i := PMMatrix rows:
814+
((r rows allButFirst: rank - 1) collect: [ :aRow |
815+
aRow allButFirst: rank - 1 ]).
797816
i := i - ((hh at: 2) tensorProduct: (hh at: 1) * (hh at: 2) * i).
798-
i rows
799-
withIndexDo: [ :aRow :index |
800-
aRow
801-
withIndexDo: [ :n :c |
802-
r
803-
rowAt: rank + index - 1
804-
columnAt: rank + c - 1
805-
put:
806-
((n equalsTo: 0)
807-
ifTrue: [ 0 ]
808-
ifFalse: [ n ]) ] ].
809-
rank + 1 to: lengthArray size do: [ :ind | lengthArray at: ind put: (lengthArray at: ind) - (r rowAt: rank columnAt: ind) squared ].
817+
i rows withIndexDo: [ :aRow :index |
818+
aRow withIndexDo: [ :n :c |
819+
r
820+
rowAt: rank + index - 1
821+
columnAt: rank + c - 1
822+
put: ((n closeTo: 0)
823+
ifTrue: [ 0 ]
824+
ifFalse: [ n ]) ] ].
825+
rank + 1 to: lengthArray size do: [ :ind |
826+
lengthArray
827+
at: ind
828+
put: (lengthArray at: ind) - (r rowAt: rank columnAt: ind) squared ].
810829
rank < lengthArray size
811830
ifTrue: [
812831
mx := (lengthArray copyFrom: rank + 1 to: lengthArray size) max.
813-
(mx equalsTo: 0)
814-
ifTrue: [ mx := 0 ].
832+
(mx closeTo: 0) ifTrue: [ mx := 0 ].
815833
mx := mx > 0
816-
ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
817-
ifFalse: [ 0 ] ]
834+
ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
835+
ifFalse: [ 0 ] ]
818836
ifFalse: [ mx := 0 ].
819837
mx > 0 ] whileTrue.
820838
i := 0.
821-
[ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ]
822-
whileTrue: [
823-
i := i + 1.
824-
colSize := colSize - 1 ].
825-
i > 0
826-
ifTrue: [
827-
r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
828-
i := q numberOfColumns - i.
829-
pivot := pivot copyFrom: 1 to: i.
830-
q := PMMatrix rows: (q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
839+
[ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ] whileTrue: [
840+
i := i + 1.
841+
colSize := colSize - 1 ].
842+
i > 0 ifTrue: [
843+
r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
844+
i := q numberOfColumns - i.
845+
pivot := pivot copyFrom: 1 to: i.
846+
q := PMMatrix rows:
847+
(q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
831848
^ Array with: q with: r with: pivot
832849
]
833850

src/Math-Numerical/Number.extension.st

Lines changed: 6 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,12 @@ Number >> dividingPolynomial: aPolynomial [
1919

2020
{ #category : #'*Math-Numerical' }
2121
Number >> equalsTo: aNumber [
22-
"compare to Float>>closeTo:"
23-
^self relativelyEqualsTo: aNumber upTo: PMFloatingPointMachine new defaultNumericalPrecision
22+
23+
self
24+
deprecated: 'Use closeTo: instead'
25+
transformWith: '`@rec equalsTo: `@arg' -> '`@rec closeTo: `@arg'.
26+
27+
^ self closeTo: aNumber
2428
]
2529

2630
{ #category : #'*Math-Numerical' }
@@ -58,17 +62,6 @@ Number >> logGamma [
5862
]
5963
]
6064

61-
{ #category : #'*Math-Numerical' }
62-
Number >> productWithMatrix: aMatrix [
63-
^aMatrix class rows: (aMatrix rowsCollect: [:r| self productWithVector: r])
64-
]
65-
66-
{ #category : #'*Math-Numerical' }
67-
Number >> productWithVector: aVector [
68-
"Answers a new vector product of the receiver with aVector."
69-
^aVector collect: [ :each | each * self]
70-
]
71-
7265
{ #category : #'*Math-Numerical' }
7366
Number >> relativelyEqualsTo: aNumber upTo: aSmallNumber [
7467
"compare to Float>>closeTo:

src/Math-Numerical/PMNewtonZeroFinder.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ PMNewtonZeroFinder >> computeInitialValues [
5151
n := 0.
5252
random := Random new.
5353

54-
[ (derivativeBlock value: result) equalsTo: 0] whileTrue: [
54+
[ (derivativeBlock value: result) closeTo: 0] whileTrue: [
5555
n := n + 1.
5656

5757
n > maximumIterations ifTrue: [

0 commit comments

Comments
 (0)