| 12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970717273747576777879808182838485868788899091929394959697989910010110210310410510610710810911011111211311411511611711811912012112212312412512612712812913013113213313413513613713813914014114214314414514614714814915015115215315415515615715815916016116216316416516616716816917017117217317417517617717817918018118218318418518618718818919019119219319419519619719819920020120220320420520620720820921021121221321421521621721821922022122222322422522622722822923023123223323423523623723823924024124224324424524624724824925025125225325425525625725825926026126226326426526626726826927027127227327427527627727827928028128228328428528628728828929029129229329429529629729829930030130230330430530630730830931031131231331431531631731831932032132232332432532632732832933033133233333433533633733833934034134234334434534634734834935035135235335435535635735835936036136236336436536636736836937037137237337437537637737837938038138238338438538638738838939039139239339439539639739839940040140240340440540640740840941041141241341441541641741841942042142242342442542642742842943043143243343443543643743843944044144244344444544644744844945045145245345445545645745845946046146246346446546646746846947047147247347447547647747847948048148248348448548648748848949049149249349449549649749849950050150250350450550650750850951051151251351451551651751851952052152252352452552652752852953053153253353453553653753853954054154254354454554654754854955055155255355455555655755855956056156256356456556656756856957057157257357457557657757857958058158258358458558658758858959059159259359459559659759859960060160260360460560660760860961061161261361461561661761861962062162262362462562662762862963063163263363463563663763863964064164264364464564664764864965065165265365465565665765865966066166266366466566666766866967067167267367467567667767867968068168268368468568668768868969069169269369469569669769869970070170270370470570670770870971071171271371471571671771871972072172272372472572672772872973073173273373473573673773873974074174274374474574674774874975075175275375475575675775875976076176276376476576676776876977077177277377477577677777877978078178278378478578678778878979079179279379479579679779879980080180280380480580680780880981081181281381481581681781881982082182282382482582682782882983083183283383483583683783883984084184284384484584684784884985085185285385485585685785885986086186286386486586686786886987087187287387487587687787887988088188288388488588688788888989089189289389489589689789889990090190290390490590690790890991091191291391491591691791891992092192292392492592692792892993093193293393493593693793893994094194294394494594694794894995095195295395495595695795895996096196296396496596696796896997097197297397497597697797897998098198298398498598698798898999099199299399499599699799899910001001100210031004100510061007100810091010101110121013101410151016101710181019102010211022102310241025102610271028102910301031103210331034103510361037103810391040104110421043104410451046104710481049105010511052105310541055105610571058105910601061106210631064106510661067106810691070107110721073107410751076107710781079108010811082108310841085108610871088108910901091109210931094109510961097109810991100110111021103110411051106110711081109111011111112111311141115111611171118111911201121112211231124112511261127112811291130113111321133113411351136113711381139114011411142114311441145114611471148114911501151115211531154115511561157115811591160116111621163116411651166116711681169117011711172117311741175117611771178117911801181118211831184118511861187118811891190119111921193119411951196119711981199120012011202120312041205120612071208120912101211121212131214121512161217121812191220122112221223122412251226122712281229123012311232123312341235123612371238123912401241124212431244124512461247124812491250125112521253125412551256125712581259126012611262126312641265126612671268126912701271127212731274127512761277127812791280128112821283128412851286128712881289129012911292129312941295129612971298129913001301130213031304130513061307130813091310131113121313 | 
							- Smalltalk current createPackage: 'Kernel-Objects'!
 
- nil subclass: #Object
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Objects'!
 
- !Object commentStamp!
 
- **I am the root of the Smalltalk class system**. All classes in the system are subclasses of me.
 
- I provide default behavior common to all normal objects, such as:
 
- - accessing
 
- - copying
 
- - comparison
 
- - error handling
 
- - message sending
 
- - reflection
 
- Also utility messages that all objects should respond to are defined here.
 
- I have no instance variable.
 
- ##Access
 
- Instance variables can be accessed with `#instVarAt:` and `#instVarAt:put:`. `#instanceVariableNames` answers a collection of all instance variable names.
 
- Accessing JavaScript properties of an object is done through `#basicAt:`, `#basicAt:put:` and `basicDelete:`.
 
- ##Copying
 
- Copying an object is handled by `#copy` and `#deepCopy`. The first one performs a shallow copy of the receiver, while the second one performs a deep copy.
 
- The hook method `#postCopy` can be overriden in subclasses to copy fields as necessary to complete the full copy. It will be sent by the copy of the receiver.
 
