Skip to content

Commit

Permalink
Merge pull request #74 from PolyMathOrg/development
Browse files Browse the repository at this point in the history
Release v0.102
  • Loading branch information
SergeStinckwich committed Jul 24, 2018
2 parents 0af624f + f49c36c commit 4cd4776
Show file tree
Hide file tree
Showing 10 changed files with 654 additions and 26 deletions.
2 changes: 1 addition & 1 deletion README.md
Expand Up @@ -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,
Expand Down
3 changes: 2 additions & 1 deletion src/BaselineOfPolyMath/BaselineOfPolyMath.class.st
Expand Up @@ -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';
Expand Down Expand Up @@ -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') ]
]
Expand Down
5 changes: 5 additions & 0 deletions src/Math-Complex/PMComplex.class.st
Expand Up @@ -650,6 +650,11 @@ PMComplex >> sign [
^ real sign
]

{ #category : #testing }
PMComplex >> signBit [
^self real signBit
]

{ #category : #'mathematical functions' }
PMComplex >> sin [
"Answer receiver's sine."
Expand Down
14 changes: 7 additions & 7 deletions src/Math-Complex/PMComplex.extension.st
Expand Up @@ -17,20 +17,20 @@ 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."
^ self class random * self

]

{ #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
Expand Down
38 changes: 38 additions & 0 deletions 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') )
]
256 changes: 256 additions & 0 deletions 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
]

0 comments on commit 4cd4776

Please sign in to comment.