'From Squeak 2.2 of Sept 23, 1998 on 7 October 1998 at 4:38:11 am'! Object subclass: #Complex instanceVariableNames: 'real imaginary ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Kernel'! Object subclass: #DirectProduct instanceVariableNames: 'contents ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #GSpace instanceVariableNames: 'group space actionBlock ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! GSpace subclass: #GSpaceByConjugation instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! GSpace subclass: #GSpaceByTranslation instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #GroupAdditiveElement instanceVariableNames: 'element ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #GroupCompositiveElement instanceVariableNames: 'element ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #Homomorphism instanceVariableNames: 'domain codomain map ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Magnitude subclass: #Infinity instanceVariableNames: 'sign ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Kernel'! Object subclass: #IntegerMod instanceVariableNames: 'representative modulo ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Kernel'! Object subclass: #Permutation instanceVariableNames: 'map ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Permutation subclass: #PermutationCycle instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #Quaternion instanceVariableNames: 'a b c d ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Kernel'! Object subclass: #RootOfUnity instanceVariableNames: 'modular ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #SemidirectProduct instanceVariableNames: 'left right action ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #Subgroup instanceVariableNames: 'elements ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #TowerOfSubgroups instanceVariableNames: 'subgroups ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! Object subclass: #TranslatedSubgroup instanceVariableNames: 'subgroup translation ' classVariableNames: '' poolDictionaries: '' category: 'Mathematics-Groups'! !Object methodsFor: 'testing' stamp: 'len 2/25/98 22:13'! isComplex "Answer true if the receiver is a Complex." ^ false! ! !Object methodsFor: 'testing' stamp: 'len 1/13/98 21:18'! isFraction "Answer true if the receiver is a Fraction." ^ false! ! !Object methodsFor: 'testing' stamp: 'len 12/13/97 02:25'! isInfinity "Answer true if the receiver is infinity." ^ false! ! !Object methodsFor: 'testing' stamp: 'len 2/25/98 03:17'! isQuaternion "Answer true if the receiver is a Quaternion." ^ false! ! !Collection methodsFor: 'accessing'! anElement self do: [ :any | ^any]. ^nil! ! !Complex commentStamp: '' prior: 0! My instances are complex numbers. For instance, the complex number '2 + 3i' can be created doing: Complex real: 2 imaginary: 3. Furthermore, Numbers implement the #i message. This way, '2 + 3i' can be created evaluating: 2 + 3 i. For some examples try the following: (2 + 3 i) - (2 + 3 i) conjugated 2 + 3 i * (2 - 3 i). (-1 + 1 i) norm2. (4 + 2 i) reciprocal. 1 i squared. ! !Complex methodsFor: 'initialization' stamp: 'len 8/4/97 22:44'! setReal: aNumber imaginary: anotherNumber real _ aNumber. imaginary _ anotherNumber! ! !Complex methodsFor: 'accessing' stamp: 'len 2/25/98 18:02'! ambient "Answer the ambient of the receiver." ^ self real ambient complex! ! !Complex methodsFor: 'accessing' stamp: 'len 8/4/97 22:42'! imaginary "Answer the imaginary part of the receiver." ^ imaginary! ! !Complex methodsFor: 'accessing' stamp: 'len 8/4/97 22:42'! real "Answer the real part of the receiver." ^ real! ! !Complex methodsFor: 'arithmetic' stamp: 'len 2/25/98 22:14'! * anObject "Answer the product of the receiver by the argument." anObject isComplex ifFalse: [^ (anObject adaptComplex: self) * anObject adaptToComplex]. ^ self class real: self real * anObject real - (self imaginary * anObject imaginary) imaginary: self real * anObject imaginary + (self imaginary * anObject real)! ! !Complex methodsFor: 'arithmetic' stamp: 'len 2/25/98 22:14'! + anObject "Answer the sum of the receiver and the argument." anObject isComplex ifFalse: [^ (anObject adaptComplex: self) + anObject adaptToComplex]. ^ self class real: self real + anObject real imaginary: self imaginary + anObject imaginary! ! !Complex methodsFor: 'arithmetic' stamp: 'len 8/4/97 22:47'! - anObject "Answer the difference between the receiver and the argument." ^ self + anObject negated! ! !Complex methodsFor: 'arithmetic' stamp: 'len 8/4/97 22:48'! / anObject "Answer the result of dividing the receiver by the argument." ^ self * anObject reciprocal! ! !Complex methodsFor: 'arithmetic' stamp: 'len 10/17/97 03:57'! conjugated "Answer the conjugated of the receiver." ^ self class real: self real imaginary: self imaginary negated! ! !Complex methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:40'! i "Answer the receiver multiplicated by i." ^ self class real: self imaginary negated imaginary: self real! ! !Complex methodsFor: 'arithmetic' stamp: 'len 8/4/97 22:19'! negated "Answer the additive inverse of the receiver." ^ self class real: self real negated imaginary: self imaginary negated! ! !Complex methodsFor: 'arithmetic' stamp: 'len 10/17/97 03:58'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self conjugated / self norm2! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 3/18/98 00:13'! abs "Answer absolute value of the receiver." ^ self norm! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 9/1/97 00:33'! arcCos "Answer the arc-cosinus of the receiver." ^ (self + ((1 - self squared) sqrt * 1 i)) ln * -1 i! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 9/1/97 00:33'! arcSin "Answer the arc-sinus of the receiver." ^ ((1 - self squared) sqrt + self * 1 i) ln * -1 i! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 8/28/1998 00:46'! exp "Answer the exponential of the receiver." | alpha m | alpha _ self imaginary. m _ self real exp. ^ self class real: alpha cos * m imaginary: alpha sin * m! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 9/1/97 00:33'! log: aNumber "Answer the log base aNumber of the receiver." ^ self ln / aNumber ln! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 3/18/98 00:12'! norm "Answer the norm of the receiver." ^ self norm2 sqrt! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 8/4/97 22:49'! norm2 "Answer the square norm of the receiver." ^ self real squared + self imaginary squared! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 9/1/97 00:40'! raisedTo: arg "Answer the receiver raised to arg." arg isInteger ifTrue: ["Do the special case of integer power" ^ self raisedToInteger: arg]. arg = 0 ifTrue: [^ 1]. "Special case of exponent=0" arg = 1 ifTrue: [^ self]. "Special case of exponent=1" ^ (arg * self ln) exp "Otherwise raise it to the power using logarithms"! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 2/25/98 03:00'! raisedToInteger: anInteger "Answer the receiver raised to the power anInteger where the argument must be a kind of Integer. This is a special case of raisedTo:." anInteger isInteger ifFalse: [^ self error: 'raisedToInteger: only works for integral arguments']. anInteger = 0 ifTrue: [^ self identity]. anInteger = 1 ifTrue: [^ self]. anInteger > 1 ifTrue: [^ (self * self raisedToInteger: anInteger // 2) * (self raisedToInteger: anInteger \\ 2)]. ^ (self raisedToInteger: anInteger negated) reciprocal! ! !Complex methodsFor: 'mathematical functions'! sin self notYetImplemented ! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 8/4/97 22:52'! squared "Answer the square of the receiver." ^ self class real: self real squared - self imaginary squared imaginary: self real * self imaginary * 2! ! !Complex methodsFor: 'mathematical functions' stamp: 'len 9/1/97 00:42'! tan "Answer the tangent of the receiver." self notYetImplemented! ! !Complex methodsFor: 'comparing' stamp: 'len 2/25/98 22:18'! = anObject "Answer true if the receiver equals the argument." anObject isNumber ifFalse: [^ false]. anObject isComplex ifFalse: [^ (anObject adaptComplex: self) = anObject adaptToComplex]. ^ self real = anObject real and: [self imaginary = anObject imaginary]! ! !Complex methodsFor: 'comparing' stamp: 'len 8/4/97 22:42'! hash "Answer the hash value for the receiver." ^ self real hash + self imaginary hash! ! !Complex methodsFor: 'converting' stamp: 'len 8/4/97 22:18'! adaptAlgebraic: anAlgebraicNumber "If I am involved in arithmetic with an AlgebraicNumber, do not convert me." ^ anAlgebraicNumber asComplex! ! !Complex methodsFor: 'converting'! adaptFloat: aFloat "If I am involved in arithmetic with a Float, convert the Float." ^ aFloat asComplex! ! !Complex methodsFor: 'converting'! adaptFraction: aFraction "If I am involved in arithmetic with a Fraction, convert the Fraction." ^ aFraction asComplex! ! !Complex methodsFor: 'converting'! adaptInteger: anInteger "If I am involved in arithmetic with an Integer, convert the Integer." ^ anInteger asComplex! ! !Complex methodsFor: 'converting' stamp: 'len 2/25/98 03:25'! adaptQuaternion: aQuaternion "If I am involved in arithmetic with a Quaternion, do not convert it." ^ aQuaternion! ! !Complex methodsFor: 'converting' stamp: 'len 8/4/97 22:18'! adaptToAlgebraic "If I am involved in arithmetic with an AlgebraicNumber, do not convert me." ^ self! ! !Complex methodsFor: 'converting'! adaptToFloat "If I am involved in arithmetic with a Float, do not convert me." ^ self! ! !Complex methodsFor: 'converting'! adaptToFraction "If I am involved in arithmetic with a Fraction, do not convert me." ^ self! ! !Complex methodsFor: 'converting'! adaptToInteger "If I am involved in arithmetic with an Integer, do not convert me." ^ self! ! !Complex methodsFor: 'converting' stamp: 'len 2/25/98 03:24'! adaptToQuaternion "If I am involved in arithmetic with a Quaternion, convert me." ^ self asQuaternion! ! !Complex methodsFor: 'converting' stamp: 'len 2/25/98 03:25'! asComplex ^ self! ! !Complex methodsFor: 'converting' stamp: 'len 2/25/98 03:24'! asQuaternion "Convert the receiver to a Quaternion." ^ Quaternion a: self real b: self imaginary c: self real null d: self real null! ! !Complex methodsFor: 'testing' stamp: 'len 2/25/98 22:15'! isComplex "Answer true if the receiver is a Complex." ^ true! ! !Complex methodsFor: 'testing' stamp: 'len 9/1/97 00:43'! isNull "Answer true if the receiver is null." ^ self real isNull and: [self imaginary isNull]! ! !Complex methodsFor: 'testing' stamp: 'len 8/5/97 00:59'! isNumber ^ true! ! !Complex methodsFor: 'testing'! isRational ^ false! ! !Complex methodsFor: 'constants' stamp: 'len 2/25/98 03:01'! identity "Answer the identity element." ^ self class real: self real identity imaginary: self imaginary null! ! !Complex methodsFor: 'constants' stamp: 'len 2/25/98 03:01'! null "Answer the null element." ^ self class real: self real null imaginary: self imaginary null! ! !Complex methodsFor: 'printing' stamp: 'len 2/25/98 03:54'! printOn: aStream "Print a representation of the receiver on the stream aStream." | number | self isNull ifTrue: [aStream print: 0. ^ self]. self real isNull ifFalse: [aStream print: self real]. self imaginary isNull ifTrue: [^ self]. number _ self imaginary. self real isNull ifTrue: [number negative ifTrue: [aStream nextPut: $-. number _ number negated]] ifFalse: [aStream nextPutAll: (number positive ifTrue: [' + '] ifFalse: [number _ number negated. ' - '])]. number = number identity ifFalse: [aStream print: number; space]. aStream nextPut: $i! ! !Complex class methodsFor: 'instance creation'! real: realPart imaginary: imaginaryPart ^self new setReal: realPart imaginary: imaginaryPart! ! !DirectProduct methodsFor: 'initialization' stamp: 'len 4/29/98 05:03'! initialize self contents: OrderedCollection new! ! !DirectProduct methodsFor: 'initialization' stamp: 'len 4/29/98 05:03'! initialize: anInteger self contents: (Array new: anInteger)! ! !DirectProduct methodsFor: 'accessing-private' stamp: 'len 4/29/98 05:03'! contents ^ contents! ! !DirectProduct methodsFor: 'accessing-private' stamp: 'len 4/29/98 05:03'! contents: aCollection contents _ aCollection! ! !DirectProduct methodsFor: 'accessing' stamp: 'len 5/3/98 00:58'! add: anObject "Add the argument to the receiver. Answer the argument." ^ self contents add: anObject! ! !DirectProduct methodsFor: 'accessing' stamp: 'len 5/3/98 00:58'! at: anInteger "Answer the anInteger-th component of the receiver." ^ self contents at: anInteger! ! !DirectProduct methodsFor: 'accessing' stamp: 'len 5/3/98 00:58'! at: anInteger put: anObject "Change the anInteger-th component of the receiver to anObject. Answer anObject." ^ self contents at: anInteger put: anObject! ! !DirectProduct methodsFor: 'accessing' stamp: 'len 5/3/98 00:58'! size "Answer the size of the receiver." ^ self contents size! ! !DirectProduct methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:58'! * aDirectProduct "Answer the product of the receiver and the argument." | answer | answer _ self class new: self size. 1 to: aDirectProduct size do: [ :each | answer at: each put: (self at: each) + (aDirectProduct at: each)]. ^ answer! ! !DirectProduct methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:58'! / aDirectProoduct "Answer the division of the receiver by the argument." ^ self * aDirectProoduct reciprocal! ! !DirectProduct methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:58'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self collect: [ :each | each reciprocal]! ! !DirectProduct methodsFor: 'constants' stamp: 'len 4/30/98 04:01'! identity "Answer the multiplicative identity of the receiver." ^ self collect: [ :each | each identity]! ! !DirectProduct methodsFor: 'enumerating' stamp: 'len 5/3/98 00:58'! collect: aBlock "Answer a copy of the receiver with the components mapped by aBlock." | answer | answer _ self class new: self size. 1 to: self size do: [ :each | answer at: each put: (aBlock value: (self at: each))]. ^ answer! ! !DirectProduct methodsFor: 'enumerating' stamp: 'len 5/3/98 00:58'! do: aBlock "Enumerate the components of the receiver." self contents do: aBlock! ! !DirectProduct methodsFor: 'comparing' stamp: 'len 5/3/98 00:58'! = aDirectProduct "Answer true if the receiver equals the argument." ^ self contents = aDirectProduct contents! ! !DirectProduct methodsFor: 'comparing' stamp: 'len 5/3/98 00:58'! hash "Answer the hash value for the receiver." ^ self contents hash! ! !DirectProduct methodsFor: 'printing' stamp: 'len 5/3/98 00:58'! printOn: aStream "Print a representation of the receiver on the stream aStream." | first | aStream nextPut: $(. first _ true. self do: [ :each | first ifFalse: [aStream nextPutAll: ', ']. each printOn: aStream. first _ false]. aStream nextPut: $)! ! !DirectProduct class methodsFor: 'instance creation' stamp: 'len 4/29/98 05:04'! new ^ super new initialize! ! !DirectProduct class methodsFor: 'instance creation' stamp: 'len 4/29/98 05:04'! new: anInteger ^ self basicNew initialize: anInteger! ! !GSpace methodsFor: 'accessing-private' stamp: 'len 5/2/98 20:30'! actionBlock: aBinaryBlock actionBlock _ aBinaryBlock! ! !GSpace methodsFor: 'accessing-private' stamp: 'len 5/1/98 18:13'! group: aSubgroup group _ aSubgroup! ! !GSpace methodsFor: 'accessing-private' stamp: 'len 5/2/98 20:31'! space: aCollection space _ aCollection! ! !GSpace methodsFor: 'accessing' stamp: 'len 5/6/98 05:11'! action "Answer the action of the receiver." | permutation | ^ Homomorphism from: self group to: (Subgroup permutationsOf: self space) evaluationBlock: [ :each | permutation _ Permutation new. self space do: [ :other | permutation map: each to: (self actionBlock value: each value: other)]. permutation]! ! !GSpace methodsFor: 'accessing' stamp: 'len 5/2/98 20:32'! actionBlock "Answer the action of the receiver as a binary block." ^ actionBlock! ! !GSpace methodsFor: 'accessing' stamp: 'len 5/1/98 18:14'! group "Answer the group of the receiver." ^ group! ! !GSpace methodsFor: 'accessing' stamp: 'len 5/2/98 20:31'! space "Answer the space over wich the group acts (a Collection)." ^ space! ! !GSpace methodsFor: 'subgroups and subsets' stamp: 'len 5/2/98 20:31'! fixedPoints "Answer the fixed points of the receiver." ^ self space select: [ :each | self isFixedPoint: each]! ! !GSpace methodsFor: 'subgroups and subsets' stamp: 'len 5/2/98 20:32'! isotropyOf: anObject "Answer the isotropy group of the argument." ^ self space select: [ :each | (self actionBlock value: each value: anObject) = anObject]! ! !GSpace methodsFor: 'subgroups and subsets' stamp: 'len 5/2/98 20:32'! orbitOf: anObject "Answer the orbit of the argument." | answer | answer _ Set new. self group do: [ :each | answer add: (self actionBlock value: each value: anObject)]. ^ answer! ! !GSpace methodsFor: 'subgroups and subsets' stamp: 'len 5/5/98 00:35'! stabilizerOf: anObject "Answer the stabilizer of the argument." ^ self isotropyOf: anObject! ! !GSpace methodsFor: 'testing' stamp: 'len 5/2/98 20:32'! isFixedPoint: anObject "Answer true if the argument is a fixed point of the receiver." self group do: [ :each | (self actionBlock value: each value: anObject) = anObject ifFalse: [^ false]]. ^ true! ! !GSpace class methodsFor: 'instance creation' stamp: 'len 5/2/98 20:33'! from: aSubgroup into: aCollection actionBlock: aBinaryBlock ^ self new group: aSubgroup; space: aCollection; actionBlock: aBinaryBlock! ! !GSpaceByConjugation methodsFor: 'subgroups and subsets' stamp: 'len 5/2/98 20:41'! orbitOf: anObject "Answer the orbit of the argument." ^ self group collect: [ :each | each * anObject * each reciprocal]! ! !GSpaceByConjugation class methodsFor: 'instance creation' stamp: 'len 5/2/98 20:33'! from: aSubgroup into: anotherSubgroup ^ self new group: aSubgroup; space: anotherSubgroup; actionBlock: [ :g :a | g * a * g reciprocal]! ! !GSpaceByConjugation class methodsFor: 'instance creation' stamp: 'len 5/2/98 20:28'! from: aSubgroup into: aCollection actionBlock: aBinaryBlock self shouldNotImplement! ! !GSpaceByTranslation methodsFor: 'subgroups and subsets' stamp: 'len 5/2/98 20:39'! orbitOf: anObject "Answer the orbit of the argument." ^ self group * anObject! ! !GSpaceByTranslation class methodsFor: 'instance creation' stamp: 'len 5/2/98 20:33'! from: aSubgroup into: anotherSubgroup ^ self new group: aSubgroup; space: anotherSubgroup; actionBlock: [ :g :a | g * a]! ! !GSpaceByTranslation class methodsFor: 'instance creation' stamp: 'len 5/2/98 20:30'! from: aSubgroup into: aCollection actionBlock: aBinaryBlock self shouldNotImplement! ! !GroupAdditiveElement methodsFor: 'accessing-private' stamp: 'len 5/3/98 00:46'! element ^ element! ! !GroupAdditiveElement methodsFor: 'accessing-private' stamp: 'len 5/3/98 00:46'! element: anObject element _ anObject! ! !GroupAdditiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:47'! * aGroupAdditiveElement "Answer the product of the receiver by the argument." ^ self class from: (self element + aGroupAdditiveElement element)! ! !GroupAdditiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:56'! / aGroupAdditiveElement "Answer the division of the receiver by the argument." ^ self * aGroupAdditiveElement reciprocal! ! !GroupAdditiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:50'! raisedToInteger: anInteger "Answer the receiver raised to the integer anInteger." ^ self class from: self element * anInteger! ! !GroupAdditiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:48'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self class from: self element negated! ! !GroupAdditiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:56'! squared "Answer the square of the receiver." ^ self * self! ! !GroupAdditiveElement methodsFor: 'comparing' stamp: 'len 5/3/98 01:04'! = aGroupAdditiveElement "Answer true if the receiver equals the argument." ^ self element = aGroupAdditiveElement element! ! !GroupAdditiveElement methodsFor: 'comparing' stamp: 'len 5/3/98 01:04'! hash "Answer the hash value of the receiver." ^ self element hash! ! !GroupAdditiveElement methodsFor: 'constants' stamp: 'len 5/3/98 00:49'! identity "Answer the multiplicative identity of the receiver." ^ self class from: self element null! ! !GroupAdditiveElement methodsFor: 'printing' stamp: 'len 5/3/98 00:49'! printOn: aStream "Print a representation of the receiver on the stream aStream." self element printOn: aStream! ! !GroupAdditiveElement class methodsFor: 'instance creation' stamp: 'len 5/3/98 00:51'! from: anObject "Answer a new instance of the receiver adapting the additive object anObject." ^ self new element: anObject! ! !GroupCompositiveElement methodsFor: 'accessing-private' stamp: 'len 5/3/98 00:52'! element ^ element! ! !GroupCompositiveElement methodsFor: 'accessing-private' stamp: 'len 5/3/98 00:52'! element: anObject element _ anObject! ! !GroupCompositiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:57'! * aGroupCompositiveElement "Answer the product of the receiver by the argument." ^ self class from: (self element @ aGroupCompositiveElement element)! ! !GroupCompositiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:53'! / aGroupCompositiveElement "Answer the division of the receiver by the argument." ^ self * aGroupCompositiveElement reciprocal! ! !GroupCompositiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:54'! raisedToInteger: anInteger "Answer the receiver raised to the integer anInteger." ^ self notYetImplemented! ! !GroupCompositiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:54'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self class from: self element inverse! ! !GroupCompositiveElement methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:54'! squared "Answer the square of the receiver." ^ self * self! ! !GroupCompositiveElement methodsFor: 'comparing' stamp: 'len 5/3/98 01:04'! = aGroupCompositiveElement "Answer true if the receiver equals the argument." ^ self element = aGroupCompositiveElement element! ! !GroupCompositiveElement methodsFor: 'comparing' stamp: 'len 5/3/98 01:05'! hash "Answer the hash value of the receiver." ^ self element hash! ! !GroupCompositiveElement methodsFor: 'constants' stamp: 'len 5/3/98 00:54'! identity "Answer the multiplicative identity of the receiver." ^ self * self reciprocal! ! !GroupCompositiveElement methodsFor: 'printing' stamp: 'len 5/3/98 00:52'! printOn: aStream "Print a representation of the receiver on the stream aStream." self element printOn: aStream! ! !GroupCompositiveElement class methodsFor: 'instance creation' stamp: 'len 5/3/98 00:59'! from: anObject "Answer a new instance of the receiver adapting the compositive object anObject." ^ self new element: anObject! ! !Homomorphism methodsFor: 'initialization' stamp: 'len 4/30/98 04:26'! initialize self map: Dictionary new! ! !Homomorphism methodsFor: 'accessing-private' stamp: 'len 4/27/98 21:33'! codomain: aSubgroup codomain _ aSubgroup! ! !Homomorphism methodsFor: 'accessing-private' stamp: 'len 4/27/98 21:33'! domain: aSubgroup domain _ aSubgroup! ! !Homomorphism methodsFor: 'accessing-private' stamp: 'len 4/30/98 04:27'! map ^ map! ! !Homomorphism methodsFor: 'accessing-private' stamp: 'len 4/30/98 04:27'! map: aDictionary map _ aDictionary! ! !Homomorphism methodsFor: 'accessing' stamp: 'len 4/27/98 21:34'! codomain "Answer the codomain of the receiver." ^ codomain! ! !Homomorphism methodsFor: 'accessing' stamp: 'len 4/27/98 21:34'! domain "Answer the domain of the receiver." ^ domain! ! !Homomorphism methodsFor: 'accessing' stamp: 'len 4/30/98 05:21'! fiberAt: anObject "Answer the fiber of the receiver at anObject, a TranslatedSubgroup. Answer nil if the element is not in the image of the receiver." | particular | particular _ self domain detect: [ :one | (self valueAt: one) = anObject] ifNone: [^ nil]. ^ self kernel * particular! ! !Homomorphism methodsFor: 'accessing' stamp: 'len 4/30/98 04:09'! image "Answer the image of the receiver." ^ self domain collect: [ :each | self valueAt: each]! ! !Homomorphism methodsFor: 'accessing' stamp: 'len 4/30/98 05:17'! kernel "Answer the kernel of the receiver." ^ self codomain select: [ :each | (self valueAt: each) = self codomain identity]! ! !Homomorphism methodsFor: 'accessing' stamp: 'len 4/30/98 04:40'! map: anObject to: anotherObject "Change the receiver to map anObject to anotherObject." anotherObject = self codomain identity ifFalse: [self map at: anObject put: anotherObject]! ! !Homomorphism methodsFor: 'arithmetic' stamp: 'len 5/5/98 00:25'! * anHomomorphism "Answer the product of the receiver by the argument." ^ self class from: self domain to: self codomain evaluationBlock: [ :each | (self valueAt: each) * (anHomomorphism valueAt: each)]! ! !Homomorphism methodsFor: 'arithmetic' stamp: 'len 5/5/98 00:24'! @ anHomomorphism "Answer the composition of the receiver with the argument." ^ self class from: anHomomorphism domain to: self codomain evaluationBlock: [ :each | self valueAt: (anHomomorphism valueAt: each)]! ! !Homomorphism methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:32'! inverse "Answer the composition inverse of the receiver." ^ self class from: self codomain to: self domain evaluationBlock: [ :each | self domain detect: [ :one | (self valueAt: one) = each]]! ! !Homomorphism methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:33'! reciprocal "Answer the product inverse of the receiver." ^ self class from: self domain to: self codomain evaluationBlock: [ :each | (self valueAt: each) reciprocal]! ! !Homomorphism methodsFor: 'operations' stamp: 'len 4/30/98 04:28'! valueAt: anObject "Answer the value of the receiver at the argument." ^ self map at: anObject ifAbsent: [self codomain identity]! ! !Homomorphism methodsFor: 'testing' stamp: 'len 4/29/98 05:36'! isAutomorphism "Answer true if the reciever is an automorphism." ^ self isEndomorphism and: [self isIsomorphism]! ! !Homomorphism methodsFor: 'testing' stamp: 'len 4/29/98 05:36'! isEndomorphism "Answer true if the reciever is an endomorphism." ^ self domain = self codomain! ! !Homomorphism methodsFor: 'testing' stamp: 'len 4/29/98 05:34'! isEpimorphism "Answer true if the receiver is a monomorphism." ^ self image = self codomain! ! !Homomorphism methodsFor: 'testing' stamp: 'len 4/29/98 05:36'! isIsomorphism "Answer true if the reciever is an isomorphism." ^ self isEpimorphism and: [self isMonomorphism]! ! !Homomorphism methodsFor: 'testing' stamp: 'len 4/29/98 05:34'! isMonomorphism "Answer true if the receiver is a monomorphism." ^ self kernel isTrivial! ! !Homomorphism methodsFor: 'testing' stamp: 'len 4/29/98 05:35'! isTrivial "Answer true if the receiver is trivial." ^ self kernel = self domain! ! !Homomorphism class methodsFor: 'instance creation' stamp: 'len 4/30/98 04:39'! from: aSubgroup to: anotherSubgroup evaluationBlock: aBlock "Answer a new instance of the receiver with domain aSubgroup, codomain anotherSubgroup and evaluating as aBlock." | answer | answer _ self new domain: aSubgroup; codomain: anotherSubgroup. aSubgroup do: [ :each | answer map: each to: (aBlock value: each)]. ^ answer! ! !Homomorphism class methodsFor: 'instance creation' stamp: 'len 4/30/98 04:36'! new ^ super new initialize! ! !Infinity commentStamp: '' prior: 0! My instances are the real +infinity or -infinity. For some examples try these: Infinity positive * Infinity negative. Infinity positive * 2. Infinity positive - 7811234871239847. Infinity negative / -199. Infinity positive reciprocal. Infinity positive > Infinity negative. Infinity negative < -19238479182374598172349871234. Infinity negative > 0. Infinity negative min: Infinity positive. The following are examples of undeterminations (they produce an error): Infinity positive + Infinity negative. Infinity positive * 0. Infinity positive / Infinity positive. Infinity positive raisedToInteger: 0. ! !Infinity methodsFor: 'accessing-private' stamp: 'len 10/9/97 20:16'! sign: anInteger sign _ anInteger! ! !Infinity methodsFor: 'accessing' stamp: 'len 10/9/97 20:17'! sign "Answer the sign of the receiver." ^ sign! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 11/14/97 14:49'! * anObject "Answer the product of the receiver by the argument." anObject = 0 ifTrue: [^ self errorUndetermined]. ^ self class sign: self sign * anObject sign! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 12/13/97 02:26'! + anObject "Answer the sum of the receiver and the argument." (anObject isInfinity and: [self sign ~= anObject sign]) ifTrue: [^ self errorUndetermined]. ^ self! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 11/12/97 21:30'! - anObject "Answer the difference between the receiver and the argument." ^ self + anObject negated! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 10/9/97 20:24'! / anObject "Answer the division of the receiver by the argument." ^ self * anObject reciprocal! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 11/12/97 21:31'! negated "Answer a copy of the receiver with the sign changed." ^ self class sign: self sign negated! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 10/17/97 04:11'! raisedToInteger: anInteger "Answer the receiver raised to the integer anInteger." anInteger = 0 ifTrue: [^ self errorUndetermined]. anInteger negative ifTrue: [^ 0]. ^ anInteger odd ifTrue: [self] ifFalse: [self negated]! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 11/12/97 21:32'! reciprocal "Answer zero. (1 / self)" ^ 0! ! !Infinity methodsFor: 'arithmetic' stamp: 'len 10/17/97 04:09'! squared "Answer the square of the receiver." ^ self class positive! ! !Infinity methodsFor: 'comparing' stamp: 'len 12/13/97 02:26'! < anObject "Answer true if the receiver is lower than the argument." anObject isInfinity ifTrue: [^ self sign < anObject sign]. ^ self negative! ! !Infinity methodsFor: 'comparing' stamp: 'len 11/14/97 14:35'! = anObject "Answer true if the receiver equals the argument." ^ self class == anObject class and: [self sign = anObject sign]! ! !Infinity methodsFor: 'comparing' stamp: 'len 12/13/97 02:26'! > anObject "Answer true if the receiver is greater than the argument." anObject isInfinity ifTrue: [^ self sign > anObject sign]. ^ self positive! ! !Infinity methodsFor: 'comparing' stamp: 'len 11/14/97 14:35'! hash "Answer the hash value of the receiver." ^ self sign hash! ! !Infinity methodsFor: 'testing' stamp: 'len 12/13/97 02:25'! isInfinity "Answer true if the receiver is infinity." ^ true! ! !Infinity methodsFor: 'testing' stamp: 'len 11/14/97 14:50'! negative "Answer true if the receiver is negative." ^ self sign negative! ! !Infinity methodsFor: 'testing' stamp: 'len 11/14/97 14:50'! positive "Answer true if the receiver is positive." ^ self sign positive! ! !Infinity methodsFor: 'testing' stamp: 'len 11/14/97 14:51'! strictlyPositive "Answer true if the receiver is strictly positive." ^ self positive! ! !Infinity methodsFor: 'private' stamp: 'len 10/9/97 20:29'! errorUndetermined ^ self error: 'undetermined'! ! !Infinity methodsFor: 'printing' stamp: 'len 10/9/97 20:13'! printOn: aStream "Print a representation of the receiver on the stream aStream." self negative ifTrue: [aStream nextPut: $-]. aStream nextPutAll: 'infinity'! ! !Infinity class methodsFor: 'instance creation' stamp: 'len 10/17/97 04:07'! negative "Answer a new instance of the receiver representing -infinity." ^ self sign: -1! ! !Infinity class methodsFor: 'instance creation' stamp: 'len 10/17/97 04:07'! positive "Answer a new instance of the receiver representing +infinity." ^ self sign: 1! ! !Infinity class methodsFor: 'instance creation' stamp: 'len 10/9/97 20:27'! sign: anInteger "Answer a new instance of the receiver with sign anInteger." ^ self new sign: anInteger! ! !IntegerMod commentStamp: '' prior: 0! My instances are modular integers, i.e. elements of the quotient Z / mZ. Modular integers are created sending the message #mod: to an Integer, with argument another Integer. For some examples try: (2 mod: 7) + (3 mod: 7). (2 mod: 7) * (3 mod: 7). (1231 mod: 5) reciprocal. (2 mod: 3) raisedToInteger: 1234081723. (3 mod: 6) isUnit. (5 mod: 6) isUnit. ! !IntegerMod methodsFor: 'accessing-private' stamp: 'len 8/25/97 00:24'! modulo: anInteger modulo _ anInteger! ! !IntegerMod methodsFor: 'accessing-private' stamp: 'len 9/28/97 00:19'! representative: anInteger representative _ anInteger! ! !IntegerMod methodsFor: 'accessing' stamp: 'len 2/25/98 04:37'! ambient "Answer the ambient of the receiver." ^ AlgebraicAmbient integersMod: self modulo! ! !IntegerMod methodsFor: 'accessing' stamp: 'len 8/25/97 00:39'! modulo "Answer the modulo of the receiver." ^ modulo! ! !IntegerMod methodsFor: 'accessing' stamp: 'len 9/28/97 00:18'! representative "Answer a representative integer element of the receiver between 0 and (modulo - 1)." ^ representative! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 9/28/97 00:36'! * anObject "Answer the product of the receiver with the argument." anObject isInteger ifTrue: [^ self class new: self representative * anObject \\ self modulo mod: self modulo]. ^ self class new: self representative * anObject representative \\ self modulo mod: self modulo! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 9/28/97 00:22'! + anIntegerMod "Answer the sum of the receiver with the argument." | sum | sum _ self representative + anIntegerMod representative. sum < self modulo ifFalse: [sum _ sum - self modulo]. ^ self class new: sum mod: self modulo! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 8/25/97 00:20'! - anObject "Answer the difference of the receiver with the argument." ^ self + anObject negated! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 8/25/97 00:20'! / anObject "Answer the division of the receiver by the argument." ^ self * anObject reciprocal! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 9/28/97 00:24'! negated "Answer the additive inverse of the receiver." ^ self isNull ifTrue: [self] ifFalse: [self class new: self modulo - self representative mod: self modulo]! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 9/28/97 00:24'! reciprocal "Answer the multiplicative inverse of the receiver (whenever it exists)." | xgcd | xgcd _ (self representative xgcd: self modulo). (xgcd at: 1) = 1 ifFalse: [^ self error: 'division by zero']. ^ self class new: (xgcd at: 2) \\ self modulo mod: self modulo! ! !IntegerMod methodsFor: 'arithmetic' stamp: 'len 9/28/97 00:30'! squared "Answer the square of the receiver." ^ self class new: self representative squared \\ self modulo mod: self modulo! ! !IntegerMod methodsFor: 'mathematical functions' stamp: 'len 8/25/97 00:16'! raisedToInteger: anInteger "Answer the receiver raised to the power anInteger where the argument must be a kind of Integer." anInteger isInteger ifFalse: [^self error: 'raisedToInteger: only works for integral arguments']. anInteger = 0 ifTrue: [^ self identity]. anInteger = 1 ifTrue: [^ self]. anInteger > 1 ifTrue: [^(self * self raisedToInteger: anInteger // 2) * (self raisedToInteger: anInteger \\ 2)]. ^ (self raisedToInteger: anInteger negated) reciprocal! ! !IntegerMod methodsFor: 'comparing' stamp: 'len 9/28/97 00:23'! = anObject "Answer true if the receiver equals the argument." ^ self class == anObject class and: [ self modulo = anObject modulo and: [ self representative = anObject representative]]! ! !IntegerMod methodsFor: 'comparing' stamp: 'len 9/28/97 00:23'! hash "Answer the hash value for the receiver." ^ self representative hash! ! !IntegerMod methodsFor: 'testing' stamp: 'len 9/28/97 00:24'! isNull "Answer true if the receiver is null." ^ self representative = 0! ! !IntegerMod methodsFor: 'testing' stamp: 'len 8/25/97 00:24'! isSquare "Answer true if the receiver is an square." self notYetImplemented! ! !IntegerMod methodsFor: 'testing' stamp: 'len 9/28/97 00:25'! isUnit "Answer true if the receiver is a unit." ^ self isNull not and: [(self representative gcd: self modulo) = 1]! ! !IntegerMod methodsFor: 'converting' stamp: 'len 9/5/97 00:28'! adaptInteger: anInteger ^ self class new: anInteger mod: self modulo! ! !IntegerMod methodsFor: 'converting' stamp: 'len 8/26/97 01:56'! adaptToInteger ^ self! ! !IntegerMod methodsFor: 'constants' stamp: 'len 9/5/97 00:29'! identity ^ self class new: 1 mod: self modulo! ! !IntegerMod methodsFor: 'constants' stamp: 'len 9/5/97 00:30'! null ^ self class new: 0 mod: self modulo! ! !IntegerMod methodsFor: 'private'! errorModuloNotMatch self error: 'modulo not match'! ! !IntegerMod methodsFor: 'private' stamp: 'len 9/5/97 00:34'! reduced ^ self class new: self value \\ self modulo mod: self modulo! ! !IntegerMod methodsFor: 'private' stamp: 'len 12/1/97 22:42'! value | value | value _ self representative <= (self modulo // 2) ifTrue: [self representative] ifFalse: [self representative - self modulo]. ^ value! ! !IntegerMod methodsFor: 'printing' stamp: 'len 4/30/98 05:05'! printOn: aStream "Print a representation of the receiver in the stream aStream." | value | value _ self representative <= (self modulo // 2) ifTrue: [self representative] ifFalse: [self representative - self modulo]. aStream print: value "; nextPutAll: ' mod: '; print: self modulo"! ! !IntegerMod class methodsFor: 'instance creation' stamp: 'len 9/28/97 00:28'! new: anInteger mod: anotherInteger "Answer a new instance of the receiver representing the residue class of anInteger modulo anotherInteger." ^ self new modulo: anotherInteger; representative: anInteger! ! !Number methodsFor: 'arithmetic' stamp: 'len 2/18/98 18:58'! conjugated "Answer the complex conjugation of the receiver." ^ self! ! !Number methodsFor: 'mathematical functions' stamp: 'len 1/5/98 20:49'! norm "Answer the norm of the receiver." ^ self abs! ! !Number methodsFor: 'mathematical functions' stamp: 'len 1/5/98 20:49'! norm2 "Answer the squared norm of the receiver." ^ self squared! ! !Number methodsFor: 'testing' stamp: 'len 1/20/98 01:46'! isNull "Answer true if the receiver is null." ^ self = 0! ! !Number methodsFor: 'converting' stamp: 'len 1/20/98 01:45'! adaptComplex: aComplex "If I am involved in arithmetic with a Complex, do not convert it." ^ aComplex! ! !Number methodsFor: 'converting' stamp: 'len 2/25/98 03:22'! adaptQuaternion: aQuaternion "If I am involved in arithmetic with a Quaternion, do not convert it." ^ aQuaternion! ! !Number methodsFor: 'converting' stamp: 'len 1/20/98 01:45'! adaptToComplex "If I am involved in arithmetic with a Complex, convert me." ^ self asComplex! ! !Number methodsFor: 'converting' stamp: 'len 2/25/98 03:22'! adaptToQuaternion "If I am involved in arithmetic with a Quaternion, convert me." ^ self asQuaternion! ! !Number methodsFor: 'converting' stamp: 'len 1/20/98 01:45'! asComplex ^ Complex real: self imaginary: 0! ! !Number methodsFor: 'converting' stamp: 'len 2/25/98 03:23'! asQuaternion "Convert the receiver to a Quaternion." ^ Quaternion a: self b: self null c: self null d: self null! ! !Number methodsFor: 'converting' stamp: 'len 1/20/98 01:45'! i "Answer a Complex number with zero real and self imaginary parts." ^ Complex real: 0 imaginary: self! ! !Number methodsFor: 'constants' stamp: 'len 1/20/98 01:45'! identity "Answer the identity element." ^ 1! ! !Number methodsFor: 'constants' stamp: 'len 1/20/98 01:46'! null "Answer the null element." ^ 0! ! !Integer methodsFor: 'testing' stamp: 'len 8/30/97 03:13'! isPrime "Answer true if the receiver is a positive prime number." #AddedByLEN. "Easy cases:" self <= 1 ifTrue: [^ false]. self even ifTrue: [^ self = 2]. "(#(3 5 7 11 13 17 19 23 29 31 37) includes: self) ifTrue: [^ true]." 3 to: ((1 bitShift: self highBit // 2 + 1) min: self - 1) by: 2 do: [:each | self \\ each = 0 ifTrue: [^ false]]. ^ true! ! !Integer methodsFor: 'testing' stamp: 'len 8/28/97 20:51'! isPrimeMillerRabin: anInteger "Answer true if the receiver is prime with probability of error less than '(1/4)^anInteger', or false if the receiver is composite. Uses the Miller-Rabin test." | samples b k minusOne n0 t satisfied x | (self negative or: [self even]) ifTrue: [^ false]. minusOne _ self - 1. samples _ 1 to: minusOne. k _ minusOne lowBit - 1. n0 _ self - 1 bitShift: k negated. anInteger timesRepeat: [ b _ samples atRandom. (self gcd: b) = 1 ifFalse: [^ false]. t _ 0. x _ b raisedToInteger: n0 mod: self. (x = 1 or: [x = minusOne]) ifFalse: [ [x _ x squared \\ self. t _ t + 1. satisfied _ x = minusOne. satisfied not and: [t < k]] whileTrue. satisfied ifFalse: [^ false]]]. ^ true! ! !Integer methodsFor: 'testing' stamp: 'len 8/20/97 02:25'! isPrimeSolovayStrassen: anInteger "Answer true if the receiver is prime with probability less than '(1/2)^anInteger', or false if the receiver is composite. Uses the Solovay-Strassen test." | samples b minusOne power | (self negative or: [self even]) ifTrue: [^ false]. minusOne _ self - 1. samples _ 1 to: minusOne. power _ minusOne bitShift: -1. anInteger timesRepeat: [ b _ samples atRandom. (self gcd: b) = 1 ifFalse: [^ false]. (b raisedToInteger: power mod: self) = ((b jacobi: self) \\ self) ifFalse: [^ false halt] ]. ^ true! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 7/16/97 02:13'! descendentPower: n "Answer the descendent power of the receiver raised to the argument." | mid | n = 0 ifTrue: [^ 1]. n = 1 ifTrue: [^ self]. n negative ifTrue: [^ (self descendentPower: n negated) reciprocal]. mid _ n bitShift: -1. ^ n even ifTrue: [ (self - mid descendentPower: mid) * (self descendentPower: mid) ] ifFalse: [ (self - mid descendentPower: mid + 1) * (self descendentPower: mid) ]! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 7/14/97 01:19'! divisors "Answer the collection of positive divisors of the receiver." | answer | #AddedByLEN. self negative ifTrue: [^ self abs divisors]. answer _ Set new. 1 to: (self bitShift: -2) + 1 do: [ :each | self \\ each = 0 ifTrue: [answer add: each; add: self // each] ]. ^ answer! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 10/2/97 01:36'! divisorsDo: aBlock "Enumerate the positive divisors of the receiver." #AddedByLEN. self divisors do: aBlock! ! !Integer methodsFor: 'mathematical functions'! factorial "Answer the factorial of the receiver. Create an error notification if the receiver is negative." self = 0 ifTrue: [^1]. self < 0 ifTrue: [self error: 'factorial invalid for: ' , self printString] ifFalse: [^ self descendentPower: self - 1]! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 10/10/97 01:16'! factors "Answer a collection with the prime factors of the receiver." | n p answer times | #AddedByLEN. n _ self abs. n <= 1 ifTrue: [^ Bag new]. answer _ Bag new. n even ifTrue: [ answer add: 2 withOccurrences: (times _ n lowBit - 1). n _ n bitShift: times negated]. p _ 3. [p <= n] whileTrue: [ p isPrime ifTrue: [ times _ 0. [n \\ p = 0] whileTrue: [times _ times + 1. n _ n // p]. times > 0 ifTrue: [answer add: p withOccurrences: times]]. p _ p + 2]. ^ answer! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 11/24/97 20:45'! factors2 "Answer a collection with the prime factors of the receiver." | n p answer times | n _ self abs. n <= 1 ifTrue: [^ Bag new]. answer _ Bag new. n even ifTrue: [ answer add: 2 withOccurrences: (times _ n lowBit - 1). n _ n bitShift: times negated]. p _ 3. [p <= (n // p)] whileTrue: [ p isPrime ifTrue: [ times _ 0. [n \\ p = 0] whileTrue: [times _ times + 1. n _ n // p]. times > 0 ifTrue: [answer add: p withOccurrences: times]]. p _ p + 2]. (p = n or: [n = 1]) ifFalse: [answer add: n]. ^ answer! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 8/20/97 02:25'! jacobi: m "Answer the Jacobi symbol of the receiver and the argument." | x y z answer | m odd ifFalse: [^ self error: 'the argument must by an odd positive integer']. (self gcd: m) = 1 ifFalse: [^ 0]. x _ self \\ m. y _ m. answer _ 1. [x > 1] whileTrue: [ [x \\ 4 = 0] whileTrue: [x _ x // 4]. x \\ 2 = 0 ifTrue: [ x _ x // 2. y + 2 \\ 8 > 4 ifTrue: [answer _ answer negated] ]. z _ y \\ x. y _ x. x _ z ]. ^ answer! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 8/20/97 02:26'! jacobiOld: n "Answer the Jacoby symbol of the receiver and the argument." | a minusOne | " n odd ifFalse: [^ self error: 'the argument must by an odd positive integer']." a _ self \\ n. a = 2 ifTrue: [^ (n squared - 1) lowBit > 3 ifTrue: [1] ifFalse: [-1]]. minusOne _ n - 1. a = minusOne ifTrue: [^ minusOne lowBit > 1 ifTrue: [1] ifFalse: [-1]]. ^ (a - 1 * minusOne) lowBit > 2 ifTrue: [n jacobiOld: a] ifFalse: [(n jacobiOld: a) negated]! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 9/17/97 02:05'! pollard "Answer a non trivial factor of the receiver. The Pollard method is used." | interval a x y p count | interval _ 1 to: self abs. a _ interval atRandom. x _ interval atRandom. y _ x. count _ 1. [x _ x squared + a \\ self. y _ (y squared + a \\ self) squared + a \\ self. (p _ y - x gcd: self) = 1 ifFalse: [^ Array with: p with: count]. count _ count + 1. true] whileTrue.! ! !Integer methodsFor: 'mathematical functions' stamp: 'len 8/20/97 00:56'! raisedToInteger: anInteger mod: otherInteger "Answer the receiver raised to the power anInteger modulo otherInteger. Both anInteger and otherInteger must be positive." anInteger = 0 ifTrue: [^ 1]. anInteger = 1 ifTrue: [^ self \\ otherInteger]. ^ (self squared \\ otherInteger raisedToInteger: anInteger // 2 mod: otherInteger) * (self raisedToInteger: anInteger \\ 2 mod: otherInteger) \\ otherInteger! ! !Integer methodsFor: 'converting' stamp: 'len 1/20/98 01:45'! mod: anInteger "Answer self modulo anInteger." ^ IntegerMod new: self \\ anInteger mod: anInteger! ! !Integer methodsFor: 'accessing' stamp: 'len 1/20/98 01:45'! denominator "Answer the denominator of the receiver." ^ 1! ! !Integer methodsFor: 'accessing' stamp: 'len 1/20/98 01:45'! numerator "Answer the numerator of the receiver." ^ self! ! !Permutation methodsFor: 'initialization' stamp: 'len 9/16/97 00:18'! initialize self map: Dictionary new! ! !Permutation methodsFor: 'accessing-private' stamp: 'len 5/6/98 04:50'! map ^ map! ! !Permutation methodsFor: 'accessing-private' stamp: 'len 9/16/97 00:13'! map: aDictionary map _ aDictionary! ! !Permutation methodsFor: 'accessing' stamp: 'len 5/6/98 05:01'! aChange "Answer an element changed by the receiver (or nil if there are no one)." self changesDo: [ :each | ^ each]. ^ nil! ! !Permutation methodsFor: 'accessing' stamp: 'len 5/6/98 05:01'! at: anObject "Answer the object to which the receiver maps the argument." ^ self map at: anObject ifAbsent: [anObject]! ! !Permutation methodsFor: 'accessing' stamp: 'len 9/28/97 00:50'! changes "Answer the elements changed by the receiver." | answer | answer _ Set new. self changesDo: [ :each | answer add: each]. ^ answer! ! !Permutation methodsFor: 'accessing' stamp: 'len 5/6/98 05:00'! cycleAt: anObject "Answer the cycle generated by anObject." | answer last | answer _ self class cycleClass new. last _ anObject. [answer map: last to: (last _ self at: last). last = anObject] whileFalse. ^ answer! ! !Permutation methodsFor: 'accessing' stamp: 'len 10/1/97 18:59'! cycles "Answer the cycles of the receiver." | answer | answer _ Set new. self cyclesDo: [ :each | answer add: each]. ^ answer! ! !Permutation methodsFor: 'accessing' stamp: 'len 5/6/98 05:01'! map: anObject to: anotherObject "Change the receiver to map the first object to the second one." anObject = anotherObject ifFalse: [self map at: anObject put: anotherObject]! ! !Permutation methodsFor: 'accessing' stamp: 'len 10/1/97 19:25'! order "Answer the order of the receiver." | answer next | answer _ 1. next _ self. [next isIdentity] whileFalse: [next _ next * self. answer _ answer + 1]. ^ answer! ! !Permutation methodsFor: 'accessing' stamp: 'len 10/1/97 19:00'! sign "Answer the sign of the receiver." | answer | answer _ 1. self cyclesDo: [ :each | answer _ answer * each sign]. ^ answer "^ self transpositions size even ifTrue: [1] ifFalse: [-1]"! ! !Permutation methodsFor: 'accessing' stamp: 'len 9/28/97 00:54'! size "Answer the number of elements changed by the receiver." ^ self map size! ! !Permutation methodsFor: 'accessing' stamp: 'len 9/30/97 00:11'! transpositions "Answer the decomposition of the receiver in product of transpositions." | answer last | answer _ OrderedCollection new. self changesDo: [ :each | last _ each. answer reverseDo: [ :one | last _ one at: last]. (self at: each) = last ifFalse: [answer addFirst: (self species transpose: last with: (self at: each))]]. ^ answer! ! !Permutation methodsFor: 'accessing' stamp: 'len 4/27/98 21:03'! type "Answer the type of the receiver." ^ (self cycles asSortedCollection: [ :a :b | a size <= b size]) collect: [ :each | each size]! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:23'! * aPermutation "Answer the product of the receiver by the argument." ^ self @ aPermutation! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:23'! @ aPermutation "Answer the composition of the receiver with the argument." | answer | answer _ self species new. self changesDo: [ :each | answer map: each to: (self at: (aPermutation at: each))]. aPermutation changesDo: [ :each | answer map: each to: (self at: (aPermutation at: each))]. ^ answer! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 10/7/1998 04:32'! identity "Answer the identity permutation." ^ self class new! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:22'! inverse "Answer the composition inverse of the receiver." | answer | answer _ self species new. self changesDo: [ :each | answer map: (self at: each) to: each]. ^ answer! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 10/2/97 19:04'! raisedToInteger: anInteger "Answer the receiver raised to the argument." anInteger = 0 ifTrue: [^ self class new]. anInteger = 1 ifTrue: [^ self]. ^ anInteger > 1 ifTrue: [(self squared raisedToInteger: anInteger // 2) * (self raisedToInteger: anInteger \\ 2)] ifFalse: [(self raisedToInteger: anInteger negated) inverse]! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:24'! reciprocal "Answer the multiplication inverse of the receiver." ^ self inverse! ! !Permutation methodsFor: 'arithmetic' stamp: 'len 10/2/97 19:04'! squared "Answer the square of the receiver." ^ self * self! ! !Permutation methodsFor: 'operations' stamp: 'len 9/30/97 00:15'! permute: aCollection "Answer the permutation of the elements of aCollection induced by the receiver." ^ (1 to: aCollection size) collect: [ :each | aCollection at: (self at: each)]! ! !Permutation methodsFor: 'operations' stamp: 'len 5/6/98 05:02'! valueAt: anObject "Answer the value of the receiver at the argument." ^ self at: anObject! ! !Permutation methodsFor: 'comparing' stamp: 'len 5/2/98 20:23'! = anObject "Answer true if the receiver equals the argument." self size = anObject size ifFalse: [^ false]. self changesDo: [ :each | (anObject at: each) = (self at: each) ifFalse: [^ false]]. ^ true! ! !Permutation methodsFor: 'comparing' stamp: 'len 5/2/98 20:23'! hash "Answer the hash value of the receiver." | answer | answer _ self size. self changesDo: [ :each | answer _ answer + each hash]. ^ answer! ! !Permutation methodsFor: 'enumerating' stamp: 'len 5/6/98 05:03'! changesDo: aBlock "Enumerate the elements changed by the receiver." self map keysDo: aBlock! ! !Permutation methodsFor: 'enumerating' stamp: 'len 10/1/97 18:56'! cyclesDo: aBlock "Enumerate the cycles of the receiver." | left first next cycle | left _ self changes. [left size > 0] whileTrue: [ cycle _ self class cycleClass new. first _ left anElement. next _ first. [cycle map: next to: (next _ self at: next). left remove: next. next ~= first] whileTrue. aBlock value: cycle]! ! !Permutation methodsFor: 'testing' stamp: 'len 10/1/97 19:09'! even "Answer true if the receiver is odd." ^ self sign = 1! ! !Permutation methodsFor: 'testing' stamp: 'len 5/6/98 05:03'! isConjugateWith: aPermutation "Answer true if the receiver and the argument are conjugate." ^ self type = aPermutation type! ! !Permutation methodsFor: 'testing' stamp: 'len 9/28/97 01:16'! isCycle "Answer true if the receiver is a cycle." ^ self cycles size = 1! ! !Permutation methodsFor: 'testing' stamp: 'len 9/28/97 01:15'! isIdentity "Answer true if the receiver is the identity permutation." ^ self size = 0! ! !Permutation methodsFor: 'testing' stamp: 'len 9/28/97 01:17'! isTransposition "Answer true if the receiver is a transposition." ^ self size = 2! ! !Permutation methodsFor: 'testing' stamp: 'len 10/1/97 19:08'! odd "Answer true if the receiver is odd." ^ self sign = -1! ! !Permutation methodsFor: 'private' stamp: 'len 9/29/97 19:14'! species ^ Permutation! ! !Permutation methodsFor: 'printing' stamp: 'len 10/1/97 18:59'! printOn: aStream "Print a representation of the receiver on the stream aStream." self isIdentity ifTrue: [aStream nextPutAll: 'id'] ifFalse: [self cyclesDo: [ :each | each printOn: aStream]]! ! !Permutation class methodsFor: 'instance creation' stamp: 'len 9/28/97 01:09'! fromArray: anArray "Answer a new instance of the receiver from the argument." | answer | answer _ self new. 1 to: anArray size do: [ :each | answer map: each to: (anArray at: each)]. ^ answer! ! !Permutation class methodsFor: 'instance creation' stamp: 'len 9/16/97 00:19'! new "Answer a new instance of the receiver representing the identity permutation." ^ super new initialize! ! !Permutation class methodsFor: 'instance creation' stamp: 'len 5/6/98 05:04'! transpose: anObject with: anotherObject "Answer the tranposition of anObject with anotherObject." ^ self new map: anObject to: anotherObject; map: anotherObject to: anObject; yourself! ! !Permutation class methodsFor: 'related classes' stamp: 'len 9/29/97 19:13'! cycleClass "Answer the class of cycles." ^ PermutationCycle! ! !PermutationCycle methodsFor: 'accessing' stamp: 'len 5/6/98 04:59'! cycleAt: anObject "Answer the cycle generated by anObject." ^ (self at: anObject) = anObject ifTrue: [self class new] ifFalse: [self]! ! !PermutationCycle methodsFor: 'accessing' stamp: 'len 5/6/98 04:59'! cycles "Answer the cycles of the receiver." ^ Set with: self! ! !PermutationCycle methodsFor: 'accessing' stamp: 'len 5/6/98 04:59'! sign "Answer the sign of the receiver." ^ self size odd ifTrue: [1] ifFalse: [-1]! ! !PermutationCycle methodsFor: 'accessing' stamp: 'len 5/6/98 04:59'! transpositions "Answer the decomposition of the receiver in product of transpositions." | answer first last | answer _ OrderedCollection new. first _ self aChange. last _ first. self size - 1 timesRepeat: [ answer addFirst: (self species transpose: first with: (last _ self at: last))]. ^ answer! ! !PermutationCycle methodsFor: 'testing' stamp: 'len 5/6/98 04:58'! isCycle "Answer true if the receiver is a cycle." ^ true! ! !PermutationCycle methodsFor: 'printing' stamp: 'len 5/6/98 04:58'! printOn: aStream "Print a representation of the receiver on the stream aStream. The receiver is supposed to be a cycle." | first last changes | self isIdentity ifTrue: [aStream nextPutAll: 'id']. changes _ self changes. first _ (changes detect: [ :one | one isInteger not] ifNone: []) isNil ifTrue: [changes asSortedCollection last] ifFalse: [self aChange]. last _ first. aStream nextPut: $(. [aStream print: (last _ self at: last). last = first] whileFalse: [aStream space]. aStream nextPut: $)! ! !PositionableStream methodsFor: 'accessing' stamp: 'len 11/24/97 20:44'! nextLine "Answer the next line of the receiver. (line delimiters are lf, cr or crlf)." | answer char cr lf | self atEnd ifTrue: [^ nil]. cr _ Character cr. lf _ Character linefeed. answer _ WriteStream with: ''. [self atEnd] whileFalse: [ char _ self next. (char = lf or: [char = cr]) ifTrue: [(char = cr and: [self peek = lf]) ifTrue: [self next]. ^ answer contents]. answer nextPut: char]. ^ answer contents! ! !Quaternion commentStamp: '' prior: 0! My instances are quaternions. Quaternions constitute an example of non-commutative field. ! !Quaternion methodsFor: 'accessing-private' stamp: 'len 2/25/98 02:41'! a: aNumber b: bNumber c: cNumber d: dNumber a _ aNumber. b _ bNumber. c _ cNumber. d _ dNumber! ! !Quaternion methodsFor: 'accessing' stamp: 'len 2/25/98 02:43'! a "Answer the 'a' component of the receiver." ^ a! ! !Quaternion methodsFor: 'accessing' stamp: 'len 2/25/98 18:02'! ambient "Answer the ambient of the receiver." ^ self a ambient quaternions! ! !Quaternion methodsFor: 'accessing' stamp: 'len 2/25/98 02:43'! b "Answer the 'b' component of the receiver." ^ b! ! !Quaternion methodsFor: 'accessing' stamp: 'len 2/25/98 02:43'! c "Answer the 'c' component of the receiver." ^ c! ! !Quaternion methodsFor: 'accessing' stamp: 'len 2/25/98 02:43'! d "Answer the 'd' component of the receiver." ^ d! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:58'! * anObject "Answer the product of the receiver by the argument." | a0 a1 a2 a3 b0 b1 b2 b3 | anObject isQuaternion ifFalse: [^ (anObject adaptQuaternion: self) * anObject adaptToQuaternion]. a0 _ self a. a1 _ self b. a2 _ self c. a3 _ self d. b0 _ anObject a. b1 _ anObject b. b2 _ anObject c. b3 _ anObject d. ^ self class a: a0 * b0 - (a1 * b1) - (a2 * b2) - (a3 * b3) b: a0 * b1 + (a1 * b0) + (a2 * b3) - (a3 * b2) c: a0 * b2 + (a2 * b0) + (a3 * b1) - (a1 * b3) d: a0 * b3 + (a3 * b0) + (a1 * b2) - (a2 * b1)! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:45'! + anObject "Answer the sum of the receiver and the argument." anObject isQuaternion ifFalse: [^ (anObject adaptQuaternion: self) + anObject adaptToQuaternion]. ^ self class a: self a + anObject a b: self b + anObject b c: self c + anObject c d: self d + anObject d! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:46'! - anObject "Answer the difference between the receiver and the argument." ^ self + anObject negated! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:47'! / anObject "Answer the division of the receiver by the argument." ^ self * anObject reciprocal! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:47'! conjugated "Answer the conjugate of the receiver." ^ self class a: self a b: self b negated c: self c negated d: self d negated! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 03:29'! i "Answer the receiver multiplicated by i." ^ self class a: self b negated b: self a c: self d d: self c negated! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 03:29'! j "Answer the receiver multiplicated by j." ^ self class a: self c negated b: self d negated c: self a d: self b! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 03:30'! k "Answer the receiver multiplicated by k." ^ self class a: self d negated b: self c c: self b negated d: self a! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:46'! negated "Answer the additive inverse of the receiver." ^ self class a: self a negated b: self b negated c: self c negated d: self d negated! ! !Quaternion methodsFor: 'arithmetic' stamp: 'len 2/25/98 02:58'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self conjugated / self norm2! ! !Quaternion methodsFor: 'mathematical functions' stamp: 'len 2/25/98 02:59'! norm2 "Answer the square norm of the receiver." ^ self a squared + self b squared + self c squared + self d squared! ! !Quaternion methodsFor: 'mathematical functions' stamp: 'len 2/25/98 03:02'! raisedToInteger: anInteger "Answer the receiver raised to the power anInteger where the argument must be a kind of Integer." anInteger isInteger ifFalse: [^ self error: 'raisedToInteger: only works for integral arguments']. anInteger = 0 ifTrue: [^ self identity]. anInteger = 1 ifTrue: [^ self]. anInteger > 1 ifTrue: [^ (self * self raisedToInteger: anInteger // 2) * (self raisedToInteger: anInteger \\ 2)]. ^ (self raisedToInteger: anInteger negated) reciprocal! ! !Quaternion methodsFor: 'mathematical functions' stamp: 'len 2/25/98 03:40'! squared "Answer the square of the receiver." ^ self * self! ! !Quaternion methodsFor: 'comparing' stamp: 'len 2/25/98 03:04'! = anObject "Answer true if the receiver equals the argument." anObject isNumber ifFalse: [^ false]. anObject isQuaternion ifFalse: [^ (anObject adaptQuaternion: self) = anObject adaptToQuaternion]. ^ self a = anObject a and: [self b = anObject b and: [self c = anObject c and: [self d = anObject d]]]! ! !Quaternion methodsFor: 'comparing' stamp: 'len 2/25/98 03:04'! hash "Answer the hash value of the receiver." ^ self a hash + self b hash + self c hash + self d hash! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:19'! adaptAlgebraic: anAlgebraicNumber "If I am involved in arithmetic with an AlgebraicNumber, do not convert me." ^ anAlgebraicNumber asQuaternion! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:20'! adaptComplex: aComplex "If I am involved in arithmetic with a Complex, do not convert me." ^ aComplex asQuaternion! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:19'! adaptFloat: aFloat "If I am involved in arithmetic with a Float, convert the Float." ^ aFloat asQuaternion! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:20'! adaptFraction: aFraction "If I am involved in arithmetic with a Fraction, convert the Fraction." ^ aFraction asQuaternion! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:20'! adaptInteger: anInteger "If I am involved in arithmetic with an Integer, convert the Integer." ^ anInteger asQuaternion! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:19'! adaptToAlgebraic "If I am involved in arithmetic with an AlgebraicNumber, do not convert me." ^ self! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:20'! adaptToComplex "If I am involved in arithmetic with a Complex, do not convert me." ^ self! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:19'! adaptToFloat "If I am involved in arithmetic with a Float, do not convert me." ^ self! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:19'! adaptToFraction "If I am involved in arithmetic with a Fraction, do not convert me." ^ self! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:19'! adaptToInteger "If I am involved in arithmetic with an Integer, do not convert me." ^ self! ! !Quaternion methodsFor: 'converting' stamp: 'len 2/25/98 03:21'! asQuaternion ^ self! ! !Quaternion methodsFor: 'testing' stamp: 'len 2/25/98 03:05'! isNull "Answer true if the receiver is null." ^ self a isNull and: [self b isNull and: [self c isNull and: [self d isNull]]]! ! !Quaternion methodsFor: 'testing' stamp: 'len 2/25/98 03:05'! isNumber ^ true! ! !Quaternion methodsFor: 'testing' stamp: 'len 2/25/98 03:17'! isQuaternion "Answer true if the receiver is a Quaternion." ^ true! ! !Quaternion methodsFor: 'constants' stamp: 'len 2/25/98 03:16'! identity "Answer the identity quaternion." ^ self class a: self a identity b: self b null c: self c null d: self d null! ! !Quaternion methodsFor: 'constants' stamp: 'len 2/25/98 03:16'! null "Answer the null quaternion." ^ self class a: self a null b: self b null c: self c null d: self d null! ! !Quaternion methodsFor: 'printing' stamp: 'len 2/25/98 03:37'! printOn: aStream "Print a representation of the receiver on the stream aStream." | something number | self isNull ifTrue: [aStream print: 0. ^ self]. something _ false. self a isNull ifFalse: [aStream print: self a. something _ true]. self b isNull ifFalse: [number _ self b. something ifTrue: [aStream nextPutAll: (number positive ifTrue: [' + '] ifFalse: [number _ number negated. ' - '])] ifFalse: [number negative ifTrue: [aStream nextPut: $-. number _ number negated]]. number = number identity ifFalse: [aStream print: number; space]. aStream nextPut: $i. something _ true]. self c isNull ifFalse: [number _ self c. something ifTrue: [aStream nextPutAll: (number positive ifTrue: [' + '] ifFalse: [number _ number negated. ' - '])] ifFalse: [number negative ifTrue: [aStream nextPut: $-. number _ number negated]]. number = number identity ifFalse: [aStream print: number; space]. aStream nextPut: $j. something _ true]. self d isNull ifFalse: [number _ self d. something ifTrue: [aStream nextPutAll: (number positive ifTrue: [' + '] ifFalse: [number _ number negated. ' - '])] ifFalse: [number negative ifTrue: [aStream nextPut: $-. number _ number negated]]. number = number identity ifFalse: [aStream print: number; space]. aStream nextPut: $k. something _ true]! ! !Quaternion class methodsFor: 'instance creation' stamp: 'len 2/25/98 02:42'! a: aNumber b: bNumber c: cNumber d: dNumber "Answer a new instance of the receiver with the given components." ^ self new a: aNumber b: bNumber c: cNumber d: dNumber! ! !Quaternion class methodsFor: 'examples' stamp: 'len 5/3/98 00:19'! i ^ Quaternion a: 0 b: 1 c: 0 d: 0! ! !Quaternion class methodsFor: 'examples' stamp: 'len 5/3/98 00:20'! j ^ Quaternion a: 0 b: 0 c: 1 d: 0! ! !Quaternion class methodsFor: 'examples' stamp: 'len 5/3/98 00:20'! k ^ Quaternion a: 0 b: 0 c: 0 d: 1! ! !RootOfUnity methodsFor: 'accessing-private' stamp: 'len 5/3/98 00:34'! modular: anIntegerMod modular _ anIntegerMod! ! !RootOfUnity methodsFor: 'accessing' stamp: 'len 5/3/98 00:35'! modular "Answer the modular integer associated with the receiver by the natural isomorphism." ^ modular! ! !RootOfUnity methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:35'! * aRootOfUnity "Answer the product of the receiver by the argument." ^ self class modular: self modular + aRootOfUnity modular! ! !RootOfUnity methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:39'! raisedToInteger: anInteger "Answer the receiver raised to the integer anInteger." ^ self class modular: self modular * anInteger! ! !RootOfUnity methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:36'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self class modular: self modular negated! ! !RootOfUnity methodsFor: 'arithmetic' stamp: 'len 5/3/98 00:39'! squared "Answer the square of the receiver." ^ self * self! ! !RootOfUnity methodsFor: 'comparing' stamp: 'len 5/3/98 01:03'! = aRootOfUnity "Answer true if the receiver equals the argument." ^ self modular = aRootOfUnity modular! ! !RootOfUnity methodsFor: 'comparing' stamp: 'len 5/3/98 01:03'! hash "Answer the hash value of the receiver." ^ self modular hash! ! !RootOfUnity methodsFor: 'converting' stamp: 'len 5/3/98 00:33'! asComplex "Convert the receiver to a Complex number." self notYetImplemented! ! !RootOfUnity methodsFor: 'constants' stamp: 'len 5/3/98 00:37'! identity "Answer the multiplicative identity of the receiver." ^ self class modular: self modular null! ! !RootOfUnity methodsFor: 'testing' stamp: 'len 5/3/98 00:38'! isPrimitive "Answer true if the recever is a primitive root of unity." ^ self modular isUnit! ! !RootOfUnity methodsFor: 'printing' stamp: 'len 5/3/98 00:43'! printOn: aStream "Print a representation of the receiver on the stream aStream." aStream nextPutAll: 'e^(i2PI'; print: self modular representative; nextPut: $/; print: self modular modulo; nextPut: $)! ! !RootOfUnity class methodsFor: 'instance creation' stamp: 'len 5/3/98 00:37'! modular: anIntegerMod "Answer a new instance of the receiver with associated modular integer anIntegerMod." ^ self new modular: anIntegerMod! ! !SemidirectProduct methodsFor: 'accessing-private' stamp: 'len 5/5/98 00:18'! action: anHomomorphism action _ anHomomorphism! ! !SemidirectProduct methodsFor: 'accessing-private' stamp: 'len 5/5/98 00:17'! left: anObject left _ anObject! ! !SemidirectProduct methodsFor: 'accessing-private' stamp: 'len 5/5/98 00:17'! right: anObject right _ anObject! ! !SemidirectProduct methodsFor: 'accessing' stamp: 'len 5/5/98 00:18'! action "Answer the action of the receiver." ^ action! ! !SemidirectProduct methodsFor: 'accessing' stamp: 'len 5/5/98 00:18'! left "Answer the left component of the receiver." ^ left! ! !SemidirectProduct methodsFor: 'accessing' stamp: 'len 5/5/98 00:18'! right "Answer the right component of the receiver." ^ right! ! !SemidirectProduct methodsFor: 'arithmetic' stamp: 'len 5/5/98 00:27'! * aSemidirectProduct "Answer the product of the receiver by the argument." ^ self class left: self left * aSemidirectProduct left right: ((self action valueAt: aSemidirectProduct left) valueAt: self right) * aSemidirectProduct right! ! !SemidirectProduct methodsFor: 'arithmetic' stamp: 'len 5/5/98 00:22'! / aSemidirectProduct "Answer the division of the receiver by the argument." ^ self * aSemidirectProduct reciprocal! ! !SemidirectProduct methodsFor: 'arithmetic' stamp: 'len 5/5/98 00:29'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self class left: self left reciprocal right: ((self action valueAt: self left reciprocal) valueAt: self right) reciprocal action: self action! ! !SemidirectProduct methodsFor: 'constants' stamp: 'len 5/5/98 00:20'! identity "Answer the multiplicative identity of the receiver." ^ self class left: self left identity right: self right identity action: self action! ! !SemidirectProduct methodsFor: 'printing' stamp: 'len 5/5/98 00:21'! printOn: aStream "Print a representation of the receiver on the stream aStream." aStream nextPut: $(; print: self left; nextPutAll: ', '; print: self right; nextPut: $)! ! !SemidirectProduct class methodsFor: 'instance creation' stamp: 'len 5/5/98 00:24'! left: anObject right: anotherObject action: anHomomorphism "Answer a new instance of the receiver, the semidirect product between anObject and anotherObject with the action given by anHomomorphism." ^ self new left: anObject; right: anotherObject; action: anHomomorphism! ! !String methodsFor: 'converting' stamp: 'len 11/24/97 20:44'! asArrayOfSubstrings "Answer an array with all the substrings of the receiver separated by separator characters (space, cr, tab, linefeed, formfeed, etc)." | substrings start end | substrings _ OrderedCollection new. start _ 1. [start <= self size] whileTrue: [ (self at: start) isSeparator ifFalse: [ end _ start + 1. [end <= self size and: [(self at: end) isSeparator not]] whileTrue: [end _ end + 1]. substrings add: (self copyFrom: start to: end - 1). start _ end - 1]. start _ start + 1]. ^ substrings asArray! ! !Subgroup methodsFor: 'initialization' stamp: 'len 4/30/98 04:20'! initialize self elements: Set new! ! !Subgroup methodsFor: 'accessing-private' stamp: 'len 4/30/98 04:16'! elements ^ elements! ! !Subgroup methodsFor: 'accessing-private' stamp: 'len 4/30/98 04:11'! elements: aCollection elements _ aCollection! ! !Subgroup methodsFor: 'accessing' stamp: 'len 4/30/98 04:16'! add: anObject "Add the argument to the receiver. Answer the argument." ^ self elements add: anObject! ! !Subgroup methodsFor: 'accessing' stamp: 'len 5/1/98 04:39'! addAll: aCollection "Add the elements of argument to the receiver. Answer the argument." aCollection do: [ :each | self add: each]. ^ aCollection! ! !Subgroup methodsFor: 'accessing' stamp: 'len 5/5/98 00:14'! exponent "Answer the exponent of the receiver." | answer | answer _ 1. self do: [ :each | answer _ answer max: (self orderOf: each)]. ^ answer! ! !Subgroup methodsFor: 'accessing' stamp: 'len 4/30/98 05:03'! generators "Answer a set of generators of the receiver." ^ self elements! ! !Subgroup methodsFor: 'accessing' stamp: 'len 4/30/98 04:18'! order "Answer the order of the receiver." ^ self elements size! ! !Subgroup methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:13'! * anObject "Answer the product of the receiver by the argument." | answer | anObject class == self class ifFalse: [^ TranslatedSubgroup subgroup: self translation: anObject]. answer _ self class new. self do: [ :each | anObject do: [ :other | answer add: each * other]]. ^ answer! ! !Subgroup methodsFor: 'arithmetic' stamp: 'len 4/30/98 04:54'! / aSubgroup "Answer the factor group of the receiver by the argument." ^ self collect: [ :each | aSubgroup * each]! ! !Subgroup methodsFor: 'arithmetic' stamp: 'len 4/30/98 05:09'! direct: aSubgroup "Answer the direct product of the receiver by the argument." | answer | answer _ self class new. self do: [ :each | aSubgroup do: [ :other | answer add: (DirectProduct new add: each; add: other; yourself)]]. ^ answer! ! !Subgroup methodsFor: 'arithmetic' stamp: 'len 5/5/98 00:12'! intersect: aSubgroup "Answer the intersection of the receiver and the argument." ^ self select: [ :each | aSubgroup includes: each]! ! !Subgroup methodsFor: 'constants' stamp: 'len 4/30/98 04:41'! identity "Answer the identity element of the receiver." self do: [ :each | ^ each identity]! ! !Subgroup methodsFor: 'enumerating' stamp: 'len 4/30/98 04:18'! collect: aBlock "Answer the subgroup resulting of mapping the elements of the receiver by aBlock." | answer | answer _ self class new. self do: [ :each | answer add: (aBlock value: each)]. ^ answer! ! !Subgroup methodsFor: 'enumerating' stamp: 'len 4/30/98 04:43'! detect: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the first element for which aBlock evaluates to true." ^ self detect: aBlock ifNone: [self errorNotFound]! ! !Subgroup methodsFor: 'enumerating' stamp: 'len 4/30/98 04:43'! detect: aBlock ifNone: exceptionBlock "Evaluate aBlock with each of the receiver's elements as the argument. Answer the first element for which aBlock evaluates to true. If none evaluate to true, then evaluate the argument, exceptionBlock." self do: [:each | (aBlock value: each) ifTrue: [^each]]. ^ exceptionBlock value! ! !Subgroup methodsFor: 'enumerating' stamp: 'len 4/30/98 04:13'! do: aBlock "Enumerate the elements of the receiver." self elements do: aBlock! ! !Subgroup methodsFor: 'enumerating' stamp: 'len 4/30/98 04:52'! select: aBlock "Evaluate aBlock with each of the receiver's elements as the argument. Collect into a new collection like the receiver, only those elements for which aBlock evaluates to true. Answer the new collection." | newCollection | newCollection _ self species new. self do: [:each | (aBlock value: each) ifTrue: [newCollection add: each]]. ^ newCollection! ! !Subgroup methodsFor: 'enumerating' stamp: 'len 4/28/98 07:00'! subgroupsDo: aBlock "Enumerate the subgroups of the receiver." self notYetImplemented! ! !Subgroup methodsFor: 'subgroups' stamp: 'len 4/30/98 04:50'! center "Answer the center of the receiver." ^ self centralizerOf: self! ! !Subgroup methodsFor: 'subgroups' stamp: 'len 4/30/98 04:51'! centralizerOf: aCollection "Answer the normalizer of anObject in the receiver." ^ self select: [ :each | (aCollection detect: [ :one | each * one * each reciprocal ~= one] ifNone: []) isNil]! ! !Subgroup methodsFor: 'subgroups' stamp: 'len 4/30/98 15:16'! commutator "Answer the commutator of the receiver." | answer | answer _ self class new. self do: [ :each | self do: [ :other | answer add: each * other * each reciprocal * other reciprocal]]. ^ answer! ! !Subgroup methodsFor: 'subgroups' stamp: 'len 4/30/98 04:48'! normalizerOf: aCollection "Answer the normalizer of aCollection in the receiver." ^ self select: [ :any | (aCollection collect: [ :each | any * each * any reciprocal]) = aCollection]! ! !Subgroup methodsFor: 'comparing' stamp: 'len 5/1/98 17:43'! < aSubgroup "Answer true if the receiver is strictly included in the argument." ^ self order < aSubgroup order and: [self <= aSubgroup]! ! !Subgroup methodsFor: 'comparing' stamp: 'len 5/1/98 17:44'! <= aSubgroup "Answer true if the receiver is included in the argument." self order <= aSubgroup order ifFalse: [^ false]. self do: [ :each | (aSubgroup includes: each) ifFalse: [^ false]]. ^ true! ! !Subgroup methodsFor: 'comparing' stamp: 'len 4/30/98 05:11'! = aSubgroup "Answer true if the receiver equals the argument." ^ self elements = aSubgroup elements! ! !Subgroup methodsFor: 'comparing' stamp: 'len 5/1/98 17:44'! > aSubgroup "Answer true if the receiver strictly includes the argument." ^ aSubgroup < self! ! !Subgroup methodsFor: 'comparing' stamp: 'len 5/1/98 17:44'! >= aSubgroup "Answer true if the receiver includes the argument." ^ aSubgroup <= self! ! !Subgroup methodsFor: 'comparing' stamp: 'len 4/30/98 05:11'! hash "Answer the hash value of the receiver." ^ self elements hash! ! !Subgroup methodsFor: 'testing' stamp: 'len 4/28/98 07:01'! includes: anObject "Answer true if the receiver includes the argument." self do: [ :each | each = anObject ifTrue: [^ true]]. ^ false! ! !Subgroup methodsFor: 'testing' stamp: 'len 10/7/1998 04:33'! isAbelian "Answer true if the receiver is abelian." self do: [ :each | self do: [ :other | each * other = (other * each) ifFalse: [^ false]]]. ^ true! ! !Subgroup methodsFor: 'testing' stamp: 'len 4/30/98 05:03'! isCyclic "Answer true if the receiver is generated by one element." self notYetImplemented! ! !Subgroup methodsFor: 'testing' stamp: 'len 5/1/98 17:41'! isNormalIn: aSubgroup "Answer true if the receiver is normal as subgroup of aSubgroup." self do: [ :each | aSubgroup do: [ :other | (self includes: other * each * other reciprocal) ifFalse: [^ false]]]. ^ true! ! !Subgroup methodsFor: 'testing' stamp: 'len 4/30/98 04:14'! isTrivial "Answer true if the receiver is trivial." ^ self order = 1! ! !Subgroup methodsFor: 'private' stamp: 'len 5/5/98 00:16'! orderOf: anObject | product id answer | id _ self identity. product _ anObject. answer _ 1. [product = id] whileFalse: [answer _ answer + 1. product _ product * anObject]. ^ answer! ! !Subgroup methodsFor: 'printing' stamp: 'len 4/30/98 05:04'! printOn: aStream "Print a representation of the receiver on the stream aStream." | first | self isTrivial ifTrue: [aStream nextPutAll: '{', self identity printString, '}'. ^ self]. first _ true. aStream nextPut: $<. self generators do: [ :each | first ifFalse: [aStream nextPutAll: '; ']. aStream print: each. first _ false]. aStream nextPut: $>! ! !Subgroup class methodsFor: 'instance creation' stamp: 'len 5/2/98 20:19'! generators: aCollection "Answer the subgroup generated by the argument." | answer previous | answer _ self new addAll: aCollection; yourself. [previous _ answer. answer _ answer copy. previous do: [ :each | previous do: [ :other | answer add: each * other]]. previous order < answer order] whileTrue. ^ answer " (Subgroup symmetricOfOrder: 5) order 120 " ! ! !Subgroup class methodsFor: 'instance creation' stamp: 'len 4/30/98 04:20'! new ^ super new initialize! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 00:21'! alternating: n "Answer the group of alternate permutation of {1, ..., n}." ^ (self symmetric: n) select: [ :each | each even]! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 01:10'! automorphismsOf: aSubgroup "Answer the group of automorphisms of aSubgroup." self notYetImplemented! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 00:21'! dihedral: n "Answer the dihedral group of 2n elements." self notYetImplemented! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 01:12'! generalLinear: n mod: p "Answer the general linear group of n by n matrices whose entries are integers modulo p. (p must be prime.)" self notYetImplemented! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 01:07'! integersMod: anInteger "Answer the cyclic group of integers modulo anInteger." | answer | answer _ self new. 0 to: anInteger - 1 do: [ :each | answer add: (GroupAdditiveElement from: (each mod: anInteger))]. ^ answer! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/6/98 05:13'! permutationsOf: aCollection "Answer the group of permutations of aCollection." | generators | generators _ OrderedCollection with: Permutation new. aCollection do: [ :each | aCollection do: [ :other | generators add: (Permutation transpose: each with: other)]]. ^ self generators: generators! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 00:19'! quaternions "Answer the quaternionic group." ^ self generators: (Array with: Quaternion i with: Quaternion j)! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 00:24'! symmetric: n "Answer the group of permutations of {1, ..., n}." | generators | generators _ OrderedCollection with: Permutation new. 1 to: n do: [ :each | 1 to: n do: [ :other | generators add: (Permutation transpose: each with: other)]]. ^ self generators: generators! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 00:28'! unitsModulo: m "Answer the multiplicative group of units of integers modulo m." | answer element | answer _ self new. 1 to: m - 1 do: [ :each | (element _ each mod: m) isUnit ifTrue: [answer add: element]]. ^ answer! ! !Subgroup class methodsFor: 'examples' stamp: 'len 5/3/98 01:14'! unityRoots: n "Answer the group of n-th roots of unity." | answer | answer _ self new. 0 to: n - 1 do: [ :each | answer add: (RootOfUnity modular: (each mod: n))]. ^ answer! ! !TowerOfSubgroups methodsFor: 'initialization' stamp: 'len 5/1/98 17:32'! initialize self subgroups: OrderedCollection new! ! !TowerOfSubgroups methodsFor: 'accessing-private' stamp: 'len 5/1/98 17:33'! subgroups: aCollection subgroups _ aCollection! ! !TowerOfSubgroups methodsFor: 'accessing' stamp: 'len 5/1/98 17:35'! add: aSubgroup ^ self subgroups add: aSubgroup! ! !TowerOfSubgroups methodsFor: 'accessing' stamp: 'len 5/1/98 17:34'! at: anInteger ^ self subgroups at: anInteger! ! !TowerOfSubgroups methodsFor: 'accessing' stamp: 'len 5/1/98 17:34'! size ^ self subgroups size! ! !TowerOfSubgroups methodsFor: 'accessing' stamp: 'len 5/1/98 17:33'! subgroups ^ subgroups! ! !TowerOfSubgroups methodsFor: 'enumerating' stamp: 'len 5/1/98 17:35'! do: aBlock self subgroups do: aBlock! ! !TowerOfSubgroups methodsFor: 'testing' stamp: 'len 5/1/98 17:52'! isAbelian "Answer true if the receiver is an abelian tower of subgroups." self isNormal ifFalse: [^ false]. 2 to: self size do: [ :each | ((self at: each - 1) / (self at: each)) isAbelian ifFalse: [^ false]]. ^ true! ! !TowerOfSubgroups methodsFor: 'testing' stamp: 'len 5/3/98 01:07'! isCyclic "Answer true if the receiver is a cyclic tower of subgroups." self isNormal ifFalse: [^ false]. 2 to: self size do: [ :each | ((self at: each - 1) / (self at: each)) isCyclic ifFalse: [^ false]]. ^ true! ! !TowerOfSubgroups methodsFor: 'testing' stamp: 'len 5/1/98 17:47'! isNormal "Answer true if the receiver is a normal tower of subgroups." 2 to: self size do: [ :each | ((self at: each) isNormalIn: (self at: each - 1)) ifFalse: [^ false]]. ^ true! ! !TranslatedSubgroup methodsFor: 'accessing-private' stamp: 'len 4/28/98 07:14'! subgroup: aSubgroup subgroup _ aSubgroup! ! !TranslatedSubgroup methodsFor: 'accessing-private' stamp: 'len 4/28/98 07:14'! translation: anObject translation _ anObject! ! !TranslatedSubgroup methodsFor: 'accessing' stamp: 'len 4/28/98 07:15'! subgroup "Answer the subgroup associated to the receiver." ^ subgroup! ! !TranslatedSubgroup methodsFor: 'accessing' stamp: 'len 4/28/98 07:15'! translation "Answer the translation of the receiver (just an element in the receiver)." ^ translation! ! !TranslatedSubgroup methodsFor: 'arithmetic' stamp: 'len 4/30/98 03:53'! * aTranslatedSubgroup "Answer the multiplication of the receiver by the argument." ^ self class subgroup: self subgroup translation: self translation * aTranslatedSubgroup translation! ! !TranslatedSubgroup methodsFor: 'arithmetic' stamp: 'len 4/30/98 03:52'! reciprocal "Answer the multiplicative inverse of the receiver." ^ self class subgroup: self subgroup translation: self translation reciprocal! ! !TranslatedSubgroup methodsFor: 'enumerating' stamp: 'len 4/28/98 07:18'! do: aBlock "Enumerate the elements of the receiver." self subgroup do: [ :each | aBlock value: each * self translation]! ! !TranslatedSubgroup methodsFor: 'comparing' stamp: 'len 4/30/98 05:14'! = aTranslatedSubgroup "Answer true if the receiver equals the argument." ^ self subgroup includes: self translation * aTranslatedSubgroup translation reciprocal! ! !TranslatedSubgroup methodsFor: 'comparing' stamp: 'len 4/30/98 05:15'! hash "Answer the hash value of the receiver." ^ self subgroup hash! ! !TranslatedSubgroup methodsFor: 'testing' stamp: 'len 4/28/98 07:16'! includes: anObject "Answer true if the receiver includes the argument." ^ self subgroup includes: anObject * self translation reciprocal! ! !TranslatedSubgroup methodsFor: 'printing' stamp: 'len 4/28/98 07:17'! printOn: aStream "Print a representation of the receiver on the stream aStream." aStream print: self subgroup; nextPutAll: ' * '; print: self translation! ! !TranslatedSubgroup class methodsFor: 'instance creation' stamp: 'len 4/28/98 07:20'! subgroup: aSubgroup translation: anObject "Answer a new instance of the receiver representing the right translation of aSubgroup by anObject." ^ self new subgroup: aSubgroup; translation: anObject! !