123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386 |
- Smalltalk createPackage: 'Kernel-Objects'!
- nil subclass: #ProtoObject
- instanceVariableNames: ''
- package: 'Kernel-Objects'!
- !ProtoObject commentStamp!
- I implement the basic behavior required for any object in Amber.
- In most cases, subclassing `ProtoObject` is wrong and `Object` should be used instead. However subclassing `ProtoObject` can be useful in some special cases like proxy implementations.!
- !ProtoObject methodsFor: 'accessing'!
- class
- <inlineJS: 'return self.klass'>
- !
- identityHash
- <inlineJS: '
- var hash=self.identityHash;
- if (hash) return hash;
- hash=$core.nextId();
- Object.defineProperty(self, ''identityHash'', {value:hash});
- return hash;
- '>
- !
- instVarAt: aString
- <inlineJS: 'return self[''@''+aString]'>
- !
- instVarAt: aString put: anObject
- <inlineJS: 'self[''@'' + aString] = anObject'>
- !
- yourself
- ^ self
- ! !
- !ProtoObject methodsFor: 'comparing'!
- = anObject
- ^ self == anObject
- !
- == anObject
- <inlineJS:
- 'return self._class() === $recv(anObject)._class() && self._isSameInstanceAs_(anObject)'>
- !
- isSameInstanceAs: anObject
- ^ self identityHash = anObject identityHash
- !
- ~= anObject
- ^ (self = anObject) = false
- !
- ~~ anObject
- ^ (self == anObject) = false
- ! !
- !ProtoObject methodsFor: 'converting'!
- asString
- ^ self printString
- ! !
- !ProtoObject methodsFor: 'error handling'!
- doesNotUnderstand: aMessage
- MessageNotUnderstood new
- receiver: self;
- message: aMessage;
- signal
- ! !
- !ProtoObject methodsFor: 'evaluating'!
- evaluate: aString on: anEvaluator
- ^ anEvaluator evaluate: aString receiver: self
- ! !
- !ProtoObject methodsFor: 'initialization'!
- initialize
- ! !
- !ProtoObject methodsFor: 'inspecting'!
- inspect
- Inspector inspect: self
- !
- inspectOn: anInspector
- ! !
- !ProtoObject methodsFor: 'message handling'!
- perform: aString
- ^ self perform: aString withArguments: #()
- !
- perform: aString withArguments: aCollection
- <inlineJS: 'return $core.send2(self, aString, aCollection)'>
- ! !
- !ProtoObject methodsFor: 'printing'!
- printOn: aStream
- aStream nextPutAll: (self class name first isVowel
- ifTrue: [ 'an ' ]
- ifFalse: [ 'a ' ]).
- aStream nextPutAll: self class name
- !
- printString
- ^ String streamContents: [ :str |
- self printOn: str ]
- ! !
- !ProtoObject 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
- !
- isKindOf: aClass
- ^ (self isMemberOf: aClass)
- ifTrue: [ true ]
- ifFalse: [ self class inheritsFrom: aClass ]
- !
- isNil
- ^ false
- !
- notNil
- ^ self isNil not
- ! !
- !ProtoObject class methodsFor: 'initialization'!
- initialize
- ! !
- ProtoObject subclass: #Object
- instanceVariableNames: ''
- package: 'Kernel-Objects'!
- !Object commentStamp!
- **I am the root of the Smalltalk class system**. With the exception of unual subclasses of `ProtoObject`, all other classes in the system are subclasses of me.
- I provide default behavior common to all normal objects (some of it inherited from `ProtoObject`), 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
- <inlineJS: 'return self[aString]'>
- !
- basicAt: aString put: anObject
- <inlineJS: 'return self[aString] = anObject'>
- !
- basicDelete: aString
- <inlineJS: 'delete self[aString]; return aString'>
- !
- size
- self error: 'Object not indexable'
- ! !
- !Object methodsFor: 'browsing'!
- browse
- Finder findClass: self class
- ! !
- !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
- ! !
- !Object methodsFor: 'copying'!
- copy
- ^ self shallowCopy postCopy
- !
- deepCopy
- <inlineJS: '
- var copy = self.klass._new();
- Object.keys(self).forEach(function (i) {
- if(/^@.+/.test(i)) {
- copy[i] = self[i]._deepCopy();
- }
- });
- return copy;
- '>
- !
- postCopy
- !
- shallowCopy
- <inlineJS: '
- var copy = self.klass._new();
- Object.keys(self).forEach(function(i) {
- 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, ')'.
- !
- deprecatedAPI: aString
- "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, ')'.
- console warn: aString
- !
- error: aString
- Error signal: aString
- !
- halt
- Halt signal
- !
- shouldNotImplement
- self error: 'This method should not be implemented in ', self class name
- !
- subclassResponsibility
- self error: 'This method is a responsibility of a subclass'
- ! !
- !Object methodsFor: 'evaluating'!
- in: aValuable
- ^ aValuable value: self
- !
- value
- <inlineJS: 'return self.valueOf()'>
- ! !
- !Object methodsFor: 'message handling'!
- basicPerform: aString
- ^ self basicPerform: aString withArguments: #()
- !
- basicPerform: aString withArguments: aCollection
- <inlineJS: 'return self[aString].apply(self, aCollection);'>
- ! !
- !Object methodsFor: 'streaming'!
- putOn: aStream
- aStream nextPut: self
- ! !
- !Object methodsFor: 'testing'!
- isBehavior
- ^ false
- !
- isBoolean
- ^ false
- !
- isClass
- ^ false
- !
- isCompiledMethod
- ^ false
- !
- isImmutable
- ^ false
- !
- isMemberOf: aClass
- ^ self class = aClass
- !
- isMetaclass
- ^ false
- !
- isNumber
- ^ false
- !
- isPackage
- ^ false
- !
- isParseFailure
- ^ false
- !
- isString
- ^ false
- !
- isSymbol
- ^ false
- !
- respondsTo: aSelector
- ^ self class canUnderstand: aSelector
- ! !
- !Object class methodsFor: 'helios'!
- accessorProtocolWith: aGenerator
- aGenerator accessorProtocolForObject
- !
- accessorsSourceCodesWith: aGenerator
- aGenerator accessorsForObject
- !
- initializeProtocolWith: aGenerator
- aGenerator initializeProtocolForObject
- !
- initializeSourceCodesWith: aGenerator
- aGenerator initializeForObject
- ! !
- !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
- <inlineJS: '
- if (typeof aBoolean === "boolean") return self.valueOf() === aBoolean;
- else if (aBoolean !!= null && typeof aBoolean === "object") return self.valueOf() === aBoolean.valueOf();
- else return false;
- '>
- ! !
- !Boolean methodsFor: 'controlling'!
- & aBoolean
- <inlineJS: '
- if(self == true) {
- return aBoolean;
- } else {
- return false;
- }
- '>
- !
- and: aBlock
- ^ self
- ifTrue: "aBlock" [ aBlock value ]
- 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"
- <inlineJS: '
- if(self == true) {
- return aBlock._value();
- } else {
- return anotherBlock._value();
- }
- '>
- !
- not
- ^ self = false
- !
- or: aBlock
- ^ self
- ifTrue: [ true ]
- ifFalse: "aBlock" [ aBlock value ]
- !
- | aBoolean
- <inlineJS: '
- if(self == true) {
- return true;
- } else {
- return aBoolean;
- }
- '>
- ! !
- !Boolean methodsFor: 'converting'!
- asBit
- ^ self ifTrue: [ 1 ] ifFalse: [ 0 ]
- !
- asJSON
- ^ self
- !
- asString
- <inlineJS: '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
- <inlineJS: 'return self.getDate()'>
- !
- dayOfMonth: aNumber
- <inlineJS: 'self.setDate(aNumber)'>
- !
- dayOfWeek
- <inlineJS: 'return self.getDay() + 1'>
- !
- dayOfWeek: aNumber
- <inlineJS: 'return self.setDay(aNumber - 1)'>
- !
- hours
- <inlineJS: 'return self.getHours()'>
- !
- hours: aNumber
- <inlineJS: 'self.setHours(aNumber)'>
- !
- milliseconds
- <inlineJS: 'return self.getMilliseconds()'>
- !
- milliseconds: aNumber
- <inlineJS: 'self.setMilliseconds(aNumber)'>
- !
- minutes
- <inlineJS: 'return self.getMinutes()'>
- !
- minutes: aNumber
- <inlineJS: 'self.setMinutes(aNumber)'>
- !
- month
- <inlineJS: 'return self.getMonth() + 1'>
- !
- month: aNumber
- <inlineJS: 'self.setMonth(aNumber - 1)'>
- !
- seconds
- <inlineJS: 'return self.getSeconds()'>
- !
- seconds: aNumber
- <inlineJS: 'self.setSeconds(aNumber)'>
- !
- time
- <inlineJS: 'return self.getTime()'>
- !
- time: aNumber
- <inlineJS: 'self.setTime(aNumber)'>
- !
- year
- <inlineJS: 'return self.getFullYear()'>
- !
- year: aNumber
- <inlineJS: 'self.setFullYear(aNumber)'>
- ! !
- !Date methodsFor: 'arithmetic'!
- + aDate
- <inlineJS: 'return self + aDate'>
- !
- - aDate
- <inlineJS: 'return self - aDate'>
- ! !
- !Date methodsFor: 'comparing'!
- < aDate
- <inlineJS: 'return self < aDate'>
- !
- <= aDate
- <inlineJS: 'return self <= aDate'>
- !
- = aDate
- ^ (aDate class == self class) and: [ self asMilliseconds == aDate asMilliseconds ]
- !
- > aDate
- <inlineJS: 'return self > aDate'>
- !
- >= aDate
- <inlineJS: 'return self >= aDate'>
- ! !
- !Date methodsFor: 'converting'!
- asDateString
- <inlineJS: 'return self.toDateString()'>
- !
- asLocaleString
- <inlineJS: 'return self.toLocaleString()'>
- !
- asMilliseconds
- ^ self time
- !
- asNumber
- ^ self asMilliseconds
- !
- asString
- <inlineJS: 'return self.toString()'>
- !
- asTimeString
- <inlineJS: 'return self.toTimeString()'>
- ! !
- !Date methodsFor: 'printing'!
- printOn: aStream
- aStream nextPutAll: self asString
- ! !
- !Date class methodsFor: 'accessing'!
- classTag
- "Returns a tag or general category for this class.
- Typically used to help tools do some reflection.
- Helios, for example, uses this to decide what icon the class should display."
-
- ^ '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
- <inlineJS: '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: 'arithmetic'!
- * aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self * aNumber'>
- !
- + aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self + aNumber'>
- !
- - aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self - aNumber'>
- !
- / aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self / aNumber'>
- !
- // aNumber
- ^ (self / aNumber) floor
- !
- \\ aNumber
- <inlineJS: 'return self % aNumber'>
- !
- abs
- <inlineJS: 'return Math.abs(self);'>
- !
- max: aNumber
- <inlineJS: 'return Math.max(self, aNumber);'>
- !
- min: aNumber
- <inlineJS: 'return Math.min(self, aNumber);'>
- !
- negated
- ^ 0 - self
- ! !
- !Number methodsFor: 'comparing'!
- < aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self < aNumber'>
- !
- <= aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self <= aNumber'>
- !
- == aNumber
- <inlineJS: '
- if (typeof aNumber === "number") return Number(self) === aNumber;
- else if (aNumber !!= null && typeof aNumber === "object") return Number(self) === aNumber.valueOf();
- else return false;
- '>
- !
- > aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self > aNumber'>
- !
- >= aNumber
- "Inlined in the Compiler"
- <inlineJS: 'return self >= aNumber'>
- ! !
- !Number methodsFor: 'converting'!
- & aNumber
- <inlineJS: 'return self & aNumber'>
- !
- @ aNumber
- ^ Point x: self y: aNumber
- !
- asJSON
- ^ self
- !
- asJavascript
- ^ '(', self printString, ')'
- !
- asNumber
- ^ self
- !
- asPoint
- ^ Point x: self y: self
- !
- asString
- <inlineJS: 'return String(self)'>
- !
- atRandom
- ^ (Random new next * self) truncated + 1
- !
- ceiling
- <inlineJS: 'return Math.ceil(self);'>
- !
- floor
- <inlineJS: 'return Math.floor(self);'>
- !
- rounded
- <inlineJS: '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
- <inlineJS: '
- if(self >= 0) {
- return Math.floor(self);
- } else {
- return Math.floor(self * (-1)) * (-1);
- };
- '>
- !
- | aNumber
- <inlineJS: '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
- <inlineJS: 'return Math.acos(self);'>
- !
- arcSin
- <inlineJS: 'return Math.asin(self);'>
- !
- arcTan
- <inlineJS: 'return Math.atan(self);'>
- !
- cos
- <inlineJS: 'return Math.cos(self);'>
- !
- ln
- <inlineJS: 'return Math.log(self);'>
- !
- log
- <inlineJS: 'return Math.log(self) / Math.LN10;'>
- !
- log: aNumber
- <inlineJS: 'return Math.log(self) / Math.log(aNumber);'>
- !
- raisedTo: exponent
- <inlineJS: 'return Math.pow(self, exponent);'>
- !
- sign
- self isZero
- ifTrue: [ ^ 0 ].
- self positive
- ifTrue: [ ^ 1 ]
- ifFalse: [ ^ -1 ].
- !
- sin
- <inlineJS: 'return Math.sin(self);'>
- !
- sqrt
- <inlineJS: 'return Math.sqrt(self)'>
- !
- squared
- ^ self * self
- !
- tan
- <inlineJS: 'return Math.tan(self);'>
- ! !
- !Number methodsFor: 'printing'!
- printOn: aStream
- aStream nextPutAll: self asString
- !
- printShowingDecimalPlaces: placesDesired
- <inlineJS: '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: 'accessing'!
- classTag
- "Returns a tag or general category for this class.
- Typically used to help tools do some reflection.
- Helios, for example, uses this to decide what icon the class should display."
-
- ^ 'magnitude'
- ! !
- !Number class methodsFor: 'instance creation'!
- e
- <inlineJS: 'return Math.E;'>
- !
- pi
- <inlineJS: '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
- ! !
- !Point methodsFor: 'comparing'!
- < aPoint
- ^ self x < aPoint x and: [
- self y < aPoint y ]
- !
- <= aPoint
- ^ self x <= aPoint x and: [
- self y <= aPoint y ]
- !
- = aPoint
- ^ aPoint class = self class and: [
- (aPoint x = self x) & (aPoint y = self y) ]
- !
- > aPoint
- ^ self x > aPoint x and: [
- self y > aPoint y ]
- !
- >= aPoint
- ^ self x >= aPoint x and: [
- self y >= aPoint 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'!
- dist: aPoint
- "Answer the distance between aPoint and the receiver."
- | dx dy |
- dx := aPoint x - x.
- dy := aPoint y - y.
- ^ (dx * dx + (dy * dy)) sqrt
- !
- translateBy: delta
- "Answer a Point translated by delta (an instance of Point)."
- ^ (delta x + x) @ (delta y + y)
- ! !
- !Point class methodsFor: 'accessing'!
- classTag
- "Returns a tag or general category for this class.
- Typically used to help tools do some reflection.
- Helios, for example, uses this to decide what icon the class should display."
-
- ^ '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
- <inlineJS: '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
- "Kept for file-in compatibility."
- ^ self subclass: aString instanceVariableNames: anotherString package: nil
- !
- subclass: aString instanceVariableNames: aString2 category: aString3
- "Kept for file-in compatibility."
- ^ self subclass: aString instanceVariableNames: aString2 package: aString3
- !
- subclass: aString instanceVariableNames: aString2 classVariableNames: classVars poolDictionaries: pools category: aString3
- "Kept for file-in compatibility. ignores class variables and pools."
- ^ 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'
- ! !
|