- ##Comparison
 
- I understand equality `#=` and identity `#==` comparison.
 
- ##Error handling
 
- - `#halt` is the typical message to use for inserting breakpoints during debugging.
 
- - `#error:` throws a generic error exception
 
- - `#doesNotUnderstand:` handles the fact that there was an attempt to send the given message to the receiver but the receiver does not understand this message.
 
- 	Overriding this message can be useful to implement proxies for example.!
 
- !Object methodsFor: 'accessing'!
 
- basicAt: aString
 
- 	<return self[aString]>
 
- !
 
- basicAt: aString put: anObject
 
- 	<return self[aString] = anObject>
 
- !
 
- basicDelete: aString
 
- 	<delete self[aString]; return aString>
 
- !
 
- class
 
- 	<return self.klass>
 
- !
 
- identityHash
 
- 	<
 
- 	var hash=self.identityHash;
 
- 	if (hash) return hash;
 
- 	hash=smalltalk.nextId();
 
- 	Object.defineProperty(self, 'identityHash', {value:hash});
 
- 	return hash;
 
- 	>
 
- !
 
- instVarAt: aString
 
- 	< return self['@'+aString] >
 
- !
 
- instVarAt: aString put: anObject
 
- 	< self['@' + aString] = anObject >
 
- !
 
- size
 
- 	self error: 'Object not indexable'
 
- !
 
- value
 
- 	<return self.valueOf()>
 
- !
 
- yourself
 
- 	^ self
 
- ! !
 
- !Object methodsFor: 'comparing'!
 
- = anObject
 
- 	^ self == anObject
 
- !
 
- == anObject
 
- 	^ self identityHash = anObject identityHash
 
- !
 
- ~= anObject
 
- 	^ (self = anObject) = false
 
- !
 
- ~~ anObject
 
- 	^ (self == anObject) = false
 
- ! !
 
- !Object methodsFor: 'converting'!
 
- -> anObject
 
- 	^ Association key: self value: anObject
 
- !
 
- asJSON
 
- 	| variables |
 
- 	variables := HashedCollection new.
 
- 	self class allInstanceVariableNames do: [ :each |
 
- 		variables at: each put: (self instVarAt: each) asJSON ].
 
- 	^ variables
 
- !
 
- asJSONString
 
- 	^ JSON stringify: self asJSON
 
- !
 
- asJavascript
 
- 	^ self asString
 
- !
 
- asString
 
- 	^ self printString
 
- !
 
- test
 
- 	| a |
 
- 	a := 1.
 
- 	self halt
 
- ! !
 
- !Object methodsFor: 'copying'!
 
- copy
 
- 	^ self shallowCopy postCopy
 
- !
 
- deepCopy
 
- 	<
 
- 		var copy = self.klass._new();
 
- 		for(var i in self) {
 
- 		if(/^@.+/.test(i)) {
 
- 			copy[i] = self[i]._deepCopy();
 
- 		}
 
- 		}
 
- 		return copy;
 
- 	>
 
- !
 
- postCopy
 
- !
 
- shallowCopy
 
- 	<
 
- 		var copy = self.klass._new();
 
- 		for(var i in self) {
 
- 		if(/^@.+/.test(i)) {
 
- 			copy[i] = self[i];
 
- 		}
 
- 		}
 
- 		return copy;
 
- 	>
 
- ! !
 
- !Object methodsFor: 'error handling'!
 
- deprecatedAPI
 
- 	"Just a simple way to deprecate methods.
 
- 	#deprecatedAPI is in the 'error handling' protocol even if it doesn't throw an error,
 
- 	but it could in the future."
 
- 	console warn: thisContext home asString, ' is deprecated!! (in ', thisContext home home asString, ')'
 
- !
 
- doesNotUnderstand: aMessage
 
- 	MessageNotUnderstood new
 
- 		receiver: self;
 
- 		message: aMessage;
 
- 		signal
 
- !
 
- error: aString
 
- 	Error signal: aString
 
- !
 
- halt
 
- 	self error: 'Halt encountered'
 
- !
 
- shouldNotImplement
 
- 	self error: 'This method should not be implemented in ', self class name
 
- !
 
- subclassResponsibility
 
- 	self error: 'This method is a responsibility of a subclass'
 
- !
 
- throw: anObject
 
- 	< throw anObject >
 
- !
 
- try: aBlock catch: anotherBlock
 
