diff --git a/README.md b/README.md index e23f68610..efb045863 100644 --- a/README.md +++ b/README.md @@ -14,7 +14,7 @@ Metacello new load ``` -We have **744** green tests ! +We have **767** green tests ! PolyMath is a Smalltalk project, similar to existing scientific libraries like NumPy, SciPy for Python or SciRuby for Ruby. PolyMath already provide the following basic functionalities: - complex and quaternions extensions, diff --git a/src/BaselineOfPolyMath/BaselineOfPolyMath.class.st b/src/BaselineOfPolyMath/BaselineOfPolyMath.class.st index 2690af847..2e762cc74 100644 --- a/src/BaselineOfPolyMath/BaselineOfPolyMath.class.st +++ b/src/BaselineOfPolyMath/BaselineOfPolyMath.class.st @@ -53,6 +53,7 @@ BaselineOfPolyMath >> baseline: spec [ package: 'Math-Matrix'; package: 'Math-Number-Extensions'; package: 'Math-ODE' with: [ spec requires: #('Math-DHB-Numerical' 'Math-Matrix' 'Math-Polynomials') ]; + package: 'Math-Permutation' with:[ spec requires: #('Math-Core' 'Math-Matrix' 'Math-Core-Process') ]; package: 'Math-Physics-Constants'; package: 'Math-PrincipalComponentAnalysis' with: [ spec requires: #('Math-DHB-Numerical' 'Math-Matrix' 'Math-Polynomials') ]; package: 'Math-Quantile'; @@ -86,7 +87,7 @@ BaselineOfPolyMath >> baseline: spec [ group: 'Accuracy' with: #('Math-Accuracy-ODE' 'Math-Accuracy-Core'); group: 'Benchmarks' with: #('Math-Benchmarks-ODE' 'Math-Benchmarks-KDTree'); group: 'Core' with: #('Math-Complex' 'Math-Quaternion' 'Math-DHB-Numerical' 'Math-Random' 'Math-KDTree' 'Math-ODE' 'Math-ArbitraryPrecisionFloat' 'Math-FastFourierTransform' 'ExtendedNumberParser' 'Math-Quantile' 'Math-Physics-Constants' 'Math-Polynomials' 'Math-TSNE'); - group: 'Extensions' with: #('Math-Clustering' 'Math-Number-Extensions' 'Math-Chromosome' 'Math-PrincipalComponentAnalysis' 'Math-FunctionFit' 'Math-AutomaticDifferenciation' 'Math-KernelSmoothing' 'Math-RandomDistributionBased' 'Math-KolmogorovSmirnov'); + group: 'Extensions' with: #('Math-Clustering' 'Math-Number-Extensions' 'Math-Chromosome' 'Math-PrincipalComponentAnalysis' 'Math-FunctionFit' 'Math-AutomaticDifferenciation' 'Math-KernelSmoothing' 'Math-Permutation' 'Math-RandomDistributionBased' 'Math-KolmogorovSmirnov'); group: 'Tests' with: #('Math-Tests-Matrix' 'Math-Tests-Clustering' 'Math-Tests-DHB-Numerical' 'Math-Tests-Complex' 'Math-Tests-Quaternion' 'Math-Tests-Random' 'Math-Tests-ODE' 'Math-Tests-KDTree' 'Math-Tests-DHB-wk' 'Math-Tests-FunctionFit' 'Math-Tests-AutomaticDifferenciation' 'Math-Tests-FastFourierTransform' 'Math-Tests-Accuracy' 'Math-Tests-ArbitraryPrecisionFloat' 'Math-Tests-KolmogorovSmirnov' 'Math-Tests-Quantile' 'Math-Tests-Polynomials'); group: 'default' with: #('Core' 'Extensions' 'Tests' 'Benchmarks' 'Accuracy') ] ] diff --git a/src/Math-Complex/PMComplex.class.st b/src/Math-Complex/PMComplex.class.st index e61e6de12..edd8fc131 100644 --- a/src/Math-Complex/PMComplex.class.st +++ b/src/Math-Complex/PMComplex.class.st @@ -650,6 +650,11 @@ PMComplex >> sign [ ^ real sign ] +{ #category : #testing } +PMComplex >> signBit [ +^self real signBit +] + { #category : #'mathematical functions' } PMComplex >> sin [ "Answer receiver's sine." diff --git a/src/Math-Complex/PMComplex.extension.st b/src/Math-Complex/PMComplex.extension.st index e55dcb5cd..efe456833 100644 --- a/src/Math-Complex/PMComplex.extension.st +++ b/src/Math-Complex/PMComplex.extension.st @@ -17,6 +17,13 @@ PMComplex >> productWithVector: aVector [ ^ aVector collect: [ :each | each * self ] ] +{ #category : #'*Math-Complex' } +PMComplex class >> random [ + "Answers a random number with abs between 0 and 1." + + ^ self abs: 1.0 random arg: 2 * Float pi random +] + { #category : #'*Math-Complex' } PMComplex >> random [ "analog to Number>>random. However, the only bound is that the abs of the produced complex is less than the length of the receive. The receiver effectively defines a disc within which the random element can be produced." @@ -24,13 +31,6 @@ PMComplex >> random [ ] -{ #category : #'*Math-Complex' } -PMComplex classSide >> random [ - "Answers a random number with abs between 0 and 1." - - ^ self abs: 1.0 random arg: 2 * Float pi random -] - { #category : #'*Math-Complex' } PMComplex >> subtractToPolynomial: aPolynomial [ ^ aPolynomial addNumber: self negated diff --git a/src/Math-Permutation/ManifestMathPermutation.class.st b/src/Math-Permutation/ManifestMathPermutation.class.st new file mode 100644 index 000000000..e57bf5550 --- /dev/null +++ b/src/Math-Permutation/ManifestMathPermutation.class.st @@ -0,0 +1,38 @@ +" +I store metadata for this package. These meta data are used by other tools such as the SmalllintManifestChecker and the critics Browser +" +Class { + #name : #ManifestMathPermutation, + #superclass : #PackageManifest, + #category : #'Math-Permutation' +} + +{ #category : #'code-critics' } +ManifestMathPermutation class >> ruleRBCollectionProtocolRuleV1FalsePositive [ + ^ #(#(#(#RGMethodDefinition #(#'Permutation class' #generator: #true)) #'2018-07-07T11:52:50.239421+02:00') ) +] + +{ #category : #'code-critics' } +ManifestMathPermutation class >> ruleRBModifiesCollectionRuleV1FalsePositive [ + ^ #(#(#(#RGMethodDefinition #(#'Permutation class' #generator: #true)) #'2018-07-07T11:52:46.085547+02:00') ) +] + +{ #category : #'code-critics' } +ManifestMathPermutation class >> ruleRBSendsDifferentSuperRuleV1FalsePositive [ + ^ #(#(#(#RGMetaclassDefinition #(#'Permutation class' #PMPermutation)) #'2018-07-07T11:53:26.042043+02:00') ) +] + +{ #category : #'code-critics' } +ManifestMathPermutation class >> ruleRBSuperSendsRuleV1FalsePositive [ + ^ #(#(#(#RGMetaclassDefinition #(#'Permutation class' #PMPermutation)) #'2018-07-07T11:53:19.542428+02:00') ) +] + +{ #category : #'code-critics' } +ManifestMathPermutation class >> ruleRBTempsReadBeforeWrittenRuleV1FalsePositive [ + ^ #(#(#(#RGMethodDefinition #(#'Permutation class' #stirling1:over: #true)) #'2018-07-07T11:54:16.87423+02:00') ) +] + +{ #category : #'code-critics' } +ManifestMathPermutation class >> ruleRBToDoRuleV1FalsePositive [ + ^ #(#(#(#RGMetaclassDefinition #(#'Permutation class' #PMPermutation)) #'2018-07-07T11:54:04.307575+02:00') ) +] diff --git a/src/Math-Permutation/PMPermutation.class.st b/src/Math-Permutation/PMPermutation.class.st new file mode 100644 index 000000000..f9cc7c69e --- /dev/null +++ b/src/Math-Permutation/PMPermutation.class.st @@ -0,0 +1,256 @@ +" +Permutation is an Array, that - if it's reduced - consists of the numbers from (1 to: self size) in the original order. +example: +Permutation ordering: #(5 4 1). -> a Permutation(3 2 1) + +you can think of a permutation as a positioning specification for a SequentialCollection. +another example: +a:=Permutation randomPermutation: 4. -> a Permutation(1 4 2 3) +a permute: #(a b cd e). -> #(#a #e #b #cd) +yet another one: +Permutation ordering: #(a e b cd). ""a Permutation(1 4 2 3)"" + + +" +Class { + #name : #PMPermutation, + #superclass : #Array, + #type : #variable, + #classVars : [ + 'RandomGenerator' + ], + #category : #'Math-Permutation' +} + +{ #category : #accessing } +PMPermutation class >> allOfSize: anInteger [ +"generates all permutations of the given size, in other words it produces the symmetric group of degree anInteger. +Heap's algorithm, used here, seems to be just a tiny bit faster than using #permutationsDo:" + | result perm c i ci| + anInteger = 0 ifTrue:[^#()]. + perm := self identity: anInteger. + (result := WriteStream on:(Array new: anInteger factorial)) nextPut: perm copy. + c := Array new: anInteger withAll: 1. + i := 1. + [ i <= anInteger ] + whileTrue: [ + (ci :=(c at: i)) < i + ifTrue: [ + i odd + ifTrue: [ perm swap: 1 with: i ] + ifFalse: [ perm swap: ci with: i ]. + result nextPut: perm copy. + c at: i put: ci + 1. + i := 1 ] + ifFalse: [ c at: i put: 1. i := i + 1 ] ]. + ^ result contents +] + +{ #category : #'instance creation' } +PMPermutation class >> fromCycles: aCollectionofCollections [ + | length | + length := aCollectionofCollections flattened. + length := length isEmpty + ifTrue: [ 0 ] + ifFalse: [ length max ]. + ^ self size: length fromCycles: aCollectionofCollections +] + +{ #category : #accessing } +PMPermutation class >> generator:arrayOfPermutations [ +|f max generators| +max:=(arrayOfPermutations collect:[:g|g size])max. +generators:=arrayOfPermutations collect:[:g| g extendTo: max]. +f:=PMFixpoint + block: [ :s| |aSet| + aSet:=Set newFrom: s. + s do:[:p|s do:[:q| + aSet add:(p permute:q)]]. + aSet] + value: generators. +f verbose:false. +^f evaluate asArray. + +] + +{ #category : #'instance creation' } +PMPermutation class >> identity: size [ +^ super withAll: (1 to: size) +] + +{ #category : #'instance creation' } +PMPermutation class >> newFrom: aCollection [ +"returns the unreduced form, for a reduced form use #ordering:. +uses super withAll: since this way a primitive can be used, which is generally much faster than super newFrom:" +^( super withAll: aCollection ) +] + +{ #category : #'instance creation' } +PMPermutation class >> ordering: aCollection [ +"use #newFrom: for an unreduced Permutation! but then most things won't work before you call #reduce. +aCollection must consist of elements that can be sorted via #<=" +^( super withAll: aCollection ) reduce +] + +{ #category : #accessing } +PMPermutation class >> randomGenerator [ +^RandomGenerator ifNil: [ RandomGenerator := Random new ] +] + +{ #category : #'instance creation' } +PMPermutation class >> randomPermutation: size [ +^self ordering: (self randomGenerator next:size) +] + +{ #category : #'instance creation' } +PMPermutation class >> size: anInteger fromCycles: aCollectionofCollections [ + | result | + result := self identity: anInteger. + aCollectionofCollections do: [ :cycle | + 1 to: cycle size do: [ :i | + result at: (cycle at: i) put: (cycle atWrap: i + 1) ] ]. + ^ result +] + +{ #category : #'instance creation' } +PMPermutation class >> size: size shift: aNumber [ +"number positive -> leftshift, negative -> rightshift" +^ (super withAll: (1 to: size) )shift: aNumber +] + +{ #category : #accessing } +PMPermutation class >> stirling1:anInteger over:anotherInteger [ +"unsigned Stirling number of the first kind: the number of permutations of size anInteger with anotherInteger number of cycles" +|block| +block:=[:nandk||n k| + n:=nandk first. + k:=nandk second. + (n=k and:[n isZero]) + ifTrue:[1] + ifFalse:[ (n * k) isZero + ifTrue:[0] + ifFalse:[ (block value:{n-1.k-1})+((n-1)*(block value:{n-1.k}))]]]memoized . +^block value:{anInteger . anotherInteger } +] + +{ #category : #converting } +PMPermutation >> asCycles [ + | unused start next result cycle | + unused := (1 to: self size) asOrderedCollection. + result := OrderedCollection new. + [ unused isEmpty ] + whileFalse: [ + next := start := unused first. + cycle := OrderedCollection new. + [ cycle add: (unused remove: next). + next := self at: next ] doWhileFalse: [ next = start ]. + result add: cycle asArray ]. + ^ result asArray +] + +{ #category : #converting } +PMPermutation >> asMatrix [ + ^ PMMatrix + rows: + (self asPMVector + collect: [ :n | + (PMVector new: self size) + atAllPut: 0; + at: n put: 1; + yourself ]) +] + +{ #category : #applying } +PMPermutation >> discriminant [ +^self size - self asCycles size +] + +{ #category : #testing } +PMPermutation >> even [ +^self odd not +] + +{ #category : #applying } +PMPermutation >> extendTo: size [ + | c | + size=self size ifTrue: [ ^self copy ]. + c := self class identity: size. + c + replaceFrom: 1 + to: self size + with: self + startingAt: 1. + ^ c +] + +{ #category : #applying } +PMPermutation >> inverse [ +|c| +c:=self class new:self size. +1 to: self size do: [:i | c at: i put: (self indexOf: i)]. +^c +] + +{ #category : #testing } +PMPermutation >> isCollection [ +"pffh, i found this useful, but i dont remember anymore why." + ^ false +] + +{ #category : #testing } +PMPermutation >> odd [ +"using the number of transpositions is faster than using the number of inversions" +^self discriminant odd. +] + +{ #category : #applying } +PMPermutation >> permute: aSequentialCollection [ + | s c | + (s := aSequentialCollection size) < self size + ifTrue: [ aSequentialCollection class==self class + ifTrue: [ ^ self permute: (aSequentialCollection extendTo: self size) ] + ifFalse: [ ^ SizeMismatch signal ] ]. + c := aSequentialCollection copy. + 1 to: self size do: [ :i | c at: i put: (aSequentialCollection at: (self at: i)) ]. + ^ c +] + +{ #category : #private } +PMPermutation >> reduce [ +"automatically used only in #withAll: so far" + | sorted range | + (sorted := self sorted) = (range := 1 to: self size) + ifTrue: [ ^ self ]. + self size = self asSet size + ifFalse: [ ^ self error: 'Permutation has doubles' ]. + range do: [ :n | self at: n put: (sorted indexOf: (self at: n)) ] +] + +{ #category : #converting } +PMPermutation >> reversed [ + "copy of SequenceableCollection>>reversed, but uses class instead of species." + | n result src | + n := self size. + result := self class new: n. + src := n + 1. + 1 to: n do: [:i | result at: i put: (self at: (src := src - 1))]. + ^ result +] + +{ #category : #converting } +PMPermutation >> shift: anInteger [ +"number positive -> leftshift, negative -> rightshift. + does _not_ return a new Permutation!" + | n c | + self ifEmpty: [ ^ self ]. + n := anInteger \\ self size. + c := self copy. + self + replaceFrom: 1 to: self size - n with: c startingAt: n + 1; + replaceFrom: self size - n + 1 to: self size with: c startingAt: 1 +] + +{ #category : #private } +PMPermutation >> species [ + ^ Array +] diff --git a/src/Math-Permutation/PMPermutationTest.class.st b/src/Math-Permutation/PMPermutationTest.class.st new file mode 100644 index 000000000..95b42f8c9 --- /dev/null +++ b/src/Math-Permutation/PMPermutationTest.class.st @@ -0,0 +1,312 @@ +Class { + #name : #PMPermutationTest, + #superclass : #TestCase, + #category : #'Math-Permutation' +} + +{ #category : #'class tests' } +PMPermutationTest >> testAllOfSize [ + | p "i w" | + "special" + self assert: (PMPermutation allOfSize: 0) equals: #(). + self + assert: (PMPermutation allOfSize: 1) + equals: {(PMPermutation identity: 1)}. + "odd" + p := PMPermutation allOfSize: 3. + self assert: p size equals: 3 factorial. + self assert: p asSet size equals: 3 factorial. + p + do: [ :per | + self assert: per size equals: 3. + self assert: per class == PMPermutation ]. + "even" + p := PMPermutation allOfSize: 4. + self assert: p size equals: 4 factorial. + self assert: p asSet size equals: 4 factorial. + p + do: [ :per | + "the following speed-test is indeed randomized and will occasionally fail!therefore it is put into comments, but it is important nevertheless, as, if this last #assert: is not true mostly, one can simplify #allOfSize: this way: +Permutation class>>allOfSize:anInteger + |result| + (result := WriteStream on:(Array new: anInteger factorial)). + (Permutation identity: anInteger) permutationsDo: [:p|result nextPut: p copy]. + ^result contents" + "Smalltalk garbageCollect. Smalltalk garbageCollect. +i := [Permutation allOfSize: 9] timeToRun. +w:=WriteStream on: ( Array new: 9 factorial ). +Smalltalk garbageCollect. Smalltalk garbageCollect. +p := [(Permutation identity: 9) permutationsDo: [:each | w nextPut: each copy]] timeToRun. +w:=nil. +self assert: i < p." + self assert: per size equals: 4. + self assert: per class == PMPermutation ] +] + +{ #category : #tests } +PMPermutationTest >> testAsCycles [ + self assert: PMPermutation new asCycles isEmpty. + self assert: (PMPermutation identity: 1) asCycles equals: #((1)). + self assert: (PMPermutation identity: 3) asCycles equals: #((1)(2)(3)). + self assert: (PMPermutation ordering: #(3 1 4 2)) asCycles equals: #((1 3 4 2)). + self assert: (PMPermutation ordering: #(2 4 3 6 7 8 5 1)) asCycles equals: #((1 2 4 6 8)(3)(5 7)). + self assert: (PMPermutation ordering: #(5 4 2 3 1)) asCycles equals: #((1 5)(2 4 3)). + self assert: (PMPermutation ordering: #(1 2 5 3 4 6)) asCycles equals: #((1)(2)(3 5 4)(6)). + +] + +{ #category : #tests } +PMPermutationTest >> testAsMatrix [ +|p| +p:=(PMPermutation newFrom: #(4 2 5 3 1)). +self assert: p asMatrix * (PMPermutation identity: 5)asPMVector + equals: p asPMVector. +self assert: p inverse asMatrix * p asPMVector + equals: (PMPermutation identity: 5) asPMVector . +] + +{ #category : #tests } +PMPermutationTest >> testDiscriminant [ + +self assert: PMPermutation new discriminant equals:0. +self assert: (PMPermutation identity: 1) discriminant equals:0. +self assert: (PMPermutation identity: 4) discriminant equals:0. +self assert: (PMPermutation ordering: #(2 1 4 3)) discriminant equals:2. +self assert: (PMPermutation ordering: #(5 3 2 4 1)) discriminant equals:2. +self assert: (PMPermutation ordering: #(3 5 2 1 6 4)) discriminant equals:5. +self assert: (PMPermutation ordering: #(4 3 1 2 6 7 5)) discriminant equals:5. + +] + +{ #category : #tests } +PMPermutationTest >> testEvenOdd [ +|a| +self assert: PMPermutation new even. +self assert: (PMPermutation identity: 1) even. +self deny: (PMPermutation identity: 4) odd. +self assert: (PMPermutation ordering: #(2 1 4 3)) even. +self deny: (PMPermutation ordering: #(5 3 2 4 1)) odd. +self assert: (PMPermutation ordering: #(3 5 2 1 6 4)) odd. +self deny: (PMPermutation ordering: #(4 3 1 2 6 7 5)) even. +a:=PMPermutation allOfSize: 4. +self assert: (a select:[:b|b odd])size equals:12. +a:=PMPermutation allOfSize: 3. +self assert: (a select:[:b|b even])size equals:3. +] + +{ #category : #tests } +PMPermutationTest >> testExtendTo [ + self assert: (PMPermutation new extendTo: 3)equals: (PMPermutation identity: 3). + self assert: ((PMPermutation identity: 1)extendTo: 3) equals: (PMPermutation identity: 3). + self assert: ((PMPermutation identity: 3)extendTo: 3) equals: (PMPermutation identity: 3). + self assert: ((PMPermutation ordering: #(3 1 4 2))extendTo: 4) equals: #(3 1 4 2). + self assert: ((PMPermutation ordering: #(3 1 4 2))extendTo: 5) equals: #(3 1 4 2 5). + self assert: ((PMPermutation ordering: #(3 1 4 2))extendTo: 7) equals: #(3 1 4 2 5 6 7). + +] + +{ #category : #'class tests' } +PMPermutationTest >> testFromCycles [ + self assert: (PMPermutation fromCycles: #()) isEmpty. + self assert: (PMPermutation fromCycles: #(#())) isEmpty. + self assert: (PMPermutation fromCycles: #(#(1))) equals: #(1). + self assert: (PMPermutation size: 3 fromCycles: #()) equals: #(1 2 3). + self assert: (PMPermutation size: 3 fromCycles: #(#())) equals: #(1 2 3). + self assert: (PMPermutation fromCycles: #(#(1 3 4 2))) equals: #(3 1 4 2). + self assert: (PMPermutation fromCycles: #(#(1 2 4 6 8) #(5 7))) equals: #(2 4 3 6 7 8 5 1). + self assert: (PMPermutation fromCycles: #(#(1 5) #(2 4 3))) equals: #(5 4 2 3 1). + self assert: (PMPermutation fromCycles: #(#(1) #(3 5 4) #(6) #(2))) equals: #(1 2 5 3 4 6). + self assert: (PMPermutation size: 6 fromCycles: #(#(3 5 4))) equals: #(1 2 5 3 4 6) +] + +{ #category : #'class tests' } +PMPermutationTest >> testGenerator [ +|g c| +g:=PMPermutation generator: {PMPermutation size: 7 shift: 2}. +g do:[:p|self assert: p class equals:PMPermutation]. +self assert: g size equals: 7. +self assert: (g includes: (PMPermutation identity: 7)) . +g:=PMPermutation generator: {PMPermutation size: 6 shift: 2. (PMPermutation identity: 6)reverse}. +self assert: g size equals: 6. +self assert: (g includes: (PMPermutation identity: 6)) . + +g:=PMPermutation generator: { PMPermutation fromCycles: #((2 3 4 5)).PMPermutation fromCycles: #((1 2))}. +c:=(PMPermutation allOfSize: 5). +self assert: g asSet equals: c asSet. +self assert: g size equals: c size. +g:=PMPermutation generator: { PMPermutation fromCycles: #((3 4 5)).PMPermutation fromCycles: #((1 2 3))}. +c:=c select:[:p|p even]. +self assert: g asSet equals: c asSet. +self assert: g size equals: c size. +] + +{ #category : #'class tests' } +PMPermutationTest >> testIdentity [ +|p c| +p:=PMPermutation identity: 0. +self assert: p equals: #(). +p:=PMPermutation identity: 1. +self assert: p equals: #(1). +p:=PMPermutation identity: 4. +c:=PMPermutation ordering: #(1 3 2 4). +self assert: (p permute: c) equals: c. +self assert: (c permute: p) equals: c. +] + +{ #category : #tests } +PMPermutationTest >> testInverse [ +|p| +p:=PMPermutation ordering: #(2 4 3 1 5). +self assert: (p inverse permute: p ) + equals: (1 to:5 ). +self assert: (p permute: p inverse) + equals: (1 to:5 ). +] + +{ #category : #tests } +PMPermutationTest >> testIsCollection [ +|p| +5 timesRepeat: [p:=PMPermutation randomPermutation: 11.self deny: p isCollection ]. + +] + +{ #category : #'class tests' } +PMPermutationTest >> testOrdering [ +|p| +self should:[PMPermutation ordering: #(2 3 3 1)]raise: Error. +p:=PMPermutation ordering: #(). +self assert: p equals: #(). +p:=PMPermutation ordering: #(4 3 -1.9). +self assert: p equals: #(3 2 1). +p:=PMPermutation ordering: #(cc cs b). +self assert: p equals: #(2 3 1). +p:=PMPermutation newFrom: #(cc cs b). +self assert: p class equals: PMPermutation. +self assert: p first equals: #cc. +self assert: p third equals: #b. +p reduce. +self assert: p equals: #(2 3 1). + +] + +{ #category : #tests } +PMPermutationTest >> testPermute [ +|p i| +p:=PMPermutation ordering: #(2 4 3 1). +i:=PMPermutation identity: 4. +self assert: (p permute: #(10 20 30 '40' 5.6)asOrderedCollection ) + equals: #(20 '40' 30 10 5.6)asOrderedCollection . +self assert: (p permute: 'abcD') + equals: 'bDca' . +self assert: (p permute: i) + equals: p . +self assert: (i permute: p) + equals: p . +self assert: (PMPermutation new permute: p) + equals: p . +self assert: (p permute: PMPermutation new) + equals: p . +self assert: (p permute: (PMPermutation fromCycles: #((1 3)))) + equals: ((PMPermutation fromCycles: #((4 3))) permute: p) . +i:=PMPermutation ordering: #(4 1 2 3). +self assert: (p permute: (i permute: 'aBcD')) + equals: ((p permute: i) permute: 'aBcD') . +self should: [ i permute:'aBc' ] raise: SizeMismatch . +"and i would say:" +self should: [ (PMPermutation identity: 4) permute:'aBc' ] raise: SizeMismatch . + +] + +{ #category : #'class tests' } +PMPermutationTest >> testRandomGenerator [ +|g| +g:=PMPermutation randomGenerator . +g:=g next:4. +self assert: g size equals: 4. +self deny: g first = g second. +self assert: g third isFloat. + +] + +{ #category : #'class tests' } +PMPermutationTest >> testRandomPermutation [ +|p p2 l| +l:=173."relatively high for a randomized test" +PMPermutation randomGenerator seed:10. "can be put into comments for a randomized test" +p:=PMPermutation randomPermutation: l. +p2:=PMPermutation randomPermutation: l. +self deny: p=p2. +self assert: p class equals: PMPermutation. +l:=1 to: l. +self assert: p sorted equals: l. +self assert: p2 sorted equals: l. + +] + +{ #category : #tests } +PMPermutationTest >> testReduce [ +|p| +p:=PMPermutation newFrom: #(2 3 1). +self assert: p reduce equals: #(2 3 1). +p:=PMPermutation newFrom: #(3 5 2). +self assert: p equals: #(3 5 2). +p reduce. +self assert: p equals: #(2 3 1). +p:=PMPermutation newFrom: #(). +self assert: p reduce equals: #(). +p:=PMPermutation newFrom: #(0.8). +self assert: p reduce equals: #(1). +] + +{ #category : #tests } +PMPermutationTest >> testReversed [ +|p| +p:=PMPermutation ordering: #(2 4 3 1 5). +self assert: (p reversed ) + equals: #(5 1 3 4 2). +self assert: (p class) + equals: PMPermutation . +] + +{ #category : #tests } +PMPermutationTest >> testShift [ +|p| +self assert: (p:=PMPermutation size: 4 shift: 1) equals: #(2 3 4 1). +self assert: (p shift: 0) equals: #(2 3 4 1). +self assert: (p shift: -1) equals: #(1 2 3 4). +self assert: (p shift: -8) equals: #(1 2 3 4). +self assert: (p shift: 4) equals: #(1 2 3 4). +self assert: (p shift: 2) equals: #(3 4 1 2). +self assert: (PMPermutation size: 5 shift: 2) equals: #(3 4 5 1 2). +self assert: (PMPermutation size: 4 shift: 3) equals: (p shift: 1). +self assert: (PMPermutation size: 4 shift: 4) equals: #(1 2 3 4). +self assert: (PMPermutation size: 4 shift: -1) equals: #(4 1 2 3). +self assert: (PMPermutation size: 5 shift: -2) equals: #(4 5 1 2 3). +self assert: (PMPermutation size: 1 shift: 1) equals: #(1). +self assert: (PMPermutation size: 0 shift: 2) equals: #(). +p:=PMPermutation randomPermutation: 6. +self assert: (p shift: -8) equals: (p shift:4). +] + +{ #category : #'class tests' } +PMPermutationTest >> testSizeShift [ +|p | +p:=PMPermutation size: 0 shift: 1. +self assert: p equals: #(). +p:=PMPermutation size: 1 shift: -1. +self assert: p equals: #(1). +p:=PMPermutation size: 4 shift: -1. +self assert: p equals: (PMPermutation ordering:#(4 1 2 3)). +p:=PMPermutation size: 4 shift: 2. +self assert: p equals: (PMPermutation ordering:#(3 4 1 2)). +] + +{ #category : #'class tests' } +PMPermutationTest >> testStirling1Over [ +self assert: (PMPermutation stirling1: 5 over: 5) equals: 1. +self assert: (PMPermutation stirling1: 5 over: 3) equals: 35. +self assert: (PMPermutation stirling1: 5 over: 2) equals: 50. +self assert: (PMPermutation stirling1: 5 over: 1) equals: 24. +self assert: (PMPermutation stirling1: 5 over: 0) equals: 0. +self assert: (PMPermutation stirling1: 0 over: 5) equals: 0. +] diff --git a/src/Math-Permutation/package.st b/src/Math-Permutation/package.st new file mode 100644 index 000000000..b1f1483f3 --- /dev/null +++ b/src/Math-Permutation/package.st @@ -0,0 +1 @@ +Package { #name : #'Math-Permutation' } diff --git a/src/Math-Tests-ArbitraryPrecisionFloat/ArbitraryPrecisionFloatTest.class.st b/src/Math-Tests-ArbitraryPrecisionFloat/ArbitraryPrecisionFloatTest.class.st index 17a9aeea7..c92a8b8f4 100644 --- a/src/Math-Tests-ArbitraryPrecisionFloat/ArbitraryPrecisionFloatTest.class.st +++ b/src/Math-Tests-ArbitraryPrecisionFloat/ArbitraryPrecisionFloatTest.class.st @@ -16,6 +16,11 @@ Class { #category : 'Math-Tests-ArbitraryPrecisionFloat' } +{ #category : #accessing } +ArbitraryPrecisionFloatTest class >> defaultTimeLimit [ +^ 120 seconds +] + { #category : #private } ArbitraryPrecisionFloatTest >> checkDoublePrecision: y forFunction: func nBits: n [ "Check that doubling the precision, then rounding would lead to the same result" @@ -645,27 +650,37 @@ ArbitraryPrecisionFloatTest >> testPositive [ { #category : #'testing-converting' } ArbitraryPrecisionFloatTest >> testPrintAndEvaluate [ - + "seconds" + + | emax emin leadingOne significands | - significands := 0 to: 1<<10-1. - leadingOne := 1<<10. + significands := 0 to: (1 << 10) - 1. + leadingOne := 1 << 10. emin := -14. emax := 15. - + "Test all normal finite half precision float" - emin to: emax do: [:e | - significands do: [:s | - | f | - f := (leadingOne + s asArbitraryPrecisionFloatNumBits: 11) timesTwoPower: e - 10. - self assert: (Compiler evaluate: f storeString) = f. - self assert: (Compiler evaluate: f printString) = f.]]. - + emin to: emax do: [ :e | + significands + do: [ :s | + | f | + f := (leadingOne + s asArbitraryPrecisionFloatNumBits: 11) + timesTwoPower: e - 10. + self + assert: (Smalltalk compiler evaluate: f storeString) + equals: f. + self + assert: (Smalltalk compiler evaluate: f printString) + equals: f ] ]. + "Test all subnormal finite half precision float" - significands do: [:s | - | f | - f := (s asArbitraryPrecisionFloatNumBits: s highBit) timesTwoPower: emin - 10. - self assert: (Compiler evaluate: f storeString) = f. - self assert: (Compiler evaluate: f printString) = f]. + significands + do: [ :s | + | f | + f := (s asArbitraryPrecisionFloatNumBits: s highBit) + timesTwoPower: emin - 10. + self assert: (Smalltalk compiler evaluate: f storeString) equals: f. + self assert: (Smalltalk compiler evaluate: f printString) equals: f ] ] { #category : #'testing-arithmetic' } diff --git a/src/Math-Tests-AutomaticDifferenciation/DualNumberTest.class.st b/src/Math-Tests-AutomaticDifferenciation/DualNumberTest.class.st index d739fdb7b..e2dc75af6 100644 --- a/src/Math-Tests-AutomaticDifferenciation/DualNumberTest.class.st +++ b/src/Math-Tests-AutomaticDifferenciation/DualNumberTest.class.st @@ -216,7 +216,7 @@ DualNumberTest >> testRaisedTo [ self assertEquality: (three raisedTo: 2) and: three squared. self assertEquality: (three raisedTo: 0) and: onec. self assertEquality: ((three + one) raisedTo: 1/2) and: (PMDualNumber value: 2 eps: (1/2)). -self assertEquality: ((three + one) raisedTo: 3/2) and: (PMDualNumber value: 8 eps: 6). +self assert: (((three + one) raisedTo: 3/2) equalsTo: (PMDualNumber value: 8 eps: 6)). self assertEquality: (zero raisedTo: 1.4)and:zeroc. a:=2 raisedTo: three. self assert: ((a value)equalsTo: 8) .