Kernel-Tests.st 24 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098
  1. Smalltalk current createPackage: 'Kernel-Tests' properties: #{}!
  2. TestCase subclass: #ArrayTest
  3. instanceVariableNames: ''
  4. package: 'Kernel-Tests'!
  5. !ArrayTest methodsFor: 'testing'!
  6. testAtIfAbsent
  7. | array |
  8. array := #('hello' 'world').
  9. self assert: (array at: 1) equals: 'hello'.
  10. self assert: (array at: 2) equals: 'world'.
  11. self assert: (array at: 2 ifAbsent: ['not found']) equals: 'world'.
  12. self assert: (array at: 0 ifAbsent: ['not found']) equals: 'not found'.
  13. self assert: (array at: -10 ifAbsent: ['not found']) equals: 'not found'.
  14. self assert: (array at: 3 ifAbsent: ['not found']) equals: 'not found'.
  15. !
  16. testFirstN
  17. self assert: {1. 2. 3} equals: ({1. 2. 3. 4. 5} first: 3).
  18. !
  19. testIfEmpty
  20. self assert: 'zork' equals: ( '' ifEmpty: ['zork'] )
  21. !
  22. testPrintString
  23. | array |
  24. array := Array new.
  25. self assert: 'a Array ()' equals: ( array printString ).
  26. array add: 1; add: 3.
  27. self assert: 'a Array (1 3)' equals: ( array printString ).
  28. array add: 'foo'.
  29. self assert: 'a Array (1 3 ''foo'')' equals: ( array printString ).
  30. array remove: 1; remove: 3.
  31. self assert: 'a Array (''foo'')' equals: ( array printString ).
  32. array addLast: 3.
  33. self assert: 'a Array (''foo'' 3)' equals: ( array printString ).
  34. array addLast: 3.
  35. self assert: 'a Array (''foo'' 3 3)' equals: ( array printString ).
  36. ! !
  37. TestCase subclass: #AssociationTest
  38. instanceVariableNames: ''
  39. package: 'Kernel-Tests'!
  40. !AssociationTest methodsFor: 'tests'!
  41. testEqualAssociations
  42. "Test if two equal Association objects compare to true"
  43. | anAssociation anotherAssociation |
  44. anAssociation := Association key: 'KEY' value: 'VALUE'.
  45. anotherAssociation := Association key: 'KEY' value: 'VALUE'.
  46. self assert: (anAssociation = anotherAssociation).
  47. !
  48. testNotEqualAssociations
  49. "Test if two unequal Association objects compare to false"
  50. | anAssociation anotherAssociation |
  51. anAssociation := Association key: 'KEY' value: 'VALUE'.
  52. anotherAssociation := Association key: 'KEY2' value: 'VALUE2'.
  53. self assert: (anAssociation = anotherAssociation) not.
  54. !
  55. testPrintString
  56. "Test if the output of the printString message is correct"
  57. | anAssociation returnString |
  58. anAssociation := Association key: 'KEY' value: 'VALUE'.
  59. returnString := anAssociation printString.
  60. self assert: ('''KEY''->''VALUE''' = returnString).
  61. ! !
  62. TestCase subclass: #BlockClosureTest
  63. instanceVariableNames: ''
  64. package: 'Kernel-Tests'!
  65. !BlockClosureTest methodsFor: 'tests'!
  66. testCompiledSource
  67. self assert: ([1+1] compiledSource includesSubString: 'function')
  68. !
  69. testEnsure
  70. self assert: ([Error new] ensure: [true])
  71. !
  72. testNumArgs
  73. self assert: [] numArgs equals: 0.
  74. self assert: [:a :b | ] numArgs equals: 2
  75. !
  76. testOnDo
  77. self assert: ([Error new signal] on: Error do: [:ex | true])
  78. !
  79. testValue
  80. self assert: ([1+1] value) equals: 2.
  81. self assert: ([:x | x +1] value: 2) equals: 3.
  82. self assert: ([:x :y | x*y] value: 2 value: 4) equals: 8.
  83. "Arguments are optional in Amber. This isn't ANSI compliant."
  84. self assert: ([:a :b :c | 1] value) equals: 1
  85. !
  86. testValueWithPossibleArguments
  87. self assert: ([1] valueWithPossibleArguments: #(3 4)) equals: 1.
  88. self assert: ([:a | a + 4] valueWithPossibleArguments: #(3 4)) equals: 7.
  89. self assert: ([:a :b | a + b] valueWithPossibleArguments: #(3 4 5)) equals: 7.
  90. !
  91. testWhileFalse
  92. | i |
  93. i := 0.
  94. [i > 5] whileFalse: [i := i + 1].
  95. self assert: i equals: 6.
  96. i := 0.
  97. [i := i + 1. i > 5] whileFalse.
  98. self assert: i equals: 6
  99. !
  100. testWhileTrue
  101. | i |
  102. i := 0.
  103. [i < 5] whileTrue: [i := i + 1].
  104. self assert: i equals: 5.
  105. i := 0.
  106. [i := i + 1. i < 5] whileTrue.
  107. self assert: i equals: 5
  108. ! !
  109. TestCase subclass: #BooleanTest
  110. instanceVariableNames: ''
  111. package: 'Kernel-Tests'!
  112. !BooleanTest methodsFor: 'tests'!
  113. testEquality
  114. "We're on top of JS...just be sure to check the basics!!"
  115. self deny: 0 = false.
  116. self deny: false = 0.
  117. self deny: '' = false.
  118. self deny: false = ''.
  119. self assert: true = true.
  120. self deny: false = true.
  121. self deny: true = false.
  122. self assert: false = false.
  123. "JS may do some type coercing after sending a message"
  124. self assert: true yourself = true.
  125. self assert: true yourself = true yourself
  126. !
  127. testIdentity
  128. "We're on top of JS...just be sure to check the basics!!"
  129. self deny: 0 == false.
  130. self deny: false == 0.
  131. self deny: '' == false.
  132. self deny: false == ''.
  133. self assert: true == true.
  134. self deny: false == true.
  135. self deny: true == false.
  136. self assert: false == false.
  137. "JS may do some type coercing after sending a message"
  138. self assert: true yourself == true.
  139. self assert: true yourself == true yourself
  140. !
  141. testIfTrueIfFalse
  142. self assert: (true ifTrue: ['alternative block']) = 'alternative block'.
  143. self assert: (true ifFalse: ['alternative block']) = nil.
  144. self assert: (false ifTrue: ['alternative block']) = nil.
  145. self assert: (false ifFalse: ['alternative block']) = 'alternative block'.
  146. self assert: (false ifTrue: ['alternative block'] ifFalse: ['alternative block2']) = 'alternative block2'.
  147. self assert: (false ifFalse: ['alternative block'] ifTrue: ['alternative block2']) = 'alternative block'.
  148. self assert: (true ifTrue: ['alternative block'] ifFalse: ['alternative block2']) = 'alternative block'.
  149. self assert: (true ifFalse: ['alternative block'] ifTrue: ['alternative block2']) = 'alternative block2'.
  150. !
  151. testLogic
  152. "Trivial logic table"
  153. self assert: (true & true); deny: (true & false); deny: (false & true); deny: (false & false).
  154. self assert: (true | true); assert: (true | false); assert: (false | true); deny: (false | false).
  155. "Checking that expressions work fine too"
  156. self assert: (true & (1 > 0)); deny: ((1 > 0) & false); deny: ((1 > 0) & (1 > 2)).
  157. self assert: (false | (1 > 0)); assert: ((1 > 0) | false); assert: ((1 > 0) | (1 > 2))
  158. !
  159. testLogicKeywords
  160. "Trivial logic table"
  161. self
  162. assert: (true and: [ true]);
  163. deny: (true and: [ false ]);
  164. deny: (false and: [ true ]);
  165. deny: (false and: [ false ]).
  166. self
  167. assert: (true or: [ true ]);
  168. assert: (true or: [ false ]);
  169. assert: (false or: [ true ]);
  170. deny: (false or: [ false ]).
  171. "Checking that expressions work fine too"
  172. self
  173. assert: (true and: [ 1 > 0 ]);
  174. deny: ((1 > 0) and: [ false ]);
  175. deny: ((1 > 0) and: [ 1 > 2 ]).
  176. self
  177. assert: (false or: [ 1 > 0 ]);
  178. assert: ((1 > 0) or: [ false ]);
  179. assert: ((1 > 0) or: [ 1 > 2 ])
  180. ! !
  181. TestCase subclass: #ClassBuilderTest
  182. instanceVariableNames: 'builder theClass'
  183. package: 'Kernel-Tests'!
  184. !ClassBuilderTest methodsFor: 'running'!
  185. setUp
  186. builder := ClassBuilder new
  187. !
  188. tearDown
  189. theClass ifNotNil: [Smalltalk current removeClass: theClass. theClass := nil]
  190. !
  191. testClassCopy
  192. theClass := builder copyClass: ObjectMock named: 'ObjectMock2'.
  193. self assert: theClass superclass == ObjectMock superclass.
  194. self assert: theClass instanceVariableNames == ObjectMock instanceVariableNames.
  195. self assert: theClass name equals: 'ObjectMock2'.
  196. self assert: theClass package == ObjectMock package.
  197. self assert: theClass methodDictionary keys equals: ObjectMock methodDictionary keys
  198. !
  199. testInstanceVariableNames
  200. self assert: (builder instanceVariableNamesFor: ' hello world ') equals: #('hello' 'world')
  201. ! !
  202. TestCase subclass: #DictionaryTest
  203. instanceVariableNames: ''
  204. package: 'Kernel-Tests'!
  205. !DictionaryTest methodsFor: 'tests'!
  206. testAccessing
  207. | d |
  208. d := Dictionary new.
  209. d at: 'hello' put: 'world'.
  210. self assert: (d at: 'hello') = 'world'.
  211. self assert: (d at: 'hello' ifAbsent: [nil]) = 'world'.
  212. self deny: (d at: 'foo' ifAbsent: [nil]) = 'world'.
  213. d at: 1 put: 2.
  214. self assert: (d at: 1) = 2.
  215. d at: 1@3 put: 3.
  216. self assert: (d at: 1@3) = 3
  217. !
  218. testDynamicDictionaries
  219. self assert: #{'hello' -> 1} asDictionary = (Dictionary with: 'hello' -> 1)
  220. !
  221. testEquality
  222. | d1 d2 |
  223. self assert: Dictionary new = Dictionary new.
  224. d1 := Dictionary new at: 1 put: 2; yourself.
  225. d2 := Dictionary new at: 1 put: 2; yourself.
  226. self assert: d1 = d2.
  227. d2 := Dictionary new at: 1 put: 3; yourself.
  228. self deny: d1 = d2.
  229. d2 := Dictionary new at: 2 put: 2; yourself.
  230. self deny: d1 = d2.
  231. d2 := Dictionary new at: 1 put: 2; at: 3 put: 4; yourself.
  232. self deny: d1 = d2.
  233. !
  234. testIfAbsent
  235. | d visited |
  236. visited := false.
  237. d := Dictionary new.
  238. d at: 'hello' ifAbsent: [ visited := true ].
  239. self assert: visited.
  240. !
  241. testIfPresent
  242. | d visited absent |
  243. visited := false.
  244. d := Dictionary new.
  245. d at: 'hello' put: 'world'.
  246. d at: 'hello' ifPresent: [ :value | visited := value ].
  247. self assert: visited = 'world'.
  248. absent := d at: 'bye' ifPresent: [ :value | visited := value ].
  249. self assert: absent isNil.
  250. !
  251. testIfPresentIfAbsent
  252. | d visited |
  253. visited := false.
  254. d := Dictionary new.
  255. d at: 'hello' put: 'world'.
  256. d at: 'hello' ifPresent: [ :value | visited := value ] ifAbsent: [ visited := true ].
  257. self assert: visited = 'world'.
  258. d at: 'buy' ifPresent: [ :value | visited := value ] ifAbsent: [ visited := true ].
  259. self assert: visited.
  260. !
  261. testKeys
  262. | d |
  263. d := Dictionary new.
  264. d at: 1 put: 2.
  265. d at: 2 put: 3.
  266. d at: 3 put: 4.
  267. self assert: d keys = #(1 2 3)
  268. !
  269. testPrintString
  270. self
  271. assert: 'a Dictionary(''firstname'' -> ''James'' , ''lastname'' -> ''Bond'')'
  272. equals: (Dictionary new
  273. at:'firstname' put: 'James';
  274. at:'lastname' put: 'Bond';
  275. printString)
  276. !
  277. testRemoveKey
  278. | d key |
  279. d := Dictionary new.
  280. d at: 1 put: 2.
  281. d at: 2 put: 3.
  282. d at: 3 put: 4.
  283. key := 2.
  284. self assert: d keys = #(1 2 3).
  285. d removeKey: key.
  286. self assert: d keys = #(1 3).
  287. self assert: d values = #(2 4).
  288. self deny: (d includesKey: 2)
  289. !
  290. testRemoveKeyIfAbsent
  291. | d key |
  292. d := Dictionary new.
  293. d at: 1 put: 2.
  294. d at: 2 put: 3.
  295. d at: 3 put: 4.
  296. key := 2.
  297. self assert: (d removeKey: key) = 3.
  298. key := 3.
  299. self assert: (d removeKey: key ifAbsent: [42]) = 4.
  300. key := 'why'.
  301. self assert: (d removeKey: key ifAbsent: [42] ) = 42.
  302. !
  303. testSize
  304. | d |
  305. d := Dictionary new.
  306. self assert: d size = 0.
  307. d at: 1 put: 2.
  308. self assert: d size = 1.
  309. d at: 2 put: 3.
  310. self assert: d size = 2.
  311. !
  312. testValues
  313. | d |
  314. d := Dictionary new.
  315. d at: 1 put: 2.
  316. d at: 2 put: 3.
  317. d at: 3 put: 4.
  318. self assert: d values = #(2 3 4)
  319. ! !
  320. TestCase subclass: #JSObjectProxyTest
  321. instanceVariableNames: ''
  322. package: 'Kernel-Tests'!
  323. !JSObjectProxyTest methodsFor: 'accessing'!
  324. jsObject
  325. <return jsObject = {a: 1, b: function() {return 2;}, c: function(object) {return object;}}>
  326. ! !
  327. !JSObjectProxyTest methodsFor: 'tests'!
  328. testDNU
  329. self should: [self jsObject foo] raise: MessageNotUnderstood
  330. !
  331. testMessageSend
  332. self assert: self jsObject a equals: 1.
  333. self assert: self jsObject b equals: 2.
  334. self assert: (self jsObject c: 3) equals: 3
  335. !
  336. testMethodWithArguments
  337. self deny: ('body' asJQuery hasClass: 'amber').
  338. 'body' asJQuery addClass: 'amber'.
  339. self assert: ('body' asJQuery hasClass: 'amber').
  340. 'body' asJQuery removeClass: 'amber'.
  341. self deny: ('body' asJQuery hasClass: 'amber').
  342. !
  343. testPrinting
  344. self assert: self jsObject printString = '[object Object]'
  345. !
  346. testPropertyThatReturnsEmptyString
  347. <document.location.hash = ''>.
  348. self assert: '' equals: document location hash.
  349. document location hash: 'test'.
  350. self assert: '#test' equals: document location hash.
  351. !
  352. testYourself
  353. |body|
  354. body := 'body' asJQuery
  355. addClass: 'amber';
  356. yourself.
  357. self assert: (body hasClass: 'amber').
  358. body removeClass: 'amber'.
  359. self deny: (body hasClass: 'amber').
  360. ! !
  361. TestCase subclass: #NumberTest
  362. instanceVariableNames: ''
  363. package: 'Kernel-Tests'!
  364. !NumberTest methodsFor: 'tests'!
  365. testArithmetic
  366. "We rely on JS here, so we won't test complex behavior, just check if
  367. message sends are corrects"
  368. self assert: 1.5 + 1 = 2.5.
  369. self assert: 2 - 1 = 1.
  370. self assert: -2 - 1 = -3.
  371. self assert: 12 / 2 = 6.
  372. self assert: 3 * 4 = 12.
  373. "Simple parenthesis and execution order"
  374. self assert: 1 + 2 * 3 = 9.
  375. self assert: 1 + (2 * 3) = 7
  376. !
  377. testComparison
  378. self assert: 3 > 2.
  379. self assert: 2 < 3.
  380. self deny: 3 < 2.
  381. self deny: 2 > 3.
  382. self assert: 3 >= 3.
  383. self assert: 3.1 >= 3.
  384. self assert: 3 <= 3.
  385. self assert: 3 <= 3.1
  386. !
  387. testCopying
  388. self assert: 1 copy == 1.
  389. self assert: 1 deepCopy == 1
  390. !
  391. testEquality
  392. self assert: 1 = 1.
  393. self assert: 0 = 0.
  394. self deny: 1 = 0.
  395. self assert: 1 yourself = 1.
  396. self assert: 1 = 1 yourself.
  397. self assert: 1 yourself = 1 yourself.
  398. self deny: 0 = false.
  399. self deny: false = 0.
  400. self deny: '' = 0.
  401. self deny: 0 = ''
  402. !
  403. testIdentity
  404. self assert: 1 == 1.
  405. self assert: 0 == 0.
  406. self deny: 1 == 0.
  407. self assert: 1 yourself == 1.
  408. self assert: 1 == 1 yourself.
  409. self assert: 1 yourself == 1 yourself.
  410. self deny: 1 == 2
  411. !
  412. testMinMax
  413. self assert: (2 max: 5) equals: 5.
  414. self assert: (2 min: 5) equals: 2
  415. !
  416. testNegated
  417. self assert: 3 negated = -3.
  418. self assert: -3 negated = 3
  419. !
  420. testPrintShowingDecimalPlaces
  421. self assert: '23.00' equals: (23 printShowingDecimalPlaces: 2).
  422. self assert: '23.57' equals: (23.5698 printShowingDecimalPlaces: 2).
  423. self assert: '-234.56700' equals:( 234.567 negated printShowingDecimalPlaces: 5).
  424. self assert: '23' equals: (23.4567 printShowingDecimalPlaces: 0).
  425. self assert: '24' equals: (23.5567 printShowingDecimalPlaces: 0).
  426. self assert: '-23' equals: (23.4567 negated printShowingDecimalPlaces: 0).
  427. self assert: '-24' equals: (23.5567 negated printShowingDecimalPlaces: 0).
  428. self assert: '100000000.0' equals: (100000000 printShowingDecimalPlaces: 1).
  429. self assert: '0.98000' equals: (0.98 printShowingDecimalPlaces: 5).
  430. self assert: '-0.98' equals: (0.98 negated printShowingDecimalPlaces: 2).
  431. self assert: '2.57' equals: (2.567 printShowingDecimalPlaces: 2).
  432. self assert: '-2.57' equals: (-2.567 printShowingDecimalPlaces: 2).
  433. self assert: '0.00' equals: (0 printShowingDecimalPlaces: 2).
  434. !
  435. testRounded
  436. self assert: 3 rounded = 3.
  437. self assert: 3.212 rounded = 3.
  438. self assert: 3.51 rounded = 4
  439. !
  440. testSqrt
  441. self assert: 4 sqrt = 2.
  442. self assert: 16 sqrt = 4
  443. !
  444. testSquared
  445. self assert: 4 squared = 16
  446. !
  447. testTimesRepeat
  448. | i |
  449. i := 0.
  450. 0 timesRepeat: [i := i + 1].
  451. self assert: i equals: 0.
  452. 5 timesRepeat: [i := i + 1].
  453. self assert: i equals: 5
  454. !
  455. testTo
  456. self assert: (1 to: 5) equals: #(1 2 3 4 5)
  457. !
  458. testToBy
  459. self assert: (0 to: 6 by: 2) equals: #(0 2 4 6).
  460. self should: [1 to: 4 by: 0] raise: Error
  461. !
  462. testTruncated
  463. self assert: 3 truncated = 3.
  464. self assert: 3.212 truncated = 3.
  465. self assert: 3.51 truncated = 3
  466. ! !
  467. Object subclass: #ObjectMock
  468. instanceVariableNames: 'foo bar'
  469. package: 'Kernel-Tests'!
  470. !ObjectMock methodsFor: 'not yet classified'!
  471. foo
  472. ^foo
  473. !
  474. foo: anObject
  475. foo := anObject
  476. ! !
  477. TestCase subclass: #ObjectTest
  478. instanceVariableNames: ''
  479. package: 'Kernel-Tests'!
  480. !ObjectTest methodsFor: 'tests'!
  481. testBasicAccess
  482. | o |
  483. o := Object new.
  484. o basicAt: 'a' put: 1.
  485. self assert: (o basicAt: 'a') equals: 1.
  486. self assert: (o basicAt: 'b') equals: nil
  487. !
  488. testBasicPerform
  489. | o |
  490. o := Object new.
  491. o basicAt: 'func' put: ['hello'].
  492. o basicAt: 'func2' put: [:a | a + 1].
  493. self assert: (o basicPerform: 'func') equals: 'hello'.
  494. self assert: (o basicPerform: 'func2' withArguments: #(3)) equals: 4
  495. !
  496. testDNU
  497. self should: [Object new foo] raise: MessageNotUnderstood
  498. !
  499. testEquality
  500. | o |
  501. o := Object new.
  502. self deny: o = Object new.
  503. self assert: o = o.
  504. self assert: o yourself = o.
  505. self assert: o = o yourself
  506. !
  507. testHalt
  508. self should: [Object new halt] raise: Error
  509. !
  510. testIdentity
  511. | o |
  512. o := Object new.
  513. self deny: o == Object new.
  514. self assert: o == o.
  515. self assert: o yourself == o.
  516. self assert: o == o yourself
  517. !
  518. testIfNil
  519. self deny: Object new isNil.
  520. self deny: (Object new ifNil: [true]) = true.
  521. self assert: (Object new ifNotNil: [true]) = true.
  522. self assert: (Object new ifNil: [false] ifNotNil: [true]) = true.
  523. self assert: (Object new ifNotNil: [true] ifNil: [false]) = true
  524. !
  525. testInstVars
  526. | o |
  527. o := ObjectMock new.
  528. self assert: (o instVarAt: #foo) equals: nil.
  529. o instVarAt: #foo put: 1.
  530. self assert: (o instVarAt: #foo) equals: 1.
  531. self assert: (o instVarAt: 'foo') equals: 1
  532. !
  533. testNilUndefined
  534. "nil in Smalltalk is the undefined object in JS"
  535. self assert: nil = undefined
  536. !
  537. testYourself
  538. | o |
  539. o := ObjectMock new.
  540. self assert: o yourself == o
  541. !
  542. testidentityHash
  543. | o1 o2 |
  544. o1 := Object new.
  545. o2 := Object new.
  546. self assert: o1 identityHash == o1 identityHash.
  547. self deny: o1 identityHash == o2 identityHash
  548. ! !
  549. TestCase subclass: #PackageTest
  550. instanceVariableNames: 'zorkPackage grulPackage backUpCommitPathJs backUpCommitPathSt'
  551. package: 'Kernel-Tests'!
  552. !PackageTest methodsFor: 'running'!
  553. setUp
  554. backUpCommitPathJs := Package defaultCommitPathJs.
  555. backUpCommitPathSt := Package defaultCommitPathSt.
  556. Package resetCommitPaths.
  557. zorkPackage := Package new name: 'Zork'.
  558. grulPackage := Package new
  559. name: 'Grul';
  560. commitPathJs: 'server/grul/js';
  561. commitPathSt: 'grul/st';
  562. yourself
  563. !
  564. tearDown
  565. Package
  566. defaultCommitPathJs: backUpCommitPathJs;
  567. defaultCommitPathSt: backUpCommitPathSt
  568. ! !
  569. !PackageTest methodsFor: 'tests'!
  570. testGrulCommitPathJsShouldBeServerGrulJs
  571. self assert: 'server/grul/js' equals: grulPackage commitPathJs
  572. !
  573. testGrulCommitPathStShouldBeGrulSt
  574. self assert: 'grul/st' equals: grulPackage commitPathSt
  575. !
  576. testZorkCommitPathJsShouldBeJs
  577. self assert: 'js' equals: zorkPackage commitPathJs
  578. !
  579. testZorkCommitPathStShouldBeSt
  580. self assert: 'st' equals: zorkPackage commitPathSt
  581. ! !
  582. PackageTest subclass: #PackageWithDefaultCommitPathChangedTest
  583. instanceVariableNames: ''
  584. package: 'Kernel-Tests'!
  585. !PackageWithDefaultCommitPathChangedTest methodsFor: 'running'!
  586. setUp
  587. super setUp.
  588. Package
  589. defaultCommitPathJs: 'javascripts/';
  590. defaultCommitPathSt: 'smalltalk/'.
  591. ! !
  592. !PackageWithDefaultCommitPathChangedTest methodsFor: 'tests'!
  593. testGrulCommitPathJsShouldBeServerGrulJs
  594. self assert: 'server/grul/js' equals: grulPackage commitPathJs
  595. !
  596. testGrulCommitPathStShouldBeGrulSt
  597. self assert: 'grul/st' equals: grulPackage commitPathSt
  598. !
  599. testZorkCommitPathJsShouldBeJavascript
  600. self assert: 'javascripts/' equals: zorkPackage commitPathJs
  601. !
  602. testZorkCommitPathStShouldBeSmalltalk
  603. self assert: 'smalltalk/' equals: zorkPackage commitPathSt
  604. ! !
  605. !PackageWithDefaultCommitPathChangedTest class methodsFor: 'accessing'!
  606. shouldInheritSelectors
  607. ^ false
  608. ! !
  609. TestCase subclass: #PointTest
  610. instanceVariableNames: ''
  611. package: 'Kernel-Tests'!
  612. !PointTest methodsFor: 'tests'!
  613. testAccessing
  614. self assert: (Point x: 3 y: 4) x equals: 3.
  615. self assert: (Point x: 3 y: 4) y equals: 4.
  616. self assert: (Point new x: 3) x equals: 3.
  617. self assert: (Point new y: 4) y equals: 4
  618. !
  619. testArithmetic
  620. self assert: 3@4 * (3@4 ) equals: (Point x: 9 y: 16).
  621. self assert: 3@4 + (3@4 ) equals: (Point x: 6 y: 8).
  622. self assert: 3@4 - (3@4 ) equals: (Point x: 0 y: 0).
  623. self assert: 6@8 / (3@4 ) equals: (Point x: 2 y: 2)
  624. !
  625. testAt
  626. self assert: 3@4 equals: (Point x: 3 y: 4)
  627. !
  628. testEgality
  629. self assert: 3@4 = (3@4).
  630. self deny: 3@5 = (3@6)
  631. !
  632. testTranslateBy
  633. self assert: 3@4 equals: (3@3 translateBy: 0@1).
  634. self assert: 3@2 equals: (3@3 translateBy: 0@1 negated).
  635. self assert: 5@6 equals: (3@3 translateBy: 2@3).
  636. self assert: 0@3 equals: (3@3 translateBy: 3 negated @0).
  637. ! !
  638. TestCase subclass: #RandomTest
  639. instanceVariableNames: ''
  640. package: 'Kernel-Tests'!
  641. !RandomTest methodsFor: 'tests'!
  642. textNext
  643. 10000 timesRepeat: [
  644. | current next |
  645. next := Random new next.
  646. self assert: (next >= 0).
  647. self assert: (next < 1).
  648. self deny: current = next.
  649. next = current]
  650. ! !
  651. TestCase subclass: #SetTest
  652. instanceVariableNames: ''
  653. package: 'Kernel-Tests'!
  654. !SetTest methodsFor: 'tests'!
  655. testAddRemove
  656. | set |
  657. set := Set new.
  658. self assert: set isEmpty.
  659. set add: 3.
  660. self assert: (set includes: 3).
  661. set add: 5.
  662. self assert: (set includes: 5).
  663. set remove: 3.
  664. self deny: (set includes: 3)
  665. !
  666. testAt
  667. self should: [Set new at: 1 put: 2] raise: Error
  668. !
  669. testPrintString
  670. | set |
  671. set := Set new.
  672. self assert: 'a Set ()' equals: ( set printString ).
  673. set add: 1; add: 3.
  674. self assert: 'a Set (1 3)' equals: ( set printString ).
  675. set add: 'foo'.
  676. self assert: 'a Set (1 3 ''foo'')' equals: ( set printString ).
  677. set remove: 1; remove: 3.
  678. self assert: 'a Set (''foo'')' equals: ( set printString ).
  679. set add: 3.
  680. self assert: 'a Set (''foo'' 3)' equals: ( set printString ).
  681. set add: 3.
  682. self assert: 'a Set (''foo'' 3)' equals: ( set printString ).
  683. !
  684. testSize
  685. self assert: Set new size equals: 0.
  686. self assert: (Set withAll: #(1 2 3 4)) size equals: 4.
  687. self assert: (Set withAll: #(1 1 1 1)) size equals: 1
  688. !
  689. testUnicity
  690. | set |
  691. set := Set new.
  692. set add: 21.
  693. set add: 'hello'.
  694. set add: 21.
  695. self assert: set size = 2.
  696. set add: 'hello'.
  697. self assert: set size = 2.
  698. self assert: set asArray equals: #(21 'hello')
  699. ! !
  700. TestCase subclass: #StringTest
  701. instanceVariableNames: ''
  702. package: 'Kernel-Tests'!
  703. !StringTest methodsFor: 'tests'!
  704. testAddRemove
  705. self should: ['hello' add: 'a'] raise: Error.
  706. self should: ['hello' remove: 'h'] raise: Error
  707. !
  708. testAsArray
  709. self assert: 'hello' asArray = #('h' 'e' 'l' 'l' 'o').
  710. !
  711. testAt
  712. self assert: ('hello' at: 1) = 'h'.
  713. self assert: ('hello' at: 5) = 'o'.
  714. self assert: ('hello' at: 6 ifAbsent: [nil]) = nil
  715. !
  716. testAtPut
  717. "String instances are read-only"
  718. self should: ['hello' at: 1 put: 'a'] raise: Error
  719. !
  720. testCopyWithoutAll
  721. self
  722. assert: 'hello world'
  723. equals: ('*hello* *world*' copyWithoutAll: '*')
  724. !
  725. testEquality
  726. self assert: 'hello' = 'hello'.
  727. self deny: 'hello' = 'world'.
  728. self assert: 'hello' = 'hello' yourself.
  729. self assert: 'hello' yourself = 'hello'.
  730. "test JS falsy value"
  731. self deny: '' = 0
  732. !
  733. testIdentity
  734. self assert: 'hello' == 'hello'.
  735. self deny: 'hello' == 'world'.
  736. self assert: 'hello' == 'hello' yourself.
  737. self assert: 'hello' yourself == 'hello'.
  738. "test JS falsy value"
  739. self deny: '' == 0
  740. !
  741. testIncludesSubString
  742. self assert: ('amber' includesSubString: 'ber').
  743. self deny: ('amber' includesSubString: 'zork').
  744. !
  745. testJoin
  746. self assert: 'hello,world' equals: (',' join: #('hello' 'world'))
  747. !
  748. testSize
  749. self assert: 'smalltalk' size equals: 9.
  750. self assert: '' size equals: 0
  751. !
  752. testStreamContents
  753. self
  754. assert: 'hello world'
  755. equals: (String streamContents: [:aStream| aStream
  756. nextPutAll: 'hello'; space;
  757. nextPutAll: 'world'])
  758. ! !
  759. TestCase subclass: #SymbolTest
  760. instanceVariableNames: ''
  761. package: 'Kernel-Tests'!
  762. !SymbolTest methodsFor: 'tests'!
  763. testAsString
  764. self assert: #hello asString equals: 'hello'
  765. !
  766. testAsSymbol
  767. self assert: #hello == #hello asSymbol
  768. !
  769. testAt
  770. self assert: (#hello at: 1) = 'h'.
  771. self assert: (#hello at: 5) = 'o'.
  772. self assert: (#hello at: 6 ifAbsent: [nil]) = nil
  773. !
  774. testAtPut
  775. "Symbol instances are read-only"
  776. self should: ['hello' at: 1 put: 'a'] raise: Error
  777. !
  778. testComparing
  779. self assert: #ab > #aa.
  780. self deny: #ab > #ba.
  781. self assert: #ab < #ba.
  782. self deny: #bb < #ba.
  783. self assert: #ab >= #aa.
  784. self deny: #ab >= #ba.
  785. self assert: #ab <= #ba.
  786. self deny: #bb <= #ba
  787. !
  788. testCopying
  789. self assert: #hello copy == #hello.
  790. self assert: #hello deepCopy == #hello
  791. !
  792. testEquality
  793. self assert: #hello = #hello.
  794. self deny: #hello = #world.
  795. self assert: #hello = #hello yourself.
  796. self assert: #hello yourself = #hello.
  797. self deny: #hello = 'hello'.
  798. self deny: 'hello' = #hello.
  799. !
  800. testIdentity
  801. self assert: #hello == #hello.
  802. self deny: #hello == #world.
  803. self assert: #hello = #hello yourself.
  804. self assert: #hello yourself = #hello asString asSymbol
  805. !
  806. testIsSymbolIsString
  807. self assert: #hello isSymbol.
  808. self deny: 'hello' isSymbol.
  809. self deny: #hello isString.
  810. self assert: 'hello' isString
  811. !
  812. testSize
  813. self assert: #a size equals: 1.
  814. self assert: #aaaaa size equals: 5
  815. ! !
  816. TestCase subclass: #UndefinedTest
  817. instanceVariableNames: ''
  818. package: 'Kernel-Tests'!
  819. !UndefinedTest methodsFor: 'tests'!
  820. testCopying
  821. self assert: nil copy equals: nil
  822. !
  823. testDeepCopy
  824. self assert: nil deepCopy = nil
  825. !
  826. testIfNil
  827. self assert: (nil ifNil: [true]) equals: true.
  828. self deny: (nil ifNotNil: [true]) = true.
  829. self assert: (nil ifNil: [true] ifNotNil: [false]) equals: true.
  830. self deny: (nil ifNotNil: [true] ifNil: [false]) = true
  831. !
  832. testIsNil
  833. self assert: nil isNil.
  834. self deny: nil notNil.
  835. ! !