- 	<try{return aBlock._value()} catch(e) {return anotherBlock._value_(e)}>
 
- ! !
 
- !Object methodsFor: 'initialization'!
 
- initialize
 
- ! !
 
- !Object methodsFor: 'inspecting'!
 
- inspect
 
- 	InspectorHandler inspect: self
 
- !
 
- inspectOn: anInspector
 
- 	| variables |
 
- 	variables := Dictionary new.
 
- 	variables at: '#self' put: self.
 
- 	self class allInstanceVariableNames do: [ :each |
 
- 		variables at: each put: (self instVarAt: each) ].
 
- 	anInspector
 
- 		setLabel: self printString;
 
- 		setVariables: variables
 
- ! !
 
- !Object methodsFor: 'message handling'!
 
- basicPerform: aString
 
- 	^ self basicPerform: aString withArguments: #()
 
- !
 
- basicPerform: aString withArguments: aCollection
 
- 	<return self[aString].apply(self, aCollection);>
 
- !
 
- perform: aString
 
- 	^ self perform: aString withArguments: #()
 
- !
 
- perform: aString withArguments: aCollection
 
- 	<return smalltalk.send(self, aString._asSelector(), aCollection)>
 
- ! !
 
- !Object methodsFor: 'printing'!
 
- printOn: aStream
 
- 	"Append to the aStream, a string representing the receiver."
 
- 	
 
- 	aStream nextPutAll: (self class name first isVowel
 
- 		ifTrue: [ 'an ' ]
 
- 		ifFalse: [ 'a ' ]).
 
- 	aStream nextPutAll: self class name
 
- !
 
- printString
 
- 	"Answer a String representation of the receiver."
 
- 	^ String streamContents: [ :stream | self printOn: stream ]
 
- ! !
 
- !Object methodsFor: 'streaming'!
 
- putOn: aStream
 
- 	aStream nextPut: self
 
- ! !
 
- !Object methodsFor: 'testing'!
 
- ifNil: aBlock
 
- 	"inlined in the Compiler"
 
- 	^ self
 
- !
 
- ifNil: aBlock ifNotNil: anotherBlock
 
- 	"inlined in the Compiler"
 
- 	^ anotherBlock value: self
 
- !
 
- ifNotNil: aBlock
 
- 	"inlined in the Compiler"
 
- 	^ aBlock value: self
 
- !
 
- ifNotNil: aBlock ifNil: anotherBlock
 
- 	"inlined in the Compiler"
 
- 	^ aBlock value: self
 
- !
 
- isBehavior
 
- 	^ false
 
- !
 
- isBoolean
 
- 	^ false
 
- !
 
- isClass
 
- 	^ false
 
- !
 
- isCompiledMethod
 
- 	^ false
 
- !
 
- isImmutable
 
- 	^ false
 
- !
 
- isKindOf: aClass
 
- 	^ (self isMemberOf: aClass)
 
- 		ifTrue: [ true ]
 
- 		ifFalse: [ self class inheritsFrom: aClass ]
 
- !
 
- isMemberOf: aClass
 
- 	^ self class = aClass
 
- !
 
- isMetaclass
 
- 	^ false
 
- !
 
- isNil
 
- 	^ false
 
- !
 
- isNumber
 
- 	^ false
 
- !
 
- isPackage
 
- 	^ false
 
- !
 
- isParseFailure
 
- 	^ false
 
- !
 
- isString
 
- 	^ false
 
- !
 
- isSymbol
 
- 	^ false
 
- !
 
- notNil
 
- 	^ self isNil not
 
- !
 
- respondsTo: aSelector
 
- 	^ self class canUnderstand: aSelector
 
- ! !
 
- !Object class methodsFor: 'helios'!
 
- heliosClass
 
- 	"Should be an Helios extension. Unfortunately, since helios can browse remote
 
- 	environments, we can't extend base classes"
 
- 	
 
- 	^ 'class'
 
- ! !
 
- !Object class methodsFor: 'initialization'!
 
- initialize
 
- 	"no op"
 
- ! !
 
- Object subclass: #Boolean
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Objects'!
 
- !Boolean commentStamp!
 
- I define the protocol for logic testing operations and conditional control structures for the logical values (see the `controlling` protocol).
 
- I have two instances, `true` and `false`.
 
- I am directly mapped to JavaScript Boolean. The `true` and `false` objects are the JavaScript boolean objects.
 
- ## Usage Example:
 
-     aBoolean not ifTrue: [ ... ] ifFalse: [ ... ]!
 
