Kernel.st 42 KB

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