smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Fixed unit tests for Widgets

Removed old dispatcher test class
This commit is contained in:
Nicolas Petton 2010-10-13 14:53:50 +02:00
parent 816155cd2c
commit 892c417337
5 changed files with 45 additions and 80 deletions

View File

@ -4,6 +4,20 @@ ILApplication subclass: ILApplicationMock [
<comment: nil>
<category: 'Iliad-Tests-Unit-Buildables'>
ILApplicationMock class [
| path |
path [
<category: 'accessing'>
^path ifNil: ['']
]
path: aString [
<category: 'accessing'>
path := aString
]
]
initialize [
<category: 'initialization'>

View File

@ -6,9 +6,21 @@ TestCase subclass: ILWidgetTest [
setUp [
<category: 'running'>
ILApplicationMock path: 'mock'.
app := ILApplicationMock new.
]
tearDown [
<category: 'running'>
ILApplicationMock path: ''
]
dirtyWidgets [
<category: 'accessing'>
^self session context
previousStateRegistry dirtyChildrenOf: app
]
testAnswer [
<category: 'testing'>
ILCurrentContext
@ -52,12 +64,12 @@ TestCase subclass: ILWidgetTest [
app w3 addDependentWidget: app w2.
app w2 addDependentWidget: app w1.
self assert: (self session dirtyWidgets isEmpty).
app build.
self assert: self dirtyWidgets isEmpty.
app w3 markDirty.
self assert: (self session dirtyWidgets includes: app w3).
self assert: (self session dirtyWidgets includes: app w2).
self assert: (self session dirtyWidgets includes: app w1)]
self assert: (self dirtyWidgets includes: app w3).
self assert: (self dirtyWidgets includes: app w2).
self assert: (self dirtyWidgets includes: app w1)]
]
testRetrieveControl [
@ -100,13 +112,13 @@ TestCase subclass: ILWidgetTest [
testDirtyWidget [
<category: 'testing'>
self withSessionDo: [
self assert: (self session dirtyWidgets isEmpty).
self assert: (self dirtyWidgets isEmpty).
app w1 markDirty.
self assert: (self session dirtyWidgets includes: app w1).
self deny: (self session dirtyWidgets includes: app w2).
self assert: (self dirtyWidgets includes: app w1).
self deny: (self dirtyWidgets includes: app w2).
app w2 markDirty.
self assert: (self session dirtyWidgets includes: app w1).
self assert: (self session dirtyWidgets includes: app w2)]
self assert: (self dirtyWidgets includes: app w1).
self assert: (self dirtyWidgets includes: app w2)]
]
testDirtyWidget2 [
@ -125,17 +137,16 @@ TestCase subclass: ILWidgetTest [
widget markDirty.
app w1 show: widget].
self assert: (self session dirtyWidgets includes: app w1).
self deny: (self session dirtyWidgets includes: widget).
self assert: (self dirtyWidgets includes: app w1).
self deny: (self dirtyWidgets includes: widget).
app build.
self deny: (self session dirtyWidgets includes: app w1).
self deny: (self session dirtyWidgets includes: widget).
self deny: (self dirtyWidgets includes: app w1).
self deny: (self dirtyWidgets includes: widget).
widget answer.
self assert: (self session dirtyWidgets includes: app w1).
self deny: (self session dirtyWidgets includes: widget)]
self assert: (self dirtyWidgets includes: app w1).
self deny: (self dirtyWidgets includes: widget)]
]
session [
@ -151,19 +162,14 @@ TestCase subclass: ILWidgetTest [
| context request |
request := ILRequest new.
context := ILContext new
application: app;
session: ILSession new;
request: request;
yourself.
session: ILSession new;
request: request;
yourself.
ILCurrentContext
use: context
during: [
context request url: (ILUrl absolute: '/').
request url: (ILUrl absolute: app class path).
context request fields: (Dictionary with: ('_state' -> context stateRegistry key)).
context stateRegistry
register: app w1;
register: app w2;
register: app w3.
app respondOn: ILResponse new.
aBlock value]
]

View File

@ -1,49 +0,0 @@
TestCase subclass: ILDispatcherTest [
| dispatcher app1 app2 request1 request2 |
<comment: nil>
<category: 'Iliad-Tests-Unit-Dispatching'>
setUp [
<category: 'running'>
dispatcher := ILDispatcher current.
app1 := ILApplicationMock1 new.
app2 := ILApplicationMock2 new.
request1 := ILRequest new
url: (ILUrl absolute: '/test/foo').
request2 := ILRequest new
url: (ILUrl absolute: '/test').
ILApplicationMock1 path: 'test'.
ILApplicationMock2 path: 'test/foo'
]
tearDown [
<category: 'running'>
ILApplicationMock1 path: nil.
ILApplicationMock2 path: nil
]
testApplicationClass [
<category: 'tests'>
| route1 route2 |
route1 := ILRoute path: #('test' 'foo').
route2 := ILRoute path: #('test').
ILCurrentContext use: ILContext new during: [
self assert: ((dispatcher applicationClassFor: route1) = app2 class).
self assert: ((dispatcher applicationClassFor: route2) = app1 class)]
]
testFindApplication [
<category: 'tests'>
| context |
context := dispatcher createContextFor: request1.
ILCurrentContext use: context during: [
context session applications at: app2 class put: app2.
self assert: ((dispatcher findApplicationFor: context route) = app2)].
context := dispatcher createContextFor: request2.
ILCurrentContext use: context during: [
context session applications at: app1 class put: app1.
self assert: ((dispatcher findApplicationFor: context route) = app1)]
]
]

View File

@ -18,7 +18,6 @@ Eval [
filein: 'Unit/Buildables/ILWidgetMock3.st';
filein: 'Unit/Buildables/ILWidgetTest.st';
filein: 'Unit/Dispatching/ILDispatcherTest.st';
filein: 'Unit/Dispatching/ILRouteTest.st';
filein: 'Unit/Elements/ILElementTest.st';

View File

@ -11,7 +11,6 @@
<filein>Unit/Sessions/ILSessionTest.st</filein>
<filein>Unit/Sessions/ILSessionManagerTest.st</filein>
<filein>Unit/Sessions/ILCurrentContextTest.st</filein>
<filein>Unit/Dispatching/ILDispatcherTest.st</filein>
<filein>Unit/Dispatching/ILRouteTest.st</filein>
<filein>Unit/Utilities/ILIdTest.st</filein>
<filein>Unit/Utilities/ILCompositeTest.st</filein>
@ -98,7 +97,6 @@
<file>Unit/Sessions/ILSessionTest.st</file>
<file>Unit/Sessions/ILSessionManagerTest.st</file>
<file>Unit/Sessions/ILCurrentContextTest.st</file>
<file>Unit/Dispatching/ILDispatcherTest.st</file>
<file>Unit/Dispatching/ILRouteTest.st</file>
<file>Unit/Utilities/ILIdTest.st</file>
<file>Unit/Utilities/ILCompositeTest.st</file>
@ -186,7 +184,6 @@
Iliad.ILSessionTest
Iliad.ILSessionManagerTest
Iliad.ILCurrentContextTest
Iliad.ILDispatcherTest
Iliad.ILRouteTest
Iliad.ILIdTest
Iliad.ILCompositeTest
@ -272,7 +269,6 @@
<filein>Unit/Buildables/ILWidgetMock2.st</filein>
<filein>Unit/Buildables/ILWidgetMock3.st</filein>
<filein>Unit/Buildables/ILWidgetTest.st</filein>
<filein>Unit/Dispatching/ILDispatcherTest.st</filein>
<filein>Unit/Dispatching/ILRouteTest.st</filein>
<filein>Unit/Elements/ILElementTest.st</filein>
<filein>Unit/Elements/ILHTMLBuilderElementTest.st</filein>
@ -359,7 +355,6 @@
<file>Unit/Buildables/ILWidgetMock2.st</file>
<file>Unit/Buildables/ILWidgetMock3.st</file>
<file>Unit/Buildables/ILWidgetTest.st</file>
<file>Unit/Dispatching/ILDispatcherTest.st</file>
<file>Unit/Dispatching/ILRouteTest.st</file>
<file>Unit/Elements/ILElementTest.st</file>
<file>Unit/Elements/ILHTMLBuilderElementTest.st</file>