- !Boolean methodsFor: 'comparing'!
 
- = aBoolean
 
- 	<
 
- 		if(!! aBoolean._isBoolean || !! aBoolean._isBoolean()) {
 
- 			return false;
 
- 		}
 
- 		return Boolean(self == true) == aBoolean
 
- 	>
 
- !
 
- == aBoolean
 
- 	^ self = aBoolean
 
- ! !
 
- !Boolean methodsFor: 'controlling'!
 
- & aBoolean
 
- 	<
 
- 		if(self == true) {
 
- 		return aBoolean;
 
- 		} else {
 
- 		return false;
 
- 		}
 
- 	>
 
- !
 
- and: aBlock
 
- 	^ self = true
 
- 		ifTrue: aBlock
 
- 		ifFalse: [ false ]
 
- !
 
- ifFalse: aBlock
 
- 	"inlined in the Compiler"
 
- 	^ self ifTrue: [] ifFalse: aBlock
 
- !
 
- ifFalse: aBlock ifTrue: anotherBlock
 
- 	"inlined in the Compiler"
 
- 	^ self ifTrue: anotherBlock ifFalse: aBlock
 
- !
 
- ifTrue: aBlock
 
- 	"inlined in the Compiler"
 
- 	^ self ifTrue: aBlock ifFalse: []
 
- !
 
- ifTrue: aBlock ifFalse: anotherBlock
 
- 	"inlined in the Compiler"
 
- 	<
 
- 		if(self == true) {
 
- 		return aBlock._value();
 
- 		} else {
 
- 		return anotherBlock._value();
 
- 		}
 
- 	>
 
- !
 
- not
 
- 	^ self = false
 
- !
 
- or: aBlock
 
- 	^ self = true
 
- 		ifTrue: [ true ]
 
- 		ifFalse: aBlock
 
- !
 
- | aBoolean
 
- 	<
 
- 		if(self == true) {
 
- 		return true;
 
- 		} else {
 
- 		return aBoolean;
 
- 		}
 
- 	>
 
- ! !
 
- !Boolean methodsFor: 'converting'!
 
- asBit
 
- 	^ self ifTrue: [ 1 ] ifFalse: [ 0 ]
 
- !
 
- asJSON
 
- 	^ self
 
- !
 
- asString
 
- 	< return self.toString() >
 
- ! !
 
- !Boolean methodsFor: 'copying'!
 
- deepCopy
 
- 	^ self
 
- !
 
- shallowCopy
 
- 	^ self
 
- ! !
 
- !Boolean methodsFor: 'printing'!
 
- printOn: aStream
 
- 	aStream nextPutAll: self asString
 
- ! !
 
- !Boolean methodsFor: 'testing'!
 
- isBoolean
 
- 	^ true
 
- !
 
- isImmutable
 
- 	^ true
 
- ! !
 
- Object subclass: #Date
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Objects'!
 
- !Date commentStamp!
 
- I am used to work with both dates and times. Therefore `Date today` and `Date now` are both valid in
 
- Amber and answer the same date object.
 
- Date directly maps to the `Date()` JavaScript constructor, and Amber date objects are JavaScript date objects.
 
- ## API
 
- The class-side `instance creation` protocol contains some convenience methods for creating date/time objects such as `#fromSeconds:`.
 
- Arithmetic and comparison is supported (see the `comparing` and `arithmetic` protocols).
 
- The `converting` protocol provides convenience methods for various convertions (to numbers, strings, etc.).!
 
- !Date methodsFor: 'accessing'!
 
- day
 
- 	^ self dayOfWeek
 
- !
 
- day: aNumber
 
- 	self dayOfWeek: aNumber
 
- !
 
- dayOfMonth
 
- 	<return self.getDate()>
 
- !
 
- dayOfMonth: aNumber
 
- 	<self.setDate(aNumber)>
 
- !
 
- dayOfWeek
 
- 	<return self.getDay() + 1>
 
- !
 
- dayOfWeek: aNumber
 
- 	<return self.setDay(aNumber - 1)>
 
- !
 
- hours
 
- 	<return self.getHours()>
 
- !
 
- hours: aNumber
 
- 	<self.setHours(aNumber)>
 
- !
 
- milliseconds
 
- 	<return self.getMilliseconds()>
 
- !
 
- milliseconds: aNumber
 
- 	<self.setMilliseconds(aNumber)>
 
- !
 
- minutes
 
- 	<return self.getMinutes()>
 
