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

Removed the outdated functional tests

This commit is contained in:
Nicolas Petton 2009-06-22 03:14:34 +00:00
parent c4b93fc88b
commit bc22096f25
7 changed files with 0 additions and 463 deletions

View File

@ -1,92 +0,0 @@
Application subclass: TestApplication [
| counterTest formTest multicounterTest sauTest |
<comment: nil>
<category: 'Iliad-Tests-Functional'>
TestApplication class >> path [
^'tests'
]
allTests [
<category: 'accessing'>
^
{self counterTest.
self multicounterTest.
self formTest.
self sauTest}
]
counterTest [
<category: 'accessing'>
^counterTest ifNil: [counterTest := TestCounter new]
]
sauTest [
<category: 'accessing'>
^sauTest ifNil: [sauTest := TestSAU new]
]
formTest [
<category: 'accessing'>
^formTest ifNil: [formTest := TestForm new]
]
multicounterTest [
<category: 'accessing'>
^multicounterTest ifNil: [multicounterTest := TestMultiCounter new]
]
counter [
<category: 'views'>
^[:e |
e h2 text: 'Fonctional tests'.
e build: self list.
e horizontalRule.
e add: self counterTest build]
]
form [
<category: 'views'>
^[:e |
e h2 text: 'Fonctional tests'.
e build: self list.
e horizontalRule.
e add: self formTest build]
]
index [
<category: 'views'>
^self counter
]
multicounter [
<category: 'views'>
^[:e |
e h2 text: 'Fonctional tests'.
e build: self list.
e horizontalRule.
e add: self multicounterTest build]
]
scriptaculous [
<category: 'views'>
^[:e |
e h2 text: 'Fonctional tests'.
e build: self list.
e horizontalRule.
e add: self sauTest build]
]
list [
<category: 'views elements'>
^[:e || f select |
f := e form.
select := f select.
select
beSubmitOnChange;
action: [:val | self redirectToLocal: val].
self allTests do: [:each | select option text: each class path]]
]
]

View File

@ -1,22 +0,0 @@
Widget subclass: TestCounter [
| counters counter |
<comment: nil>
<category: 'Iliad-Tests-Functional'>
TestCounter class >> path [
^'counter'
]
contents [
^[:e | e add: self counter build]
]
children [
^Array with: self counter
]
counter [
^counter ifNil: [counter := Counter new]
]
]

View File

@ -1,48 +0,0 @@
Widget subclass: TestForm [
| value1 value2 value3 |
<comment: nil>
<category: 'Iliad-Tests-Functional'>
TestForm class >> path [
^'form'
]
contents [
^[:e |
e build: self form.
e break.
e build: self result]
]
form [
^[:e || form |
value1 ifNil: [value1 := ''].
value2 ifNil: [value2 := ''].
value3 ifNil: [value3 := false].
form := e form.
form input
action: [:val | self markDirty. value1 := val];
value: value1.
form break.
form textArea
action: [:val | value2 := val];
text: value2.
form break.
form checkbox
action: [:val | value3 := val];
checked: value3.
form break.
form button text: 'go']
]
result [
^[:e |
e text: 'value 1 = ' , value1.
e break.
e text: 'value 2 = ' , value2.
e break.
e text: 'value 3 = ' , value3 printString]
]
]

View File

@ -1,21 +0,0 @@
Widget subclass: TestImage [
<comment: nil>
<category: 'Iliad-Tests-Functional'>
TestImage class >> path [
^'image'
]
contents [
^[:e |
e image
source: '/files/reeb-logo.png'
alternativeText: 'logo'.
e break.
e image
source: 'http://planet.smalltalk.org/images/balloon_small.gif'
alternativeText: 'smalltalk']
]
]

View File

@ -1,28 +0,0 @@
Widget subclass: TestMultiCounter [
| counters |
<comment: nil>
<category: 'Iliad-Tests-Functional'>
TestMultiCounter class >> path [
^'multicounter'
]
contents [
^[:e | self counters do: [:each | e add: each build]]
]
counters [
^counters ifNil: [counters := self initCounters]
]
initCounters [
^
{Counter new.
Counter new.
Counter new.
Counter new.
Counter new}
]
]

View File

