Kernel.st 47 KB

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