- !
 
- minutes: aNumber
 
- 	<self.setMinutes(aNumber)>
 
- !
 
- month
 
- 	<return self.getMonth() + 1>
 
- !
 
- month: aNumber
 
- 	<self.setMonth(aNumber - 1)>
 
- !
 
- seconds
 
- 	<return self.getSeconds()>
 
- !
 
- seconds: aNumber
 
- 	<self.setSeconds(aNumber)>
 
- !
 
- time
 
- 	<return self.getTime()>
 
- !
 
- time: aNumber
 
- 	<self.setTime(aNumber)>
 
- !
 
- year
 
- 	<return self.getFullYear()>
 
- !
 
- year: aNumber
 
- 	<self.setFullYear(aNumber)>
 
- ! !
 
- !Date methodsFor: 'arithmetic'!
 
- + aDate
 
- 	<return self + aDate>
 
- !
 
- - aDate
 
- 	<return self - aDate>
 
- ! !
 
- !Date methodsFor: 'comparing'!
 
- < aDate
 
- 	<return self < aDate>
 
- !
 
- <= aDate
 
- 	<return self <= aDate>
 
- !
 
- > aDate
 
- 	<return self >> aDate>
 
- !
 
- >= aDate
 
- 	<return self >>= aDate>
 
- ! !
 
- !Date methodsFor: 'converting'!
 
- asDateString
 
- 	<return self.toDateString()>
 
- !
 
- asLocaleString
 
- 	<return self.toLocaleString()>
 
- !
 
- asMilliseconds
 
- 	^ self time
 
- !
 
- asNumber
 
- 	^ self asMilliseconds
 
- !
 
- asString
 
- 	<return self.toString()>
 
- !
 
- asTimeString
 
- 	<return self.toTimeString()>
 
- ! !
 
- !Date methodsFor: 'printing'!
 
- printOn: aStream
 
- 	aStream nextPutAll: self asString
 
- ! !
 
- !Date class methodsFor: 'helios'!
 
- heliosClass
 
- 	^ 'magnitude'
 
- ! !
 
- !Date class methodsFor: 'instance creation'!
 
- fromMilliseconds: aNumber
 
- 	^ self new: aNumber
 
- !
 
- fromSeconds: aNumber
 
- 	^ self fromMilliseconds: aNumber * 1000
 
- !
 
- fromString: aString
 
- 	"Example: Date fromString('2011/04/15 00:00:00')"
 
- 	^ self new: aString
 
- !
 
- millisecondsToRun: aBlock
 
- 	| t |
 
- 	t := Date now.
 
- 	aBlock value.
 
- 	^ Date now - t
 
- !
 
- new: anObject
 
- 	<return new Date(anObject)>
 
- !
 
- now
 
- 	^ self today
 
- !
 
- today
 
- 	^ self new
 
- ! !
 
- Object subclass: #Number
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Objects'!
 
- !Number commentStamp!
 
- I am the Amber representation for all numbers.
 
- I am directly mapped to JavaScript Number.
 
- ## API
 
- I provide all necessary methods for arithmetic operations, comparison, conversion and so on with numbers.
 
- My instances can also be used to evaluate a block a fixed number of times:
 
- 	5 timesRepeat: [ Transcript show: 'This will be printed 5 times'; cr ].
 
- 	
 
- 	1 to: 5 do: [ :aNumber| Transcript show: aNumber asString; cr ].
 
- 	
 
- 	1 to: 10 by: 2 do: [ :aNumber| Transcript show: aNumber asString; cr ].!
 
- !Number methodsFor: 'accessing'!
 
- identityHash
 
- 	^ self asString, 'n'
 
- ! !
 
- !Number methodsFor: 'arithmetic'!
 
- * aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self * aNumber>
 
- !
 
- + aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self + aNumber>
 
- !
 
- - aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self - aNumber>
 
- !
 
- / aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self / aNumber>
 
- !
 
- // aNumber
 
- 	^ (self / aNumber) floor
 
- !
 
- \\ aNumber
 
- 	<return self % aNumber>
 
- !
 
- abs
 
- 	<return Math.abs(self);>
 
- !
 
- max: aNumber
 
- 	<return Math.max(self, aNumber);>
 
- !
 
- min: aNumber
 
- 	<return Math.min(self, aNumber);>
 
- !
 
- negated
 
- 	^ 0 - self
 
- ! !
 
- !Number methodsFor: 'comparing'!
 
- < aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self < aNumber>
 
