Skip to content

Commit d4e3c71

Browse files
committed
Replaced the calls to Number>>equalsTo: with closeTo:
1 parent 497c9f6 commit d4e3c71

File tree

23 files changed

+494
-484
lines changed

23 files changed

+494
-484
lines changed

src/Math-AutomaticDifferenciation/PMDualNumber.class.st

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -157,7 +157,9 @@ PMDualNumber >> eps: aNumber [
157157

158158
{ #category : #comparing }
159159
PMDualNumber >> equalsTo: aDualNumber [
160-
^ (value equalsTo: aDualNumber value) and: [ eps equalsTo: aDualNumber eps ]
160+
161+
^ (value closeTo: aDualNumber value) and: [
162+
eps closeTo: aDualNumber eps ]
161163
]
162164

163165
{ #category : #testing }

src/Math-AutomaticDifferenciation/PMHyperDualNumber.class.st

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -126,9 +126,10 @@ PMHyperDualNumber >> eps2: anEps2 [
126126

127127
{ #category : #comparing }
128128
PMHyperDualNumber >> equalsTo: aHyperDualNumber [
129-
^ (super equalsTo: aHyperDualNumber)
130-
and: [ (eps2 equalsTo: aHyperDualNumber eps2)
131-
and: [ eps1eps2 equalsTo: aHyperDualNumber eps1eps2 ] ]
129+
130+
^ (super equalsTo: aHyperDualNumber) and: [
131+
(eps2 closeTo: aHyperDualNumber eps2) and: [
132+
eps1eps2 closeTo: aHyperDualNumber eps1eps2 ] ]
132133
]
133134

134135
{ #category : #'mathematical functions' }

src/Math-Core/SequenceableCollection.extension.st

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,10 @@ Extension { #name : #SequenceableCollection }
33
{ #category : #'*Math-Core' }
44
SequenceableCollection >> equalsTo: aSequenceableCollection [
55

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

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: 63 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -746,35 +746,50 @@ PMMatrix >> productWithVector: aVector [
746746

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

773787
{ #category : #'as yet unclassified' }
774788
PMMatrix >> qrFactorizationWithPivoting [
789+
775790
| identMat q r hh colSize i lengthArray rank mx pivot |
776-
self numberOfRows < self numberOfColumns
777-
ifTrue: [ self error: 'numberOfRows<numberOfColumns' ].
791+
self numberOfRows < self numberOfColumns ifTrue: [
792+
self error: 'numberOfRows<numberOfColumns' ].
778793
lengthArray := self columnsCollect: [ :col | col * col ].
779794
mx := lengthArray indexOf: lengthArray max.
780795
pivot := Array new: lengthArray size.
@@ -791,41 +806,41 @@ PMMatrix >> qrFactorizationWithPivoting [
791806
hh := ((r columnAt: rank) copyFrom: rank to: colSize) householder.
792807
i := (PMVector new: rank - 1 withAll: 0) , (hh at: 2).
793808
q := q * (identMat - ((hh at: 1) * i tensorProduct: i)).
794-
i := PMMatrix rows: ((r rows allButFirst: rank - 1) collect: [ :aRow | aRow allButFirst: rank - 1 ]).
809+
i := PMMatrix rows:
810+
((r rows allButFirst: rank - 1) collect: [ :aRow |
811+
aRow allButFirst: rank - 1 ]).
795812
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 ].
813+
i rows withIndexDo: [ :aRow :index |
814+
aRow withIndexDo: [ :n :c |
815+
r
816+
rowAt: rank + index - 1
817+
columnAt: rank + c - 1
818+
put: ((n closeTo: 0)
819+
ifTrue: [ 0 ]
820+
ifFalse: [ n ]) ] ].
821+
rank + 1 to: lengthArray size do: [ :ind |
822+
lengthArray
823+
at: ind
824+
put: (lengthArray at: ind) - (r rowAt: rank columnAt: ind) squared ].
808825
rank < lengthArray size
809826
ifTrue: [
810827
mx := (lengthArray copyFrom: rank + 1 to: lengthArray size) max.
811-
(mx equalsTo: 0)
812-
ifTrue: [ mx := 0 ].
828+
(mx closeTo: 0) ifTrue: [ mx := 0 ].
813829
mx := mx > 0
814-
ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
815-
ifFalse: [ 0 ] ]
830+
ifTrue: [ lengthArray indexOf: mx startingAt: rank + 1 ]
831+
ifFalse: [ 0 ] ]
816832
ifFalse: [ mx := 0 ].
817833
mx > 0 ] whileTrue.
818834
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 ]) ].
835+
[ (r rowAt: colSize) allSatisfy: [ :n | n = 0 ] ] whileTrue: [
836+
i := i + 1.
837+
colSize := colSize - 1 ].
838+
i > 0 ifTrue: [
839+
r := PMMatrix rows: (r rows copyFrom: 1 to: colSize).
840+
i := q numberOfColumns - i.
841+
pivot := pivot copyFrom: 1 to: i.
842+
q := PMMatrix rows:
843+
(q rows collect: [ :row | row copyFrom: 1 to: i ]) ].
829844
^ Array with: q with: r with: pivot
830845
]
831846

src/Math-Tests-AutomaticDifferenciation/PMDualNumberTest.class.st

Lines changed: 25 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -52,20 +52,22 @@ PMDualNumberTest >> testAdd [
5252

5353
{ #category : #'tests-mathematical functions' }
5454
PMDualNumberTest >> testArcCos [
55+
5556
| a |
56-
self
57-
assert: (zero arcCos equalsTo: (PMDualNumber value: Float halfPi eps: -1)).
57+
self assert:
58+
(zero arcCos equalsTo: (PMDualNumber value: Float halfPi eps: -1)).
5859
a := (PMDualNumber value: -1.0 successor eps: 1) arcCos.
59-
self assert: (a value equalsTo: Float pi).
60+
self assert: (a value closeTo: Float pi).
6061
self assert: a eps < -1e6
6162
]
6263

6364
{ #category : #'tests-mathematical functions' }
6465
PMDualNumberTest >> testArcSin [
66+
6567
| a |
6668
self assert: zero arcSin equals: zero.
6769
a := (PMDualNumber value: 1.0 predecessor eps: 1) arcSin.
68-
self assert: (a value equalsTo: Float halfPi).
70+
self assert: (a value closeTo: Float halfPi).
6971
self assert: a eps > 1e6.
7072
a := (PMDualNumber value: -0.5 eps: 1) arcSin.
7173
self assert: a value equals: -0.5 arcSin.
@@ -74,11 +76,12 @@ PMDualNumberTest >> testArcSin [
7476

7577
{ #category : #'tests-mathematical functions' }
7678
PMDualNumberTest >> testArcTan [
79+
7780
self assertEquality: zero arcTan and: zero.
7881
self
7982
assertEquality: one negated arcTan
8083
and: (PMDualNumber value: -1 arcTan eps: -1 / 2).
81-
self assert: (three arcTan eps equalsTo: 0.1)
84+
self assert: (three arcTan eps closeTo: 0.1)
8285
]
8386

8487
{ #category : #test }
@@ -166,19 +169,20 @@ PMDualNumberTest >> testEqualsTo [
166169
self
167170
assert: (one equalsTo: (PMDualNumber value: 1.0000000001 eps: 1.0000000001)).
168171
self
169-
deny: (one equalsTo: (PMDualNumber value: 1.0000000001 eps: 1.0000001)).
172+
deny: (one equalsTo: (PMDualNumber value: 1.0000000001 eps: 1.001)).
170173
self
171-
deny: (one equalsTo: (PMDualNumber value: 1.0000001 eps: 1.0000000001)).
174+
deny: (one equalsTo: (PMDualNumber value: 1.001 eps: 1.0000000001)).
172175
self
173-
deny: (one equalsTo: (PMDualNumber value: 1.0000001 eps: 1.0000001))
176+
deny: (one equalsTo: (PMDualNumber value: 1.001 eps: 1.001))
174177
]
175178

176179
{ #category : #'tests-mathematical functions' }
177180
PMDualNumberTest >> testExp [
181+
178182
| a b |
179183
b := 3 exp.
180184
a := three exp.
181-
self assert: (a eps equalsTo: b).
185+
self assert: (a eps closeTo: b).
182186
self assert: a value equals: b.
183187
self assert: one equals: zero exp
184188
]
@@ -199,9 +203,10 @@ PMDualNumberTest >> testHash [
199203

200204
{ #category : #'tests-mathematical functions' }
201205
PMDualNumberTest >> testLn [
206+
202207
| a |
203208
a := three ln.
204-
self assert: (a eps equalsTo: 1 / 3).
209+
self assert: (a eps closeTo: 1 / 3).
205210
self assert: a value equals: 3 ln.
206211
self assert: one ln equals: zero
207212
]
@@ -247,25 +252,24 @@ PMDualNumberTest >> testPrintOn [
247252

248253
{ #category : #'tests-mathematical functions' }
249254
PMDualNumberTest >> testRaisedTo [
255+
250256
| a |
251257
self assertEquality: (three raisedTo: 2) and: three squared.
252258
self assertEquality: (three raisedTo: 0) and: onec.
253259
self
254260
assertEquality: (three + one raisedTo: 1 / 2)
255261
and: (PMDualNumber value: 2 eps: 1 / 2).
256-
self
257-
assert:
258-
((three + one raisedTo: 3 / 2)
259-
equalsTo: (PMDualNumber value: 8 eps: 6)).
262+
self assert: ((three + one raisedTo: 3 / 2) equalsTo:
263+
(PMDualNumber value: 8 eps: 6)).
260264
self assertEquality: (zero raisedTo: 1.4) and: zeroc.
261265
a := 2 raisedTo: three.
262-
self assert: (a value equalsTo: 8).
263-
self assert: (a eps equalsTo: 2 ln * (2 raisedTo: 3)).
266+
self assert: (a value closeTo: 8).
267+
self assert: (a eps closeTo: 2 ln * (2 raisedTo: 3)).
264268
self assertEquality: (1 raisedTo: three) and: onec.
265269
self assertEquality: (one raisedTo: one) and: one.
266270
a := three raisedTo: three.
267-
self assert: (a value equalsTo: 27).
268-
self assert: (a eps equalsTo: (3 raisedTo: 3) * (3 ln + 1))
271+
self assert: (a value closeTo: 27).
272+
self assert: (a eps closeTo: (3 raisedTo: 3) * (3 ln + 1))
269273
]
270274

271275
{ #category : #'tests-mathematical functions' }
@@ -349,14 +353,15 @@ PMDualNumberTest >> testSubtract [
349353

350354
{ #category : #'tests-mathematical functions' }
351355
PMDualNumberTest >> testTan [
356+
352357
| a b |
353358
a := three tan.
354359
self assert: a value equals: 3 tan.
355-
self assert: (a eps equalsTo: 3 tan squared + 1).
360+
self assert: (a eps closeTo: 3 tan squared + 1).
356361
b := Float halfPi - 0.000000000001.
357362
a := (PMDualNumber value: b eps: 1) tan.
358363
self assert: a value equals: b tan.
359-
self assert: (a eps equalsTo: b tan squared + 1)
364+
self assert: (a eps closeTo: b tan squared + 1)
360365
]
361366

362367
{ #category : #'tests-testing' }

0 commit comments

Comments
 (0)