1
0

Kernel-Objects.st 21 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269
  1. Smalltalk current createPackage: 'Kernel-Objects' properties: #{}!
  2. nil subclass: #Object
  3. instanceVariableNames: ''
  4. category: 'Kernel-Objects'!
  5. !Object methodsFor: 'accessing'!
  6. yourself
  7. ^self
  8. !
  9. class
  10. <return self.klass>
  11. !
  12. size
  13. self error: 'Object not indexable'
  14. !
  15. instVarAt: aString
  16. <return self['@'+aString]>
  17. !
  18. instVarAt: aString put: anObject
  19. <self['@' + aString] = anObject>
  20. !
  21. basicAt: aString
  22. <return self[aString]>
  23. !
  24. basicAt: aString put: anObject
  25. <return self[aString] = anObject>
  26. !
  27. basicDelete: aString
  28. <delete self[aString]; return aString>
  29. !
  30. identityHash
  31. <return self.identityHash || (self.identityHash = smalltalk.nextId());>
  32. ! !
  33. !Object methodsFor: 'comparing'!
  34. = anObject
  35. ^self == anObject
  36. !
  37. ~= anObject
  38. ^(self = anObject) = false
  39. !
  40. == anObject
  41. ^self identityHash = anObject identityHash
  42. !
  43. ~~ anObject
  44. ^(self == anObject) = false
  45. ! !
  46. !Object methodsFor: 'converting'!
  47. -> anObject
  48. ^Association key: self value: anObject
  49. !
  50. asString
  51. ^self printString
  52. !
  53. asJavascript
  54. ^self asString
  55. !
  56. asJSON
  57. ^JSON parse: self asJSONString
  58. !
  59. asJSONString
  60. ^JSON stringify: self
  61. ! !
  62. !Object methodsFor: 'copying'!
  63. copy
  64. ^self shallowCopy postCopy
  65. !
  66. shallowCopy
  67. <
  68. var copy = self.klass._new();
  69. for(var i in self) {
  70. if(/^@.+/.test(i)) {
  71. copy[i] = self[i];
  72. }
  73. }
  74. return copy;
  75. >
  76. !
  77. deepCopy
  78. <
  79. var copy = self.klass._new();
  80. for(var i in self) {
  81. if(/^@.+/.test(i)) {
  82. copy[i] = self[i]._deepCopy();
  83. }
  84. }
  85. return copy;
  86. >
  87. !
  88. postCopy
  89. ! !
  90. !Object methodsFor: 'error handling'!
  91. error: aString
  92. Error signal: aString
  93. !
  94. subclassResponsibility
  95. self error: 'This method is a responsibility of a subclass'
  96. !
  97. shouldNotImplement
  98. self error: 'This method should not be implemented in ', self class name
  99. !
  100. try: aBlock catch: anotherBlock
  101. <try{result = aBlock()} catch(e) {result = anotherBlock(e)};
  102. return result;>
  103. !
  104. doesNotUnderstand: aMessage
  105. MessageNotUnderstood new
  106. receiver: self;
  107. message: aMessage;
  108. signal
  109. !
  110. halt
  111. self error: 'Halt encountered'
  112. !
  113. deprecatedAPI
  114. "Just a simple way to deprecate methods.
  115. #deprecatedAPI is in the 'error handling' protocol even if it doesn't throw an error,
  116. but it could in the future."
  117. console warn: thisContext home asString, ' is deprecated!! (in ', thisContext home home asString, ')'
  118. ! !
  119. !Object methodsFor: 'initialization'!
  120. initialize
  121. ! !
  122. !Object methodsFor: 'message handling'!
  123. perform: aSymbol
  124. ^self perform: aSymbol withArguments: #()
  125. !
  126. perform: aSymbol withArguments: aCollection
  127. ^self basicPerform: aSymbol asSelector withArguments: aCollection
  128. !
  129. basicPerform: aSymbol
  130. ^self basicPerform: aSymbol withArguments: #()
  131. !
  132. basicPerform: aSymbol withArguments: aCollection
  133. <return self[aSymbol].apply(self, aCollection);>
  134. ! !
  135. !Object methodsFor: 'printing'!
  136. printString
  137. ^'a ', self class name
  138. !
  139. printNl
  140. <console.log(self)>
  141. !
  142. log: aString block: aBlock
  143. | result |
  144. console log: aString, ' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
  145. ^result
  146. !
  147. storeString
  148. "Answer a String representation of the receiver from which the receiver
  149. can be reconstructed."
  150. ^ String streamContents: [:s | self storeOn: s]
  151. !
  152. storeOn: aStream
  153. aStream nextPutAll: self printString
  154. ! !
  155. !Object methodsFor: 'testing'!
  156. isKindOf: aClass
  157. ^(self isMemberOf: aClass)
  158. ifTrue: [true]
  159. ifFalse: [self class inheritsFrom: aClass]
  160. !
  161. isMemberOf: aClass
  162. ^self class = aClass
  163. !
  164. ifNil: aBlock
  165. "inlined in the Compiler"
  166. ^self
  167. !
  168. ifNil: aBlock ifNotNil: anotherBlock
  169. "inlined in the Compiler"
  170. ^anotherBlock value
  171. !
  172. ifNotNil: aBlock
  173. "inlined in the Compiler"
  174. ^aBlock value
  175. !
  176. ifNotNil: aBlock ifNil: anotherBlock
  177. "inlined in the Compiler"
  178. ^aBlock value
  179. !
  180. isNil
  181. ^false
  182. !
  183. notNil
  184. ^self isNil not
  185. !
  186. isClass
  187. ^false
  188. !
  189. isMetaclass
  190. ^false
  191. !
  192. isNumber
  193. ^false
  194. !
  195. isString
  196. ^false
  197. !
  198. isParseFailure
  199. ^false
  200. !
  201. isSymbol
  202. ^false
  203. ! !
  204. !Object class methodsFor: 'initialization'!
  205. initialize
  206. "no op"
  207. ! !
  208. Object subclass: #Smalltalk
  209. instanceVariableNames: ''
  210. category: 'Kernel-Objects'!
  211. !Smalltalk methodsFor: 'accessing'!
  212. classes
  213. <return self.classes()>
  214. !
  215. at: aString
  216. <return self[aString]>
  217. !
  218. basicParse: aString
  219. <return smalltalk.parser.parse(aString)>
  220. !
  221. parse: aString
  222. | result |
  223. self try: [result := self basicParse: aString] catch: [:ex | (self parseError: ex parsing: aString) signal].
  224. ^result
  225. !
  226. parseError: anException parsing: aString
  227. | row col message lines badLine code |
  228. <row = anException.line;
  229. col = anException.column;
  230. message = anException.message;>.
  231. lines := aString lines.
  232. badLine := lines at: row.
  233. badLine := (badLine copyFrom: 1 to: col - 1), ' ===>', (badLine copyFrom: col to: badLine size).
  234. lines at: row put: badLine.
  235. code := String streamContents: [:s |
  236. lines withIndexDo: [:l :i |
  237. s nextPutAll: i asString, ': ', l, String lf]].
  238. ^ Error new messageText: ('Parse error on line ' , row , ' column ' , col , ' : ' , message , ' Below is code with line numbers and ===> marker inserted:' , String lf, code)
  239. !
  240. reservedWords
  241. "JavaScript reserved words"
  242. <return self.reservedWords>
  243. !
  244. readJSObject: anObject
  245. <return self.readJSObject(anObject)>
  246. ! !
  247. !Smalltalk methodsFor: 'classes'!
  248. removeClass: aClass
  249. aClass isMetaclass ifTrue: [self error: aClass asString, ' is a Metaclass and cannot be removed!!'].
  250. aClass methodDictionary values do: [:each |
  251. aClass removeCompiledMethod: each].
  252. aClass class methodDictionary values do: [:each |
  253. aClass class removeCompiledMethod: each].
  254. self basicDelete: aClass name
  255. ! !
  256. !Smalltalk methodsFor: 'packages'!
  257. packages
  258. "Return all Package instances in the system."
  259. <return self.packages.all()>
  260. !
  261. packageAt: packageName
  262. <return self.packages[packageName]>
  263. !
  264. packageAt: packageName ifAbsent: aBlock
  265. ^(self packageAt: packageName) ifNil: aBlock
  266. !
  267. removePackage: packageName
  268. "Removes a package and all its classes."
  269. | pkg |
  270. pkg := self packageAt: packageName ifAbsent: [self error: 'Missing package: ', packageName].
  271. pkg classes do: [:each |
  272. self removeClass: each].
  273. self deletePackage: packageName
  274. !
  275. renamePackage: packageName to: newName
  276. "Rename a package."
  277. | pkg |
  278. pkg := self packageAt: packageName ifAbsent: [self error: 'Missing package: ', packageName].
  279. (self packageAt: newName) ifNotNil: [self error: 'Already exists a package called: ', newName].
  280. <smalltalk.packages[newName] = smalltalk.packages[packageName]>.
  281. pkg name: newName.
  282. self deletePackage: packageName.
  283. ! !
  284. !Smalltalk methodsFor: 'private'!
  285. createPackage: packageName
  286. "Create and bind a new package with given name and return it."
  287. <return smalltalk.addPackage(packageName, nil)>
  288. !
  289. deletePackage: packageName
  290. "Deletes a package by deleting its binding, but does not check if it contains classes etc.
  291. To remove a package, use #removePackage instead."
  292. <delete smalltalk.packages[packageName]>
  293. !
  294. createPackage: packageName properties: aDict
  295. "Create and bind a new package with given name and return it."
  296. | object |
  297. <object = {};>.
  298. aDict keysAndValuesDo: [:key :value |
  299. <object[key] = value>.
  300. ].
  301. <return smalltalk.addPackage(packageName, object)>
  302. ! !
  303. Smalltalk class instanceVariableNames: 'current'!
  304. !Smalltalk class methodsFor: 'accessing'!
  305. current
  306. <return smalltalk>
  307. ! !
  308. Object subclass: #Package
  309. instanceVariableNames: 'commitPathJs commitPathSt'
  310. category: 'Kernel-Objects'!
  311. !Package commentStamp!
  312. A Package is similar to a "class category" typically found in other Smalltalks like Pharo or Squeak. Amber does not have class categories anymore, it had in the beginning but now each class in the system knows which package it belongs to.
  313. A Package has a name, an Array of "requires", a comment and a Dictionary with other optional key value attributes. A Package can also be queried for its classes, but it will then resort to a reverse scan of all classes to find them.
  314. Packages are manipulated through "Smalltalk current", like for example finding one based on a name:
  315. Smalltalk current packageAt: 'Kernel'
  316. ...but you can also use:
  317. Package named: 'Kernel'
  318. A Package differs slightly from a Monticello package which can span multiple class categories using a naming convention based on hyphenation. But just as in Monticello a Package supports "class extensions" so a Package
  319. can define behaviors in foreign classes using a naming convention for method categories where the category starts with an asterisk and then the name of the owning package follows. This can easily be seen in for example class
  320. String where the method category "*IDE" defines #inspectOn: which thus is a method belonging to the IDE package.!
  321. !Package methodsFor: 'accessing'!
  322. name
  323. <return self.pkgName>
  324. !
  325. name: aString
  326. <self.pkgName = aString>
  327. !
  328. dependencies
  329. ^self propertyAt: 'dependencies' ifAbsent: [#()]
  330. !
  331. dependencies: anArray
  332. ^self propertyAt: 'dependencies' put: anArray
  333. !
  334. properties
  335. ^Smalltalk current readJSObject: (self basicAt: 'properties')
  336. !
  337. properties: aDict
  338. "We store it as a javascript object."
  339. | object |
  340. <object = {};>.
  341. aDict keysAndValuesDo: [:key :value |
  342. <object[key] = value>.
  343. ].
  344. <return self.properties = object>
  345. !
  346. commitPathJs
  347. ^ commitPathJs ifNil: [self class defaultCommitPathJs]
  348. !
  349. commitPathJs: aString
  350. commitPathJs := aString
  351. !
  352. commitPathSt
  353. ^ commitPathSt ifNil: [self class defaultCommitPathSt]
  354. !
  355. commitPathSt: aString
  356. commitPathSt := aString
  357. ! !
  358. !Package methodsFor: 'classes'!
  359. classes
  360. "We need to do a reverse scan."
  361. ^Smalltalk current classes select: [:c | c package == self]
  362. ! !
  363. !Package methodsFor: 'printing'!
  364. printString
  365. ^self name
  366. ! !
  367. !Package methodsFor: 'private'!
  368. propertiesAsJSON
  369. <return JSON.stringify(self.properties)>
  370. !
  371. jsProperties
  372. <return self.properties>
  373. !
  374. jsProperties: aJSObject
  375. <return self.properties = aJSObject>
  376. ! !
  377. !Package methodsFor: 'properties'!
  378. propertyAt: key
  379. <return self.properties[key]>
  380. !
  381. propertyAt: key put: value
  382. <return self.properties[key] = value>
  383. !
  384. propertyAt: key ifAbsent: block
  385. ^(self propertyAt: key) ifNil: [block value]
  386. ! !
  387. Package class instanceVariableNames: 'defaultCommitPathJs defaultCommitPathSt'!
  388. !Package class methodsFor: 'commit paths'!
  389. defaultCommitPathJs
  390. ^ defaultCommitPathJs ifNil: [ defaultCommitPathJs := 'js']
  391. !
  392. defaultCommitPathJs: aString
  393. defaultCommitPathJs := aString
  394. !
  395. defaultCommitPathSt
  396. ^ defaultCommitPathSt ifNil: [ defaultCommitPathSt := 'st']
  397. !
  398. defaultCommitPathSt: aString
  399. defaultCommitPathSt := aString
  400. !
  401. resetCommitPaths
  402. defaultCommitPathJs := nil.
  403. defaultCommitPathSt := nil.
  404. ! !
  405. !Package class methodsFor: 'not yet classified'!
  406. named: aPackageName
  407. ^Smalltalk current packageAt: aPackageName
  408. !
  409. named: aPackageName ifAbsent: aBlock
  410. ^Smalltalk current packageAt: aPackageName ifAbsent: aBlock
  411. ! !
  412. Object subclass: #Number
  413. instanceVariableNames: ''
  414. category: 'Kernel-Objects'!
  415. !Number methodsFor: ''!
  416. ! !
  417. !Number methodsFor: 'accessing'!
  418. identityHash
  419. ^self asString, 'n'
  420. ! !
  421. !Number methodsFor: 'arithmetic'!
  422. + aNumber
  423. "Inlined in the Compiler"
  424. <return self + aNumber>
  425. !
  426. - aNumber
  427. "Inlined in the Compiler"
  428. <return self - aNumber>
  429. !
  430. * aNumber
  431. "Inlined in the Compiler"
  432. <return self * aNumber>
  433. !
  434. / aNumber
  435. "Inlined in the Compiler"
  436. <return self / aNumber>
  437. !
  438. max: aNumber
  439. <return Math.max(self, aNumber);>
  440. !
  441. min: aNumber
  442. <return Math.min(self, aNumber);>
  443. !
  444. negated
  445. ^0 - self
  446. !
  447. \\ aNumber
  448. <return self % aNumber>
  449. !
  450. sqrt
  451. <return Math.sqrt(self)>
  452. !
  453. squared
  454. ^self * self
  455. ! !
  456. !Number methodsFor: 'comparing'!
  457. = aNumber
  458. aNumber isNumber ifFalse: [^false].
  459. <return Number(self) == aNumber>
  460. !
  461. > aNumber
  462. "Inlined in the Compiler"
  463. <return self >> aNumber>
  464. !
  465. < aNumber
  466. "Inlined in the Compiler"
  467. <return self < aNumber>
  468. !
  469. >= aNumber
  470. "Inlined in the Compiler"
  471. <return self >>= aNumber>
  472. !
  473. <= aNumber
  474. "Inlined in the Compiler"
  475. <return self <= aNumber>
  476. ! !
  477. !Number methodsFor: 'converting'!
  478. rounded
  479. <return Math.round(self);>
  480. !
  481. truncated
  482. |result|
  483. self >= 0
  484. ifTrue: [<result = Math.floor(self);>]
  485. ifFalse: [<result = (Math.floor(self * (-1)) * (-1));>].
  486. ^ result
  487. !
  488. to: aNumber
  489. | array first last count |
  490. first := self truncated.
  491. last := aNumber truncated + 1.
  492. count := 1.
  493. array := Array new.
  494. (last - first) timesRepeat: [
  495. array at: count put: first.
  496. count := count + 1.
  497. first := first + 1].
  498. ^array
  499. !
  500. asString
  501. ^self printString
  502. !
  503. asJavascript
  504. ^'(', self printString, ')'
  505. !
  506. atRandom
  507. ^(Random new next * self) truncated + 1
  508. !
  509. @ aNumber
  510. ^Point x: self y: aNumber
  511. !
  512. asPoint
  513. ^Point x: self y: self
  514. !
  515. to: stop by: step
  516. | array value pos |
  517. value := self.
  518. array := Array new.
  519. pos := 1.
  520. step = 0 ifTrue: [self error: 'step must be non-zero'].
  521. step < 0
  522. ifTrue: [[ value >= stop ] whileTrue: [
  523. array at: pos put: value.
  524. pos := pos + 1.
  525. value := value + step]]
  526. ifFalse: [[ value <= stop ] whileTrue: [
  527. array at: pos put: value.
  528. pos := pos + 1.
  529. value := value + step]].
  530. ^array
  531. ! !
  532. !Number methodsFor: 'copying'!
  533. deepCopy
  534. ^self copy
  535. !
  536. copy
  537. ^self
  538. ! !
  539. !Number methodsFor: 'enumerating'!
  540. timesRepeat: aBlock
  541. | integer count |
  542. integer := self truncated.
  543. count := 1.
  544. [count > self] whileFalse: [
  545. aBlock value.
  546. count := count + 1]
  547. !
  548. to: stop do: aBlock
  549. "Evaluate aBlock for each number from self to aNumber."
  550. | nextValue |
  551. nextValue := self.
  552. [nextValue <= stop]
  553. whileTrue:
  554. [aBlock value: nextValue.
  555. nextValue := nextValue + 1]
  556. !
  557. to: stop by: step do: aBlock
  558. | value |
  559. value := self.
  560. step = 0 ifTrue: [self error: 'step must be non-zero'].
  561. step < 0
  562. ifTrue: [[ value >= stop ] whileTrue: [
  563. aBlock value: value.
  564. value := value + step]]
  565. ifFalse: [[ value <= stop ] whileTrue: [
  566. aBlock value: value.
  567. value := value + step]]
  568. ! !
  569. !Number methodsFor: 'printing'!
  570. printString
  571. <return String(self)>
  572. !
  573. printShowingDecimalPlaces: placesDesired
  574. <return self.toFixed(placesDesired)>
  575. ! !
  576. !Number methodsFor: 'testing'!
  577. isNumber
  578. ^true
  579. !
  580. even
  581. ^ 0 = (self \\ 2)
  582. !
  583. odd
  584. ^ self even not
  585. ! !
  586. !Number methodsFor: 'timeouts/intervals'!
  587. clearInterval
  588. <clearInterval(Number(self))>
  589. !
  590. clearTimeout
  591. <clearTimeout(Number(self))>
  592. ! !
  593. !Number class methodsFor: 'instance creation'!
  594. pi
  595. <return Math.PI>
  596. ! !
  597. Object subclass: #Boolean
  598. instanceVariableNames: ''
  599. category: 'Kernel-Objects'!
  600. !Boolean methodsFor: 'comparing'!
  601. = aBoolean
  602. aBoolean class = self class ifFalse: [^false].
  603. <return Boolean(self == true) == aBoolean>
  604. ! !
  605. !Boolean methodsFor: 'controlling'!
  606. ifTrue: aBlock
  607. "inlined in the Compiler"
  608. ^self ifTrue: aBlock ifFalse: []
  609. !
  610. ifFalse: aBlock
  611. "inlined in the Compiler"
  612. ^self ifTrue: [] ifFalse: aBlock
  613. !
  614. ifFalse: aBlock ifTrue: anotherBlock
  615. "inlined in the Compiler"
  616. ^self ifTrue: anotherBlock ifFalse: aBlock
  617. !
  618. ifTrue: aBlock ifFalse: anotherBlock
  619. "inlined in the Compiler"
  620. <
  621. if(self == true) {
  622. return aBlock();
  623. } else {
  624. return anotherBlock();
  625. }
  626. >
  627. !
  628. and: aBlock
  629. ^self = true
  630. ifTrue: aBlock
  631. ifFalse: [false]
  632. !
  633. or: aBlock
  634. ^self = true
  635. ifTrue: [true]
  636. ifFalse: aBlock
  637. !
  638. not
  639. ^self = false
  640. !
  641. & aBoolean
  642. <
  643. if(self == true) {
  644. return aBoolean;
  645. } else {
  646. return false;
  647. }
  648. >
  649. !
  650. | aBoolean
  651. <
  652. if(self == true) {
  653. return true;
  654. } else {
  655. return aBoolean;
  656. }
  657. >
  658. ! !
  659. !Boolean methodsFor: 'copying'!
  660. shallowCopy
  661. ^self
  662. !
  663. deepCopy
  664. ^self
  665. ! !
  666. !Boolean methodsFor: 'printing'!
  667. printString
  668. <return self.toString()>
  669. ! !
  670. Object subclass: #Date
  671. instanceVariableNames: ''
  672. category: 'Kernel-Objects'!
  673. !Date commentStamp!
  674. The Date class is used to work with dates and times.!
  675. !Date methodsFor: 'accessing'!
  676. year
  677. <return self.getFullYear()>
  678. !
  679. month
  680. <return self.getMonth() + 1>
  681. !
  682. month: aNumber
  683. <self.setMonth(aNumber - 1)>
  684. !
  685. day
  686. ^self dayOfWeek
  687. !
  688. dayOfWeek
  689. <return self.getDay() + 1>
  690. !
  691. dayOfWeek: aNumber
  692. <return self.setDay(aNumber - 1)>
  693. !
  694. day: aNumber
  695. self day: aNumber
  696. !
  697. year: aNumber
  698. <self.setFullYear(aNumber)>
  699. !
  700. dayOfMonth
  701. <return self.getDate()>
  702. !
  703. dayOfMonth: aNumber
  704. <self.setDate(aNumber)>
  705. !
  706. time
  707. <return self.getTime()>
  708. !
  709. time: aNumber
  710. <self.setTime(aNumber)>
  711. !
  712. hours: aNumber
  713. <self.setHours(aNumber)>
  714. !
  715. minutes: aNumber
  716. <self.setMinutes(aNumber)>
  717. !
  718. seconds: aNumber
  719. <self.setSeconds(aNumber)>
  720. !
  721. milliseconds: aNumber
  722. <self.setMilliseconds(aNumber)>
  723. !
  724. hours
  725. <return self.getHours()>
  726. !
  727. minutes
  728. <return self.getMinutes()>
  729. !
  730. seconds
  731. <return self.getSeconds()>
  732. !
  733. milliseconds
  734. <return self.getMilliseconds()>
  735. ! !
  736. !Date methodsFor: 'arithmetic'!
  737. - aDate
  738. <return self - aDate>
  739. !
  740. + aDate
  741. <return self + aDate>
  742. ! !
  743. !Date methodsFor: 'comparing'!
  744. < aDate
  745. <return self < aDate>
  746. !
  747. > aDate
  748. <return self >> aDate>
  749. !
  750. <= aDate
  751. <return self <= aDate>
  752. !
  753. >= aDate
  754. <return self >>= aDate>
  755. ! !
  756. !Date methodsFor: 'converting'!
  757. asString
  758. <return self.toString()>
  759. !
  760. asMilliseconds
  761. ^self time
  762. !
  763. asDateString
  764. <return self.toDateString()>
  765. !
  766. asTimeString
  767. <return self.toTimeString()>
  768. !
  769. asLocaleString
  770. <return self.toLocaleString()>
  771. !
  772. asNumber
  773. ^self asMilliseconds
  774. ! !
  775. !Date methodsFor: 'printing'!
  776. printString
  777. ^self asString
  778. ! !
  779. !Date class methodsFor: 'instance creation'!
  780. new: anObject
  781. <return new Date(anObject)>
  782. !
  783. fromString: aString
  784. "Example: Date fromString('2011/04/15 00:00:00')"
  785. ^self new: aString
  786. !
  787. fromSeconds: aNumber
  788. ^self fromMilliseconds: aNumber * 1000
  789. !
  790. fromMilliseconds: aNumber
  791. ^self new: aNumber
  792. !
  793. today
  794. ^self new
  795. !
  796. now
  797. ^self today
  798. !
  799. millisecondsToRun: aBlock
  800. | t |
  801. t := Date now.
  802. aBlock value.
  803. ^Date now - t
  804. ! !
  805. Object subclass: #UndefinedObject
  806. instanceVariableNames: ''
  807. category: 'Kernel-Objects'!
  808. !UndefinedObject methodsFor: 'class creation'!
  809. subclass: aString instanceVariableNames: anotherString
  810. ^self subclass: aString instanceVariableNames: anotherString package: nil
  811. !
  812. subclass: aString instanceVariableNames: aString2 category: aString3
  813. "Kept for compatibility."
  814. self deprecatedAPI.
  815. ^self subclass: aString instanceVariableNames: aString2 package: aString3
  816. !
  817. subclass: aString instanceVariableNames: aString2 package: aString3
  818. ^ClassBuilder new
  819. superclass: self subclass: aString instanceVariableNames: aString2 package: aString3
  820. ! !
  821. !UndefinedObject methodsFor: 'copying'!
  822. shallowCopy
  823. ^self
  824. !
  825. deepCopy
  826. ^self
  827. ! !
  828. !UndefinedObject methodsFor: 'printing'!
  829. printString
  830. ^'nil'
  831. ! !
  832. !UndefinedObject methodsFor: 'testing'!
  833. ifNil: aBlock
  834. "inlined in the Compiler"
  835. ^self ifNil: aBlock ifNotNil: []
  836. !
  837. ifNotNil: aBlock
  838. "inlined in the Compiler"
  839. ^self
  840. !
  841. ifNil: aBlock ifNotNil: anotherBlock
  842. "inlined in the Compiler"
  843. ^aBlock value
  844. !
  845. ifNotNil: aBlock ifNil: anotherBlock
  846. "inlined in the Compiler"
  847. ^anotherBlock value
  848. !
  849. isNil
  850. ^true
  851. !
  852. notNil
  853. ^false
  854. ! !
  855. !UndefinedObject class methodsFor: 'instance creation'!
  856. new
  857. self error: 'You cannot create new instances of UndefinedObject. Use nil'
  858. ! !
  859. Object subclass: #Random
  860. instanceVariableNames: ''
  861. category: 'Kernel-Objects'!
  862. !Random methodsFor: 'accessing'!
  863. next
  864. <return Math.random()>
  865. !
  866. next: anInteger
  867. ^(1 to: anInteger) collect: [:each | self next]
  868. ! !
  869. Object subclass: #Point
  870. instanceVariableNames: 'x y'
  871. category: 'Kernel-Objects'!
  872. !Point methodsFor: 'accessing'!
  873. x
  874. ^x
  875. !
  876. y
  877. ^y
  878. !
  879. y: aNumber
  880. y := aNumber
  881. !
  882. x: aNumber
  883. x := aNumber
  884. ! !
  885. !Point methodsFor: 'arithmetic'!
  886. * aPoint
  887. ^Point x: self x * aPoint asPoint x y: self y * aPoint asPoint y
  888. !
  889. + aPoint
  890. ^Point x: self x + aPoint asPoint x y: self y + aPoint asPoint y
  891. !
  892. - aPoint
  893. ^Point x: self x - aPoint asPoint x y: self y - aPoint asPoint y
  894. !
  895. / aPoint
  896. ^Point x: self x / aPoint asPoint x y: self y / aPoint asPoint y
  897. !
  898. = aPoint
  899. ^aPoint class = self class and: [
  900. (aPoint x = self x) & (aPoint y = self y)]
  901. ! !
  902. !Point methodsFor: 'converting'!
  903. asPoint
  904. ^self
  905. ! !
  906. !Point class methodsFor: 'instance creation'!
  907. x: aNumber y: anotherNumber
  908. ^self new
  909. x: aNumber;
  910. y: anotherNumber;
  911. yourself
  912. ! !
  913. Object subclass: #JSObjectProxy
  914. instanceVariableNames: 'jsObject'
  915. category: 'Kernel-Objects'!
  916. !JSObjectProxy methodsFor: 'accessing'!
  917. jsObject: aJSObject
  918. jsObject := aJSObject
  919. !
  920. jsObject
  921. ^jsObject
  922. !
  923. at: aString
  924. <return self['@jsObject'][aString]>
  925. !
  926. at: aString put: anObject
  927. <self['@jsObject'][aString] = anObject>
  928. ! !
  929. !JSObjectProxy methodsFor: 'proxy'!
  930. printString
  931. ^self jsObject toString
  932. !
  933. inspectOn: anInspector
  934. | variables |
  935. variables := Dictionary new.
  936. variables at: '#self' put: self jsObject.
  937. anInspector setLabel: self printString.
  938. <for(var i in self['@jsObject']) {
  939. variables._at_put_(i, self['@jsObject'][i]);
  940. }>.
  941. anInspector setVariables: variables
  942. !
  943. doesNotUnderstand: aMessage
  944. | obj selector jsSelector arguments |
  945. obj := self jsObject.
  946. selector := aMessage selector.
  947. jsSelector := selector asJavaScriptSelector.
  948. arguments := aMessage arguments.
  949. <if(obj[jsSelector] !!= undefined) {return smalltalk.send(obj, jsSelector, arguments)}>.
  950. super doesNotUnderstand: aMessage
  951. ! !
  952. !JSObjectProxy class methodsFor: 'instance creation'!
  953. on: aJSObject
  954. ^self new
  955. jsObject: aJSObject;
  956. yourself
  957. ! !