1
0

Kernel-Tests.st 31 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209121012111212121312141215121612171218121912201221122212231224122512261227122812291230123112321233123412351236123712381239124012411242124312441245124612471248124912501251125212531254125512561257125812591260126112621263126412651266126712681269127012711272127312741275127612771278127912801281128212831284128512861287128812891290129112921293129412951296129712981299130013011302130313041305130613071308130913101311131213131314131513161317131813191320132113221323132413251326132713281329133013311332133313341335133613371338133913401341134213431344134513461347134813491350135113521353135413551356135713581359136013611362136313641365136613671368136913701371137213731374137513761377137813791380138113821383138413851386138713881389139013911392139313941395139613971398139914001401140214031404140514061407140814091410141114121413141414151416141714181419142014211422142314241425142614271428
  1. Smalltalk current createPackage: 'Kernel-Tests' properties: #{}!
  2. TestCase subclass: #BlockClosureTest
  3. instanceVariableNames: ''
  4. package: 'Kernel-Tests'!
  5. !BlockClosureTest methodsFor: 'tests'!
  6. testCompiledSource
  7. self assert: ([1+1] compiledSource includesSubString: 'function')
  8. !
  9. testEnsure
  10. self assert: 3 equals: ([3] ensure: [4])
  11. !
  12. testEnsureRaises
  13. self should: [[Error new signal] ensure: [true]] raise: Error
  14. !
  15. testNumArgs
  16. self assert: [] numArgs equals: 0.
  17. self assert: [:a :b | ] numArgs equals: 2
  18. !
  19. testOnDo
  20. self assert: ([Error new signal] on: Error do: [:ex | true])
  21. !
  22. testValue
  23. self assert: ([1+1] value) equals: 2.
  24. self assert: ([:x | x +1] value: 2) equals: 3.
  25. self assert: ([:x :y | x*y] value: 2 value: 4) equals: 8.
  26. "Arguments are optional in Amber. This isn't ANSI compliant."
  27. self assert: ([:a :b :c | 1] value) equals: 1
  28. !
  29. testValueWithPossibleArguments
  30. self assert: ([1] valueWithPossibleArguments: #(3 4)) equals: 1.
  31. self assert: ([:a | a + 4] valueWithPossibleArguments: #(3 4)) equals: 7.
  32. self assert: ([:a :b | a + b] valueWithPossibleArguments: #(3 4 5)) equals: 7.
  33. !
  34. testWhileFalse
  35. | i |
  36. i := 0.
  37. [i > 5] whileFalse: [i := i + 1].
  38. self assert: i equals: 6.
  39. i := 0.
  40. [i := i + 1. i > 5] whileFalse.
  41. self assert: i equals: 6
  42. !
  43. testWhileTrue
  44. | i |
  45. i := 0.
  46. [i < 5] whileTrue: [i := i + 1].
  47. self assert: i equals: 5.
  48. i := 0.
  49. [i := i + 1. i < 5] whileTrue.
  50. self assert: i equals: 5
  51. ! !
  52. TestCase subclass: #BooleanTest
  53. instanceVariableNames: ''
  54. package: 'Kernel-Tests'!
  55. !BooleanTest methodsFor: 'tests'!
  56. testEquality
  57. "We're on top of JS...just be sure to check the basics!!"
  58. self deny: 0 = false.
  59. self deny: false = 0.
  60. self deny: '' = false.
  61. self deny: false = ''.
  62. self assert: true = true.
  63. self deny: false = true.
  64. self deny: true = false.
  65. self assert: false = false.
  66. "JS may do some type coercing after sending a message"
  67. self assert: true yourself = true.
  68. self assert: true yourself = true yourself
  69. !
  70. testIdentity
  71. "We're on top of JS...just be sure to check the basics!!"
  72. self deny: 0 == false.
  73. self deny: false == 0.
  74. self deny: '' == false.
  75. self deny: false == ''.
  76. self assert: true == true.
  77. self deny: false == true.
  78. self deny: true == false.
  79. self assert: false == false.
  80. "JS may do some type coercing after sending a message"
  81. self assert: true yourself == true.
  82. self assert: true yourself == true yourself
  83. !
  84. testIfTrueIfFalse
  85. self assert: (true ifTrue: ['alternative block']) = 'alternative block'.
  86. self assert: (true ifFalse: ['alternative block']) = nil.
  87. self assert: (false ifTrue: ['alternative block']) = nil.
  88. self assert: (false ifFalse: ['alternative block']) = 'alternative block'.
  89. self assert: (false ifTrue: ['alternative block'] ifFalse: ['alternative block2']) = 'alternative block2'.
  90. self assert: (false ifFalse: ['alternative block'] ifTrue: ['alternative block2']) = 'alternative block'.
  91. self assert: (true ifTrue: ['alternative block'] ifFalse: ['alternative block2']) = 'alternative block'.
  92. self assert: (true ifFalse: ['alternative block'] ifTrue: ['alternative block2']) = 'alternative block2'.
  93. !
  94. testIfTrueIfFalseWithBoxing
  95. self assert: (true yourself ifTrue: ['alternative block']) = 'alternative block'.
  96. self assert: (true yourself ifFalse: ['alternative block']) = nil.
  97. self assert: (false yourself ifTrue: ['alternative block']) = nil.
  98. self assert: (false yourself ifFalse: ['alternative block']) = 'alternative block'.
  99. self assert: (false yourself ifTrue: ['alternative block'] ifFalse: ['alternative block2']) = 'alternative block2'.
  100. self assert: (false yourself ifFalse: ['alternative block'] ifTrue: ['alternative block2']) = 'alternative block'.
  101. self assert: (true yourself ifTrue: ['alternative block'] ifFalse: ['alternative block2']) = 'alternative block'.
  102. self assert: (true yourself ifFalse: ['alternative block'] ifTrue: ['alternative block2']) = 'alternative block2'.
  103. !
  104. testLogic
  105. "Trivial logic table"
  106. self assert: (true & true); deny: (true & false); deny: (false & true); deny: (false & false).
  107. self assert: (true | true); assert: (true | false); assert: (false | true); deny: (false | false).
  108. "Checking that expressions work fine too"
  109. self assert: (true & (1 > 0)); deny: ((1 > 0) & false); deny: ((1 > 0) & (1 > 2)).
  110. self assert: (false | (1 > 0)); assert: ((1 > 0) | false); assert: ((1 > 0) | (1 > 2))
  111. !
  112. testLogicKeywords
  113. "Trivial logic table"
  114. self
  115. assert: (true and: [ true]);
  116. deny: (true and: [ false ]);
  117. deny: (false and: [ true ]);
  118. deny: (false and: [ false ]).
  119. self
  120. assert: (true or: [ true ]);
  121. assert: (true or: [ false ]);
  122. assert: (false or: [ true ]);
  123. deny: (false or: [ false ]).
  124. "Checking that expressions work fine too"
  125. self
  126. assert: (true and: [ 1 > 0 ]);
  127. deny: ((1 > 0) and: [ false ]);
  128. deny: ((1 > 0) and: [ 1 > 2 ]).
  129. self
  130. assert: (false or: [ 1 > 0 ]);
  131. assert: ((1 > 0) or: [ false ]);
  132. assert: ((1 > 0) or: [ 1 > 2 ])
  133. !
  134. testNonBooleanError
  135. self should: [ '' ifTrue: [] ifFalse: [] ] raise: NonBooleanReceiver
  136. ! !
  137. TestCase subclass: #ClassBuilderTest
  138. instanceVariableNames: 'builder theClass'
  139. package: 'Kernel-Tests'!
  140. !ClassBuilderTest methodsFor: 'running'!
  141. setUp
  142. builder := ClassBuilder new
  143. !
  144. tearDown
  145. theClass ifNotNil: [Smalltalk current removeClass: theClass. theClass := nil]
  146. !
  147. testClassCopy
  148. theClass := builder copyClass: ObjectMock named: 'ObjectMock2'.
  149. self assert: theClass superclass == ObjectMock superclass.
  150. self assert: theClass instanceVariableNames == ObjectMock instanceVariableNames.
  151. self assert: theClass name equals: 'ObjectMock2'.
  152. self assert: theClass package == ObjectMock package.
  153. self assert: theClass methodDictionary keys equals: ObjectMock methodDictionary keys
  154. !
  155. testInstanceVariableNames
  156. self assert: (builder instanceVariableNamesFor: ' hello world ') equals: #('hello' 'world')
  157. ! !
  158. TestCase subclass: #CollectionTest
  159. instanceVariableNames: ''
  160. package: 'Kernel-Tests'!
  161. !CollectionTest methodsFor: 'accessing'!
  162. collection
  163. ^ self collectionClass withAll: self defaultValues
  164. !
  165. collectionClass
  166. ^ self class collectionClass
  167. !
  168. collectionWithDuplicates
  169. ^ self collectionClass withAll: #('a' 'b' 'c' 1 2 1 'a')
  170. !
  171. defaultValues
  172. ^ #(1 2 3 -4)
  173. ! !
  174. !CollectionTest methodsFor: 'convenience'!
  175. assertSameContents: aCollection as: anotherCollection
  176. self assert: aCollection size = anotherCollection size.
  177. aCollection do: [ :each |
  178. self assert: (aCollection occurrencesOf: each) = (anotherCollection occurrencesOf: each) ]
  179. ! !
  180. !CollectionTest methodsFor: 'testing'!
  181. isCollectionReadOnly
  182. ^ false
  183. ! !
  184. !CollectionTest methodsFor: 'tests'!
  185. testAsArray
  186. self
  187. assertSameContents: self collection
  188. as: self collection asArray
  189. !
  190. testAsOrderedCollection
  191. self
  192. assertSameContents: self collection
  193. as: self collection asOrderedCollection
  194. !
  195. testAsSet
  196. | c set |
  197. c := self collectionWithDuplicates.
  198. set := c asSet.
  199. self assert: set size = 5.
  200. c do: [ :each |
  201. self assert: (set includes: each) ]
  202. !
  203. testCollect
  204. | newCollection |
  205. newCollection := #(1 2 3 4).
  206. self
  207. assertSameContents: (self collection collect: [ :each |
  208. each abs ])
  209. as: newCollection
  210. !
  211. testDetect
  212. self assert: (self collection detect: [ :each | each < 0 ]) = -4.
  213. self
  214. should: [ self collection detect: [ :each | each = 6 ] ]
  215. raise: Error
  216. !
  217. testDo
  218. | newCollection |
  219. newCollection := OrderedCollection new.
  220. self collection do: [ :each |
  221. newCollection add: each ].
  222. self
  223. assertSameContents: self collection
  224. as: newCollection
  225. !
  226. testIsEmpty
  227. self assert: self collectionClass new isEmpty.
  228. self deny: self collection isEmpty
  229. !
  230. testSelect
  231. | newCollection |
  232. newCollection := #(2 -4).
  233. self
  234. assertSameContents: (self collection select: [ :each |
  235. each even ])
  236. as: newCollection
  237. !
  238. testSize
  239. self assert: self collectionClass new size = 0.
  240. self assert: self collection size = 4
  241. ! !
  242. !CollectionTest class methodsFor: 'accessing'!
  243. collectionClass
  244. ^ nil
  245. ! !
  246. !CollectionTest class methodsFor: 'testing'!
  247. isAbstract
  248. ^ self collectionClass isNil
  249. ! !
  250. CollectionTest subclass: #HashedCollectionTest
  251. instanceVariableNames: ''
  252. package: 'Kernel-Tests'!
  253. !HashedCollectionTest methodsFor: 'accessing'!
  254. collection
  255. ^ #{ 'a' -> 1. 'b' -> 2. 'c' -> 3. 'd' -> -4 }
  256. !
  257. collectionWithDuplicates
  258. ^ #{ 'a' -> 1. 'b' -> 2. 'c' -> 3. 'd' -> -4. 'e' -> 1. 'f' -> 2. 'g' -> 10 }
  259. ! !
  260. !HashedCollectionTest class methodsFor: 'accessing'!
  261. collectionClass
  262. ^ HashedCollection
  263. ! !
  264. HashedCollectionTest subclass: #DictionaryTest
  265. instanceVariableNames: ''
  266. package: 'Kernel-Tests'!
  267. !DictionaryTest methodsFor: 'accessing'!
  268. collection
  269. ^ Dictionary new
  270. at: 1 put: 1;
  271. at: 'a' put: 2;
  272. at: true put: 3;
  273. at: 4 put: -4;
  274. yourself
  275. !
  276. collectionWithDuplicates
  277. ^ Dictionary new
  278. at: 1 put: 1;
  279. at: 'a' put: 2;
  280. at: true put: 3;
  281. at: 4 put: -4;
  282. at: 'b' put: 1;
  283. at: 3 put: 3;
  284. at: false put: 12;
  285. yourself
  286. ! !
  287. !DictionaryTest methodsFor: 'tests'!
  288. testAccessing
  289. | d |
  290. d := Dictionary new.
  291. d at: 'hello' put: 'world'.
  292. self assert: (d at: 'hello') = 'world'.
  293. self assert: (d at: 'hello' ifAbsent: [nil]) = 'world'.
  294. self deny: (d at: 'foo' ifAbsent: [nil]) = 'world'.
  295. d at: 1 put: 2.
  296. self assert: (d at: 1) = 2.
  297. d at: 1@3 put: 3.
  298. self assert: (d at: 1@3) = 3
  299. !
  300. testDynamicDictionaries
  301. self assert: #{'hello' -> 1} asDictionary = (Dictionary with: 'hello' -> 1)
  302. !
  303. testEquality
  304. | d1 d2 |
  305. self assert: Dictionary new = Dictionary new.
  306. d1 := Dictionary new at: 1 put: 2; yourself.
  307. d2 := Dictionary new at: 1 put: 2; yourself.
  308. self assert: d1 = d2.
  309. d2 := Dictionary new at: 1 put: 3; yourself.
  310. self deny: d1 = d2.
  311. d2 := Dictionary new at: 2 put: 2; yourself.
  312. self deny: d1 = d2.
  313. d2 := Dictionary new at: 1 put: 2; at: 3 put: 4; yourself.
  314. self deny: d1 = d2.
  315. !
  316. testIfAbsent
  317. | d visited |
  318. visited := false.
  319. d := Dictionary new.
  320. d at: 'hello' ifAbsent: [ visited := true ].
  321. self assert: visited.
  322. !
  323. testIfPresent
  324. | d visited absent |
  325. visited := false.
  326. d := Dictionary new.
  327. d at: 'hello' put: 'world'.
  328. d at: 'hello' ifPresent: [ :value | visited := value ].
  329. self assert: visited = 'world'.
  330. absent := d at: 'bye' ifPresent: [ :value | visited := value ].
  331. self assert: absent isNil.
  332. !
  333. testIfPresentIfAbsent
  334. | d visited |
  335. visited := false.
  336. d := Dictionary new.
  337. d at: 'hello' put: 'world'.
  338. d at: 'hello' ifPresent: [ :value | visited := value ] ifAbsent: [ visited := true ].
  339. self assert: visited = 'world'.
  340. d at: 'buy' ifPresent: [ :value | visited := value ] ifAbsent: [ visited := true ].
  341. self assert: visited.
  342. !
  343. testKeys
  344. | d |
  345. d := Dictionary new.
  346. d at: 1 put: 2.
  347. d at: 2 put: 3.
  348. d at: 3 put: 4.
  349. self assert: d keys = #(1 2 3)
  350. !
  351. testPrintString
  352. self
  353. assert: 'a Dictionary(''firstname''->''James'' , ''lastname''->''Bond'')'
  354. equals: (Dictionary new
  355. at:'firstname' put: 'James';
  356. at:'lastname' put: 'Bond';
  357. printString)
  358. !
  359. testRemoveKey
  360. | d key |
  361. d := Dictionary new.
  362. d at: 1 put: 2.
  363. d at: 2 put: 3.
  364. d at: 3 put: 4.
  365. key := 2.
  366. self assert: d keys = #(1 2 3).
  367. d removeKey: key.
  368. self assert: d keys = #(1 3).
  369. self assert: d values = #(2 4).
  370. self deny: (d includesKey: 2)
  371. !
  372. testRemoveKeyIfAbsent
  373. | d key |
  374. d := Dictionary new.
  375. d at: 1 put: 2.
  376. d at: 2 put: 3.
  377. d at: 3 put: 4.
  378. key := 2.
  379. self assert: (d removeKey: key) = 3.
  380. key := 3.
  381. self assert: (d removeKey: key ifAbsent: [42]) = 4.
  382. key := 'why'.
  383. self assert: (d removeKey: key ifAbsent: [42] ) = 42.
  384. !
  385. testSize
  386. | d |
  387. d := Dictionary new.
  388. self assert: d size = 0.
  389. d at: 1 put: 2.
  390. self assert: d size = 1.
  391. d at: 2 put: 3.
  392. self assert: d size = 2.
  393. !
  394. testValues
  395. | d |
  396. d := Dictionary new.
  397. d at: 1 put: 2.
  398. d at: 2 put: 3.
  399. d at: 3 put: 4.
  400. self assert: d values = #(2 3 4)
  401. ! !
  402. !DictionaryTest class methodsFor: 'accessing'!
  403. collectionClass
  404. ^ Dictionary
  405. ! !
  406. CollectionTest subclass: #SequenceableCollectionTest
  407. instanceVariableNames: ''
  408. package: 'Kernel-Tests'!
  409. !SequenceableCollectionTest methodsFor: 'tests'!
  410. testAt
  411. self assert: (self collection at: 4) = -4.
  412. self should: [ self collection at: 5 ] raise: Error
  413. !
  414. testAtIfAbsent
  415. self assert: (self collection at: (self collection size + 1) ifAbsent: [ 'none' ]) = 'none'
  416. ! !
  417. SequenceableCollectionTest subclass: #ArrayTest
  418. instanceVariableNames: ''
  419. package: 'Kernel-Tests'!
  420. !ArrayTest methodsFor: 'testing'!
  421. testAtIfAbsent
  422. | array |
  423. array := #('hello' 'world').
  424. self assert: (array at: 1) equals: 'hello'.
  425. self assert: (array at: 2) equals: 'world'.
  426. self assert: (array at: 2 ifAbsent: ['not found']) equals: 'world'.
  427. self assert: (array at: 0 ifAbsent: ['not found']) equals: 'not found'.
  428. self assert: (array at: -10 ifAbsent: ['not found']) equals: 'not found'.
  429. self assert: (array at: 3 ifAbsent: ['not found']) equals: 'not found'.
  430. !
  431. testFirstN
  432. self assert: {1. 2. 3} equals: ({1. 2. 3. 4. 5} first: 3).
  433. !
  434. testIfEmpty
  435. self assert: 'zork' equals: ( '' ifEmpty: ['zork'] )
  436. !
  437. testPrintString
  438. | array |
  439. array := Array new.
  440. self assert: 'a Array ()' equals: ( array printString ).
  441. array add: 1; add: 3.
  442. self assert: 'a Array (1 3)' equals: ( array printString ).
  443. array add: 'foo'.
  444. self assert: 'a Array (1 3 ''foo'')' equals: ( array printString ).
  445. array remove: 1; remove: 3.
  446. self assert: 'a Array (''foo'')' equals: ( array printString ).
  447. array addLast: 3.
  448. self assert: 'a Array (''foo'' 3)' equals: ( array printString ).
  449. array addLast: 3.
  450. self assert: 'a Array (''foo'' 3 3)' equals: ( array printString ).
  451. ! !
  452. !ArrayTest class methodsFor: 'accessing'!
  453. collectionClass
  454. ^ Array
  455. ! !
  456. SequenceableCollectionTest subclass: #StringTest
  457. instanceVariableNames: ''
  458. package: 'Kernel-Tests'!
  459. !StringTest methodsFor: 'accessing'!
  460. collection
  461. ^'hello'
  462. !
  463. collectionWithDuplicates
  464. ^ 'abbaerte'
  465. ! !
  466. !StringTest methodsFor: 'tests'!
  467. testAddRemove
  468. self should: ['hello' add: 'a'] raise: Error.
  469. self should: ['hello' remove: 'h'] raise: Error
  470. !
  471. testAsArray
  472. self assert: 'hello' asArray = #('h' 'e' 'l' 'l' 'o').
  473. !
  474. testAt
  475. self assert: ('hello' at: 1) = 'h'.
  476. self assert: ('hello' at: 5) = 'o'.
  477. self assert: ('hello' at: 6 ifAbsent: [nil]) = nil
  478. !
  479. testAtPut
  480. "String instances are read-only"
  481. self should: ['hello' at: 1 put: 'a'] raise: Error
  482. !
  483. testCollect
  484. | newCollection |
  485. newCollection := 'hheelllloo'.
  486. self
  487. assertSameContents: (self collection collect: [ :each |
  488. each, each ])
  489. as: newCollection
  490. !
  491. testCopyWithoutAll
  492. self
  493. assert: 'hello world'
  494. equals: ('*hello* *world*' copyWithoutAll: '*')
  495. !
  496. testDetect
  497. self assert: (self collection detect: [ :each | each = 'h' ]) = 'h'.
  498. self
  499. should: [ self collection detect: [ :each | each = 6 ] ]
  500. raise: Error
  501. !
  502. testEquality
  503. self assert: 'hello' = 'hello'.
  504. self deny: 'hello' = 'world'.
  505. self assert: 'hello' = 'hello' yourself.
  506. self assert: 'hello' yourself = 'hello'.
  507. "test JS falsy value"
  508. self deny: '' = 0
  509. !
  510. testIdentity
  511. self assert: 'hello' == 'hello'.
  512. self deny: 'hello' == 'world'.
  513. self assert: 'hello' == 'hello' yourself.
  514. self assert: 'hello' yourself == 'hello'.
  515. "test JS falsy value"
  516. self deny: '' == 0
  517. !
  518. testIncludesSubString
  519. self assert: ('amber' includesSubString: 'ber').
  520. self deny: ('amber' includesSubString: 'zork').
  521. !
  522. testJoin
  523. self assert: 'hello,world' equals: (',' join: #('hello' 'world'))
  524. !
  525. testSelect
  526. | newCollection |
  527. newCollection := 'o'.
  528. self
  529. assertSameContents: (self collection select: [ :each |
  530. each = 'o' ])
  531. as: newCollection
  532. !
  533. testSize
  534. self assert: 'smalltalk' size equals: 9.
  535. self assert: '' size equals: 0
  536. !
  537. testStreamContents
  538. self
  539. assert: 'hello world'
  540. equals: (String streamContents: [ :aStream |
  541. aStream
  542. nextPutAll: 'hello'; space;
  543. nextPutAll: 'world' ])
  544. ! !
  545. !StringTest class methodsFor: 'accessing'!
  546. collectionClass
  547. ^ String
  548. ! !
  549. SequenceableCollectionTest subclass: #SymbolTest
  550. instanceVariableNames: ''
  551. package: 'Kernel-Tests'!
  552. !SymbolTest methodsFor: 'accessing'!
  553. collection
  554. ^ #hello
  555. !
  556. collectionWithDuplicates
  557. ^ #phhaaarorra
  558. ! !
  559. !SymbolTest methodsFor: 'tests'!
  560. testAsString
  561. self assert: #hello asString equals: 'hello'
  562. !
  563. testAsSymbol
  564. self assert: #hello == #hello asSymbol
  565. !
  566. testAt
  567. self assert: (#hello at: 1) = 'h'.
  568. self assert: (#hello at: 5) = 'o'.
  569. self assert: (#hello at: 6 ifAbsent: [nil]) = nil
  570. !
  571. testAtPut
  572. "Symbol instances are read-only"
  573. self should: ['hello' at: 1 put: 'a'] raise: Error
  574. !
  575. testCollect
  576. | newCollection |
  577. newCollection := #hheelllloo.
  578. self
  579. assertSameContents: (self collection collect: [ :each |
  580. each, each ])
  581. as: newCollection
  582. !
  583. testComparing
  584. self assert: #ab > #aa.
  585. self deny: #ab > #ba.
  586. self assert: #ab < #ba.
  587. self deny: #bb < #ba.
  588. self assert: #ab >= #aa.
  589. self deny: #ab >= #ba.
  590. self assert: #ab <= #ba.
  591. self deny: #bb <= #ba
  592. !
  593. testCopying
  594. self assert: #hello copy == #hello.
  595. self assert: #hello deepCopy == #hello
  596. !
  597. testDetect
  598. self assert: (self collection detect: [ :each | each = 'h' ]) = 'h'.
  599. self
  600. should: [ self collection detect: [ :each | each = 'z' ] ]
  601. raise: Error
  602. !
  603. testEquality
  604. self assert: #hello = #hello.
  605. self deny: #hello = #world.
  606. self assert: #hello = #hello yourself.
  607. self assert: #hello yourself = #hello.
  608. self deny: #hello = 'hello'.
  609. self deny: 'hello' = #hello.
  610. !
  611. testIdentity
  612. self assert: #hello == #hello.
  613. self deny: #hello == #world.
  614. self assert: #hello = #hello yourself.
  615. self assert: #hello yourself = #hello asString asSymbol
  616. !
  617. testIsEmpty
  618. self deny: self collection isEmpty.
  619. self assert: '' asSymbol isEmpty
  620. !
  621. testIsSymbolIsString
  622. self assert: #hello isSymbol.
  623. self deny: 'hello' isSymbol.
  624. self deny: #hello isString.
  625. self assert: 'hello' isString
  626. !
  627. testSelect
  628. | newCollection |
  629. newCollection := 'o'.
  630. self
  631. assertSameContents: (self collection select: [ :each |
  632. each = 'o' ])
  633. as: newCollection
  634. !
  635. testSize
  636. self assert: #a size equals: 1.
  637. self assert: #aaaaa size equals: 5
  638. ! !
  639. !SymbolTest class methodsFor: 'accessing'!
  640. collectionClass
  641. ^ Symbol
  642. ! !
  643. TestCase subclass: #JSObjectProxyTest
  644. instanceVariableNames: ''
  645. package: 'Kernel-Tests'!
  646. !JSObjectProxyTest methodsFor: 'accessing'!
  647. jsObject
  648. <return jsObject = {a: 1, b: function() {return 2;}, c: function(object) {return object;}, d: '', 'e': null}>
  649. ! !
  650. !JSObjectProxyTest methodsFor: 'tests'!
  651. testDNU
  652. self should: [self jsObject foo] raise: MessageNotUnderstood
  653. !
  654. testMessageSend
  655. self assert: self jsObject a equals: 1.
  656. self assert: self jsObject b equals: 2.
  657. self assert: (self jsObject c: 3) equals: 3
  658. !
  659. testMethodWithArguments
  660. self assert: (self jsObject c: 1) equals: 1
  661. !
  662. testPrinting
  663. self assert: self jsObject printString = '[object Object]'
  664. !
  665. testPropertyThatReturnsEmptyString
  666. | object |
  667. object := self jsObject.
  668. self assert: '' equals: object d.
  669. object d: 'hello'.
  670. self assert: 'hello' equals: object d
  671. !
  672. testPropertyThatReturnsUndefined
  673. | object |
  674. object := self jsObject.
  675. self shouldnt: [ object e ] raise: MessageNotUnderstood.
  676. self assert: object e isNil
  677. !
  678. testYourself
  679. | object |
  680. object := self jsObject
  681. d: 'test';
  682. yourself.
  683. self assert: object d equals: 'test'
  684. ! !
  685. TestCase subclass: #NumberTest
  686. instanceVariableNames: ''
  687. package: 'Kernel-Tests'!
  688. !NumberTest methodsFor: 'tests'!
  689. testAbs
  690. self assert: 4 abs = 4.
  691. self assert: -4 abs = 4
  692. !
  693. testArithmetic
  694. "We rely on JS here, so we won't test complex behavior, just check if
  695. message sends are corrects"
  696. self assert: 1.5 + 1 = 2.5.
  697. self assert: 2 - 1 = 1.
  698. self assert: -2 - 1 = -3.
  699. self assert: 12 / 2 = 6.
  700. self assert: 3 * 4 = 12.
  701. "Simple parenthesis and execution order"
  702. self assert: 1 + 2 * 3 = 9.
  703. self assert: 1 + (2 * 3) = 7
  704. !
  705. testComparison
  706. self assert: 3 > 2.
  707. self assert: 2 < 3.
  708. self deny: 3 < 2.
  709. self deny: 2 > 3.
  710. self assert: 3 >= 3.
  711. self assert: 3.1 >= 3.
  712. self assert: 3 <= 3.
  713. self assert: 3 <= 3.1
  714. !
  715. testCopying
  716. self assert: 1 copy == 1.
  717. self assert: 1 deepCopy == 1
  718. !
  719. testEquality
  720. self assert: 1 = 1.
  721. self assert: 0 = 0.
  722. self deny: 1 = 0.
  723. self assert: 1 yourself = 1.
  724. self assert: 1 = 1 yourself.
  725. self assert: 1 yourself = 1 yourself.
  726. self deny: 0 = false.
  727. self deny: false = 0.
  728. self deny: '' = 0.
  729. self deny: 0 = ''
  730. !
  731. testHexNumbers
  732. self assert: 16r9 = 9.
  733. self assert: 16rA truncated = 10.
  734. self assert: 16rB truncated = 11.
  735. self assert: 16rC truncated = 12.
  736. self assert: 16rD truncated = 13.
  737. self assert: 16rE truncated = 14.
  738. self assert: 16rF truncated = 15
  739. !
  740. testIdentity
  741. self assert: 1 == 1.
  742. self assert: 0 == 0.
  743. self deny: 1 == 0.
  744. self assert: 1 yourself == 1.
  745. self assert: 1 == 1 yourself.
  746. self assert: 1 yourself == 1 yourself.
  747. self deny: 1 == 2
  748. !
  749. testInvalidHexNumbers
  750. self should: [16rG] raise: MessageNotUnderstood.
  751. self should: [16rg] raise: MessageNotUnderstood.
  752. self should: [16rH] raise: MessageNotUnderstood.
  753. self should: [16rh] raise: MessageNotUnderstood.
  754. self should: [16rI] raise: MessageNotUnderstood.
  755. self should: [16ri] raise: MessageNotUnderstood.
  756. self should: [16rJ] raise: MessageNotUnderstood.
  757. self should: [16rj] raise: MessageNotUnderstood.
  758. self should: [16rK] raise: MessageNotUnderstood.
  759. self should: [16rk] raise: MessageNotUnderstood.
  760. self should: [16rL] raise: MessageNotUnderstood.
  761. self should: [16rl] raise: MessageNotUnderstood.
  762. self should: [16rM] raise: MessageNotUnderstood.
  763. self should: [16rm] raise: MessageNotUnderstood.
  764. self should: [16rN] raise: MessageNotUnderstood.
  765. self should: [16rn] raise: MessageNotUnderstood.
  766. self should: [16rO] raise: MessageNotUnderstood.
  767. self should: [16ro] raise: MessageNotUnderstood.
  768. self should: [16rP] raise: MessageNotUnderstood.
  769. self should: [16rp] raise: MessageNotUnderstood.
  770. self should: [16rQ] raise: MessageNotUnderstood.
  771. self should: [16rq] raise: MessageNotUnderstood.
  772. self should: [16rR] raise: MessageNotUnderstood.
  773. self should: [16rr] raise: MessageNotUnderstood.
  774. self should: [16rS] raise: MessageNotUnderstood.
  775. self should: [16rs] raise: MessageNotUnderstood.
  776. self should: [16rT] raise: MessageNotUnderstood.
  777. self should: [16rt] raise: MessageNotUnderstood.
  778. self should: [16rU] raise: MessageNotUnderstood.
  779. self should: [16ru] raise: MessageNotUnderstood.
  780. self should: [16rV] raise: MessageNotUnderstood.
  781. self should: [16rv] raise: MessageNotUnderstood.
  782. self should: [16rW] raise: MessageNotUnderstood.
  783. self should: [16rw] raise: MessageNotUnderstood.
  784. self should: [16rX] raise: MessageNotUnderstood.
  785. self should: [16rx] raise: MessageNotUnderstood.
  786. self should: [16rY] raise: MessageNotUnderstood.
  787. self should: [16ry] raise: MessageNotUnderstood.
  788. self should: [16rZ] raise: MessageNotUnderstood.
  789. self should: [16rz] raise: MessageNotUnderstood.
  790. self should: [16rABcdEfZ] raise: MessageNotUnderstood.
  791. !
  792. testMinMax
  793. self assert: (2 max: 5) equals: 5.
  794. self assert: (2 min: 5) equals: 2
  795. !
  796. testNegated
  797. self assert: 3 negated = -3.
  798. self assert: -3 negated = 3
  799. !
  800. testPrintShowingDecimalPlaces
  801. self assert: '23.00' equals: (23 printShowingDecimalPlaces: 2).
  802. self assert: '23.57' equals: (23.5698 printShowingDecimalPlaces: 2).
  803. self assert: '-234.56700' equals:( 234.567 negated printShowingDecimalPlaces: 5).
  804. self assert: '23' equals: (23.4567 printShowingDecimalPlaces: 0).
  805. self assert: '24' equals: (23.5567 printShowingDecimalPlaces: 0).
  806. self assert: '-23' equals: (23.4567 negated printShowingDecimalPlaces: 0).
  807. self assert: '-24' equals: (23.5567 negated printShowingDecimalPlaces: 0).
  808. self assert: '100000000.0' equals: (100000000 printShowingDecimalPlaces: 1).
  809. self assert: '0.98000' equals: (0.98 printShowingDecimalPlaces: 5).
  810. self assert: '-0.98' equals: (0.98 negated printShowingDecimalPlaces: 2).
  811. self assert: '2.57' equals: (2.567 printShowingDecimalPlaces: 2).
  812. self assert: '-2.57' equals: (-2.567 printShowingDecimalPlaces: 2).
  813. self assert: '0.00' equals: (0 printShowingDecimalPlaces: 2).
  814. !
  815. testRounded
  816. self assert: 3 rounded = 3.
  817. self assert: 3.212 rounded = 3.
  818. self assert: 3.51 rounded = 4
  819. !
  820. testSqrt
  821. self assert: 4 sqrt = 2.
  822. self assert: 16 sqrt = 4
  823. !
  824. testSquared
  825. self assert: 4 squared = 16
  826. !
  827. testTimesRepeat
  828. | i |
  829. i := 0.
  830. 0 timesRepeat: [i := i + 1].
  831. self assert: i equals: 0.
  832. 5 timesRepeat: [i := i + 1].
  833. self assert: i equals: 5
  834. !
  835. testTo
  836. self assert: (1 to: 5) equals: #(1 2 3 4 5)
  837. !
  838. testToBy
  839. self assert: (0 to: 6 by: 2) equals: #(0 2 4 6).
  840. self should: [1 to: 4 by: 0] raise: Error
  841. !
  842. testTruncated
  843. self assert: 3 truncated = 3.
  844. self assert: 3.212 truncated = 3.
  845. self assert: 3.51 truncated = 3
  846. ! !
  847. Object subclass: #ObjectMock
  848. instanceVariableNames: 'foo bar'
  849. package: 'Kernel-Tests'!
  850. !ObjectMock methodsFor: 'not yet classified'!
  851. foo
  852. ^foo
  853. !
  854. foo: anObject
  855. foo := anObject
  856. ! !
  857. TestCase subclass: #ObjectTest
  858. instanceVariableNames: ''
  859. package: 'Kernel-Tests'!
  860. !ObjectTest methodsFor: 'tests'!
  861. notDefined
  862. <return undefined;>
  863. !
  864. testBasicAccess
  865. | o |
  866. o := Object new.
  867. o basicAt: 'a' put: 1.
  868. self assert: (o basicAt: 'a') equals: 1.
  869. self assert: (o basicAt: 'b') equals: nil
  870. !
  871. testBasicPerform
  872. | o |
  873. o := Object new.
  874. o basicAt: 'func' put: ['hello'].
  875. o basicAt: 'func2' put: [:a | a + 1].
  876. self assert: (o basicPerform: 'func') equals: 'hello'.
  877. self assert: (o basicPerform: 'func2' withArguments: #(3)) equals: 4
  878. !
  879. testDNU
  880. self should: [Object new foo] raise: MessageNotUnderstood
  881. !
  882. testEquality
  883. | o |
  884. o := Object new.
  885. self deny: o = Object new.
  886. self assert: o = o.
  887. self assert: o yourself = o.
  888. self assert: o = o yourself
  889. !
  890. testHalt
  891. self should: [Object new halt] raise: Error
  892. !
  893. testIdentity
  894. | o |
  895. o := Object new.
  896. self deny: o == Object new.
  897. self assert: o == o.
  898. self assert: o yourself == o.
  899. self assert: o == o yourself
  900. !
  901. testIfNil
  902. self deny: Object new isNil.
  903. self deny: (Object new ifNil: [true]) = true.
  904. self assert: (Object new ifNotNil: [true]) = true.
  905. self assert: (Object new ifNil: [false] ifNotNil: [true]) = true.
  906. self assert: (Object new ifNotNil: [true] ifNil: [false]) = true
  907. !
  908. testInstVars
  909. | o |
  910. o := ObjectMock new.
  911. self assert: (o instVarAt: #foo) equals: nil.
  912. o instVarAt: #foo put: 1.
  913. self assert: (o instVarAt: #foo) equals: 1.
  914. self assert: (o instVarAt: 'foo') equals: 1
  915. !
  916. testNilUndefined
  917. "nil in Smalltalk is the undefined object in JS"
  918. self assert: nil = self notDefined
  919. !
  920. testYourself
  921. | o |
  922. o := ObjectMock new.
  923. self assert: o yourself == o
  924. !
  925. testidentityHash
  926. | o1 o2 |
  927. o1 := Object new.
  928. o2 := Object new.
  929. self assert: o1 identityHash == o1 identityHash.
  930. self deny: o1 identityHash == o2 identityHash
  931. ! !
  932. TestCase subclass: #PackageTest
  933. instanceVariableNames: 'zorkPackage grulPackage backUpCommitPathJs backUpCommitPathSt'
  934. package: 'Kernel-Tests'!
  935. !PackageTest methodsFor: 'running'!
  936. setUp
  937. backUpCommitPathJs := Package defaultCommitPathJs.
  938. backUpCommitPathSt := Package defaultCommitPathSt.
  939. Package resetCommitPaths.
  940. zorkPackage := Package new name: 'Zork'.
  941. grulPackage := Package new
  942. name: 'Grul';
  943. commitPathJs: 'server/grul/js';
  944. commitPathSt: 'grul/st';
  945. yourself
  946. !
  947. tearDown
  948. Package
  949. defaultCommitPathJs: backUpCommitPathJs;
  950. defaultCommitPathSt: backUpCommitPathSt
  951. ! !
  952. !PackageTest methodsFor: 'tests'!
  953. testGrulCommitPathJsShouldBeServerGrulJs
  954. self assert: 'server/grul/js' equals: grulPackage commitPathJs
  955. !
  956. testGrulCommitPathStShouldBeGrulSt
  957. self assert: 'grul/st' equals: grulPackage commitPathSt
  958. !
  959. testZorkCommitPathJsShouldBeJs
  960. self assert: 'js' equals: zorkPackage commitPathJs
  961. !
  962. testZorkCommitPathStShouldBeSt
  963. self assert: 'st' equals: zorkPackage commitPathSt
  964. ! !
  965. PackageTest subclass: #PackageWithDefaultCommitPathChangedTest
  966. instanceVariableNames: ''
  967. package: 'Kernel-Tests'!
  968. !PackageWithDefaultCommitPathChangedTest methodsFor: 'running'!
  969. setUp
  970. super setUp.
  971. Package
  972. defaultCommitPathJs: 'javascripts/';
  973. defaultCommitPathSt: 'smalltalk/'.
  974. ! !
  975. !PackageWithDefaultCommitPathChangedTest methodsFor: 'tests'!
  976. testGrulCommitPathJsShouldBeServerGrulJs
  977. self assert: 'server/grul/js' equals: grulPackage commitPathJs
  978. !
  979. testGrulCommitPathStShouldBeGrulSt
  980. self assert: 'grul/st' equals: grulPackage commitPathSt
  981. !
  982. testZorkCommitPathJsShouldBeJavascript
  983. self assert: 'javascripts/' equals: zorkPackage commitPathJs
  984. !
  985. testZorkCommitPathStShouldBeSmalltalk
  986. self assert: 'smalltalk/' equals: zorkPackage commitPathSt
  987. ! !
  988. !PackageWithDefaultCommitPathChangedTest class methodsFor: 'accessing'!
  989. shouldInheritSelectors
  990. ^ false
  991. ! !
  992. TestCase subclass: #PointTest
  993. instanceVariableNames: ''
  994. package: 'Kernel-Tests'!
  995. !PointTest methodsFor: 'tests'!
  996. testAccessing
  997. self assert: (Point x: 3 y: 4) x equals: 3.
  998. self assert: (Point x: 3 y: 4) y equals: 4.
  999. self assert: (Point new x: 3) x equals: 3.
  1000. self assert: (Point new y: 4) y equals: 4
  1001. !
  1002. testArithmetic
  1003. self assert: 3@4 * (3@4 ) equals: (Point x: 9 y: 16).
  1004. self assert: 3@4 + (3@4 ) equals: (Point x: 6 y: 8).
  1005. self assert: 3@4 - (3@4 ) equals: (Point x: 0 y: 0).
  1006. self assert: 6@8 / (3@4 ) equals: (Point x: 2 y: 2)
  1007. !
  1008. testAt
  1009. self assert: 3@4 equals: (Point x: 3 y: 4)
  1010. !
  1011. testEgality
  1012. self assert: 3@4 = (3@4).
  1013. self deny: 3@5 = (3@6)
  1014. !
  1015. testTranslateBy
  1016. self assert: 3@4 equals: (3@3 translateBy: 0@1).
  1017. self assert: 3@2 equals: (3@3 translateBy: 0@1 negated).
  1018. self assert: 5@6 equals: (3@3 translateBy: 2@3).
  1019. self assert: 0@3 equals: (3@3 translateBy: 3 negated @0).
  1020. ! !
  1021. TestCase subclass: #RandomTest
  1022. instanceVariableNames: ''
  1023. package: 'Kernel-Tests'!
  1024. !RandomTest methodsFor: 'tests'!
  1025. textNext
  1026. 10000 timesRepeat: [
  1027. | current next |
  1028. next := Random new next.
  1029. self assert: (next >= 0).
  1030. self assert: (next < 1).
  1031. self deny: current = next.
  1032. next = current]
  1033. ! !
  1034. TestCase subclass: #SetTest
  1035. instanceVariableNames: ''
  1036. package: 'Kernel-Tests'!
  1037. !SetTest methodsFor: 'tests'!
  1038. testAddRemove
  1039. | set |
  1040. set := Set new.
  1041. self assert: set isEmpty.
  1042. set add: 3.
  1043. self assert: (set includes: 3).
  1044. set add: 5.
  1045. self assert: (set includes: 5).
  1046. set remove: 3.
  1047. self deny: (set includes: 3)
  1048. !
  1049. testAt
  1050. self should: [Set new at: 1 put: 2] raise: Error
  1051. !
  1052. testPrintString
  1053. | set |
  1054. set := Set new.
  1055. self assert: 'a Set ()' equals: ( set printString ).
  1056. set add: 1; add: 3.
  1057. self assert: 'a Set (1 3)' equals: ( set printString ).
  1058. set add: 'foo'.
  1059. self assert: 'a Set (1 3 ''foo'')' equals: ( set printString ).
  1060. set remove: 1; remove: 3.
  1061. self assert: 'a Set (''foo'')' equals: ( set printString ).
  1062. set add: 3.
  1063. self assert: 'a Set (''foo'' 3)' equals: ( set printString ).
  1064. set add: 3.
  1065. self assert: 'a Set (''foo'' 3)' equals: ( set printString ).
  1066. !
  1067. testSize
  1068. self assert: Set new size equals: 0.
  1069. self assert: (Set withAll: #(1 2 3 4)) size equals: 4.
  1070. self assert: (Set withAll: #(1 1 1 1)) size equals: 1
  1071. !
  1072. testUnicity
  1073. | set |
  1074. set := Set new.
  1075. set add: 21.
  1076. set add: 'hello'.
  1077. set add: 21.
  1078. self assert: set size = 2.
  1079. set add: 'hello'.
  1080. self assert: set size = 2.
  1081. self assert: set asArray equals: #(21 'hello')
  1082. ! !
  1083. TestCase subclass: #UndefinedTest
  1084. instanceVariableNames: ''
  1085. package: 'Kernel-Tests'!
  1086. !UndefinedTest methodsFor: 'tests'!
  1087. testCopying
  1088. self assert: nil copy equals: nil
  1089. !
  1090. testDeepCopy
  1091. self assert: nil deepCopy = nil
  1092. !
  1093. testIfNil
  1094. self assert: (nil ifNil: [true]) equals: true.
  1095. self deny: (nil ifNotNil: [true]) = true.
  1096. self assert: (nil ifNil: [true] ifNotNil: [false]) equals: true.
  1097. self deny: (nil ifNotNil: [true] ifNil: [false]) = true
  1098. !
  1099. testIsNil
  1100. self assert: nil isNil.
  1101. self deny: nil notNil.
  1102. ! !