Kernel.st 44 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428142914301431143214331434143514361437143814391440144114421443144414451446144714481449145014511452145314541455145614571458145914601461146214631464146514661467146814691470147114721473147414751476147714781479148014811482148314841485148614871488148914901491149214931494149514961497149814991500150115021503150415051506150715081509151015111512151315141515151615171518151915201521152215231524152515261527152815291530153115321533153415351536153715381539154015411542154315441545154615471548154915501551155215531554155515561557155815591560156115621563156415651566156715681569157015711572157315741575157615771578157915801581158215831584158515861587158815891590159115921593159415951596159715981599160016011602160316041605160616071608160916101611161216131614161516161617161816191620162116221623162416251626162716281629163016311632163316341635163616371638163916401641164216431644164516461647164816491650165116521653165416551656165716581659166016611662166316641665166616671668166916701671167216731674167516761677167816791680168116821683168416851686168716881689169016911692169316941695169616971698169917001701170217031704170517061707170817091710171117121713171417151716171717181719172017211722172317241725172617271728172917301731173217331734173517361737173817391740174117421743174417451746174717481749175017511752175317541755175617571758175917601761176217631764176517661767176817691770177117721773177417751776177717781779178017811782178317841785178617871788178917901791179217931794179517961797179817991800180118021803180418051806180718081809181018111812181318141815181618171818181918201821182218231824182518261827182818291830183118321833183418351836183718381839184018411842184318441845184618471848184918501851185218531854185518561857185818591860186118621863186418651866186718681869187018711872187318741875187618771878187918801881188218831884188518861887188818891890189118921893189418951896189718981899190019011902190319041905190619071908190919101911191219131914191519161917191819191920192119221923192419251926192719281929193019311932193319341935193619371938193919401941194219431944194519461947194819491950195119521953195419551956195719581959196019611962196319641965196619671968196919701971197219731974197519761977197819791980198119821983198419851986198719881989199019911992199319941995199619971998199920002001200220032004200520062007200820092010201120122013201420152016201720182019202020212022202320242025202620272028202920302031203220332034203520362037203820392040204120422043204420452046204720482049205020512052205320542055205620572058205920602061206220632064206520662067206820692070207120722073207420752076207720782079208020812082208320842085208620872088208920902091209220932094209520962097209820992100210121022103210421052106210721082109211021112112211321142115211621172118211921202121212221232124212521262127212821292130213121322133213421352136213721382139214021412142214321442145214621472148214921502151215221532154215521562157215821592160216121622163216421652166216721682169217021712172217321742175217621772178217921802181218221832184218521862187218821892190219121922193219421952196219721982199220022012202220322042205220622072208220922102211221222132214221522162217221822192220222122222223222422252226222722282229223022312232223322342235223622372238223922402241224222432244224522462247224822492250225122522253225422552256225722582259226022612262226322642265226622672268226922702271227222732274227522762277227822792280228122822283228422852286228722882289229022912292229322942295229622972298229923002301230223032304230523062307230823092310231123122313231423152316231723182319232023212322232323242325232623272328232923302331233223332334233523362337233823392340234123422343234423452346234723482349235023512352235323542355235623572358235923602361236223632364236523662367236823692370237123722373237423752376237723782379238023812382238323842385238623872388238923902391239223932394239523962397239823992400240124022403240424052406240724082409241024112412241324142415241624172418241924202421242224232424242524262427242824292430243124322433243424352436243724382439244024412442244324442445244624472448244924502451245224532454245524562457245824592460246124622463246424652466246724682469247024712472247324742475247624772478247924802481248224832484248524862487248824892490249124922493249424952496249724982499250025012502250325042505250625072508250925102511251225132514251525162517251825192520252125222523252425252526252725282529253025312532253325342535253625372538253925402541254225432544254525462547254825492550255125522553255425552556255725582559256025612562256325642565256625672568256925702571257225732574257525762577257825792580258125822583258425852586258725882589259025912592259325942595259625972598259926002601260226032604260526062607260826092610261126122613261426152616261726182619262026212622262326242625262626272628262926302631263226332634263526362637263826392640264126422643264426452646264726482649265026512652265326542655265626572658265926602661266226632664266526662667266826692670267126722673267426752676267726782679268026812682268326842685268626872688268926902691269226932694269526962697269826992700270127022703270427052706270727082709271027112712271327142715271627172718271927202721272227232724272527262727272827292730273127322733273427352736273727382739274027412742274327442745274627472748274927502751275227532754
  1. nil subclass: #Object
  2. instanceVariableNames: ''
  3. category: 'Kernel'!
  4. !Object methodsFor: ''!
  5. foo ^ self
  6. ! !
  7. !Object methodsFor: 'accessing'!
  8. yourself
  9. ^self
  10. !
  11. class
  12. <return self.klass>
  13. !
  14. size
  15. self error: 'Object not indexable'
  16. !
  17. instVarAt: aString
  18. <return self['@'+aString]>
  19. !
  20. instVarAt: aString put: anObject
  21. <self['@' + aString] = anObject>
  22. !
  23. basicAt: aString
  24. <return self[aString]>
  25. !
  26. basicAt: aString put: anObject
  27. <return self[aString] = anObject>
  28. !
  29. basicDelete: aString
  30. <delete self[aString]>
  31. ! !
  32. !Object methodsFor: 'comparing'!
  33. = anObject
  34. <return self == anObject>
  35. !
  36. ~= anObject
  37. ^(self = anObject) = false
  38. ! !
  39. !Object methodsFor: 'converting'!
  40. -> anObject
  41. ^Association key: self value: anObject
  42. !
  43. asString
  44. ^self printString
  45. !
  46. asJavascript
  47. ^self asString
  48. !
  49. asJSON
  50. <return JSON.stringify(self._asJSONObject())>
  51. !
  52. asJSONObject
  53. | object |
  54. object := Object new.
  55. self class instanceVariableNames do: [:each |
  56. object basicAt: each put: (self instVarAt: each) asJSONObject].
  57. ^object
  58. ! !
  59. !Object methodsFor: 'copying'!
  60. copy
  61. ^self shallowCopy postCopy
  62. !
  63. shallowCopy
  64. <
  65. var copy = self.klass._new();
  66. for(var i in self) {
  67. if(/^@.+/.test(i)) {
  68. copy[i] = self[i];
  69. }
  70. }
  71. return copy;
  72. >
  73. !
  74. deepCopy
  75. <
  76. var copy = self.klass._new();
  77. for(var i in self) {
  78. if(/^@.+/.test(i)) {
  79. copy[i] = self[i]._deepCopy();
  80. }
  81. }
  82. return copy;
  83. >
  84. !
  85. postCopy
  86. ! !
  87. !Object methodsFor: 'error handling'!
  88. error: aString
  89. Error signal: aString
  90. !
  91. subclassResponsibility
  92. self error: 'This method is a responsibility of a subclass'
  93. !
  94. shouldNotImplement
  95. self error: 'This method should not be implemented in ', self class name
  96. !
  97. try: aBlock catch: anotherBlock
  98. <try{aBlock()} catch(e) {anotherBlock(e)}>
  99. !
  100. doesNotUnderstand: aMessage
  101. MessageNotUnderstood new
  102. receiver: self;
  103. message: aMessage;
  104. signal
  105. !
  106. halt
  107. self error: 'Halt encountered'
  108. ! !
  109. !Object methodsFor: 'initialization'!
  110. initialize
  111. ! !
  112. !Object methodsFor: 'message handling'!
  113. perform: aSymbol
  114. ^self perform: aSymbol withArguments: #()
  115. !
  116. perform: aSymbol withArguments: aCollection
  117. ^self basicPerform: aSymbol asSelector withArguments: aCollection
  118. !
  119. basicPerform: aSymbol
  120. ^self basicPerform: aSymbol withArguments: #()
  121. !
  122. basicPerform: aSymbol withArguments: aCollection
  123. <return self[aSymbol].apply(self, aCollection);>
  124. ! !
  125. !Object methodsFor: 'printing'!
  126. printString
  127. ^'a ', self class name
  128. !
  129. printNl
  130. <console.log(self)>
  131. !
  132. log: aString block: aBlock
  133. | result |
  134. console log: aString, ' time: ', (Date millisecondsToRun: [result := aBlock value]) printString.
  135. ^result
  136. ! !
  137. !Object methodsFor: 'testing'!
  138. isKindOf: aClass
  139. ^(self isMemberOf: aClass)
  140. ifTrue: [true]
  141. ifFalse: [self class inheritsFrom: aClass]
  142. !
  143. isMemberOf: aClass
  144. ^self class = aClass
  145. !
  146. ifNil: aBlock
  147. "inlined in the Compiler"
  148. ^self
  149. !
  150. ifNil: aBlock ifNotNil: anotherBlock
  151. "inlined in the Compiler"
  152. ^anotherBlock value
  153. !
  154. ifNotNil: aBlock
  155. "inlined in the Compiler"
  156. ^aBlock value
  157. !
  158. ifNotNil: aBlock ifNil: anotherBlock
  159. "inlined in the Compiler"
  160. ^aBlock value
  161. !
  162. isNil
  163. ^false
  164. !
  165. notNil
  166. ^self isNil not
  167. !
  168. isClass
  169. ^false
  170. !
  171. isMetaclass
  172. ^false
  173. !
  174. isNumber
  175. ^false
  176. !
  177. isString
  178. ^false
  179. !
  180. isParseFailure
  181. ^false
  182. ! !
  183. !Object class methodsFor: 'initialization'!
  184. initialize
  185. "no op"
  186. ! !
  187. Object subclass: #Smalltalk
  188. instanceVariableNames: ''
  189. category: 'Kernel'!
  190. !Smalltalk methodsFor: 'accessing'!
  191. classes
  192. <return self.classes()>
  193. !
  194. readJSON: anObject
  195. <return self.readJSObject(anObject)>
  196. !
  197. at: aString
  198. <return self[aString]>
  199. !
  200. removeClass: aClass
  201. aClass isMetaclass ifTrue: [self error: aClass asString, ' is a Metaclass and cannot be removed!!'].
  202. aClass methodDictionary values do: [:each |
  203. aClass removeCompiledMethod: each].
  204. aClass class methodDictionary values do: [:each |
  205. aClass class removeCompiledMethod: each].
  206. self basicDelete: aClass name
  207. !
  208. basicParse: aString
  209. <return smalltalk.parser.parse(aString)>
  210. !
  211. parse: aString
  212. | result |
  213. self try: [result := self basicParse: aString] catch: [:ex | (self parseError: ex parsing: aString) signal].
  214. ^result
  215. !
  216. parseError: anException parsing: aString
  217. | row col message lines badLine code |
  218. <row = anException.line;
  219. col = anException.column;
  220. message = anException.message;>.
  221. lines := aString lines.
  222. badLine := lines at: row.
  223. badLine := (badLine copyFrom: 1 to: col - 1), ' ===>', (badLine copyFrom: col to: badLine size).
  224. lines at: row put: badLine.
  225. code := String streamContents: [:s |
  226. lines withIndexDo: [:l :i |
  227. s nextPutAll: i asString, ': ', l, String lf]].
  228. ^ Error new messageText: ('Parse error on line ' , row , ' column ' , col , ' : ' , message , ' Below is code with line numbers and ===> marker inserted:' , String lf, code)
  229. ! !
  230. Smalltalk class instanceVariableNames: 'current'!
  231. !Smalltalk class methodsFor: 'accessing'!
  232. current
  233. <return smalltalk>
  234. ! !
  235. Object subclass: #Behavior
  236. instanceVariableNames: ''
  237. category: 'Kernel'!
  238. !Behavior methodsFor: 'accessing'!
  239. name
  240. <return self.className || nil>
  241. !
  242. superclass
  243. <return self.superclass || nil>
  244. !
  245. subclasses
  246. <return smalltalk.subclasses(self)>
  247. !
  248. allSubclasses
  249. | result |
  250. result := self subclasses.
  251. self subclasses do: [:each |
  252. result addAll: each allSubclasses].
  253. ^result
  254. !
  255. withAllSubclasses
  256. ^(Array with: self) addAll: self allSubclasses; yourself
  257. !
  258. prototype
  259. <return self.fn.prototype>
  260. !
  261. methodDictionary
  262. <var dict = smalltalk.Dictionary._new();
  263. var methods = self.fn.prototype.methods;
  264. for(var i in methods) {
  265. if(methods[i].selector) {
  266. dict._at_put_(methods[i].selector, methods[i]);
  267. }
  268. };
  269. return dict>
  270. !
  271. methodsFor: aString
  272. ^ClassCategoryReader new
  273. class: self category: aString;
  274. yourself
  275. !
  276. addCompiledMethod: aMethod
  277. <smalltalk.addMethod(aMethod.selector._asSelector(), aMethod, self)>
  278. !
  279. instanceVariableNames
  280. <return self.iVarNames>
  281. !
  282. comment
  283. ^(self basicAt: 'comment') ifNil: ['']
  284. !
  285. comment: aString
  286. self basicAt: 'comment' put: aString
  287. !
  288. commentStamp
  289. ^ClassCommentReader new
  290. class: self;
  291. yourself
  292. !
  293. removeCompiledMethod: aMethod
  294. <delete self.fn.prototype[aMethod.selector._asSelector()];
  295. delete self.fn.prototype.methods[aMethod.selector];
  296. smalltalk.init(self);>
  297. !
  298. protocols
  299. | protocols |
  300. protocols := Array new.
  301. self methodDictionary do: [:each |
  302. (protocols includes: each category) ifFalse: [
  303. protocols add: each category]].
  304. ^protocols sort
  305. !
  306. protocolsDo: aBlock
  307. "Execute aBlock for each method category with
  308. its collection of methods in the sort order of category name."
  309. | methodsByCategory |
  310. methodsByCategory := Dictionary new.
  311. self methodDictionary values do: [:m |
  312. (methodsByCategory at: m category ifAbsentPut: [Array new])
  313. add: m].
  314. self protocols do: [:category |
  315. aBlock value: category value: (methodsByCategory at: category)]
  316. !
  317. allInstanceVariableNames
  318. | result |
  319. result := self instanceVariableNames copy.
  320. self superclass ifNotNil: [
  321. result addAll: self superclass allInstanceVariableNames].
  322. ^result
  323. !
  324. methodAt: aString
  325. <return smalltalk.methods(self)[aString]>
  326. !
  327. methodsFor: aString stamp: aStamp
  328. "Added for compatibility, right now ignores stamp."
  329. ^self methodsFor: aString
  330. !
  331. commentStamp: aStamp prior: prior
  332. ^self commentStamp
  333. ! !
  334. !Behavior methodsFor: 'compiling'!
  335. compile: aString
  336. self compile: aString category: ''
  337. !
  338. compile: aString category: anotherString
  339. | method |
  340. method := Compiler new load: aString forClass: self.
  341. method category: anotherString.
  342. self addCompiledMethod: method
  343. ! !
  344. !Behavior methodsFor: 'instance creation'!
  345. new
  346. ^self basicNew initialize
  347. !
  348. basicNew
  349. <return new self.fn()>
  350. !
  351. inheritsFrom: aClass
  352. ^aClass allSubclasses includes: self
  353. ! !
  354. Behavior subclass: #Class
  355. instanceVariableNames: ''
  356. category: 'Kernel'!
  357. !Class methodsFor: 'accessing'!
  358. category
  359. <return self.category>
  360. !
  361. category: aString
  362. <self.category = aString>
  363. !
  364. rename: aString
  365. <
  366. smalltalk[aString] = self;
  367. delete smalltalk[self.className];
  368. self.className = aString;
  369. >
  370. ! !
  371. !Class methodsFor: 'class creation'!
  372. subclass: aString instanceVariableNames: anotherString
  373. ^self subclass: aString instanceVariableNames: anotherString category: nil
  374. !
  375. subclass: aString instanceVariableNames: aString2 category: aString3
  376. ^ClassBuilder new
  377. superclass: self subclass: aString instanceVariableNames: aString2 category: aString3
  378. !
  379. subclass: aString instanceVariableNames: aString2 classVariableNames: classVars poolDictionaries: pools category: aString3
  380. "Just ignore class variables and pools. Added for compatibility."
  381. ^self subclass: aString instanceVariableNames: aString2 category: aString3
  382. ! !
  383. !Class methodsFor: 'printing'!
  384. printString
  385. ^self name
  386. ! !
  387. !Class methodsFor: 'testing'!
  388. isClass
  389. ^true
  390. ! !
  391. Behavior subclass: #Metaclass
  392. instanceVariableNames: ''
  393. category: 'Kernel'!
  394. !Metaclass methodsFor: 'accessing'!
  395. instanceClass
  396. <return self.instanceClass>
  397. !
  398. instanceVariableNames: aCollection
  399. ClassBuilder new
  400. class: self instanceVariableNames: aCollection
  401. ! !
  402. !Metaclass methodsFor: 'printing'!
  403. printString
  404. ^self instanceClass name, ' class'
  405. ! !
  406. !Metaclass methodsFor: 'testing'!
  407. isMetaclass
  408. ^true
  409. ! !
  410. Object subclass: #CompiledMethod
  411. instanceVariableNames: ''
  412. category: 'Kernel'!
  413. !CompiledMethod methodsFor: 'accessing'!
  414. source
  415. ^(self basicAt: 'source') ifNil: ['']
  416. !
  417. source: aString
  418. self basicAt: 'source' put: aString
  419. !
  420. category
  421. ^(self basicAt: 'category') ifNil: ['']
  422. !
  423. category: aString
  424. self basicAt: 'category' put: aString
  425. !
  426. selector
  427. ^self basicAt: 'selector'
  428. !
  429. selector: aString
  430. self basicAt: 'selector' put: aString
  431. !
  432. fn
  433. ^self basicAt: 'fn'
  434. !
  435. fn: aBlock
  436. self basicAt: 'fn' put: aBlock
  437. !
  438. messageSends
  439. ^self basicAt: 'messageSends'
  440. !
  441. methodClass
  442. ^self basicAt: 'methodClass'
  443. !
  444. referencedClasses
  445. ^self basicAt: 'referencedClasses'
  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. ifNotEmpty: aBlock
  1030. self notEmpty ifTrue: aBlock.
  1031. !
  1032. ifEmpty: aBlock
  1033. self isEmpty ifTrue: aBlock.
  1034. ! !
  1035. !Collection class methodsFor: 'accessing'!
  1036. streamClass
  1037. ^Stream
  1038. ! !
  1039. !Collection class methodsFor: 'instance creation'!
  1040. with: anObject
  1041. ^self new
  1042. add: anObject;
  1043. yourself
  1044. !
  1045. with: anObject with: anotherObject
  1046. ^self new
  1047. add: anObject;
  1048. add: anotherObject;
  1049. yourself
  1050. !
  1051. with: firstObject with: secondObject with: thirdObject
  1052. ^self new
  1053. add: firstObject;
  1054. add: secondObject;
  1055. add: thirdObject;
  1056. yourself
  1057. !
  1058. withAll: aCollection
  1059. ^self new
  1060. addAll: aCollection;
  1061. yourself
  1062. ! !
  1063. Collection subclass: #SequenceableCollection
  1064. instanceVariableNames: ''
  1065. category: 'Kernel'!
  1066. !SequenceableCollection methodsFor: 'accessing'!
  1067. at: anIndex
  1068. ^self at: anIndex ifAbsent: [
  1069. self errorNotFound]
  1070. !
  1071. at: anIndex ifAbsent: aBlock
  1072. self subclassResponsibility
  1073. !
  1074. at: anIndex put: anObject
  1075. self subclassResponsibility
  1076. !
  1077. first
  1078. ^self at: 1
  1079. !
  1080. fourth
  1081. ^self at: 4
  1082. !
  1083. last
  1084. ^self at: self size
  1085. !
  1086. second
  1087. ^self at: 2
  1088. !
  1089. third
  1090. ^self at: 3
  1091. !
  1092. allButFirst
  1093. ^self copyFrom: 2 to: self size
  1094. !
  1095. allButLast
  1096. ^self copyFrom: 1 to: self size - 1
  1097. !
  1098. indexOf: anObject
  1099. ^self indexOf: anObject ifAbsent: [self errorNotFound]
  1100. !
  1101. indexOf: anObject ifAbsent: aBlock
  1102. <
  1103. for(var i=0;i<self.length;i++){
  1104. if(self[i].__eq(anObject)) {return i+1}
  1105. }
  1106. return aBlock();
  1107. >
  1108. !
  1109. indexOf: anObject startingAt: start ifAbsent: aBlock
  1110. <
  1111. for(var i=start-1;i<self.length;i++){
  1112. if(self[i].__eq(anObject)) {return i+1}
  1113. }
  1114. return aBlock();
  1115. >
  1116. !
  1117. indexOf: anObject startingAt: start
  1118. "Answer the index of the first occurence of anElement after start
  1119. within the receiver. If the receiver does not contain anElement,
  1120. answer 0."
  1121. ^self indexOf: anObject startingAt: start ifAbsent: [0]
  1122. ! !
  1123. !SequenceableCollection methodsFor: 'adding'!
  1124. removeLast
  1125. self remove: self last
  1126. !
  1127. addLast: anObject
  1128. self add: anObject
  1129. ! !
  1130. !SequenceableCollection methodsFor: 'converting'!
  1131. reversed
  1132. self subclassResponsibility
  1133. ! !
  1134. !SequenceableCollection methodsFor: 'copying'!
  1135. copyFrom: anIndex to: anotherIndex
  1136. self subclassResponsibility
  1137. ! !
  1138. !SequenceableCollection methodsFor: 'enumerating'!
  1139. withIndexDo: aBlock
  1140. <for(var i=0;i<self.length;i++){aBlock(self[i], i+1);}>
  1141. ! !
  1142. SequenceableCollection subclass: #String
  1143. instanceVariableNames: ''
  1144. category: 'Kernel'!
  1145. !String methodsFor: 'accessing'!
  1146. size
  1147. <return self.length>
  1148. !
  1149. at: anIndex
  1150. <return self[anIndex - 1]>
  1151. !
  1152. at: anIndex put: anObject
  1153. self errorReadOnly
  1154. !
  1155. at: anIndex ifAbsent: aBlock
  1156. (self at: anIndex) ifNil: [aBlock]
  1157. !
  1158. escaped
  1159. <return escape(self)>
  1160. !
  1161. unescaped
  1162. <return unescape(self)>
  1163. !
  1164. asciiValue
  1165. <return self.charCodeAt(0);>
  1166. ! !
  1167. !String methodsFor: 'adding'!
  1168. add: anObject
  1169. self errorReadOnly
  1170. !
  1171. remove: anObject
  1172. self errorReadOnly
  1173. ! !
  1174. !String methodsFor: 'comparing'!
  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. >= aString
  1185. <return String(self) >>= aString>
  1186. !
  1187. <= aString
  1188. <return String(self) <= aString>
  1189. ! !
  1190. !String methodsFor: 'converting'!
  1191. asSelector
  1192. "If you change this method, change smalltalk.convertSelector too (see js/boot.js file)"
  1193. | selector |
  1194. selector := '_', self.
  1195. selector := selector replace: ':' with: '_'.
  1196. selector := selector replace: '[+]' with: '_plus'.
  1197. selector := selector replace: '-' with: '_minus'.
  1198. selector := selector replace: '[*]' with: '_star'.
  1199. selector := selector replace: '[/]' with: '_slash'.
  1200. selector := selector replace: '>' with: '_gt'.
  1201. selector := selector replace: '<' with: '_lt'.
  1202. selector := selector replace: '=' with: '_eq'.
  1203. selector := selector replace: ',' with: '_comma'.
  1204. selector := selector replace: '[@]' with: '_at'.
  1205. ^selector
  1206. !
  1207. asJavascript
  1208. <
  1209. if(self.search(/^[a-zA-Z0-9_:.$ ]*$/) == -1)
  1210. return "unescape(\"" + escape(self) + "\")";
  1211. else
  1212. return "\"" + self + "\"";
  1213. >
  1214. !
  1215. tokenize: aString
  1216. <return self.split(aString)>
  1217. !
  1218. asString
  1219. ^self
  1220. !
  1221. asNumber
  1222. <return Number(self)>
  1223. !
  1224. asJSONObject
  1225. ^self
  1226. !
  1227. asLowercase
  1228. <return self.toLowerCase()>
  1229. !
  1230. asUppercase
  1231. <return self.toUpperCase()>
  1232. !
  1233. reversed
  1234. <return self.split("").reverse().join("")>
  1235. ! !
  1236. !String methodsFor: 'copying'!
  1237. , aString
  1238. <return self + aString>
  1239. !
  1240. copyFrom: anIndex to: anotherIndex
  1241. <return self.substring(anIndex - 1, anotherIndex)>
  1242. !
  1243. shallowCopy
  1244. ^self class fromString: self
  1245. !
  1246. deepCopy
  1247. ^self shallowCopy
  1248. ! !
  1249. !String methodsFor: 'error handling'!
  1250. errorReadOnly
  1251. self error: 'Object is read-only'
  1252. ! !
  1253. !String methodsFor: 'printing'!
  1254. printString
  1255. ^'''', self, ''''
  1256. !
  1257. printNl
  1258. <console.log(self)>
  1259. ! !
  1260. !String methodsFor: 'regular expressions'!
  1261. replace: aString with: anotherString
  1262. ^self replaceRegexp: (RegularExpression fromString: aString flag: 'g') with: anotherString
  1263. !
  1264. replaceRegexp: aRegexp with: aString
  1265. <return self.replace(aRegexp, aString)>
  1266. !
  1267. match: aRegexp
  1268. <return self.search(aRegexp) !!= -1>
  1269. !
  1270. trimLeft: separators
  1271. ^self replaceRegexp: (RegularExpression fromString: '^[', separators, ']+' flag: 'g') with: ''
  1272. !
  1273. trimRight: separators
  1274. ^self replaceRegexp: (RegularExpression fromString: '[', separators, ']+$' flag: 'g') with: ''
  1275. !
  1276. trimLeft
  1277. ^self trimLeft: '\s'
  1278. !
  1279. trimRight
  1280. ^self trimRight: '\s'
  1281. !
  1282. trimBoth
  1283. ^self trimBoth: '\s'
  1284. !
  1285. trimBoth: separators
  1286. ^(self trimLeft: separators) trimRight: separators
  1287. ! !
  1288. !String methodsFor: 'split join'!
  1289. join: aCollection
  1290. ^ String
  1291. streamContents: [:stream | aCollection
  1292. do: [:each | stream nextPutAll: each asString]
  1293. separatedBy: [stream nextPutAll: self]]
  1294. !
  1295. lineIndicesDo: aBlock
  1296. "execute aBlock with 3 arguments for each line:
  1297. - start index of line
  1298. - end index of line without line delimiter
  1299. - end index of line including line delimiter(s) CR, LF or CRLF"
  1300. | cr lf start sz nextLF nextCR |
  1301. start := 1.
  1302. sz := self size.
  1303. cr := String cr.
  1304. nextCR := self indexOf: cr startingAt: 1.
  1305. lf := String lf.
  1306. nextLF := self indexOf: lf startingAt: 1.
  1307. [ start <= sz ] whileTrue: [
  1308. (nextLF = 0 and: [ nextCR = 0 ])
  1309. ifTrue: [ "No more CR, nor LF, the string is over"
  1310. aBlock value: start value: sz value: sz.
  1311. ^self ].
  1312. (nextCR = 0 or: [ 0 < nextLF and: [ nextLF < nextCR ] ])
  1313. ifTrue: [ "Found a LF"
  1314. aBlock value: start value: nextLF - 1 value: nextLF.
  1315. start := 1 + nextLF.
  1316. nextLF := self indexOf: lf startingAt: start ]
  1317. ifFalse: [ 1 + nextCR = nextLF
  1318. ifTrue: [ "Found a CR-LF pair"
  1319. aBlock value: start value: nextCR - 1 value: nextLF.
  1320. start := 1 + nextLF.
  1321. nextCR := self indexOf: cr startingAt: start.
  1322. nextLF := self indexOf: lf startingAt: start ]
  1323. ifFalse: [ "Found a CR"
  1324. aBlock value: start value: nextCR - 1 value: nextCR.
  1325. start := 1 + nextCR.
  1326. nextCR := self indexOf: cr startingAt: start ]]]
  1327. !
  1328. linesDo: aBlock
  1329. "Execute aBlock with each line in this string. The terminating line
  1330. delimiters CR, LF or CRLF pairs are not included in what is passed to aBlock"
  1331. self lineIndicesDo: [:start :endWithoutDelimiters :end |
  1332. aBlock value: (self copyFrom: start to: endWithoutDelimiters)]
  1333. !
  1334. lines
  1335. "Answer an array of lines composing this receiver without the line ending delimiters."
  1336. | lines |
  1337. lines := Array new.
  1338. self linesDo: [:aLine | lines add: aLine].
  1339. ^lines
  1340. !
  1341. lineNumber: anIndex
  1342. "Answer a string containing the characters in the given line number."
  1343. | lineCount |
  1344. lineCount := 0.
  1345. self lineIndicesDo: [:start :endWithoutDelimiters :end |
  1346. (lineCount := lineCount + 1) = anIndex ifTrue: [^self copyFrom: start to: endWithoutDelimiters]].
  1347. ^nil
  1348. ! !
  1349. !String methodsFor: 'testing'!
  1350. isString
  1351. ^true
  1352. !
  1353. includesSubString: subString
  1354. < return self.indexOf(subString) !!= -1 >
  1355. ! !
  1356. !String class methodsFor: 'accessing'!
  1357. streamClass
  1358. ^StringStream
  1359. !
  1360. cr
  1361. <return '\r'>
  1362. !
  1363. lf
  1364. <return '\n'>
  1365. !
  1366. space
  1367. <return ' '>
  1368. !
  1369. tab
  1370. <return '\t'>
  1371. !
  1372. crlf
  1373. <return '\r\n'>
  1374. ! !
  1375. !String class methodsFor: 'instance creation'!
  1376. fromString: aString
  1377. <return new self.fn(aString)>
  1378. !
  1379. streamContents: blockWithArg
  1380. |stream|
  1381. stream := (self streamClass on: String new).
  1382. blockWithArg value: stream.
  1383. ^ stream contents
  1384. !
  1385. value: aUTFCharCode
  1386. <return String.fromCharCode(aUTFCharCode);>
  1387. ! !
  1388. SequenceableCollection subclass: #Array
  1389. instanceVariableNames: ''
  1390. category: 'Kernel'!
  1391. !Array methodsFor: 'accessing'!
  1392. size
  1393. <return self.length>
  1394. !
  1395. at: anIndex put: anObject
  1396. <return self[anIndex - 1] = anObject>
  1397. !
  1398. at: anIndex ifAbsent: aBlock
  1399. <
  1400. var value = self[anIndex - 1];
  1401. if(value === undefined) {
  1402. return aBlock();
  1403. } else {
  1404. return value;
  1405. }
  1406. >
  1407. ! !
  1408. !Array methodsFor: 'adding/removing'!
  1409. add: anObject
  1410. <self.push(anObject); return anObject;>
  1411. !
  1412. remove: anObject
  1413. <
  1414. for(var i=0;i<self.length;i++) {
  1415. if(self[i] == anObject) {
  1416. self.splice(i,1);
  1417. break;
  1418. }
  1419. }
  1420. >
  1421. !
  1422. removeFrom: aNumber to: anotherNumber
  1423. <self.splice(aNumber - 1,anotherNumber - 1)>
  1424. ! !
  1425. !Array methodsFor: 'converting'!
  1426. asJavascript
  1427. ^'[', ((self collect: [:each | each asJavascript]) join: ', '), ']'
  1428. !
  1429. asJSONObject
  1430. ^self collect: [:each | each asJSONObject]
  1431. !
  1432. reversed
  1433. <return self._copy().reverse()>
  1434. ! !
  1435. !Array methodsFor: 'copying'!
  1436. shallowCopy
  1437. | newCollection |
  1438. newCollection := self class new.
  1439. self do: [:each | newCollection add: each].
  1440. ^newCollection
  1441. !
  1442. deepCopy
  1443. | newCollection |
  1444. newCollection := self class new.
  1445. self do: [:each | newCollection add: each deepCopy].
  1446. ^newCollection
  1447. !
  1448. copyFrom: anIndex to: anotherIndex
  1449. | array |
  1450. array := self class new.
  1451. anIndex to: anotherIndex do: [:each |
  1452. array add: (self at: each)].
  1453. ^array
  1454. ! !
  1455. !Array methodsFor: 'enumerating'!
  1456. join: aString
  1457. <return self.join(aString)>
  1458. !
  1459. sort
  1460. ^self basicPerform: 'sort'
  1461. !
  1462. sort: aBlock
  1463. <
  1464. return self.sort(function(a, b) {
  1465. if(aBlock(a,b)) {return -1} else {return 1}
  1466. })
  1467. >
  1468. !
  1469. sorted
  1470. ^self copy sort
  1471. !
  1472. sorted: aBlock
  1473. ^self copy sort: aBlock
  1474. !
  1475. printString
  1476. | str |
  1477. str := '' writeStream.
  1478. str nextPutAll: super printString, ' ('.
  1479. self
  1480. do: [:each | str nextPutAll: each printString]
  1481. separatedBy: [str nextPutAll: ' '].
  1482. str nextPutAll: ')'.
  1483. ^str contents
  1484. ! !
  1485. Object subclass: #RegularExpression
  1486. instanceVariableNames: ''
  1487. category: 'Kernel'!
  1488. !RegularExpression methodsFor: 'evaluating'!
  1489. compile: aString
  1490. <return self.compile(aString)>
  1491. !
  1492. exec: aString
  1493. <return self.exec(aString) || nil>
  1494. !
  1495. test: aString
  1496. <return self.test(aString)>
  1497. ! !
  1498. !RegularExpression class methodsFor: 'instance creation'!
  1499. fromString: aString flag: anotherString
  1500. <return new RegExp(aString, anotherString)>
  1501. !
  1502. fromString: aString
  1503. ^self fromString: aString flag: ''
  1504. ! !
  1505. Object subclass: #Error
  1506. instanceVariableNames: 'messageText'
  1507. category: 'Kernel'!
  1508. !Error methodsFor: 'accessing'!
  1509. messageText
  1510. ^messageText
  1511. !
  1512. messageText: aString
  1513. messageText := aString
  1514. !
  1515. context
  1516. <return self.context>
  1517. ! !
  1518. !Error methodsFor: 'signaling'!
  1519. signal
  1520. <self.context = thisContext; self.smalltalkError = true; throw(self)>
  1521. ! !
  1522. !Error class methodsFor: 'instance creation'!
  1523. signal: aString
  1524. ^self new
  1525. messageText: aString;
  1526. signal
  1527. ! !
  1528. Object subclass: #MethodContext
  1529. instanceVariableNames: ''
  1530. category: 'Kernel'!
  1531. !MethodContext methodsFor: 'accessing'!
  1532. receiver
  1533. <return self.receiver>
  1534. !
  1535. selector
  1536. <return smalltalk.convertSelector(self.selector)>
  1537. !
  1538. home
  1539. <return self.homeContext>
  1540. !
  1541. temps
  1542. <return self.temps>
  1543. !
  1544. printString
  1545. ^super printString, '(', self asString, ')'
  1546. !
  1547. asString
  1548. ^self receiver class printString, ' >> ', self selector
  1549. ! !
  1550. Object subclass: #Association
  1551. instanceVariableNames: 'key value'
  1552. category: 'Kernel'!
  1553. !Association methodsFor: 'accessing'!
  1554. key: aKey
  1555. key := aKey
  1556. !
  1557. key
  1558. ^key
  1559. !
  1560. value: aValue
  1561. value := aValue
  1562. !
  1563. value
  1564. ^value
  1565. ! !
  1566. !Association methodsFor: 'comparing'!
  1567. = anAssociation
  1568. ^self class = anAssociation class and: [
  1569. self key = anAssociation key and: [
  1570. self value = anAssociation value]]
  1571. ! !
  1572. !Association class methodsFor: 'instance creation'!
  1573. key: aKey value: aValue
  1574. ^self new
  1575. key: aKey;
  1576. value: aValue;
  1577. yourself
  1578. ! !
  1579. Collection subclass: #Dictionary
  1580. instanceVariableNames: 'keys'
  1581. category: 'Kernel'!
  1582. !Dictionary methodsFor: 'accessing'!
  1583. size
  1584. ^keys size
  1585. !
  1586. associations
  1587. | associations |
  1588. associations := #().
  1589. keys do: [:each |
  1590. associations add: (Association key: each value: (self at: each))].
  1591. ^associations
  1592. !
  1593. keys
  1594. ^keys copy
  1595. !
  1596. values
  1597. ^keys collect: [:each | self at: each]
  1598. !
  1599. at: aKey put: aValue
  1600. (keys includes: aKey) ifFalse: [keys add: aKey].
  1601. ^self basicAt: aKey put: aValue
  1602. !
  1603. at: aKey ifAbsent: aBlock
  1604. ^(self keys includes: aKey)
  1605. ifTrue: [self basicAt: aKey]
  1606. ifFalse: aBlock
  1607. !
  1608. at: aKey ifAbsentPut: aBlock
  1609. ^self at: aKey ifAbsent: [
  1610. self at: aKey put: aBlock value]
  1611. !
  1612. at: aKey ifPresent: aBlock
  1613. ^(self basicAt: aKey) ifNotNil: [aBlock value: (self at: aKey)]
  1614. !
  1615. at: aKey ifPresent: aBlock ifAbsent: anotherBlock
  1616. ^(self basicAt: aKey)
  1617. ifNil: anotherBlock
  1618. ifNotNil: [aBlock value: (self at: aKey)]
  1619. !
  1620. at: aKey
  1621. ^self at: aKey ifAbsent: [self errorNotFound]
  1622. ! !
  1623. !Dictionary methodsFor: 'adding/removing'!
  1624. add: anAssociation
  1625. self at: anAssociation key put: anAssociation value
  1626. !
  1627. addAll: aDictionary
  1628. super addAll: aDictionary associations.
  1629. ^aDictionary
  1630. !
  1631. remove: aKey
  1632. self removeKey: aKey
  1633. !
  1634. removeKey: aKey
  1635. keys remove: aKey
  1636. ! !
  1637. !Dictionary methodsFor: 'comparing'!
  1638. = aDictionary
  1639. self class = aDictionary class ifFalse: [^false].
  1640. self associationsDo: [:assoc |
  1641. (aDictionary at: assoc key ifAbsent: [^false]) = assoc value
  1642. ifFalse: [^false]].
  1643. ^true
  1644. ! !
  1645. !Dictionary methodsFor: 'converting'!
  1646. asJSONObject
  1647. | object |
  1648. object := Object new.
  1649. self keysAndValuesDo: [:key :value |
  1650. object basicAt: key put: value asJSONObject].
  1651. ^object
  1652. ! !
  1653. !Dictionary methodsFor: 'copying'!
  1654. shallowCopy
  1655. | copy |
  1656. copy := self class new.
  1657. self associationsDo: [:each |
  1658. copy at: each key put: each value].
  1659. ^copy
  1660. !
  1661. , aCollection
  1662. self shouldNotImplement
  1663. !
  1664. copyFrom: anIndex to: anotherIndex
  1665. self shouldNotImplement
  1666. ! !
  1667. !Dictionary methodsFor: 'enumerating'!
  1668. associationsDo: aBlock
  1669. self associations do: aBlock
  1670. !
  1671. keysAndValuesDo: aBlock
  1672. self associationsDo: [:each |
  1673. aBlock value: each key value: each value]
  1674. !
  1675. do: aBlock
  1676. self values do: aBlock
  1677. !
  1678. select: aBlock
  1679. | newDict |
  1680. newDict := self class new.
  1681. self keysAndValuesDo: [:key :value |
  1682. (aBlock value: value) ifTrue: [newDict at: key put: value]].
  1683. ^newDict
  1684. !
  1685. collect: aBlock
  1686. | newDict |
  1687. newDict := self class new.
  1688. self keysAndValuesDo: [:key :value |
  1689. newDict at: key put: (aBlock value: value)].
  1690. ^newDict
  1691. !
  1692. detect: aBlock ifNone: anotherBlock
  1693. ^self values detect: aBlock ifNone: anotherBlock
  1694. !
  1695. includes: anObject
  1696. ^self values includes: anObject
  1697. ! !
  1698. !Dictionary methodsFor: 'initialization'!
  1699. initialize
  1700. super initialize.
  1701. keys := #()
  1702. ! !
  1703. !Dictionary methodsFor: 'printing'!
  1704. printString
  1705. ^ String streamContents: [:aStream|
  1706. aStream
  1707. nextPutAll: super printString;
  1708. nextPutAll: '('.
  1709. self associations
  1710. do: [:anAssociation|
  1711. aStream
  1712. nextPutAll: anAssociation key printString;
  1713. nextPutAll: ' -> ';
  1714. nextPutAll: anAssociation value printString]
  1715. separatedBy: [aStream nextPutAll: ' , '].
  1716. aStream nextPutAll: ')'.
  1717. ]
  1718. ! !
  1719. !Dictionary class methodsFor: 'instance creation'!
  1720. fromPairs: aCollection
  1721. | dict |
  1722. dict := self new.
  1723. aCollection do: [:each | dict add: each].
  1724. ^dict
  1725. ! !
  1726. Object subclass: #ClassBuilder
  1727. instanceVariableNames: ''
  1728. category: 'Kernel'!
  1729. !ClassBuilder methodsFor: 'class creation'!
  1730. superclass: aClass subclass: aString
  1731. self superclass: aClass subclass: aString instanceVariableNames: '' category: nil
  1732. !
  1733. superclass: aClass subclass: aString instanceVariableNames: aString2 category: aString3
  1734. | newClass |
  1735. newClass := self addSubclassOf: aClass named: aString instanceVariableNames: (self instanceVariableNamesFor: aString2).
  1736. self setupClass: newClass.
  1737. newClass category: (aString3 ifNil: ['unclassified'])
  1738. !
  1739. class: aClass instanceVariableNames: aString
  1740. aClass isMetaclass ifFalse: [self error: aClass name, ' is not a metaclass'].
  1741. aClass basicAt: 'iVarNames' put: (self instanceVariableNamesFor: aString).
  1742. self setupClass: aClass
  1743. ! !
  1744. !ClassBuilder methodsFor: 'private'!
  1745. instanceVariableNamesFor: aString
  1746. ^(aString tokenize: ' ') reject: [:each | each isEmpty]
  1747. !
  1748. addSubclassOf: aClass named: aString instanceVariableNames: aCollection
  1749. <smalltalk.addClass(aString, aClass, aCollection);
  1750. return smalltalk[aString]>
  1751. !
  1752. setupClass: aClass
  1753. <smalltalk.init(aClass);>
  1754. ! !
  1755. Object subclass: #ClassCategoryReader
  1756. instanceVariableNames: 'class category chunkParser'
  1757. category: 'Kernel'!
  1758. !ClassCategoryReader methodsFor: 'accessing'!
  1759. class: aClass category: aString
  1760. class := aClass.
  1761. category := aString
  1762. ! !
  1763. !ClassCategoryReader methodsFor: 'fileIn'!
  1764. scanFrom: aChunkParser
  1765. | chunk |
  1766. [chunk := aChunkParser nextChunk.
  1767. chunk isEmpty] whileFalse: [
  1768. self compileMethod: chunk]
  1769. ! !
  1770. !ClassCategoryReader methodsFor: 'initialization'!
  1771. initialize
  1772. super initialize.
  1773. chunkParser := ChunkParser new.
  1774. ! !
  1775. !ClassCategoryReader methodsFor: 'private'!
  1776. compileMethod: aString
  1777. | method |
  1778. method := Compiler new load: aString forClass: class.
  1779. method category: category.
  1780. class addCompiledMethod: method
  1781. ! !
  1782. Object subclass: #Stream
  1783. instanceVariableNames: 'collection position streamSize'
  1784. category: 'Kernel'!
  1785. !Stream methodsFor: 'accessing'!
  1786. collection
  1787. ^collection
  1788. !
  1789. setCollection: aCollection
  1790. collection := aCollection
  1791. !
  1792. position
  1793. ^position ifNil: [position := 0]
  1794. !
  1795. position: anInteger
  1796. position := anInteger
  1797. !
  1798. streamSize
  1799. ^streamSize
  1800. !
  1801. setStreamSize: anInteger
  1802. streamSize := anInteger
  1803. !
  1804. contents
  1805. ^self collection
  1806. copyFrom: 1
  1807. to: self streamSize
  1808. !
  1809. size
  1810. ^self streamSize
  1811. ! !
  1812. !Stream methodsFor: 'actions'!
  1813. reset
  1814. self position: 0
  1815. !
  1816. close
  1817. !
  1818. flush
  1819. !
  1820. resetContents
  1821. self reset.
  1822. self setStreamSize: 0
  1823. ! !
  1824. !Stream methodsFor: 'enumerating'!
  1825. do: aBlock
  1826. [self atEnd] whileFalse: [aBlock value: self next]
  1827. ! !
  1828. !Stream methodsFor: 'positioning'!
  1829. setToEnd
  1830. self position: self size
  1831. !
  1832. skip: anInteger
  1833. self position: ((self position + anInteger) min: self size max: 0)
  1834. ! !
  1835. !Stream methodsFor: 'reading'!
  1836. next
  1837. self position: self position + 1.
  1838. ^collection at: self position
  1839. !
  1840. next: anInteger
  1841. | tempCollection |
  1842. tempCollection := self collection class new.
  1843. anInteger timesRepeat: [
  1844. self atEnd ifFalse: [
  1845. tempCollection add: self next]].
  1846. ^tempCollection
  1847. !
  1848. peek
  1849. ^self atEnd ifFalse: [
  1850. self collection at: self position + 1]
  1851. ! !
  1852. !Stream methodsFor: 'testing'!
  1853. atEnd
  1854. ^self position = self size
  1855. !
  1856. atStart
  1857. ^self position = 0
  1858. !
  1859. isEmpty
  1860. ^self size = 0
  1861. ! !
  1862. !Stream methodsFor: 'writing'!
  1863. nextPut: anObject
  1864. self position: self position + 1.
  1865. self collection at: self position put: anObject.
  1866. self setStreamSize: (self streamSize max: self position)
  1867. !
  1868. nextPutAll: aCollection
  1869. aCollection do: [:each |
  1870. self nextPut: each]
  1871. ! !
  1872. !Stream class methodsFor: 'instance creation'!
  1873. on: aCollection
  1874. ^self new
  1875. setCollection: aCollection;
  1876. setStreamSize: aCollection size;
  1877. yourself
  1878. ! !
  1879. Stream subclass: #StringStream
  1880. instanceVariableNames: ''
  1881. category: 'Kernel'!
  1882. !StringStream methodsFor: 'reading'!
  1883. next: anInteger
  1884. | tempCollection |
  1885. tempCollection := self collection class new.
  1886. anInteger timesRepeat: [
  1887. self atEnd ifFalse: [
  1888. tempCollection := tempCollection, self next]].
  1889. ^tempCollection
  1890. ! !
  1891. !StringStream methodsFor: 'writing'!
  1892. nextPut: aString
  1893. self nextPutAll: aString
  1894. !
  1895. nextPutAll: aString
  1896. self setCollection:
  1897. (self collection copyFrom: 1 to: self position),
  1898. aString,
  1899. (self collection copyFrom: (self position + 1 + aString size) to: self collection size).
  1900. self position: self position + aString size.
  1901. self setStreamSize: (self streamSize max: self position)
  1902. !
  1903. cr
  1904. ^self nextPutAll: String cr
  1905. !
  1906. crlf
  1907. ^self nextPutAll: String crlf
  1908. !
  1909. lf
  1910. ^self nextPutAll: String lf
  1911. !
  1912. space
  1913. self nextPut: ' '
  1914. ! !
  1915. Object subclass: #ClassCommentReader
  1916. instanceVariableNames: 'class chunkParser'
  1917. category: 'Kernel'!
  1918. !ClassCommentReader methodsFor: 'accessing'!
  1919. class: aClass
  1920. class := aClass
  1921. ! !
  1922. !ClassCommentReader methodsFor: 'fileIn'!
  1923. scanFrom: aChunkParser
  1924. | chunk |
  1925. chunk := aChunkParser nextChunk.
  1926. chunk isEmpty ifFalse: [
  1927. self setComment: chunk].
  1928. ! !
  1929. !ClassCommentReader methodsFor: 'initialization'!
  1930. initialize
  1931. super initialize.
  1932. chunkParser := ChunkParser new.
  1933. ! !
  1934. !ClassCommentReader methodsFor: 'private'!
  1935. setComment: aString
  1936. class comment: aString
  1937. ! !
  1938. Object subclass: #Random
  1939. instanceVariableNames: ''
  1940. category: 'Kernel'!
  1941. !Random methodsFor: 'accessing'!
  1942. next
  1943. <return Math.random()>
  1944. !
  1945. next: anInteger
  1946. ^1 to: anInteger collect: [:each | self next]
  1947. ! !
  1948. Object subclass: #Point
  1949. instanceVariableNames: 'x y'
  1950. category: 'Kernel'!
  1951. !Point methodsFor: 'accessing'!
  1952. x
  1953. ^x
  1954. !
  1955. y
  1956. ^y
  1957. !
  1958. y: aNumber
  1959. y := aNumber
  1960. !
  1961. x: aNumber
  1962. x := aNumber
  1963. ! !
  1964. !Point methodsFor: 'arithmetic'!
  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. - aPoint
  1972. ^Point x: self x - aPoint asPoint x y: self y - aPoint asPoint y
  1973. !
  1974. / aPoint
  1975. ^Point x: self x / aPoint asPoint x y: self y / aPoint asPoint y
  1976. ! !
  1977. !Point methodsFor: 'converting'!
  1978. asPoint
  1979. ^self
  1980. ! !
  1981. !Point class methodsFor: 'instance creation'!
  1982. x: aNumber y: anotherNumber
  1983. ^self new
  1984. x: aNumber;
  1985. y: anotherNumber;
  1986. yourself
  1987. ! !
  1988. Object subclass: #Message
  1989. instanceVariableNames: 'selector arguments'
  1990. category: 'Kernel'!
  1991. !Message methodsFor: 'accessing'!
  1992. selector
  1993. ^selector
  1994. !
  1995. selector: aString
  1996. selector := aString
  1997. !
  1998. arguments: anArray
  1999. arguments := anArray
  2000. !
  2001. arguments
  2002. ^arguments
  2003. ! !
  2004. !Message class methodsFor: 'instance creation'!
  2005. selector: aString arguments: anArray
  2006. ^self new
  2007. selector: aString;
  2008. arguments: anArray;
  2009. yourself
  2010. ! !
  2011. Error subclass: #MessageNotUnderstood
  2012. instanceVariableNames: 'message receiver'
  2013. category: 'Kernel'!
  2014. !MessageNotUnderstood methodsFor: 'accessing'!
  2015. message
  2016. ^message
  2017. !
  2018. message: aMessage
  2019. message := aMessage
  2020. !
  2021. receiver
  2022. ^receiver
  2023. !
  2024. receiver: anObject
  2025. receiver := anObject
  2026. !
  2027. messageText
  2028. ^self receiver asString, ' does not understand #', self message selector
  2029. ! !
  2030. Object subclass: #ErrorHandler
  2031. instanceVariableNames: ''
  2032. category: 'Kernel'!
  2033. !ErrorHandler methodsFor: 'error handling'!
  2034. handleError: anError
  2035. anError context ifNotNil: [self logErrorContext: anError context].
  2036. self logError: anError
  2037. ! !
  2038. !ErrorHandler methodsFor: 'private'!
  2039. logContext: aContext
  2040. aContext home ifNotNil: [
  2041. self logContext: aContext home].
  2042. self log: aContext receiver asString, '>>', aContext selector
  2043. !
  2044. logErrorContext: aContext
  2045. aContext ifNotNil: [
  2046. aContext home ifNotNil: [
  2047. self logContext: aContext home]]
  2048. !
  2049. logError: anError
  2050. self log: anError messageText
  2051. !
  2052. log: aString
  2053. console log: aString
  2054. ! !
  2055. ErrorHandler class instanceVariableNames: 'current'!
  2056. !ErrorHandler class methodsFor: 'accessing'!
  2057. current
  2058. ^current
  2059. !
  2060. setCurrent: anHandler
  2061. current := anHandler
  2062. ! !
  2063. !ErrorHandler class methodsFor: 'initialization'!
  2064. initialize
  2065. self register
  2066. !
  2067. register
  2068. ErrorHandler setCurrent: self new
  2069. ! !
  2070. Object subclass: #JSObjectProxy
  2071. instanceVariableNames: 'jsObject'
  2072. category: 'Kernel'!
  2073. !JSObjectProxy methodsFor: 'accessing'!
  2074. jsObject: aJSObject
  2075. jsObject := aJSObject
  2076. !
  2077. jsObject
  2078. ^jsObject
  2079. ! !
  2080. !JSObjectProxy methodsFor: 'proxy'!
  2081. printString
  2082. ^self jsObject toString
  2083. !
  2084. inspectOn: anInspector
  2085. | variables |
  2086. variables := Dictionary new.
  2087. variables at: '#self' put: self jsObject.
  2088. anInspector setLabel: self printString.
  2089. <for(var i in self['@jsObject']) {
  2090. variables._at_put_(i, self['@jsObject'][i]);
  2091. }>.
  2092. anInspector setVariables: variables
  2093. ! !
  2094. !JSObjectProxy class methodsFor: 'instance creation'!
  2095. on: aJSObject
  2096. ^self new
  2097. jsObject: aJSObject;
  2098. yourself
  2099. ! !