Kernel-Objects.st 21 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335
  1. Smalltalk current createPackage: 'Kernel-Objects'!
  2. nil subclass: #ProtoObject
  3. instanceVariableNames: ''
  4. package: 'Kernel-Objects'!
  5. !ProtoObject commentStamp!
  6. I implement the basic behavior required for any object in Amber.
  7. 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.!
  8. !ProtoObject methodsFor: 'accessing'!
  9. class
  10. <return self.klass>
  11. !
  12. identityHash
  13. <
  14. var hash=self.identityHash;
  15. if (hash) return hash;
  16. hash=smalltalk.nextId();
  17. Object.defineProperty(self, 'identityHash', {value:hash});
  18. return hash;
  19. >
  20. !
  21. instVarAt: aString
  22. < return self['@'+aString] >
  23. !
  24. instVarAt: aString put: anObject
  25. < self['@' + aString] = anObject >
  26. !
  27. yourself
  28. ^ self
  29. ! !
  30. !ProtoObject methodsFor: 'converting'!
  31. asString
  32. ^ self printString
  33. ! !
  34. !ProtoObject methodsFor: 'error handling'!
  35. doesNotUnderstand: aMessage
  36. MessageNotUnderstood new
  37. receiver: self;
  38. message: aMessage;
  39. signal
  40. ! !
  41. !ProtoObject methodsFor: 'initialization'!
  42. initialize
  43. ! !
  44. !ProtoObject methodsFor: 'inspecting'!
  45. inspect
  46. InspectorHandler inspect: self
  47. !
  48. inspectOn: anInspector
  49. ! !
  50. !ProtoObject methodsFor: 'message handling'!
  51. perform: aString
  52. ^ self perform: aString withArguments: #()
  53. !
  54. perform: aString withArguments: aCollection
  55. <return smalltalk.send(self, aString._asSelector(), aCollection)>
  56. ! !
  57. !ProtoObject methodsFor: 'printing'!
  58. printOn: aStream
  59. aStream nextPutAll: (self class name first isVowel
  60. ifTrue: [ 'an ' ]
  61. ifFalse: [ 'a ' ]).
  62. aStream nextPutAll: self class name
  63. !
  64. printString
  65. ^ String streamContents: [ :str |
  66. self printOn: str ]
  67. ! !
  68. !ProtoObject class methodsFor: 'accessing'!
  69. heliosClass
  70. "Should be an Helios extension. Unfortunately, since helios can browse remote
  71. environments, we can't extend base classes"
  72. ^ 'class'
  73. ! !
  74. !ProtoObject class methodsFor: 'initialization'!
  75. initialize
  76. ! !
  77. ProtoObject subclass: #Object
  78. instanceVariableNames: ''
  79. package: 'Kernel-Objects'!
  80. !Object commentStamp!
  81. **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.
  82. I provide default behavior common to all normal objects (some of it inherited from `ProtoObject`), such as:
  83. - accessing
  84. - copying
  85. - comparison
  86. - error handling
  87. - message sending
  88. - reflection
  89. Also utility messages that all objects should respond to are defined here.
  90. I have no instance variable.
  91. ##Access
  92. Instance variables can be accessed with `#instVarAt:` and `#instVarAt:put:`. `#instanceVariableNames` answers a collection of all instance variable names.
  93. Accessing JavaScript properties of an object is done through `#basicAt:`, `#basicAt:put:` and `basicDelete:`.
  94. ##Copying
  95. 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.
  96. 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.
  97. ##Comparison
  98. I understand equality `#=` and identity `#==` comparison.
  99. ##Error handling
  100. - `#halt` is the typical message to use for inserting breakpoints during debugging.
  101. - `#error:` throws a generic error exception
  102. - `#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.
  103. Overriding this message can be useful to implement proxies for example.!
  104. !Object methodsFor: 'accessing'!
  105. basicAt: aString
  106. <return self[aString]>
  107. !
  108. basicAt: aString put: anObject
  109. <return self[aString] = anObject>
  110. !
  111. basicDelete: aString
  112. <delete self[aString]; return aString>
  113. !
  114. size
  115. self error: 'Object not indexable'
  116. !
  117. value
  118. <return self.valueOf()>
  119. ! !
  120. !Object methodsFor: 'comparing'!
  121. = anObject
  122. ^ self == anObject
  123. !
  124. == anObject
  125. ^ self identityHash = anObject identityHash
  126. !
  127. ~= anObject
  128. ^ (self = anObject) = false
  129. !
  130. ~~ anObject
  131. ^ (self == anObject) = false
  132. ! !
  133. !Object methodsFor: 'converting'!
  134. -> anObject
  135. ^ Association key: self value: anObject
  136. !
  137. asJSON
  138. | variables |
  139. variables := HashedCollection new.
  140. self class allInstanceVariableNames do: [ :each |
  141. variables at: each put: (self instVarAt: each) asJSON ].
  142. ^ variables
  143. !
  144. asJSONString
  145. ^ JSON stringify: self asJSON
  146. !
  147. asJavascript
  148. ^ self asString
  149. ! !
  150. !Object methodsFor: 'copying'!
  151. copy
  152. ^ self shallowCopy postCopy
  153. !
  154. deepCopy
  155. <
  156. var copy = self.klass._new();
  157. Object.keys(self).forEach(function (i) {
  158. if(/^@.+/.test(i)) {
  159. copy[i] = self[i]._deepCopy();
  160. }
  161. });
  162. return copy;
  163. >
  164. !
  165. postCopy
  166. !
  167. shallowCopy
  168. <
  169. var copy = self.klass._new();
  170. Object.keys(self).forEach(function(i) {
  171. if(/^@.+/.test(i)) {
  172. copy[i] = self[i];
  173. }
  174. });
  175. return copy;
  176. >
  177. ! !
  178. !Object methodsFor: 'error handling'!
  179. deprecatedAPI
  180. "Just a simple way to deprecate methods.
  181. #deprecatedAPI is in the 'error handling' protocol even if it doesn't throw an error,
  182. but it could in the future."
  183. console warn: thisContext home asString, ' is deprecated!! (in ', thisContext home home asString, ')'
  184. !
  185. error: aString
  186. Error signal: aString
  187. !
  188. halt
  189. self error: 'Halt encountered'
  190. !
  191. shouldNotImplement
  192. self error: 'This method should not be implemented in ', self class name
  193. !
  194. subclassResponsibility
  195. self error: 'This method is a responsibility of a subclass'
  196. !
  197. throw: anObject
  198. < throw anObject >
  199. !
  200. try: aBlock catch: anotherBlock
  201. <try{return aBlock._value()} catch(e) {return anotherBlock._value_(e)}>
  202. ! !
  203. !Object methodsFor: 'inspecting'!
  204. inspectOn: anInspector
  205. | variables |
  206. variables := Dictionary new.
  207. variables at: '#self' put: self.
  208. self class allInstanceVariableNames do: [ :each |
  209. variables at: each put: (self instVarAt: each) ].
  210. anInspector
  211. setLabel: self printString;
  212. setVariables: variables
  213. ! !
  214. !Object methodsFor: 'message handling'!
  215. basicPerform: aString
  216. ^ self basicPerform: aString withArguments: #()
  217. !
  218. basicPerform: aString withArguments: aCollection
  219. <return self[aString].apply(self, aCollection);>
  220. ! !
  221. !Object methodsFor: 'streaming'!
  222. putOn: aStream
  223. aStream nextPut: self
  224. ! !
  225. !Object methodsFor: 'testing'!
  226. ifNil: aBlock
  227. "inlined in the Compiler"
  228. ^ self
  229. !
  230. ifNil: aBlock ifNotNil: anotherBlock
  231. "inlined in the Compiler"
  232. ^ anotherBlock value: self
  233. !
  234. ifNotNil: aBlock
  235. "inlined in the Compiler"
  236. ^ aBlock value: self
  237. !
  238. ifNotNil: aBlock ifNil: anotherBlock
  239. "inlined in the Compiler"
  240. ^ aBlock value: self
  241. !
  242. isBehavior
  243. ^ false
  244. !
  245. isBoolean
  246. ^ false
  247. !
  248. isClass
  249. ^ false
  250. !
  251. isCompiledMethod
  252. ^ false
  253. !
  254. isImmutable
  255. ^ false
  256. !
  257. isKindOf: aClass
  258. ^ (self isMemberOf: aClass)
  259. ifTrue: [ true ]
  260. ifFalse: [ self class inheritsFrom: aClass ]
  261. !
  262. isMemberOf: aClass
  263. ^ self class = aClass
  264. !
  265. isMetaclass
  266. ^ false
  267. !
  268. isNil
  269. ^ false
  270. !
  271. isNumber
  272. ^ false
  273. !
  274. isPackage
  275. ^ false
  276. !
  277. isParseFailure
  278. ^ false
  279. !
  280. isString
  281. ^ false
  282. !
  283. isSymbol
  284. ^ false
  285. !
  286. notNil
  287. ^ self isNil not
  288. !
  289. respondsTo: aSelector
  290. ^ self class canUnderstand: aSelector
  291. ! !
  292. !Object class methodsFor: 'helios'!
  293. heliosClass
  294. "Should be an Helios extension. Unfortunately, since helios can browse remote
  295. environments, we can't extend base classes"
  296. ^ 'class'
  297. ! !
  298. !Object class methodsFor: 'initialization'!
  299. initialize
  300. "no op"
  301. ! !
  302. Object subclass: #Boolean
  303. instanceVariableNames: ''
  304. package: 'Kernel-Objects'!
  305. !Boolean commentStamp!
  306. I define the protocol for logic testing operations and conditional control structures for the logical values (see the `controlling` protocol).
  307. I have two instances, `true` and `false`.
  308. I am directly mapped to JavaScript Boolean. The `true` and `false` objects are the JavaScript boolean objects.
  309. ## Usage Example:
  310. aBoolean not ifTrue: [ ... ] ifFalse: [ ... ]!
  311. !Boolean methodsFor: 'comparing'!
  312. = aBoolean
  313. <
  314. if(!! aBoolean._isBoolean || !! aBoolean._isBoolean()) {
  315. return false;
  316. }
  317. return Boolean(self == true) == aBoolean
  318. >
  319. !
  320. == aBoolean
  321. ^ self = aBoolean
  322. ! !
  323. !Boolean methodsFor: 'controlling'!
  324. & aBoolean
  325. <
  326. if(self == true) {
  327. return aBoolean;
  328. } else {
  329. return false;
  330. }
  331. >
  332. !
  333. and: aBlock
  334. ^ self = true
  335. ifTrue: aBlock
  336. ifFalse: [ false ]
  337. !
  338. ifFalse: aBlock
  339. "inlined in the Compiler"
  340. ^ self ifTrue: [] ifFalse: aBlock
  341. !
  342. ifFalse: aBlock ifTrue: anotherBlock
  343. "inlined in the Compiler"
  344. ^ self ifTrue: anotherBlock ifFalse: aBlock
  345. !
  346. ifTrue: aBlock
  347. "inlined in the Compiler"
  348. ^ self ifTrue: aBlock ifFalse: []
  349. !
  350. ifTrue: aBlock ifFalse: anotherBlock
  351. "inlined in the Compiler"
  352. <
  353. if(self == true) {
  354. return aBlock._value();
  355. } else {
  356. return anotherBlock._value();
  357. }
  358. >
  359. !
  360. not
  361. ^ self = false
  362. !
  363. or: aBlock
  364. ^ self = true
  365. ifTrue: [ true ]
  366. ifFalse: aBlock
  367. !
  368. | aBoolean
  369. <
  370. if(self == true) {
  371. return true;
  372. } else {
  373. return aBoolean;
  374. }
  375. >
  376. ! !
  377. !Boolean methodsFor: 'converting'!
  378. asBit
  379. ^ self ifTrue: [ 1 ] ifFalse: [ 0 ]
  380. !
  381. asJSON
  382. ^ self
  383. !
  384. asString
  385. < return self.toString() >
  386. ! !
  387. !Boolean methodsFor: 'copying'!
  388. deepCopy
  389. ^ self
  390. !
  391. shallowCopy
  392. ^ self
  393. ! !
  394. !Boolean methodsFor: 'printing'!
  395. printOn: aStream
  396. aStream nextPutAll: self asString
  397. ! !
  398. !Boolean methodsFor: 'testing'!
  399. isBoolean
  400. ^ true
  401. !
  402. isImmutable
  403. ^ true
  404. ! !
  405. Object subclass: #Date
  406. instanceVariableNames: ''
  407. package: 'Kernel-Objects'!
  408. !Date commentStamp!
  409. I am used to work with both dates and times. Therefore `Date today` and `Date now` are both valid in
  410. Amber and answer the same date object.
  411. Date directly maps to the `Date()` JavaScript constructor, and Amber date objects are JavaScript date objects.
  412. ## API
  413. The class-side `instance creation` protocol contains some convenience methods for creating date/time objects such as `#fromSeconds:`.
  414. Arithmetic and comparison is supported (see the `comparing` and `arithmetic` protocols).
  415. The `converting` protocol provides convenience methods for various convertions (to numbers, strings, etc.).!
  416. !Date methodsFor: 'accessing'!
  417. day
  418. ^ self dayOfWeek
  419. !
  420. day: aNumber
  421. self dayOfWeek: aNumber
  422. !
  423. dayOfMonth
  424. <return self.getDate()>
  425. !
  426. dayOfMonth: aNumber
  427. <self.setDate(aNumber)>
  428. !
  429. dayOfWeek
  430. <return self.getDay() + 1>
  431. !
  432. dayOfWeek: aNumber
  433. <return self.setDay(aNumber - 1)>
  434. !
  435. hours
  436. <return self.getHours()>
  437. !
  438. hours: aNumber
  439. <self.setHours(aNumber)>
  440. !
  441. milliseconds
  442. <return self.getMilliseconds()>
  443. !
  444. milliseconds: aNumber
  445. <self.setMilliseconds(aNumber)>
  446. !
  447. minutes
  448. <return self.getMinutes()>
  449. !
  450. minutes: aNumber
  451. <self.setMinutes(aNumber)>
  452. !
  453. month
  454. <return self.getMonth() + 1>
  455. !
  456. month: aNumber
  457. <self.setMonth(aNumber - 1)>
  458. !
  459. seconds
  460. <return self.getSeconds()>
  461. !
  462. seconds: aNumber
  463. <self.setSeconds(aNumber)>
  464. !
  465. time
  466. <return self.getTime()>
  467. !
  468. time: aNumber
  469. <self.setTime(aNumber)>
  470. !
  471. year
  472. <return self.getFullYear()>
  473. !
  474. year: aNumber
  475. <self.setFullYear(aNumber)>
  476. ! !
  477. !Date methodsFor: 'arithmetic'!
  478. + aDate
  479. <return self + aDate>
  480. !
  481. - aDate
  482. <return self - aDate>
  483. ! !
  484. !Date methodsFor: 'comparing'!
  485. < aDate
  486. <return self < aDate>
  487. !
  488. <= aDate
  489. <return self <= aDate>
  490. !
  491. > aDate
  492. <return self >> aDate>
  493. !
  494. >= aDate
  495. <return self >>= aDate>
  496. ! !
  497. !Date methodsFor: 'converting'!
  498. asDateString
  499. <return self.toDateString()>
  500. !
  501. asLocaleString
  502. <return self.toLocaleString()>
  503. !
  504. asMilliseconds
  505. ^ self time
  506. !
  507. asNumber
  508. ^ self asMilliseconds
  509. !
  510. asString
  511. <return self.toString()>
  512. !
  513. asTimeString
  514. <return self.toTimeString()>
  515. ! !
  516. !Date methodsFor: 'printing'!
  517. printOn: aStream
  518. aStream nextPutAll: self asString
  519. ! !
  520. !Date class methodsFor: 'helios'!
  521. heliosClass
  522. ^ 'magnitude'
  523. ! !
  524. !Date class methodsFor: 'instance creation'!
  525. fromMilliseconds: aNumber
  526. ^ self new: aNumber
  527. !
  528. fromSeconds: aNumber
  529. ^ self fromMilliseconds: aNumber * 1000
  530. !
  531. fromString: aString
  532. "Example: Date fromString('2011/04/15 00:00:00')"
  533. ^ self new: aString
  534. !
  535. millisecondsToRun: aBlock
  536. | t |
  537. t := Date now.
  538. aBlock value.
  539. ^ Date now - t
  540. !
  541. new: anObject
  542. <return new Date(anObject)>
  543. !
  544. now
  545. ^ self today
  546. !
  547. today
  548. ^ self new
  549. ! !
  550. Object subclass: #Number
  551. instanceVariableNames: ''
  552. package: 'Kernel-Objects'!
  553. !Number commentStamp!
  554. I am the Amber representation for all numbers.
  555. I am directly mapped to JavaScript Number.
  556. ## API
  557. I provide all necessary methods for arithmetic operations, comparison, conversion and so on with numbers.
  558. My instances can also be used to evaluate a block a fixed number of times:
  559. 5 timesRepeat: [ Transcript show: 'This will be printed 5 times'; cr ].
  560. 1 to: 5 do: [ :aNumber| Transcript show: aNumber asString; cr ].
  561. 1 to: 10 by: 2 do: [ :aNumber| Transcript show: aNumber asString; cr ].!
  562. !Number methodsFor: 'accessing'!
  563. identityHash
  564. ^ self asString, 'n'
  565. ! !
  566. !Number methodsFor: 'arithmetic'!
  567. * aNumber
  568. "Inlined in the Compiler"
  569. <return self * aNumber>
  570. !
  571. + aNumber
  572. "Inlined in the Compiler"
  573. <return self + aNumber>
  574. !
  575. - aNumber
  576. "Inlined in the Compiler"
  577. <return self - aNumber>
  578. !
  579. / aNumber
  580. "Inlined in the Compiler"
  581. <return self / aNumber>
  582. !
  583. // aNumber
  584. ^ (self / aNumber) floor
  585. !
  586. \\ aNumber
  587. <return self % aNumber>
  588. !
  589. abs
  590. <return Math.abs(self);>
  591. !
  592. max: aNumber
  593. <return Math.max(self, aNumber);>
  594. !
  595. min: aNumber
  596. <return Math.min(self, aNumber);>
  597. !
  598. negated
  599. ^ 0 - self
  600. ! !
  601. !Number methodsFor: 'comparing'!
  602. < aNumber
  603. "Inlined in the Compiler"
  604. <return self < aNumber>
  605. !
  606. <= aNumber
  607. "Inlined in the Compiler"
  608. <return self <= aNumber>
  609. !
  610. = aNumber
  611. <
  612. if(!! aNumber._isNumber || !! aNumber._isNumber()) {
  613. return false;
  614. }
  615. return Number(self) == aNumber
  616. >
  617. !
  618. > aNumber
  619. "Inlined in the Compiler"
  620. <return self >> aNumber>
  621. !
  622. >= aNumber
  623. "Inlined in the Compiler"
  624. <return self >>= aNumber>
  625. ! !
  626. !Number methodsFor: 'converting'!
  627. & aNumber
  628. <return self & aNumber>
  629. !
  630. @ aNumber
  631. ^ Point x: self y: aNumber
  632. !
  633. asJSON
  634. ^ self
  635. !
  636. asJavascript
  637. ^ '(', self printString, ')'
  638. !
  639. asNumber
  640. ^ self
  641. !
  642. asPoint
  643. ^ Point x: self y: self
  644. !
  645. asString
  646. < return String(self) >
  647. !
  648. atRandom
  649. ^ (Random new next * self) truncated + 1
  650. !
  651. ceiling
  652. <return Math.ceil(self);>
  653. !
  654. floor
  655. <return Math.floor(self);>
  656. !
  657. rounded
  658. <return Math.round(self);>
  659. !
  660. to: aNumber
  661. | array first last count |
  662. first := self truncated.
  663. last := aNumber truncated + 1.
  664. count := 1.
  665. array := Array new.
  666. (last - first) timesRepeat: [
  667. array at: count put: first.
  668. count := count + 1.
  669. first := first + 1 ].
  670. ^ array
  671. !
  672. to: stop by: step
  673. | array value pos |
  674. value := self.
  675. array := Array new.
  676. pos := 1.
  677. step = 0 ifTrue: [ self error: 'step must be non-zero' ].
  678. step < 0
  679. ifTrue: [ [ value >= stop ] whileTrue: [
  680. array at: pos put: value.
  681. pos := pos + 1.
  682. value := value + step ]]
  683. ifFalse: [ [ value <= stop ] whileTrue: [
  684. array at: pos put: value.
  685. pos := pos + 1.
  686. value := value + step ]].
  687. ^ array
  688. !
  689. truncated
  690. <
  691. if(self >>= 0) {
  692. return Math.floor(self);
  693. } else {
  694. return Math.floor(self * (-1)) * (-1);
  695. };
  696. >
  697. !
  698. | aNumber
  699. <return self | aNumber>
  700. ! !
  701. !Number methodsFor: 'copying'!
  702. copy
  703. ^ self
  704. !
  705. deepCopy
  706. ^ self copy
  707. ! !
  708. !Number methodsFor: 'enumerating'!
  709. timesRepeat: aBlock
  710. | count |
  711. count := 1.
  712. [ count > self ] whileFalse: [
  713. aBlock value.
  714. count := count + 1 ]
  715. !
  716. to: stop by: step do: aBlock
  717. | value |
  718. value := self.
  719. step = 0 ifTrue: [ self error: 'step must be non-zero' ].
  720. step < 0
  721. ifTrue: [ [ value >= stop ] whileTrue: [
  722. aBlock value: value.
  723. value := value + step ]]
  724. ifFalse: [ [ value <= stop ] whileTrue: [
  725. aBlock value: value.
  726. value := value + step ]]
  727. !
  728. to: stop do: aBlock
  729. "Evaluate aBlock for each number from self to aNumber."
  730. | nextValue |
  731. nextValue := self.
  732. [ nextValue <= stop ]
  733. whileTrue:
  734. [ aBlock value: nextValue.
  735. nextValue := nextValue + 1 ]
  736. ! !
  737. !Number methodsFor: 'mathematical functions'!
  738. ** exponent
  739. ^ self raisedTo: exponent
  740. !
  741. arcCos
  742. <return Math.acos(self);>
  743. !
  744. arcSin
  745. <return Math.asin(self);>
  746. !
  747. arcTan
  748. <return Math.atan(self);>
  749. !
  750. cos
  751. <return Math.cos(self);>
  752. !
  753. ln
  754. <return Math.log(self);>
  755. !
  756. log
  757. <return Math.log(self) / Math.LN10;>
  758. !
  759. log: aNumber
  760. <return Math.log(self) / Math.log(aNumber);>
  761. !
  762. raisedTo: exponent
  763. <return Math.pow(self, exponent);>
  764. !
  765. sign
  766. self isZero
  767. ifTrue: [ ^ 0 ].
  768. self positive
  769. ifTrue: [ ^ 1 ]
  770. ifFalse: [ ^ -1 ].
  771. !
  772. sin
  773. <return Math.sin(self);>
  774. !
  775. sqrt
  776. <return Math.sqrt(self)>
  777. !
  778. squared
  779. ^ self * self
  780. !
  781. tan
  782. <return Math.tan(self);>
  783. ! !
  784. !Number methodsFor: 'printing'!
  785. printOn: aStream
  786. aStream nextPutAll: self asString
  787. !
  788. printShowingDecimalPlaces: placesDesired
  789. <return self.toFixed(placesDesired)>
  790. ! !
  791. !Number methodsFor: 'testing'!
  792. even
  793. ^ 0 = (self \\ 2)
  794. !
  795. isImmutable
  796. ^ true
  797. !
  798. isNumber
  799. ^ true
  800. !
  801. isZero
  802. ^ self = 0
  803. !
  804. negative
  805. "Answer whether the receiver is mathematically negative."
  806. ^ self < 0
  807. !
  808. odd
  809. ^ self even not
  810. !
  811. positive
  812. "Answer whether the receiver is positive or equal to 0. (ST-80 protocol)."
  813. ^ self >= 0
  814. ! !
  815. !Number class methodsFor: 'helios'!
  816. heliosClass
  817. ^ 'magnitude'
  818. ! !
  819. !Number class methodsFor: 'instance creation'!
  820. e
  821. <return Math.E;>
  822. !
  823. pi
  824. <return Math.PI>
  825. ! !
  826. Object subclass: #Point
  827. instanceVariableNames: 'x y'
  828. package: 'Kernel-Objects'!
  829. !Point commentStamp!
  830. I represent an x-y pair of numbers usually designating a geometric coordinate.
  831. ## API
  832. Instances are traditionally created using the binary `#@` message to a number:
  833. 100@120
  834. Points can then be arithmetically manipulated:
  835. 100@100 + (10@10)
  836. ...or for example:
  837. (100@100) * 2
  838. **NOTE:** Creating a point with a negative y-value will need a space after `@` in order to avoid a parsing error:
  839. 100@ -100 "but 100@-100 would not parse"!
  840. !Point methodsFor: 'accessing'!
  841. x
  842. ^ x
  843. !
  844. x: aNumber
  845. x := aNumber
  846. !
  847. y
  848. ^ y
  849. !
  850. y: aNumber
  851. y := aNumber
  852. ! !
  853. !Point methodsFor: 'arithmetic'!
  854. * aPoint
  855. ^ Point x: self x * aPoint asPoint x y: self y * aPoint asPoint y
  856. !
  857. + aPoint
  858. ^ Point x: self x + aPoint asPoint x y: self y + aPoint asPoint y
  859. !
  860. - aPoint
  861. ^ Point x: self x - aPoint asPoint x y: self y - aPoint asPoint y
  862. !
  863. / aPoint
  864. ^ Point x: self x / aPoint asPoint x y: self y / aPoint asPoint y
  865. !
  866. = aPoint
  867. ^ aPoint class = self class and: [
  868. (aPoint x = self x) & (aPoint y = self y) ]
  869. ! !
  870. !Point methodsFor: 'converting'!
  871. asPoint
  872. ^ self
  873. ! !
  874. !Point methodsFor: 'printing'!
  875. printOn: aStream
  876. "Print receiver in classic x@y notation."
  877. x printOn: aStream.
  878. aStream nextPutAll: '@'.
  879. (y notNil and: [ y negative ]) ifTrue: [
  880. "Avoid ambiguous @- construct"
  881. aStream space ].
  882. y printOn: aStream
  883. ! !
  884. !Point methodsFor: 'transforming'!
  885. translateBy: delta
  886. "Answer a Point translated by delta (an instance of Point)."
  887. ^ (delta x + x) @ (delta y + y)
  888. ! !
  889. !Point class methodsFor: 'helios'!
  890. heliosClass
  891. ^ 'magnitude'
  892. ! !
  893. !Point class methodsFor: 'instance creation'!
  894. x: aNumber y: anotherNumber
  895. ^ self new
  896. x: aNumber;
  897. y: anotherNumber;
  898. yourself
  899. ! !
  900. Object subclass: #Random
  901. instanceVariableNames: ''
  902. package: 'Kernel-Objects'!
  903. !Random commentStamp!
  904. I an used to generate a random number and I am implemented as a trivial wrapper around javascript `Math.random()`.
  905. ## API
  906. The typical use case it to use the `#next` method like the following:
  907. Random new next
  908. 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`
  909. 10 atRandom
  910. A random number in a specific interval can be obtained with the following:
  911. (3 to: 7) atRandom
  912. 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:
  913. 5 atRandom + 2
  914. Since `#atRandom` is implemented in `SequencableCollection` you can easy pick an element at random:
  915. #('a' 'b' 'c') atRandom
  916. As well as letter from a `String`:
  917. 'abc' atRandom
  918. Since Amber does not have Characters this will return a `String` of length 1 like for example `'b'`.!
  919. !Random methodsFor: 'accessing'!
  920. next
  921. <return Math.random()>
  922. !
  923. next: anInteger
  924. ^ (1 to: anInteger) collect: [ :each | self next ]
  925. ! !
  926. Object subclass: #UndefinedObject
  927. instanceVariableNames: ''
  928. package: 'Kernel-Objects'!
  929. !UndefinedObject commentStamp!
  930. 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.
  931. `nil` is the Smalltalk equivalent of the `undefined` JavaScript object.
  932. __note:__ When sending messages to the `undefined` JavaScript object, it will be replaced by `nil`.!
  933. !UndefinedObject methodsFor: 'class creation'!
  934. subclass: aString instanceVariableNames: anotherString
  935. ^ self subclass: aString instanceVariableNames: anotherString package: nil
  936. !
  937. subclass: aString instanceVariableNames: aString2 category: aString3
  938. "Kept for compatibility."
  939. self deprecatedAPI.
  940. ^ self subclass: aString instanceVariableNames: aString2 package: aString3
  941. !
  942. subclass: aString instanceVariableNames: aString2 package: aString3
  943. ^ ClassBuilder new
  944. superclass: self subclass: aString asString instanceVariableNames: aString2 package: aString3
  945. ! !
  946. !UndefinedObject methodsFor: 'converting'!
  947. asJSON
  948. ^ null
  949. ! !
  950. !UndefinedObject methodsFor: 'copying'!
  951. deepCopy
  952. ^ self
  953. !
  954. shallowCopy
  955. ^ self
  956. ! !
  957. !UndefinedObject methodsFor: 'printing'!
  958. printOn: aStream
  959. aStream nextPutAll: 'nil'
  960. ! !
  961. !UndefinedObject methodsFor: 'testing'!
  962. ifNil: aBlock
  963. "inlined in the Compiler"
  964. ^ self ifNil: aBlock ifNotNil: []
  965. !
  966. ifNil: aBlock ifNotNil: anotherBlock
  967. "inlined in the Compiler"
  968. ^ aBlock value
  969. !
  970. ifNotNil: aBlock
  971. "inlined in the Compiler"
  972. ^ self
  973. !
  974. ifNotNil: aBlock ifNil: anotherBlock
  975. "inlined in the Compiler"
  976. ^ anotherBlock value
  977. !
  978. isImmutable
  979. ^ true
  980. !
  981. isNil
  982. ^ true
  983. !
  984. notNil
  985. ^ false
  986. ! !
  987. !UndefinedObject class methodsFor: 'instance creation'!
  988. new
  989. self error: 'You cannot create new instances of UndefinedObject. Use nil'
  990. ! !