Skip to content

Commit ad0cfc0

Browse files
authored
Merge pull request #272 from olekscode/267-Remove-equalsTo-because-it-is-closeTo-and-not-equalsTo
Fixed #267. Deprecated equalsTo: and changed all senders to use closeTo: instead
2 parents 98b8504 + 785482b commit ad0cfc0

39 files changed

+756
-714
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' }
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 }

src/Math-Matrix/PMMatrix.class.st

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

484484
{ #category : #'as yet unclassified' }
485485
PMMatrix >> equalsTo: aMatrix [
486-
self rows
487-
with: aMatrix rows
488-
do: [:a :b| (a equalsTo: b) ifFalse: [ ^false ] ].
489-
^ true
486+
487+
self
488+
deprecated: 'Use closeTo: instead'
489+
transformWith: '`@rec equalsTo: `@arg' -> '`@rec closeTo: `@arg'.
490+
491+
^ self closeTo: aMatrix
490492
]
491493

492494
{ #category : #'as yet unclassified' }
@@ -746,35 +748,50 @@ PMMatrix >> productWithVector: aVector [
746748

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

773789
{ #category : #'as yet unclassified' }
774790
PMMatrix >> qrFactorizationWithPivoting [
791+
775792
| identMat q r hh colSize i lengthArray rank mx pivot |
776-
self numberOfRows < self numberOfColumns
777-
ifTrue: [ self error: 'numberOfRows<numberOfColumns' ].
793+
self numberOfRows < self numberOfColumns ifTrue: [
794+
self error: 'numberOfRows<numberOfColumns' ].
778795
lengthArray := self columnsCollect: [ :col | col * col ].
779796
mx := lengthArray indexOf: lengthArray max.
780797
pivot := Array new: lengthArray size.
@@ -791,41 +808,41 @@ PMMatrix >> qrFactorizationWithPivoting [
791808
hh := ((r columnAt: rank) copyFrom: rank to: colSize) householder.
792809
i := (PMVector new: rank - 1 withAll: 0) , (hh at: 2).
793810
q := q * (identMat - ((hh at: 1) * i tensorProduct: i)).
794-
i := PMMatrix rows: ((r rows allButFirst: rank - 1) collect: [ :aRow | aRow allButFirst: rank - 1 ]).
811+
i := PMMatrix rows:
812+
((r rows allButFirst: rank - 1) collect: [ :aRow |
813+
aRow allButFirst: rank - 1 ]).
795814
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 ].
815+
i rows withIndexDo: [ :aRow :index |
816+
aRow withIndexDo: [ :n :c |
817+
r
818+
rowAt: rank + index - 1
819+
columnAt: rank + c - 1
820+
put: ((n closeTo: 0)
821+
ifTrue: [ 0 ]
822+
ifFalse: [ n ]) ] ].
823+
rank + 1 to: lengthArray size do: [ :ind |
824+
lengthArray
825+
at: ind
826+
put: (lengthArray at: ind) - (r rowAt: rank columnAt: ind) squared ].
808827
rank < lengthArray size
809828
ifTrue: [
810829
mx := (lengthArray copyFrom: rank + 1 to: lengthArray size) max.
811-
(mx equalsTo: 0)
812-
ifTrue: [ mx := 0 ].
830+
(mx closeTo: 0) ifTrue: [ mx := 0 ].
813831
mx := mx > 0
814-
ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
815-
ifFalse: [ 0 ] ]
832+
ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
833+
ifFalse: [ 0 ] ]
816834
ifFalse: [ mx := 0 ].
817835
mx > 0 ] whileTrue.
818836
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 ]) ].
837+
[ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ] whileTrue: [
838+
i := i + 1.
839+
colSize := colSize - 1 ].
840+
i > 0 ifTrue: [
841+
r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
842+
i := q numberOfColumns - i.
843+
pivot := pivot copyFrom: 1 to: i.
844+
q := PMMatrix rows:
845+
(q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
829846
^ Array with: q with: r with: pivot
830847
]
831848

src/Math-Numerical/Number.extension.st

Lines changed: 6 additions & 2 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' }

src/Math-Numerical/PMNewtonZeroFinder.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,7 @@ PMNewtonZeroFinder >> computeInitialValues [
4949
derivativeBlock isNil
5050
ifTrue: [ derivativeBlock := self defaultDerivativeBlock].
5151
n := 0.
52-
[ (derivativeBlock value: result) equalsTo: 0]
52+
[ (derivativeBlock value: result) closeTo: 0]
5353
whileTrue: [ n := n + 1.
5454
n > maximumIterations
5555
ifTrue: [ self error: 'Function''s derivative seems to be zero everywhere'].

src/Math-ODE/PMAB2Solver.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,7 @@ PMAB2Solver >> firstStepperClass [
3434
{ #category : #solving }
3535
PMAB2Solver >> lastStepPrevState: prevState endTime: endTime [
3636
"catch partial or full step at end"
37-
(lastTime equalsTo: endTime )
37+
(lastTime closeTo: endTime )
3838
ifFalse:
3939
[state := stepper
4040
lastStep: state

src/Math-ODE/PMAB3Solver.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ PMAB3Solver class >> stepperClass [
2121
{ #category : #'as yet unclassified' }
2222
PMAB3Solver >> lastStepPrevState: prevState prevPrevState: prevPrevState endTime: endTime [
2323
"catch partial or full step at end"
24-
(lastTime equalsTo: endTime )
24+
(lastTime closeTo: endTime )
2525
ifFalse:
2626
[state := stepper
2727
lastStep: state

src/Math-ODE/PMAB4Solver.class.st

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ PMAB4Solver class >> thirdStepperClass [
2121
{ #category : #'as yet unclassified' }
2222
PMAB4Solver >> lastStepPrevState: prevState prevPrevState: prevPrevState initState:initState endTime: endTime [
2323
"catch partial or full step at end"
24-
(lastTime equalsTo: endTime )
24+
(lastTime closeTo: endTime )
2525
ifFalse:
2626
[state := stepper
2727
lastStep: state

0 commit comments

Comments
 (0)