Kernel.st 44 KB

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