- !
 
- <= aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self <= aNumber>
 
- !
 
- = aNumber
 
- 	<
 
- 		if(!! aNumber._isNumber || !! aNumber._isNumber()) {
 
- 			return false;
 
- 		}
 
- 		return Number(self) == aNumber
 
- 	>
 
- !
 
- > aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self >> aNumber>
 
- !
 
- >= aNumber
 
- 	"Inlined in the Compiler"
 
- 	<return self >>= aNumber>
 
- ! !
 
- !Number methodsFor: 'converting'!
 
- & aNumber
 
- 	<return self & aNumber>
 
- !
 
- @ aNumber
 
- 	^ Point x: self y: aNumber
 
- !
 
- asJSON
 
- 	^ self
 
- !
 
- asJavascript
 
- 	^ '(', self printString, ')'
 
- !
 
- asNumber
 
- 	^ self
 
- !
 
- asPoint
 
- 	^ Point x: self y: self
 
- !
 
- asString
 
- 	< return String(self) >
 
- !
 
- atRandom
 
- 	^ (Random new next * self) truncated + 1
 
- !
 
- ceiling
 
- 	<return Math.ceil(self);>
 
- !
 
- floor
 
- 	<return Math.floor(self);>
 
- !
 
- rounded
 
- 	<return Math.round(self);>
 
- !
 
- to: aNumber
 
- 	| array first last count |
 
- 	first := self truncated.
 
- 	last := aNumber truncated + 1.
 
- 	count := 1.
 
- 	array := Array new.
 
- 	(last - first) timesRepeat: [
 
- 		array at: count put: first.
 
- 		count := count + 1.
 
- 		first := first + 1 ].
 
- 	^ array
 
- !
 
- to: stop by: step
 
- 	| array value pos |
 
- 	value := self.
 
- 	array := Array new.
 
- 	pos := 1.
 
- 	step = 0 ifTrue: [ self error: 'step must be non-zero' ].
 
- 	step < 0
 
- 		ifTrue: [ [ value >= stop ] whileTrue: [
 
- 					array at: pos put: value.
 
- 					pos := pos + 1.
 
- 					value := value + step ]]
 
- 		ifFalse: [ [ value <= stop ] whileTrue: [
 
- 					array at: pos put: value.
 
- 				pos := pos + 1.
 
- 					value := value + step ]].
 
- 	^ array
 
- !
 
- truncated
 
- 	<
 
- 		if(self >>= 0) {
 
- 			return Math.floor(self);
 
- 		} else {
 
- 			return Math.floor(self * (-1)) * (-1);
 
- 		};
 
- 	>
 
- !
 
- | aNumber
 
- 	<return self | aNumber>
 
- ! !
 
- !Number methodsFor: 'copying'!
 
- copy
 
- 	^ self
 
- !
 
- deepCopy
 
- 	^ self copy
 
- ! !
 
- !Number methodsFor: 'enumerating'!
 
- timesRepeat: aBlock
 
- 	| count |
 
- 	count := 1.
 
- 	[ count > self ] whileFalse: [
 
- 		aBlock value.
 
- 		count := count + 1 ]
 
- !
 
- to: stop by: step do: aBlock
 
- 	| value |
 
- 	value := self.
 
- 	step = 0 ifTrue: [ self error: 'step must be non-zero' ].
 
- 	step < 0
 
- 		ifTrue: [ [ value >= stop ] whileTrue: [
 
- 					aBlock value: value.
 
- 					value := value + step ]]
 
- 		ifFalse: [ [ value <= stop ] whileTrue: [
 
- 					aBlock value: value.
 
- 					value := value + step ]]
 
- !
 
- to: stop do: aBlock
 
- 	"Evaluate aBlock for each number from self to aNumber."
 
- 	| nextValue |
 
- 	nextValue := self.
 
- 	[ nextValue <= stop ]
 
- 		whileTrue:
 
- 			[ aBlock value: nextValue.
 
- 			nextValue := nextValue + 1 ]
 
- ! !
 
- !Number methodsFor: 'mathematical functions'!
 
- ** exponent
 
- 	^ self raisedTo: exponent
 
- !
 
- arcCos
 
- 	<return Math.acos(self);>
 
- !
 
- arcSin
 
- 	<return Math.asin(self);>
 
- !
 
- arcTan
 
- 	<return Math.atan(self);>
 
- !
 
- cos
 
- 	<return Math.cos(self);>
 
- !
 
- ln
 
