Kernel.st 41 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217221822192220222122222223222422252226222722282229223022312232223322342235223622372238223922402241224222432244224522462247224822492250225122522253225422552256225722582259226022612262226322642265226622672268226922702271227222732274227522762277227822792280228122822283228422852286228722882289229022912292229322942295229622972298229923002301230223032304230523062307230823092310231123122313231423152316231723182319232023212322232323242325232623272328232923302331233223332334233523362337233823392340234123422343234423452346234723482349235023512352235323542355235623572358235923602361236223632364236523662367236823692370237123722373237423752376237723782379238023812382238323842385238623872388238923902391239223932394239523962397239823992400240124022403240424052406240724082409241024112412241324142415241624172418241924202421242224232424242524262427242824292430243124322433243424352436243724382439244024412442244324442445244624472448244924502451245224532454245524562457245824592460246124622463246424652466246724682469247024712472247324742475247624772478247924802481248224832484248524862487248824892490249124922493249424952496249724982499250025012502250325042505250625072508250925102511251225132514251525162517251825192520252125222523252425252526252725282529253025312532253325342535253625372538253925402541254225432544254525462547254825492550255125522553255425552556255725582559256025612562256325642565256625672568256925702571257225732574257525762577257825792580258125822583258425852586258725882589259025912592259325942595
  1. nil subclass: #Object
  2. instanceVariableNames: ''
  3. category: 'Kernel'!
  4. !Object methodsFor: 'accessing'!
  5. yourself
  6. ^self
  7. !
  8. class
  9. <return self.klass>
  10. !
  11. size
  12. self error: 'Object not indexable'
  13. !
  14. instVarAt: aString
  15. <return self['@'+aString]>
  16. !
  17. instVarAt: aString put: anObject
  18. <self['@' + aString] = anObject>
  19. !
  20. basicAt: aString
  21. <return self[aString]>
  22. !
  23. basicAt: aString put: anObject
  24. <return self[aString] = anObject>
  25. !
  26. basicDelete: aString
  27. <delete self[aString]>
  28. ! !
  29. !Object methodsFor: 'comparing'!
  30. = anObject
  31. <return self == anObject>
  32. !
  33. ~= anObject
  34. ^(self = anObject) = false
  35. ! !
  36. !Object methodsFor: 'converting'!
  37. -> anObject
  38. ^Association key: self value: anObject
  39. !
  40. asString
  41. ^self printString
  42. !
  43. asJavascript
  44. ^self asString
  45. !
  46. asJSON
  47. <return JSON.stringify(self._asJSONObject())>
  48. !
  49. asJSONObject
  50. | object |
  51. object := Object new.
  52. self class instanceVariableNames do: [:each |
  53. object basicAt: each put: (self instVarAt: each) asJSONObject].
  54. ^object
  55. ! !
  56. !Object methodsFor: 'copying'!
  57. copy
  58. ^self shallowCopy postCopy
  59. !
  60. shallowCopy
  61. <
  62. var copy = self.klass._new();
  63. for(var i in self) {
  64. if(/^@.+/.test(i)) {
  65. copy[i] = self[i];
  66. }
  67. }
  68. return copy;
  69. >
  70. !
  71. deepCopy
  72. <
  73. var copy = self.klass._new();
  74. for(var i in self) {
  75. if(/^@.+/.test(i)) {
  76. copy[i] = self[i]._deepCopy();
  77. }
  78. }
  79. return copy;
  80. >
  81. !
  82. postCopy
  83. ! !
  84. !Object methodsFor: 'error handling'!
  85. error: aString
  86. Error signal: aString
  87. !
  88. subclassResponsibility
  89. self error: 'This method is a responsibility of a subclass'
  90. !
  91. shouldNotImplement
  92. self error: 'This method should not be implemented in ', self class name
  93. !
  94. try: aBlock catch: anotherBlock
  95. <try{aBlock()} catch(e) {anotherBlock(e)}>
  96. !
  97. doesNotUnderstand: aMessage
  98. MessageNotUnderstood new
  99. receiver: self;
  100. message: aMessage;
  101. signal
  102. !
  103. halt
  104. self error: 'Halt encountered'
  105. ! !
  106. !Object methodsFor: 'initialization'!
  107. initialize
  108. ! !
  109. !Object methodsFor: 'message handling'!
  110. perform: aSymbol
  111. ^self perform: aSymbol withArguments: #()
  112. !
  113. perform: aSymbol withArguments: aCollection
  114. ^self basicPerform: aSymbol asSelector withArguments: aCollection
  115. !
  116. basicPerform: aSymbol
  117. ^self basicPerform: aSymbol withArguments: #()
  118. !
  119. basicPerform: aSymbol withArguments: aCollection
  120. <return self[aSymbol].apply(self, aCollection);>
  121. ! !
  122. !Object methodsFor: 'printing'!
  123. printString
  124. ^'a ', self class name
  125. !
  126. printNl
  127. <console.log(self)>
  128. !
  129. log: aString block: aBlock
  130. | result |
  131. "console log:" aString, ' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
  132. ^result
  133. ! !
  134. !Object methodsFor: 'testing'!
  135. isKindOf: aClass
  136. ^(self isMemberOf: aClass)
  137. ifTrue: [true]
  138. ifFalse: [self class inheritsFrom: aClass]
  139. !
  140. isMemberOf: aClass
  141. ^self class = aClass
  142. !
  143. ifNil: aBlock
  144. "inlined in the Compiler"
  145. ^self
  146. !
  147. ifNil: aBlock ifNotNil: anotherBlock
  148. "inlined in the Compiler"
  149. ^anotherBlock value
  150. !
  151. ifNotNil: aBlock
  152. "inlined in the Compiler"
  153. ^aBlock value
  154. !
  155. ifNotNil: aBlock ifNil: anotherBlock
  156. "inlined in the Compiler"
  157. ^aBlock value
  158. !
  159. isNil
  160. ^false
  161. !
  162. notNil
  163. ^self isNil not
  164. !
  165. isClass
  166. ^false
  167. !
  168. isMetaclass
  169. ^false
  170. !
  171. isNumber
  172. ^false
  173. !
  174. isString
  175. ^false
  176. !
  177. isParseFailure
  178. ^false
  179. ! !
  180. !Object class methodsFor: 'initialization'!
  181. initialize
  182. "no op"
  183. ! !
  184. Object subclass: #Smalltalk
  185. instanceVariableNames: ''
  186. category: 'Kernel'!
  187. !Smalltalk methodsFor: 'accessing'!
  188. classes
  189. <return self.classes()>
  190. !
  191. readJSON: anObject
  192. <return self.readJSObject(anObject)>
  193. !
  194. at: aString
  195. <return self[aString]>
  196. !
  197. removeClass: aClass
  198. aClass isMetaclass ifTrue: [self error: aClass asString, ' is a Metaclass and cannot be removed!!'].
  199. aClass methodDictionary values do: [:each |
  200. aClass removeCompiledMethod: each].
  201. aClass class methodDictionary values do: [:each |
  202. aClass class removeCompiledMethod: each].
  203. self basicDelete: aClass name
  204. !
  205. basicParse: aString
  206. <return smalltalk.parser.parse(aString)>
  207. !
  208. parse: aString
  209. | result |
  210. self try: [result := self basicParse: aString] catch: [:ex | (self parseError: ex) signal].
  211. ^result
  212. !
  213. parseError: anException
  214. <return smalltalk.Error._new()
  215. ._messageText_('Parse error on line ' + anException.line + ' column ' + anException.column + ' : ' + anException.message)>
  216. ! !
  217. Smalltalk class instanceVariableNames: 'current'!
  218. !Smalltalk class methodsFor: 'accessing'!
  219. current
  220. <return smalltalk>
  221. ! !
  222. Object subclass: #Behavior
  223. instanceVariableNames: ''
  224. category: 'Kernel'!
  225. !Behavior methodsFor: 'accessing'!
  226. name
  227. <return self.className || nil>
  228. !
  229. superclass
  230. <return self.superclass || nil>
  231. !
  232. subclasses
  233. <return smalltalk.subclasses(self)>
  234. !
  235. allSubclasses
  236. | result |
  237. result := self subclasses.
  238. self subclasses do: [:each |
  239. result addAll: each allSubclasses].
  240. ^result
  241. !
  242. withAllSubclasses
  243. ^(Array with: self) addAll: self allSubclasses; yourself
  244. !
  245. prototype
  246. <return self.fn.prototype>
  247. !
  248. methodDictionary
  249. <var dict = smalltalk.Dictionary._new();
  250. var methods = self.fn.prototype.methods;
  251. for(var i in methods) {
  252. if(methods[i].selector) {
  253. dict._at_put_(methods[i].selector, methods[i]);
  254. }
  255. };
  256. return dict>
  257. !
  258. methodsFor: aString
  259. ^ClassCategoryReader new
  260. class: self category: aString;
  261. yourself
  262. !
  263. addCompiledMethod: aMethod
  264. <smalltalk.addMethod(aMethod.selector._asSelector(), aMethod, self)>
  265. !
  266. instanceVariableNames
  267. <return self.iVarNames>
  268. !
  269. comment
  270. ^(self basicAt: 'comment') ifNil: ['']
  271. !
  272. comment: aString
  273. self basicAt: 'comment' put: aString
  274. !
  275. commentStamp
  276. ^ClassCommentReader new
  277. class: self;
  278. yourself
  279. !
  280. removeCompiledMethod: aMethod
  281. <delete self.fn.prototype[aMethod.selector._asSelector()];
  282. delete self.fn.prototype.methods[aMethod.selector];
  283. smalltalk.init(self);>
  284. !
  285. protocols
  286. | protocols |
  287. protocols := Array new.
  288. self methodDictionary do: [:each |
  289. (protocols includes: each category) ifFalse: [
  290. protocols add: each category]].
  291. ^protocols sort
  292. !
  293. protocolsDo: aBlock
  294. "Execute aBlock for each method category with
  295. its collection of methods in the sort order of category name."
  296. | methodsByCategory |
  297. methodsByCategory := Dictionary new.
  298. self methodDictionary values do: [:m |
  299. (methodsByCategory at: m category ifAbsentPut: [Array new])
  300. add: m].
  301. self protocols do: [:category |
  302. aBlock value: category value: (methodsByCategory at: category)]
  303. !
  304. allInstanceVariableNames
  305. | result |
  306. result := self instanceVariableNames copy.
  307. self superclass ifNotNil: [
  308. result addAll: self superclass allInstanceVariableNames].
  309. ^result
  310. !
  311. methodAt: aString
  312. <return smalltalk.methods(self)[aString]>
  313. !
  314. methodsFor: aString stamp: aStamp
  315. "Added for compatibility, right now ignores stamp."
  316. ^self methodsFor: aString
  317. !
  318. commentStamp: aStamp prior: prior
  319. "Ignored right now."
  320. ! !
  321. !Behavior methodsFor: 'instance creation'!
  322. new
  323. ^self basicNew initialize
  324. !
  325. basicNew
  326. <return new self.fn()>
  327. !
  328. inheritsFrom: aClass
  329. ^aClass allSubclasses includes: self
  330. ! !
  331. Behavior subclass: #Class
  332. instanceVariableNames: ''
  333. category: 'Kernel'!
  334. !Class methodsFor: 'accessing'!
  335. category
  336. <return self.category>
  337. !
  338. category: aString
  339. <self.category = aString>
  340. !
  341. rename: aString
  342. <
  343. smalltalk[aString] = self;
  344. delete smalltalk[self.className];
  345. self.className = aString;
  346. >
  347. ! !
  348. !Class methodsFor: 'class creation'!
  349. subclass: aString instanceVariableNames: anotherString
  350. ^self subclass: aString instanceVariableNames: anotherString category: nil
  351. !
  352. subclass: aString instanceVariableNames: aString2 category: aString3
  353. ^ClassBuilder new
  354. superclass: self subclass: aString instanceVariableNames: aString2 category: aString3
  355. !
  356. subclass: aString instanceVariableNames: aString2 classVariableNames: classVars poolDictionaries: pools category: aString3
  357. "Just ignore class variables and pools. Added for compatibility."
  358. ^self subclass: aString instanceVariableNames: aString2 category: aString3
  359. ! !
  360. !Class methodsFor: 'printing'!
  361. printString
  362. ^self name
  363. ! !
  364. !Class methodsFor: 'testing'!
  365. isClass
  366. ^true
  367. ! !
  368. Behavior subclass: #Metaclass
  369. instanceVariableNames: ''
  370. category: 'Kernel'!
  371. !Metaclass methodsFor: 'accessing'!
  372. instanceClass
  373. <return self.instanceClass>
  374. !
  375. instanceVariableNames: aCollection
  376. ClassBuilder new
  377. class: self instanceVariableNames: aCollection
  378. ! !
  379. !Metaclass methodsFor: 'printing'!
  380. printString
  381. ^self instanceClass name, ' class'
  382. ! !
  383. !Metaclass methodsFor: 'testing'!
  384. isMetaclass
  385. ^true
  386. ! !
  387. Object subclass: #CompiledMethod
  388. instanceVariableNames: ''
  389. category: 'Kernel'!
  390. !CompiledMethod methodsFor: 'accessing'!
  391. source
  392. ^(self basicAt: 'source') ifNil: ['']
  393. !
  394. source: aString
  395. self basicAt: 'source' put: aString
  396. !
  397. category
  398. ^(self basicAt: 'category') ifNil: ['']
  399. !
  400. category: aString
  401. self basicAt: 'category' put: aString
  402. !
  403. selector
  404. ^self basicAt: 'selector'
  405. !
  406. selector: aString
  407. self basicAt: 'selector' put: aString
  408. !
  409. fn
  410. ^self basicAt: 'fn'
  411. !
  412. fn: aBlock
  413. self basicAt: 'fn' put: aBlock
  414. !
  415. messageSends
  416. ^self basicAt: 'messageSends'
  417. !
  418. methodClass
  419. ^self basicAt: 'methodClass'
  420. !
  421. referencedClasses
  422. ^self basicAt: 'referencedClasses'
  423. ! !
  424. Object subclass: #Number
  425. instanceVariableNames: ''
  426. category: 'Kernel'!
  427. !Number methodsFor: 'arithmetic'!
  428. + aNumber
  429. "Inlined in the Compiler"
  430. <return self + aNumber>
  431. !
  432. - aNumber
  433. "Inlined in the Compiler"
  434. <return self - aNumber>
  435. !
  436. * aNumber
  437. "Inlined in the Compiler"
  438. <return self * aNumber>
  439. !
  440. / aNumber
  441. "Inlined in the Compiler"
  442. <return self / aNumber>
  443. !
  444. max: aNumber
  445. <return Math.max(self, aNumber);>
  446. !
  447. min: aNumber
  448. <return Math.min(self, aNumber);>
  449. !
  450. modulo: aNumber
  451. <return self % aNumber>
  452. !
  453. negated
  454. ^0 - self
  455. ! !
  456. !Number methodsFor: 'comparing'!
  457. = aNumber
  458. "Inlined in the Compiler"
  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. <return Math.floor(self);>
  483. !
  484. to: aNumber
  485. | array first last count |
  486. first := self truncated.
  487. last := aNumber truncated + 1.
  488. count := 1.
  489. (first <= last) ifFalse: [self error: 'Wrong interval'].
  490. array := Array new.
  491. (last - first) timesRepeat: [
  492. array at: count put: first.
  493. count := count + 1.
  494. first := first + 1].
  495. ^array
  496. !
  497. asString
  498. ^self printString
  499. !
  500. asJavascript
  501. ^'(', self printString, ')'
  502. !
  503. atRandom
  504. ^(Random new next * self) truncated + 1
  505. !
  506. @ aNumber
  507. ^Point x: self y: aNumber
  508. !
  509. asPoint
  510. ^Point x: self y: self
  511. !
  512. asJSONObject
  513. ^self
  514. ! !
  515. !Number methodsFor: 'enumerating'!
  516. timesRepeat: aBlock
  517. | integer count |
  518. integer := self truncated.
  519. count := 1.
  520. [count > self] whileFalse: [
  521. aBlock value.
  522. count := count + 1]
  523. !
  524. to: aNumber do: aBlock
  525. ^(self to: aNumber) do: aBlock
  526. ! !
  527. !Number methodsFor: 'printing'!
  528. printString
  529. <return String(self)>
  530. ! !
  531. !Number methodsFor: 'testing'!
  532. isNumber
  533. ^true
  534. !
  535. even
  536. ^ 0 = (self modulo: 2)
  537. !
  538. odd
  539. ^ self even not
  540. ! !
  541. !Number methodsFor: 'timeouts/intervals'!
  542. clearInterval
  543. <clearInterval(Number(self))>
  544. !
  545. clearTimeout
  546. <clearTimeout(Number(self))>
  547. ! !
  548. !Number class methodsFor: 'instance creation'!
  549. pi
  550. <return Math.PI>
  551. ! !
  552. Object subclass: #BlockClosure
  553. instanceVariableNames: ''
  554. category: 'Kernel'!
  555. !BlockClosure methodsFor: 'accessing'!
  556. compiledSource
  557. <return self.toString()>
  558. ! !
  559. !BlockClosure methodsFor: 'controlling'!
  560. whileTrue: aBlock
  561. "inlined in the Compiler"
  562. <while(self()) {aBlock()}>
  563. !
  564. whileFalse: aBlock
  565. "inlined in the Compiler"
  566. <while(!!self()) {aBlock()}>
  567. !
  568. whileFalse
  569. "inlined in the Compiler"
  570. self whileFalse: []
  571. !
  572. whileTrue
  573. "inlined in the Compiler"
  574. self whileTrue: []
  575. ! !
  576. !BlockClosure methodsFor: 'error handling'!
  577. on: anErrorClass do: aBlock
  578. self try: self catch: [:error |
  579. (error isKindOf: anErrorClass)
  580. ifTrue: [aBlock value: error]
  581. ifFalse: [error signal]]
  582. ! !
  583. !BlockClosure methodsFor: 'evaluating'!
  584. value
  585. "inlined in the Compiler"
  586. <return self();>
  587. !
  588. value: anArg
  589. "inlined in the Compiler"
  590. <return self(anArg);>
  591. !
  592. value: firstArg value: secondArg
  593. "inlined in the Compiler"
  594. <return self(firstArg, secondArg);>
  595. !
  596. value: firstArg value: secondArg value: thirdArg
  597. "inlined in the Compiler"
  598. <return self(firstArg, secondArg, thirdArg);>
  599. !
  600. valueWithPossibleArguments: aCollection
  601. <return self.apply(null, aCollection);>
  602. !
  603. new
  604. "Use the receiver as a JS constructor.
  605. *Do not* use this method to instanciate Smalltalk objects!!"
  606. <return new self()>
  607. ! !
  608. !BlockClosure methodsFor: 'printing'!
  609. printString
  610. ^ String streamContents: [:aStream|
  611. aStream
  612. nextPutAll: super printString;
  613. nextPutAll: '(';
  614. nextPutAll: self compiledSource;
  615. nextPutAll: ')';
  616. cr.
  617. ]
  618. ! !
  619. !BlockClosure methodsFor: 'timeout/interval'!
  620. valueWithTimeout: aNumber
  621. <return setTimeout(self, aNumber)>
  622. !
  623. valueWithInterval: aNumber
  624. <return setInterval(self, aNumber)>
  625. ! !
  626. Object subclass: #Boolean
  627. instanceVariableNames: ''
  628. category: 'Kernel'!
  629. !Boolean methodsFor: 'comparing'!
  630. = aBoolean
  631. <return Boolean(self == true) == aBoolean>
  632. !
  633. asJSONObject
  634. ^self
  635. ! !
  636. !Boolean methodsFor: 'controlling'!
  637. ifTrue: aBlock
  638. "inlined in the Compiler"
  639. ^self ifTrue: aBlock ifFalse: []
  640. !
  641. ifFalse: aBlock
  642. "inlined in the Compiler"
  643. ^self ifTrue: [] ifFalse: aBlock
  644. !
  645. ifFalse: aBlock ifTrue: anotherBlock
  646. "inlined in the Compiler"
  647. ^self ifTrue: anotherBlock ifFalse: aBlock
  648. !
  649. ifTrue: aBlock ifFalse: anotherBlock
  650. "inlined in the Compiler"
  651. <
  652. if(self == true) {
  653. return aBlock();
  654. } else {
  655. return anotherBlock();
  656. }
  657. >
  658. !
  659. and: aBlock
  660. ^self = true
  661. ifTrue: aBlock
  662. ifFalse: [false]
  663. !
  664. or: aBlock
  665. ^self = true
  666. ifTrue: [true]
  667. ifFalse: aBlock
  668. !
  669. not
  670. ^self = false
  671. !
  672. & aBoolean
  673. <
  674. if(self == true) {
  675. return aBoolean;
  676. } else {
  677. return false;
  678. }
  679. >
  680. !
  681. | aBoolean
  682. <
  683. if(self == true) {
  684. return true;
  685. } else {
  686. return aBoolean;
  687. }
  688. >
  689. ! !
  690. !Boolean methodsFor: 'copying'!
  691. shallowCopy
  692. ^self
  693. !
  694. deepCopy
  695. ^self
  696. ! !
  697. !Boolean methodsFor: 'printing'!
  698. printString
  699. <return self.toString()>
  700. ! !
  701. Object subclass: #Date
  702. instanceVariableNames: ''
  703. category: 'Kernel'!
  704. !Date commentStamp!
  705. The Date class is used to work with dates and times.!
  706. !Date methodsFor: 'accessing'!
  707. year
  708. <return self.getFullYear()>
  709. !
  710. month
  711. <return self.getMonth() + 1>
  712. !
  713. month: aNumber
  714. <self.setMonth(aNumber - 1)>
  715. !
  716. day
  717. ^self dayOfWeek
  718. !
  719. dayOfWeek
  720. <return self.getDay() + 1>
  721. !
  722. dayOfWeek: aNumber
  723. <return self.setDay(aNumber - 1)>
  724. !
  725. day: aNumber
  726. self day: aNumber
  727. !
  728. year: aNumber
  729. <self.setFullYear(aNumber)>
  730. !
  731. dayOfMonth
  732. <return self.getDate()>
  733. !
  734. dayOfMonth: aNumber
  735. <self.setDate(aNumber)>
  736. !
  737. time
  738. <return self.getTime()>
  739. !
  740. time: aNumber
  741. <self.setTime(aNumber)>
  742. !
  743. hours: aNumber
  744. <self.setHours(aNumber)>
  745. !
  746. minutes: aNumber
  747. <self.setMinutes(aNumber)>
  748. !
  749. seconds: aNumber
  750. <self.setSeconds(aNumber)>
  751. !
  752. milliseconds: aNumber
  753. <self.setMilliseconds(aNumber)>
  754. !
  755. hours
  756. <return self.getHours()>
  757. !
  758. minutes
  759. <return self.getMinutes()>
  760. !
  761. seconds
  762. <return self.getSeconds()>
  763. !
  764. milliseconds
  765. <return self.getMilliseconds()>
  766. ! !
  767. !Date methodsFor: 'arithmetic'!
  768. - aDate
  769. <return self - aDate>
  770. !
  771. + aDate
  772. <return self + aDate>
  773. ! !
  774. !Date methodsFor: 'comparing'!
  775. < aDate
  776. <return self < aDate>
  777. !
  778. > aDate
  779. <return self >> aDate>
  780. !
  781. <= aDate
  782. <self <= aDate>
  783. !
  784. >= aDate
  785. <self >>= aDate>
  786. ! !
  787. !Date methodsFor: 'converting'!
  788. asString
  789. <return self.toString()>
  790. !
  791. asMilliseconds
  792. ^self time
  793. !
  794. asDateString
  795. <return self.toDateString()>
  796. !
  797. asTimeString
  798. <return self.toTimeString()>
  799. !
  800. asLocaleString
  801. <return self.toLocaleString()>
  802. !
  803. asNumber
  804. ^self asMilliseconds
  805. !
  806. asJSONObject
  807. ^self
  808. ! !
  809. !Date methodsFor: 'printing'!
  810. printString
  811. ^self asString
  812. ! !
  813. !Date class methodsFor: 'instance creation'!
  814. new: anObject
  815. <return new Date(anObject)>
  816. !
  817. fromString: aString
  818. "Example: Date fromString('2011/04/15 00:00:00')"
  819. ^self new: aString
  820. !
  821. fromSeconds: aNumber
  822. ^self fromMilliseconds: aNumber * 1000
  823. !
  824. fromMilliseconds: aNumber
  825. ^self new: aNumber
  826. !
  827. today
  828. ^self new
  829. !
  830. now
  831. ^self today
  832. !
  833. millisecondsToRun: aBlock
  834. | t |
  835. t := Date now.
  836. aBlock value.
  837. ^Date now - t
  838. ! !
  839. Object subclass: #UndefinedObject
  840. instanceVariableNames: ''
  841. category: 'Kernel'!
  842. !UndefinedObject methodsFor: 'class creation'!
  843. subclass: aString instanceVariableNames: anotherString
  844. ^self subclass: aString instanceVariableNames: anotherString category: nil
  845. !
  846. subclass: aString instanceVariableNames: aString2 category: aString3
  847. ^ClassBuilder new
  848. superclass: self subclass: aString instanceVariableNames: aString2 category: aString3
  849. ! !
  850. !UndefinedObject methodsFor: 'copying'!
  851. shallowCopy
  852. ^self
  853. !
  854. deepCopy
  855. ^self
  856. ! !
  857. !UndefinedObject methodsFor: 'printing'!
  858. printString
  859. ^'nil'
  860. ! !
  861. !UndefinedObject methodsFor: 'testing'!
  862. ifNil: aBlock
  863. "inlined in the Compiler"
  864. ^self ifNil: aBlock ifNotNil: []
  865. !
  866. ifNotNil: aBlock
  867. "inlined in the Compiler"
  868. ^self
  869. !
  870. ifNil: aBlock ifNotNil: anotherBlock
  871. "inlined in the Compiler"
  872. ^aBlock value
  873. !
  874. ifNotNil: aBlock ifNil: anotherBlock
  875. "inlined in the Compiler"
  876. ^anotherBlock value
  877. !
  878. isNil
  879. ^true
  880. !
  881. notNil
  882. ^false
  883. ! !
  884. !UndefinedObject class methodsFor: 'instance creation'!
  885. new
  886. self error: 'You cannot create new instances of UndefinedObject. Use nil'
  887. ! !
  888. Object subclass: #Collection
  889. instanceVariableNames: ''
  890. category: 'Kernel'!
  891. !Collection methodsFor: 'accessing'!
  892. size
  893. self subclassResponsibility
  894. !
  895. readStream
  896. ^self stream
  897. !
  898. writeStream
  899. ^self stream
  900. !
  901. stream
  902. ^self streamClass on: self
  903. !
  904. streamClass
  905. ^self class streamClass
  906. ! !
  907. !Collection methodsFor: 'adding/removing'!
  908. add: anObject
  909. self subclassResponsibility
  910. !
  911. addAll: aCollection
  912. aCollection do: [:each |
  913. self add: each].
  914. ^aCollection
  915. !
  916. remove: anObject
  917. self subclassResponsibility
  918. ! !
  919. !Collection methodsFor: 'converting'!
  920. asArray
  921. | array index |
  922. array := Array new.
  923. index := 0.
  924. self do: [:each |
  925. index := index + 1.
  926. array at: index put: each].
  927. ^array
  928. ! !
  929. !Collection methodsFor: 'copying'!
  930. , aCollection
  931. ^self copy
  932. addAll: aCollection;
  933. yourself
  934. !
  935. copyWith: anObject
  936. ^self copy add: anObject; yourself
  937. !
  938. copyWithAll: aCollection
  939. ^self copy addAll: aCollection; yourself
  940. ! !
  941. !Collection methodsFor: 'enumerating'!
  942. do: aBlock
  943. <for(var i=0;i<self.length;i++){aBlock(self[i]);}>
  944. !
  945. collect: aBlock
  946. | newCollection |
  947. newCollection := self class new.
  948. self do: [:each |
  949. newCollection add: (aBlock value: each)].
  950. ^newCollection
  951. !
  952. detect: aBlock
  953. ^self detect: aBlock ifNone: [self errorNotFound]
  954. !
  955. detect: aBlock ifNone: anotherBlock
  956. <
  957. for(var i = 0; i < self.length; i++)
  958. if(aBlock(self[i]))
  959. return self[i];
  960. return anotherBlock();
  961. >
  962. !
  963. do: aBlock separatedBy: anotherBlock
  964. | first |
  965. first := true.
  966. self do: [:each |
  967. first
  968. ifTrue: [first := false]
  969. ifFalse: [anotherBlock value].
  970. aBlock value: each]
  971. !
  972. inject: anObject into: aBlock
  973. | result |
  974. result := anObject.
  975. self do: [:each |
  976. result := aBlock value: result value: each].
  977. ^result
  978. !
  979. reject: aBlock
  980. ^self select: [:each | (aBlock value: each) = false]
  981. !
  982. select: aBlock
  983. | stream |
  984. stream := self class new writeStream.
  985. self do: [:each |
  986. (aBlock value: each) ifTrue: [
  987. stream nextPut: each]].
  988. ^stream contents
  989. ! !
  990. !Collection methodsFor: 'error handling'!
  991. errorNotFound
  992. self error: 'Object is not in the collection'
  993. ! !
  994. !Collection methodsFor: 'testing'!
  995. includes: anObject
  996. <
  997. var i = self.length;
  998. while (i--) {
  999. if (smalltalk.send(self[i], "__eq", [anObject])) {return true;}
  1000. }
  1001. return false
  1002. >
  1003. !
  1004. notEmpty
  1005. ^self isEmpty not
  1006. !
  1007. isEmpty
  1008. ^self size = 0
  1009. ! !
  1010. !Collection class methodsFor: 'accessing'!
  1011. streamClass
  1012. ^Stream
  1013. ! !
  1014. !Collection class methodsFor: 'instance creation'!
  1015. with: anObject
  1016. ^self new
  1017. add: anObject;
  1018. yourself
  1019. !
  1020. with: anObject with: anotherObject
  1021. ^self new
  1022. add: anObject;
  1023. add: anotherObject;
  1024. yourself
  1025. !
  1026. with: firstObject with: secondObject with: thirdObject
  1027. ^self new
  1028. add: firstObject;
  1029. add: secondObject;
  1030. add: thirdObject;
  1031. yourself
  1032. !
  1033. withAll: aCollection
  1034. ^self new
  1035. addAll: aCollection;
  1036. yourself
  1037. ! !
  1038. Collection subclass: #SequenceableCollection
  1039. instanceVariableNames: ''
  1040. category: 'Kernel'!
  1041. !SequenceableCollection methodsFor: 'accessing'!
  1042. at: anIndex
  1043. ^self at: anIndex ifAbsent: [
  1044. self errorNotFound]
  1045. !
  1046. at: anIndex ifAbsent: aBlock
  1047. self subclassResponsibility
  1048. !
  1049. at: anIndex put: anObject
  1050. self subclassResponsibility
  1051. !
  1052. first
  1053. ^self at: 1
  1054. !
  1055. fourth
  1056. ^self at: 4
  1057. !
  1058. last
  1059. ^self at: self size
  1060. !
  1061. second
  1062. ^self at: 2
  1063. !
  1064. third
  1065. ^self at: 3
  1066. !
  1067. allButFirst
  1068. ^self copyFrom: 2 to: self size
  1069. !
  1070. allButLast
  1071. ^self copyFrom: 1 to: self size - 1
  1072. !
  1073. indexOf: anObject
  1074. ^self indexOf: anObject ifAbsent: [self errorNotFound]
  1075. !
  1076. indexOf: anObject ifAbsent: aBlock
  1077. <
  1078. for(var i=0;i<self.length;i++){
  1079. if(self[i].__eq(anObject)) {return i+1}
  1080. }
  1081. return aBlock();
  1082. >
  1083. ! !
  1084. !SequenceableCollection methodsFor: 'adding'!
  1085. removeLast
  1086. self remove: self last
  1087. !
  1088. addLast: anObject
  1089. self add: anObject
  1090. ! !
  1091. !SequenceableCollection methodsFor: 'copying'!
  1092. copyFrom: anIndex to: anotherIndex
  1093. self subclassResponsibility
  1094. ! !
  1095. !SequenceableCollection methodsFor: 'enumerating'!
  1096. withIndexDo: aBlock
  1097. <for(var i=0;i<self.length;i++){aBlock(self[i], i+1);}>
  1098. ! !
  1099. SequenceableCollection subclass: #String
  1100. instanceVariableNames: ''
  1101. category: 'Kernel'!
  1102. !String methodsFor: 'accessing'!
  1103. size
  1104. <return self.length>
  1105. !
  1106. at: anIndex
  1107. <return self[anIndex - 1]>
  1108. !
  1109. at: anIndex put: anObject
  1110. self errorReadOnly
  1111. !
  1112. at: anIndex ifAbsent: aBlock
  1113. (self at: anIndex) ifNil: [aBlock]
  1114. !
  1115. escaped
  1116. <return escape(self)>
  1117. !
  1118. unescaped
  1119. <return unescape(self)>
  1120. !
  1121. asciiValue
  1122. <return self.charCodeAt(0);>
  1123. ! !
  1124. !String methodsFor: 'adding'!
  1125. add: anObject
  1126. self errorReadOnly
  1127. !
  1128. remove: anObject
  1129. self errorReadOnly
  1130. ! !
  1131. !String methodsFor: 'comparing'!
  1132. = aString
  1133. <return String(self) == aString>
  1134. !
  1135. > aString
  1136. <return String(self) >> aString>
  1137. !
  1138. < aString
  1139. <return String(self) < aString>
  1140. !
  1141. >= aString
  1142. <return String(self) >>= aString>
  1143. !
  1144. <= aString
  1145. <return String(self) <= aString>
  1146. ! !
  1147. !String methodsFor: 'converting'!
  1148. asSelector
  1149. "If you change this method, change smalltalk.convertSelector too (see js/boot.js file)"
  1150. | selector |
  1151. selector := '_', self.
  1152. selector := selector replace: ':' with: '_'.
  1153. selector := selector replace: '[+]' with: '_plus'.
  1154. selector := selector replace: '-' with: '_minus'.
  1155. selector := selector replace: '[*]' with: '_star'.
  1156. selector := selector replace: '[/]' with: '_slash'.
  1157. selector := selector replace: '>' with: '_gt'.
  1158. selector := selector replace: '<' with: '_lt'.
  1159. selector := selector replace: '=' with: '_eq'.
  1160. selector := selector replace: ',' with: '_comma'.
  1161. selector := selector replace: '[@]' with: '_at'.
  1162. ^selector
  1163. !
  1164. asJavascript
  1165. <
  1166. if(self.search(/^[a-zA-Z0-9_:.$ ]*$/) == -1)
  1167. return "unescape(\"" + escape(self) + "\")";
  1168. else
  1169. return "\"" + self + "\"";
  1170. >
  1171. !
  1172. tokenize: aString
  1173. <return self.split(aString)>
  1174. !
  1175. asString
  1176. ^self
  1177. !
  1178. asNumber
  1179. <return Number(self)>
  1180. !
  1181. asParser
  1182. ^PPStringParser new string: self
  1183. !
  1184. asChoiceParser
  1185. ^PPChoiceParser withAll: (self asArray collect: [:each | each asParser])
  1186. !
  1187. asCharacterParser
  1188. ^PPCharacterParser new string: self
  1189. !
  1190. asJSONObject
  1191. ^self
  1192. !
  1193. asLowercase
  1194. <return self.toLowerCase()>
  1195. !
  1196. asUppercase
  1197. <return self.toUpperCase()>
  1198. ! !
  1199. !String methodsFor: 'copying'!
  1200. , aString
  1201. <return self + aString>
  1202. !
  1203. copyFrom: anIndex to: anotherIndex
  1204. <return self.substring(anIndex - 1, anotherIndex)>
  1205. !
  1206. shallowCopy
  1207. ^self class fromString: self
  1208. !
  1209. deepCopy
  1210. ^self shallowCopy
  1211. ! !
  1212. !String methodsFor: 'error handling'!
  1213. errorReadOnly
  1214. self error: 'Object is read-only'
  1215. ! !
  1216. !String methodsFor: 'printing'!
  1217. printString
  1218. ^'''', self, ''''
  1219. !
  1220. printNl
  1221. <console.log(self)>
  1222. ! !
  1223. !String methodsFor: 'regular expressions'!
  1224. replace: aString with: anotherString
  1225. ^self replaceRegexp: (RegularExpression fromString: aString flag: 'g') with: anotherString
  1226. !
  1227. replaceRegexp: aRegexp with: aString
  1228. <return self.replace(aRegexp, aString)>
  1229. !
  1230. match: aRegexp
  1231. <return self.search(aRegexp) !!= -1>
  1232. !
  1233. trimLeft: separators
  1234. ^self replaceRegexp: (RegularExpression fromString: '^[', separators, ']+' flag: 'g') with: ''
  1235. !
  1236. trimRight: separators
  1237. ^self replaceRegexp: (RegularExpression fromString: '[', separators, ']+$' flag: 'g') with: ''
  1238. !
  1239. trimLeft
  1240. ^self trimLeft: '\s'
  1241. !
  1242. trimRight
  1243. ^self trimRight: '\s'
  1244. !
  1245. trimBoth
  1246. ^self trimBoth: '\s'
  1247. !
  1248. trimBoth: separators
  1249. ^(self trimLeft: separators) trimRight: separators
  1250. ! !
  1251. !String methodsFor: 'split join'!
  1252. join: aCollection
  1253. ^ String
  1254. streamContents: [:stream | aCollection
  1255. do: [:each | stream nextPutAll: each asString]
  1256. separatedBy: [stream nextPutAll: self]]
  1257. ! !
  1258. !String methodsFor: 'testing'!
  1259. isString
  1260. ^true
  1261. !
  1262. includesSubString: subString
  1263. < return self.indexOf(subString) !!= -1 >
  1264. ! !
  1265. !String class methodsFor: 'accessing'!
  1266. streamClass
  1267. ^StringStream
  1268. !
  1269. cr
  1270. <return '\r'>
  1271. !
  1272. lf
  1273. <return '\n'>
  1274. !
  1275. space
  1276. <return ' '>
  1277. !
  1278. tab
  1279. <return '\t'>
  1280. !
  1281. crlf
  1282. <return '\r\n'>
  1283. ! !
  1284. !String class methodsFor: 'instance creation'!
  1285. fromString: aString
  1286. <return new self.fn(aString)>
  1287. !
  1288. streamContents: blockWithArg
  1289. |stream|
  1290. stream := (self streamClass on: String new).
  1291. blockWithArg value: stream.
  1292. ^ stream contents
  1293. !
  1294. value: aUTFCharCode
  1295. <return String.fromCharCode(aUTFCharCode);>
  1296. ! !
  1297. SequenceableCollection subclass: #Array
  1298. instanceVariableNames: ''
  1299. category: 'Kernel'!
  1300. !Array methodsFor: 'accessing'!
  1301. size
  1302. <return self.length>
  1303. !
  1304. at: anIndex put: anObject
  1305. <return self[anIndex - 1] = anObject>
  1306. !
  1307. at: anIndex ifAbsent: aBlock
  1308. <
  1309. var value = self[anIndex - 1];
  1310. if(value === undefined) {
  1311. return aBlock();
  1312. } else {
  1313. return value;
  1314. }
  1315. >
  1316. ! !
  1317. !Array methodsFor: 'adding/removing'!
  1318. add: anObject
  1319. <self.push(anObject); return anObject;>
  1320. !
  1321. remove: anObject
  1322. <
  1323. for(var i=0;i<self.length;i++) {
  1324. if(self[i] == anObject) {
  1325. self.splice(i,1);
  1326. break;
  1327. }
  1328. }
  1329. >
  1330. !
  1331. removeFrom: aNumber to: anotherNumber
  1332. <self.splice(aNumber - 1,anotherNumber - 1)>
  1333. ! !
  1334. !Array methodsFor: 'converting'!
  1335. asJavascript
  1336. ^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
  1337. !
  1338. asJSONObject
  1339. ^self collect: [:each | each asJSONObject]
  1340. ! !
  1341. !Array methodsFor: 'copying'!
  1342. shallowCopy
  1343. | newCollection |
  1344. newCollection := self class new.
  1345. self do: [:each | newCollection add: each].
  1346. ^newCollection
  1347. !
  1348. deepCopy
  1349. | newCollection |
  1350. newCollection := self class new.
  1351. self do: [:each | newCollection add: each deepCopy].
  1352. ^newCollection
  1353. !
  1354. copyFrom: anIndex to: anotherIndex
  1355. | array |
  1356. array := self class new.
  1357. anIndex to: anotherIndex do: [:each |
  1358. array add: (self at: each)].
  1359. ^array
  1360. ! !
  1361. !Array methodsFor: 'enumerating'!
  1362. join: aString
  1363. <return self.join(aString)>
  1364. !
  1365. sort
  1366. ^self basicPerform: 'sort'
  1367. !
  1368. sort: aBlock
  1369. <
  1370. return self.sort(function(a, b) {
  1371. if(aBlock(a,b)) {return -1} else {return 1}
  1372. })
  1373. >
  1374. !
  1375. sorted
  1376. ^self copy sort
  1377. !
  1378. sorted: aBlock
  1379. ^self copy sort: aBlock
  1380. !
  1381. printString
  1382. | str |
  1383. str := '' writeStream.
  1384. str nextPutAll: super printString, ' ('.
  1385. self
  1386. do: [:each | str nextPutAll: each printString]
  1387. separatedBy: [str nextPutAll: ' '].
  1388. str nextPutAll: ')'.
  1389. ^str contents
  1390. ! !
  1391. Object subclass: #RegularExpression
  1392. instanceVariableNames: ''
  1393. category: 'Kernel'!
  1394. !RegularExpression methodsFor: 'evaluating'!
  1395. compile: aString
  1396. <return self.compile(aString)>
  1397. !
  1398. exec: aString
  1399. <return self.exec(aString) || nil>
  1400. !
  1401. test: aString
  1402. <return self.test(aString)>
  1403. ! !
  1404. !RegularExpression class methodsFor: 'instance creation'!
  1405. fromString: aString flag: anotherString
  1406. <return new RegExp(aString, anotherString)>
  1407. !
  1408. fromString: aString
  1409. ^self fromString: aString flag: ''
  1410. ! !
  1411. Object subclass: #Error
  1412. instanceVariableNames: 'messageText'
  1413. category: 'Kernel'!
  1414. !Error methodsFor: 'accessing'!
  1415. messageText
  1416. ^messageText
  1417. !
  1418. messageText: aString
  1419. messageText := aString
  1420. !
  1421. context
  1422. <return self.context>
  1423. ! !
  1424. !Error methodsFor: 'signaling'!
  1425. signal
  1426. <self.context = thisContext; self.smalltalkError = true; throw(self)>
  1427. ! !
  1428. !Error class methodsFor: 'instance creation'!
  1429. signal: aString
  1430. ^self new
  1431. messageText: aString;
  1432. signal
  1433. ! !
  1434. Object subclass: #MethodContext
  1435. instanceVariableNames: ''
  1436. category: 'Kernel'!
  1437. !MethodContext methodsFor: 'accessing'!
  1438. receiver
  1439. <return self.receiver>
  1440. !
  1441. selector
  1442. <return smalltalk.convertSelector(self.selector)>
  1443. !
  1444. home
  1445. <return self.homeContext>
  1446. !
  1447. temps
  1448. <return self.temps>
  1449. !
  1450. printString
  1451. ^super printString, '(', self asString, ')'
  1452. !
  1453. asString
  1454. ^self receiver class printString, ' >> ', self selector
  1455. ! !
  1456. Object subclass: #Association
  1457. instanceVariableNames: 'key value'
  1458. category: 'Kernel'!
  1459. !Association methodsFor: 'accessing'!
  1460. key: aKey
  1461. key := aKey
  1462. !
  1463. key
  1464. ^key
  1465. !
  1466. value: aValue
  1467. value := aValue
  1468. !
  1469. value
  1470. ^value
  1471. ! !
  1472. !Association methodsFor: 'comparing'!
  1473. = anAssociation
  1474. ^self class = anAssociation class and: [
  1475. self key = anAssociation key and: [
  1476. self value = anAssociation value]]
  1477. ! !
  1478. !Association class methodsFor: 'instance creation'!
  1479. key: aKey value: aValue
  1480. ^self new
  1481. key: aKey;
  1482. value: aValue;
  1483. yourself
  1484. ! !
  1485. Collection subclass: #Dictionary
  1486. instanceVariableNames: 'keys'
  1487. category: 'Kernel'!
  1488. !Dictionary methodsFor: 'accessing'!
  1489. size
  1490. ^keys size
  1491. !
  1492. associations
  1493. | associations |
  1494. associations := #().
  1495. keys do: [:each |
  1496. associations add: (Association key: each value: (self at: each))].
  1497. ^associations
  1498. !
  1499. keys
  1500. ^keys copy
  1501. !
  1502. values
  1503. ^keys collect: [:each | self at: each]
  1504. !
  1505. at: aKey put: aValue
  1506. (keys includes: aKey) ifFalse: [keys add: aKey].
  1507. ^self basicAt: aKey put: aValue
  1508. !
  1509. at: aKey ifAbsent: aBlock
  1510. ^(self keys includes: aKey)
  1511. ifTrue: [self basicAt: aKey]
  1512. ifFalse: aBlock
  1513. !
  1514. at: aKey ifAbsentPut: aBlock
  1515. ^self at: aKey ifAbsent: [
  1516. self at: aKey put: aBlock value]
  1517. !
  1518. at: aKey ifPresent: aBlock
  1519. ^(self basicAt: aKey) ifNotNil: [aBlock value: (self at: aKey)]
  1520. !
  1521. at: aKey ifPresent: aBlock ifAbsent: anotherBlock
  1522. ^(self basicAt: aKey)
  1523. ifNil: anotherBlock
  1524. ifNotNil: [aBlock value: (self at: aKey)]
  1525. !
  1526. at: aKey
  1527. ^self at: aKey ifAbsent: [self errorNotFound]
  1528. ! !
  1529. !Dictionary methodsFor: 'adding/removing'!
  1530. add: anAssociation
  1531. self at: anAssociation key put: anAssociation value
  1532. !
  1533. addAll: aDictionary
  1534. super addAll: aDictionary associations.
  1535. ^aDictionary
  1536. !
  1537. remove: aKey
  1538. self removeKey: aKey
  1539. !
  1540. removeKey: aKey
  1541. keys remove: aKey
  1542. ! !
  1543. !Dictionary methodsFor: 'comparing'!
  1544. = aDictionary
  1545. self class = aDictionary class ifFalse: [^false].
  1546. self associationsDo: [:assoc |
  1547. (aDictionary at: assoc key ifAbsent: [^false]) = assoc value
  1548. ifFalse: [^false]].
  1549. ^true
  1550. ! !
  1551. !Dictionary methodsFor: 'converting'!
  1552. asJSONObject
  1553. | object |
  1554. object := Object new.
  1555. self keysAndValuesDo: [:key :value |
  1556. object basicAt: key put: value asJSONObject].
  1557. ^object
  1558. ! !
  1559. !Dictionary methodsFor: 'copying'!
  1560. shallowCopy
  1561. | copy |
  1562. copy := self class new.
  1563. self associationsDo: [:each |
  1564. copy at: each key put: each value].
  1565. ^copy
  1566. !
  1567. , aCollection
  1568. self shouldNotImplement
  1569. !
  1570. copyFrom: anIndex to: anotherIndex
  1571. self shouldNotImplement
  1572. ! !
  1573. !Dictionary methodsFor: 'enumerating'!
  1574. associationsDo: aBlock
  1575. self associations do: aBlock
  1576. !
  1577. keysAndValuesDo: aBlock
  1578. self associationsDo: [:each |
  1579. aBlock value: each key value: each value]
  1580. !
  1581. do: aBlock
  1582. self values do: aBlock
  1583. !
  1584. select: aBlock
  1585. | newDict |
  1586. newDict := self class new.
  1587. self keysAndValuesDo: [:key :value |
  1588. (aBlock value: value) ifTrue: [newDict at: key put: value]].
  1589. ^newDict
  1590. !
  1591. collect: aBlock
  1592. | newDict |
  1593. newDict := self class new.
  1594. self keysAndValuesDo: [:key :value |
  1595. newDict at: key put: (aBlock value: value)].
  1596. ^newDict
  1597. !
  1598. detect: aBlock ifNone: anotherBlock
  1599. ^self values detect: aBlock ifNone: anotherBlock
  1600. !
  1601. includes: anObject
  1602. ^self values includes: anObject
  1603. ! !
  1604. !Dictionary methodsFor: 'initialization'!
  1605. initialize
  1606. super initialize.
  1607. keys := #()
  1608. ! !
  1609. !Dictionary methodsFor: 'printing'!
  1610. printString
  1611. ^ String streamContents: [:aStream|
  1612. aStream
  1613. nextPutAll: super printString;
  1614. nextPutAll: '('.
  1615. self associations
  1616. do: [:anAssociation|
  1617. aStream
  1618. nextPutAll: anAssociation key printString;
  1619. nextPutAll: ' -> ';
  1620. nextPutAll: anAssociation value printString]
  1621. separatedBy: [aStream nextPutAll: ' , '].
  1622. aStream nextPutAll: ')'.
  1623. ]
  1624. ! !
  1625. Object subclass: #ClassBuilder
  1626. instanceVariableNames: ''
  1627. category: 'Kernel'!
  1628. !ClassBuilder methodsFor: 'class creation'!
  1629. superclass: aClass subclass: aString
  1630. self superclass: aClass subclass: aString instanceVariableNames: '' category: nil
  1631. !
  1632. superclass: aClass subclass: aString instanceVariableNames: aString2 category: aString3
  1633. | newClass |
  1634. newClass := self addSubclassOf: aClass named: aString instanceVariableNames: (self instanceVariableNamesFor: aString2).
  1635. self setupClass: newClass.
  1636. newClass category: (aString3 ifNil: ['unclassified'])
  1637. !
  1638. class: aClass instanceVariableNames: aString
  1639. aClass isMetaclass ifFalse: [self error: aClass name, ' is not a metaclass'].
  1640. aClass basicAt: 'iVarNames' put: (self instanceVariableNamesFor: aString).
  1641. self setupClass: aClass
  1642. ! !
  1643. !ClassBuilder methodsFor: 'private'!
  1644. instanceVariableNamesFor: aString
  1645. ^(aString tokenize: ' ') reject: [:each | each isEmpty]
  1646. !
  1647. addSubclassOf: aClass named: aString instanceVariableNames: aCollection
  1648. <smalltalk.addClass(aString, aClass, aCollection);
  1649. return smalltalk[aString]>
  1650. !
  1651. setupClass: aClass
  1652. <smalltalk.init(aClass);>
  1653. ! !
  1654. Object subclass: #ClassCategoryReader
  1655. instanceVariableNames: 'class category chunkParser'
  1656. category: 'Kernel'!
  1657. !ClassCategoryReader methodsFor: 'accessing'!
  1658. class: aClass category: aString
  1659. class := aClass.
  1660. category := aString
  1661. ! !
  1662. !ClassCategoryReader methodsFor: 'fileIn'!
  1663. scanFrom: aStream
  1664. | nextChunk par |
  1665. self log: 'nextChunk build' block: [par := (chunkParser emptyChunk / chunkParser chunk)].
  1666. self log: 'nextChunk' block: [nextChunk := par parse: aStream].
  1667. nextChunk isEmptyChunk ifFalse: [
  1668. self compileMethod: nextChunk contents.
  1669. self scanFrom: aStream].
  1670. ! !
  1671. !ClassCategoryReader methodsFor: 'initialization'!
  1672. initialize
  1673. super initialize.
  1674. chunkParser := ChunkParser new.
  1675. ! !
  1676. !ClassCategoryReader methodsFor: 'private'!
  1677. compileMethod: aString
  1678. | method |
  1679. method := Compiler new load: aString forClass: class.
  1680. method category: category.
  1681. self log: 'addCompiledMethod' block: [class addCompiledMethod: method]
  1682. ! !
  1683. Object subclass: #Stream
  1684. instanceVariableNames: 'collection position streamSize'
  1685. category: 'Kernel'!
  1686. !Stream methodsFor: 'accessing'!
  1687. collection
  1688. ^collection
  1689. !
  1690. setCollection: aCollection
  1691. collection := aCollection
  1692. !
  1693. position
  1694. ^position ifNil: [position := 0]
  1695. !
  1696. position: anInteger
  1697. position := anInteger
  1698. !
  1699. streamSize
  1700. ^streamSize
  1701. !
  1702. setStreamSize: anInteger
  1703. streamSize := anInteger
  1704. !
  1705. contents
  1706. ^self collection
  1707. copyFrom: 1
  1708. to: self streamSize
  1709. !
  1710. size
  1711. ^self streamSize
  1712. ! !
  1713. !Stream methodsFor: 'actions'!
  1714. reset
  1715. self position: 0
  1716. !
  1717. close
  1718. !
  1719. flush
  1720. !
  1721. resetContents
  1722. self reset.
  1723. self setStreamSize: 0
  1724. ! !
  1725. !Stream methodsFor: 'enumerating'!
  1726. do: aBlock
  1727. [self atEnd] whileFalse: [aBlock value: self next]
  1728. ! !
  1729. !Stream methodsFor: 'positioning'!
  1730. setToEnd
  1731. self position: self size
  1732. !
  1733. skip: anInteger
  1734. self position: ((self position + anInteger) min: self size max: 0)
  1735. ! !
  1736. !Stream methodsFor: 'reading'!
  1737. next
  1738. self position: self position + 1.
  1739. ^collection at: self position
  1740. !
  1741. next: anInteger
  1742. | tempCollection |
  1743. tempCollection := self collection class new.
  1744. anInteger timesRepeat: [
  1745. self atEnd ifFalse: [
  1746. tempCollection add: self next]].
  1747. ^tempCollection
  1748. !
  1749. peek
  1750. ^self atEnd ifFalse: [
  1751. self collection at: self position + 1]
  1752. ! !
  1753. !Stream methodsFor: 'testing'!
  1754. atEnd
  1755. ^self position = self size
  1756. !
  1757. atStart
  1758. ^self position = 0
  1759. !
  1760. isEmpty
  1761. ^self size = 0
  1762. ! !
  1763. !Stream methodsFor: 'writing'!
  1764. nextPut: anObject
  1765. self position: self position + 1.
  1766. self collection at: self position put: anObject.
  1767. self setStreamSize: (self streamSize max: self position)
  1768. !
  1769. nextPutAll: aCollection
  1770. aCollection do: [:each |
  1771. self nextPut: each]
  1772. ! !
  1773. !Stream class methodsFor: 'instance creation'!
  1774. on: aCollection
  1775. ^self new
  1776. setCollection: aCollection;
  1777. setStreamSize: aCollection size;
  1778. yourself
  1779. ! !
  1780. Stream subclass: #StringStream
  1781. instanceVariableNames: ''
  1782. category: 'Kernel'!
  1783. !StringStream methodsFor: 'reading'!
  1784. next: anInteger
  1785. | tempCollection |
  1786. tempCollection := self collection class new.
  1787. anInteger timesRepeat: [
  1788. self atEnd ifFalse: [
  1789. tempCollection := tempCollection, self next]].
  1790. ^tempCollection
  1791. ! !
  1792. !StringStream methodsFor: 'writing'!
  1793. nextPut: aString
  1794. self nextPutAll: aString
  1795. !
  1796. nextPutAll: aString
  1797. self setCollection:
  1798. (self collection copyFrom: 1 to: self position),
  1799. aString,
  1800. (self collection copyFrom: (self position + 1 + aString size) to: self collection size).
  1801. self position: self position + aString size.
  1802. self setStreamSize: (self streamSize max: self position)
  1803. !
  1804. cr
  1805. ^self nextPutAll: String cr
  1806. !
  1807. crlf
  1808. ^self nextPutAll: String crlf
  1809. !
  1810. lf
  1811. ^self nextPutAll: String lf
  1812. !
  1813. space
  1814. self nextPut: ' '
  1815. ! !
  1816. Object subclass: #ClassCommentReader
  1817. instanceVariableNames: 'class chunkParser'
  1818. category: 'Kernel'!
  1819. !ClassCommentReader methodsFor: 'accessing'!
  1820. class: aClass
  1821. class := aClass
  1822. ! !
  1823. !ClassCommentReader methodsFor: 'fileIn'!
  1824. scanFrom: aStream
  1825. | nextChunk |
  1826. nextChunk := (chunkParser emptyChunk / chunkParser chunk) parse: aStream.
  1827. nextChunk isEmptyChunk ifFalse: [
  1828. self setComment: nextChunk contents].
  1829. ! !
  1830. !ClassCommentReader methodsFor: 'initialization'!
  1831. initialize
  1832. super initialize.
  1833. chunkParser := ChunkParser new.
  1834. ! !
  1835. !ClassCommentReader methodsFor: 'private'!
  1836. setComment: aString
  1837. class comment: aString
  1838. ! !
  1839. Object subclass: #Random
  1840. instanceVariableNames: ''
  1841. category: 'Kernel'!
  1842. !Random methodsFor: 'accessing'!
  1843. next
  1844. <return Math.random()>
  1845. !
  1846. next: anInteger
  1847. ^1 to: anInteger collect: [:each | self next]
  1848. ! !
  1849. Object subclass: #Point
  1850. instanceVariableNames: 'x y'
  1851. category: 'Kernel'!
  1852. !Point methodsFor: 'accessing'!
  1853. x
  1854. ^x
  1855. !
  1856. y
  1857. ^y
  1858. !
  1859. y: aNumber
  1860. y := aNumber
  1861. !
  1862. x: aNumber
  1863. x := aNumber
  1864. ! !
  1865. !Point methodsFor: 'arithmetic'!
  1866. * aPoint
  1867. ^Point x: self x * aPoint asPoint x y: self y * aPoint asPoint y
  1868. !
  1869. + aPoint
  1870. ^Point x: self x + aPoint asPoint x y: self y + aPoint asPoint y
  1871. !
  1872. - aPoint
  1873. ^Point x: self x - aPoint asPoint x y: self y - aPoint asPoint y
  1874. !
  1875. / aPoint
  1876. ^Point x: self x / aPoint asPoint x y: self y / aPoint asPoint y
  1877. ! !
  1878. !Point methodsFor: 'converting'!
  1879. asPoint
  1880. ^self
  1881. ! !
  1882. !Point class methodsFor: 'instance creation'!
  1883. x: aNumber y: anotherNumber
  1884. ^self new
  1885. x: aNumber;
  1886. y: anotherNumber;
  1887. yourself
  1888. ! !
  1889. Object subclass: #Message
  1890. instanceVariableNames: 'selector arguments'
  1891. category: 'Kernel'!
  1892. !Message methodsFor: 'accessing'!
  1893. selector
  1894. ^selector
  1895. !
  1896. selector: aString
  1897. selector := aString
  1898. !
  1899. arguments: anArray
  1900. arguments := anArray
  1901. !
  1902. arguments
  1903. ^arguments
  1904. ! !
  1905. !Message class methodsFor: 'instance creation'!
  1906. selector: aString arguments: anArray
  1907. ^self new
  1908. selector: aString;
  1909. arguments: anArray;
  1910. yourself
  1911. ! !
  1912. Error subclass: #MessageNotUnderstood
  1913. instanceVariableNames: 'message receiver'
  1914. category: 'Kernel'!
  1915. !MessageNotUnderstood methodsFor: 'accessing'!
  1916. message
  1917. ^message
  1918. !
  1919. message: aMessage
  1920. message := aMessage
  1921. !
  1922. receiver
  1923. ^receiver
  1924. !
  1925. receiver: anObject
  1926. receiver := anObject
  1927. !
  1928. messageText
  1929. ^self receiver asString, ' does not understand #', self message selector
  1930. ! !
  1931. Object subclass: #ErrorHandler
  1932. instanceVariableNames: ''
  1933. category: 'Kernel'!
  1934. !ErrorHandler methodsFor: 'error handling'!
  1935. handleError: anError
  1936. anError context ifNotNil: [self logErrorContext: anError context].
  1937. self logError: anError
  1938. ! !
  1939. !ErrorHandler methodsFor: 'private'!
  1940. logContext: aContext
  1941. aContext home ifNotNil: [
  1942. self logContext: aContext home].
  1943. self log: aContext receiver asString, '>>', aContext selector
  1944. !
  1945. logErrorContext: aContext
  1946. aContext ifNotNil: [
  1947. aContext home ifNotNil: [
  1948. self logContext: aContext home]]
  1949. !
  1950. logError: anError
  1951. self log: anError messageText
  1952. !
  1953. log: aString
  1954. console log: aString
  1955. ! !
  1956. ErrorHandler class instanceVariableNames: 'current'!
  1957. !ErrorHandler class methodsFor: 'accessing'!
  1958. current
  1959. ^current
  1960. !
  1961. setCurrent: anHandler
  1962. current := anHandler
  1963. ! !
  1964. !ErrorHandler class methodsFor: 'initialization'!
  1965. initialize
  1966. self register
  1967. !
  1968. register
  1969. ErrorHandler setCurrent: self new
  1970. ! !