@ -1,239 +0,0 @@
Widget subclass: TestSAU [
| counter count text editText checked dropped |
<comment: nil>
<category: 'Iliad-Tests-Functional'>
TestSAU class >> path [
^'scriptaculous'
]
buildDraggableOn: aCanvas [
<category: 'building'>
| id1 id2 |
id1 := aCanvas draggableId.
id2 := aCanvas draggableId.
aCanvas h1 text: 'Draggable'.
(aCanvas div)
id: id1;
class: 'draggable';
passenger: 'Drag me!';
with: [aCanvas h2 text: 'Drag me!'].
(aCanvas div)
id: id2;
class: 'draggable';
passenger: 'Drag me too!';
with: [aCanvas h2 text: 'Drag me too!'].
aCanvas script: ((aCanvas draggable)
id: id1;
revert: true;
build).
aCanvas script: ((aCanvas draggable)
id: id2;
revert: true;
build).
(aCanvas div)
id: 'droppable';
with: [aCanvas text: 'Drop here :)'].
aCanvas script: ((aCanvas droppable)
id: 'droppable';
accept: 'draggable';
hoverClass: 'hover';
onDrop: ((aCanvas updater)
id: 'droppable';
triggerPassenger: [:val | dropped := val];
action: [:canvas | canvas text: dropped];
yourself);
build)
]
contents [
<category: 'building'>
self updatePage.
^[:e |
e build: self effects.
"self buildDraggableOn: anElement."
e build: self sortable.
e build: self updater.
e build: self periodicalUpdater.
e build: self form.
e build: self inPlaceEditor]
]
count [
<category: 'building'>
^[:e | e text: count printString]
]
description [
<category: 'building'>
^'scriptaculous'
]
effects [
<category: 'building'>
| div |
^[:e |
e h1: 'Effects'.
div := e div.
div id: 'id'.
div add: counter build.
(e anchor)
href: 'javascript:void(0)';
onClick: ((div scriptaculous effect)
id: 'id';
duration: 2;
afterFinish: ((div scriptaculous effect)
id: 'id';
highlight);
appear;
build);
text: 'Appear'.
e text: ' '.
(e anchor)
href: 'javascript:void(0)';
onClick: ((div scriptaculous effect)
id: 'id';
blindUp;
build);
text: 'BlindUp'.
e text: ' '.
(e anchor)
href: 'javascript:void(0)';
onClick: ((div scriptaculous effect)
id: 'id';
toggleBlind;
build);
text: 'ToggleBlind']
]
form [
<category: 'building'>
| form |
^[:e |
text ifNil: [text := 'some text'].
e h1 text: 'Form'.
form := e form.
form id: 'form'.
(form input)
action: [:val | text := val];
value: text.
(form button)
onClick: ((form prototype updater)
id: 'essai';
triggerForm: 'form';
return: false;
build);
text: 'go'.
(e div)
id: 'essai';
text: text]
]
inPlaceEditor [
<category: 'building'>
| div |
^[:e |
editText := 'Edit me :)'.
e h1: 'In place Editor'.
div := e div.
div
id: 'edit';
text: editText.
e javascript: ((div scriptaculous inPlaceEditor)
id: 'edit';
triggerInPlaceEditor: [:val | editText := val];
onComplete: ((e prototype updater)
id: 'edit';
action: [:f | f text: editText];
yourself);
build)]
]
periodicalUpdater [
<category: 'building'>
| div |
^[:e |
e h1 text: 'PeriodicalUpdater'.
div := e div.
div id: 'periodical_update'.
div build: self time.
div javascript: ((div prototype periodicalUpdater)
id: 'periodical_update';
frequency: 1;
action: [:f | f build: self time];
build)]
]
sortable [
<category: 'building'>
| div1 |
^[:e |
e h1 text: 'sortable1'.
div1 := e div id: 'sortable1'.
(div1 div)
id: div1 sortableId;
passenger: 'Sort me!';
text: 'Sort me!'.
(div1 div)
id: div1 sortableId;
passenger: 'Sort me too!';
text: 'Sort me too!'.
e javascript: ((e scriptaculous sortable)
id: 'sortable1';
tag: 'div';
constraint: false;
dropOnEmpty: true;
onUpdate: ((e prototype updater)
id: '';
triggerSortable: 'sortable1' action: [:val | Transcript show: val];
yourself);
build)]
]
time [
<category: 'building'>
^[:e | e text: SpTimestamp now printString]
]
updatePage [
<category: 'building'>
self page headElement javascript source: '/prototype/prototype.js'.
self page headElement javascript source: '/scriptaculous/scriptaculous.js'
]
updater [
<category: 'building'>
| div |
^
[:e |
e h1: 'Updater'.
count ifNil: [count := 0].
div := e div.
div id: 'update'.
div build: self count.
(e anchor)
href: 'javascript:void(0)';
onClick: ((e prototype updater)
id: 'update';
action:
[:f |
count := count + 1.
f build: self count.
f];
build);
text: 'increase']
]
children [
<category: 'accessing'>
^Array with: counter
]
initialize [
<category: 'initialize-release'>
super initialize.
counter := Counter new
]
]

View File

@ -189,13 +189,6 @@
<filein>RequestHandlers/ApplicationHandler.st</filein>
<filein>RequestHandlers/RedirectHandler.st</filein>
<filein>Tests/Functional/TestSAU.st</filein>
<filein>Tests/Functional/TestCounter.st</filein>
<filein>Tests/Functional/TestMultiCounter.st</filein>
<filein>Tests/Functional/TestForm.st</filein>
<filein>Tests/Functional/TestImage.st</filein>
<filein>Tests/Functional/TestApplication.st</filein>
<file>Utilities/IliadObject.st</file>
<file>Utilities/Support.st</file>
<file>Utilities/Id.st</file>
@ -339,10 +332,4 @@
<file>lib/JSON/JsonObject.st</file>
<file>lib/JSON/JsonTests.st</file>
<file>Tests/Functional/TestSAU.st</file>
<file>Tests/Functional/TestCounter.st</file>
<file>Tests/Functional/TestMultiCounter.st</file>
<file>Tests/Functional/TestForm.st</file>
<file>Tests/Functional/TestImage.st</file>
<file>Tests/Functional/TestApplication.st</file>
</package>