- 	<return Math.log(self);>
 
- !
 
- log
 
- 	<return Math.log(self) / Math.LN10;>
 
- !
 
- log: aNumber
 
- 	<return Math.log(self) / Math.log(aNumber);>
 
- !
 
- raisedTo: exponent
 
- 	<return Math.pow(self, exponent);>
 
- !
 
- sign
 
- 	self isZero 
 
- 		ifTrue: [ ^ 0 ].
 
- 	self positive
 
- 		ifTrue: [ ^ 1 ]
 
- 		ifFalse: [ ^ -1 ].
 
- !
 
- sin
 
- 	<return Math.sin(self);>
 
- !
 
- sqrt
 
- 	<return Math.sqrt(self)>
 
- !
 
- squared
 
- 	^ self * self
 
- !
 
- tan
 
- 	<return Math.tan(self);>
 
- ! !
 
- !Number methodsFor: 'printing'!
 
- printOn: aStream
 
- 	aStream nextPutAll: self asString
 
- !
 
- printShowingDecimalPlaces: placesDesired
 
- 	<return self.toFixed(placesDesired)>
 
- ! !
 
- !Number methodsFor: 'testing'!
 
- even
 
- 	^ 0 = (self \\ 2)
 
- !
 
- isImmutable
 
- 	^ true
 
- !
 
- isNumber
 
- 	^ true
 
- !
 
- isZero
 
- 	^ self = 0
 
- !
 
- negative
 
- 	"Answer whether the receiver is mathematically negative."
 
- 	^ self < 0
 
- !
 
- odd
 
- 	^ self even not
 
- !
 
- positive
 
- 	"Answer whether the receiver is positive or equal to 0. (ST-80 protocol)."
 
- 	^ self >= 0
 
- ! !
 
- !Number class methodsFor: 'helios'!
 
- heliosClass
 
- 	^ 'magnitude'
 
- ! !
 
- !Number class methodsFor: 'instance creation'!
 
- e
 
- 	<return Math.E;>
 
- !
 
- fromNumber: aNumber
 
- 	<return Number(aNumber)>
 
- !
 
- pi
 
- 	<return Math.PI>
 
- ! !
 
- Object subclass: #Point
 
- 	instanceVariableNames: 'x y'
 
- 	package: 'Kernel-Objects'!
 
- !Point commentStamp!
 
- I represent an x-y pair of numbers usually designating a geometric coordinate.
 
- ## API
 
- Instances are traditionally created using the binary `#@` message to a number:
 
- 	100@120
 
- Points can then be arithmetically manipulated:
 
- 	100@100 + (10@10)
 
- ...or for example:
 
- 	(100@100) * 2
 
- **NOTE:** Creating a point with a negative y-value will need a space after `@` in order to avoid a parsing error:
 
- 	100@ -100 "but 100@-100 would not parse"!
 
- !Point methodsFor: 'accessing'!
 
- x
 
- 	^ x
 
- !
 
- x: aNumber
 
- 	x := aNumber
 
- !
 
- y
 
- 	^ y
 
- !
 
- y: aNumber
 
- 	y := aNumber
 
- ! !
 
- !Point methodsFor: 'arithmetic'!
 
- * aPoint
 
- 	^ Point x: self x * aPoint asPoint x y: self y * aPoint asPoint y
 
- !
 
- + aPoint
 
- 	^ Point x: self x + aPoint asPoint x y: self y + aPoint asPoint y
 
- !
 
- - aPoint
 
- 	^ Point x: self x - aPoint asPoint x y: self y - aPoint asPoint y
 
- !
 
- / aPoint
 
- 	^ Point x: self x / aPoint asPoint x y: self y / aPoint asPoint y
 
- !
 
- = aPoint
 
- 	^ aPoint class = self class and: [
 
- 		(aPoint x = self x) & (aPoint y = self y) ]
 
- ! !
 
- !Point methodsFor: 'converting'!
 
- asPoint
 
- 	^ self
 
- ! !
 
- !Point methodsFor: 'printing'!
 
- printOn: aStream
 
- 	"Print receiver in classic x@y notation."
 
- 	x printOn: aStream.
 
- 	
 
- 	aStream nextPutAll: '@'.
 
- 	(y notNil and: [ y negative ]) ifTrue: [
 
- 			"Avoid ambiguous @- construct"
 
- 			aStream space ].
 
- 	
 
- 	y printOn: aStream
 
- ! !
 
- !Point methodsFor: 'transforming'!
 
- translateBy: delta
 
- 	"Answer a Point translated by delta (an instance of Point)."
 
- 	^ (delta x + x) @ (delta y + y)
 
- ! !
 
- !Point class methodsFor: 'helios'!
 
- heliosClass
 
- 	^ 'magnitude'
 
- ! !
 
- !Point class methodsFor: 'instance creation'!
 
- x: aNumber y: anotherNumber
 
- 	^ self new
 
- 		x: aNumber;
 
- 		y: anotherNumber;
 
- 		yourself
 
- ! !
 
- Object subclass: #Random
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Objects'!
 
- !Random commentStamp!
 
- I an used to generate a random number and I am implemented as a trivial wrapper around javascript `Math.random()`.
 
- ## API
 
- The typical use case it to use the `#next` method like the following:
 
- 	Random new next
 
- This will return a float x where x < 1 and x > 0. If you want a random integer from 1 to 10 you can use `#atRandom`
 
- 	10 atRandom
 
- A random number in a specific interval can be obtained with the following:
 
- 	(3 to: 7) atRandom
 
- Be aware that `#to:` does not create an Interval as in other Smalltalk implementations but in fact an `Array` of numbers, so it's better to use:
 
- 	5 atRandom + 2
 
- Since `#atRandom` is implemented in `SequencableCollection` you can easy pick an element at random:
 
- 	#('a' 'b' 'c') atRandom
 
- As well as letter from a `String`:
 
- 	'abc' atRandom
 
- Since Amber does not have Characters this will return a `String` of length 1 like for example `'b'`.!
 
- !Random methodsFor: 'accessing'!
 
- next
 
- 	<return Math.random()>
 
- !
 
- next: anInteger
 
- 	^ (1 to: anInteger) collect: [ :each | self next ]
 
- ! !
 
- Object subclass: #UndefinedObject
 
- 	instanceVariableNames: ''
 
- 	package: 'Kernel-Objects'!
 
- !UndefinedObject commentStamp!
 
- I describe the behavior of my sole instance, `nil`. `nil` represents a prior value for variables that have not been initialized, or for results which are meaningless.
 
- `nil` is the Smalltalk equivalent of the `undefined` JavaScript object.
 
- __note:__ When sending messages to the `undefined` JavaScript object, it will be replaced by `nil`.!
 
- !UndefinedObject methodsFor: 'class creation'!
 
- subclass: aString instanceVariableNames: anotherString
 
- 	^ self subclass: aString instanceVariableNames: anotherString package: nil
 
- !
 
- subclass: aString instanceVariableNames: aString2 category: aString3
 
- 	"Kept for compatibility."
 
- 	self deprecatedAPI.
 
- 	^ self subclass: aString instanceVariableNames: aString2 package: aString3
 
- !
 
- subclass: aString instanceVariableNames: aString2 package: aString3
 
- 	^ ClassBuilder new
 
- 		superclass: self subclass: aString asString instanceVariableNames: aString2 package: aString3
 
- ! !
 
- !UndefinedObject methodsFor: 'converting'!
 
- asJSON
 
- 	^ null
 
- ! !
 
- !UndefinedObject methodsFor: 'copying'!
 
- deepCopy
 
- 	^ self
 
- !
 
- shallowCopy
 
- 	^ self
 
- ! !
 
- !UndefinedObject methodsFor: 'printing'!
 
- printOn: aStream
 
- 	aStream nextPutAll: 'nil'
 
- ! !
 
- !UndefinedObject methodsFor: 'testing'!
 
- ifNil: aBlock
 
- 	"inlined in the Compiler"
 
- 	^ self ifNil: aBlock ifNotNil: []
 
- !
 
- ifNil: aBlock ifNotNil: anotherBlock
 
- 	"inlined in the Compiler"
 
- 	^ aBlock value
 
- !
 
- ifNotNil: aBlock
 
- 	"inlined in the Compiler"
 
- 	^ self
 
- !
 
- ifNotNil: aBlock ifNil: anotherBlock
 
- 	"inlined in the Compiler"
 
- 	^ anotherBlock value
 
- !
 
- isImmutable
 
- 	^ true
 
- !
 
- isNil
 
- 	^ true
 
- !
 
- notNil
 
- 	^ false
 
- ! !
 
- !UndefinedObject class methodsFor: 'instance creation'!
 
- new
 
- 		self error: 'You cannot create new instances of UndefinedObject. Use nil'
 
- ! !
 
 
  |