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

Element (see Core/Utilities/Composite.st) now uses a circular linked list representation for children

This commit is contained in:
Nicolas Petton 2009-07-22 04:25:59 +00:00
parent bf61741c75
commit 31b741d52d
5 changed files with 95 additions and 31 deletions

View File

@ -36,24 +36,17 @@
IliadObject subclass: Element [
| children attributes |
Composite subclass: Element [
| attributes |
<category: 'Iliad-Core-Elements'>
<comment: 'I am the abstract root class of the composite element hierarchy.
I know how to print myself in HTML format with the #printHtmlOn: method'>
initialize [
<category: 'initialize-release'>
super initialize.
children := OrderedCollection new.
attributes := Dictionary new
]
attributes [
<category: 'accessing'>
^attributes
^attributes ifNil: [attributes := Dictionary new]
]
attributeAt: akey [
@ -76,11 +69,6 @@ I know how to print myself in HTML format with the #printHtmlOn: method'>
^self attributes at: akey put: aValue
]
children [
<category: 'accessing'>
^children
]
contentType [
<category: 'accessing'>
self subclassResponsibility
@ -91,13 +79,6 @@ I know how to print myself in HTML format with the #printHtmlOn: method'>
^nil
]
withAllChildrenDo: aBlock [
<category: 'accessing'>
self children do: [:each |
aBlock value: each.
each withAllChildrenDo: aBlock]
]
printJsonOn: aStream [
<category: 'printing'>
| str |
@ -110,7 +91,8 @@ I know how to print myself in HTML format with the #printHtmlOn: method'>
<category: 'printing'>
self beforePrintHtml.
self printOpenTagOn: aStream.
self children do: [:each | each printHtmlOn: aStream].
self childrenDo: [:each |
each printHtmlOn: aStream].
self printCloseTagOn: aStream.
self afterPrintHtml
]
@ -154,12 +136,6 @@ I know how to print myself in HTML format with the #printHtmlOn: method'>
aBuildable buildOn: self
]
add: anElement [
<category: 'adding'>
self children add: anElement.
^anElement
]
text: aString [
<category: 'adding-conveniance'>
self add: (TextElement new

View File

@ -60,7 +60,7 @@ RequestHandler subclass: JsonHandler [
self session dirtyWidgets do: [:each || e |
e := each build.
widgets at: each id put: e.
e withAllChildrenDo: [:child |
e allChildrenDo: [:child |
child tag = 'script' ifTrue: [
scripts add: child]]].
jsonContents at: 'widgets' put: widgets.

View File

@ -63,7 +63,7 @@ IliadObject subclass: ActionRegistry [
actions [
<category: 'accessing'>
^actions ifNil: [actions := LookupTable new]
^actions ifNil: [actions := Dictionary new]
]
owner [

View File

@ -0,0 +1,86 @@
"======================================================================
|
| Iliad.Composite class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2009
| Nicolas Petton <petton.nicolas@gmail.com>,
| Sébastien Audier <sebastien.audier@gmail.com>
|
| Some parts of this file reuse code from the Seaside framework written
| by Avi Bryant, Julian Fitzell, Lukas Renggli, Michel Bany, Philippe
| Marschall and Seaside contributors http://www.seaside.st
|
| This file is part of the Iliad framework.
|
| Permission is hereby granted, free of charge, to any person obtaining
| a copy of this software and associated documentation files (the
| 'Software'), to deal in the Software without restriction, including
| without limitation the rights to use, copy, modify, merge, publish,
| distribute, sublicense, and/or sell copies of the Software, and to
| permit persons to whom the Software is furnished to do so, subject to
| the following conditions:
|
| The above copyright notice and this permission notice shall be
| included in all copies or substantial portions of the Software.
|
| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
|
======================================================================"
IliadObject subclass: Composite [
| tail next |
<comment: nil>
<category: 'Iliad-Core-Utilities'>
add: aComposite [
<category: 'adding'>
| head |
tail ifNil: [tail := aComposite].
head := tail next ifNil: [tail].
tail next: aComposite.
tail := tail next.
tail next: head.
^aComposite
]
allChildrenDo: aBlock [
<category: 'iterating'>
self childrenDo: [:each |
aBlock value: each.
each allChildrenDo: aBlock]
]
childrenDo: aBlock [
<category: 'iterating'>
| child |
tail ifNil: [^self].
child := tail next.
[child == tail] whileFalse: [
aBlock value: child.
child := child next].
aBlock value: tail
]
next [
<category: 'accessing'>
^next
]
next: aLinkedObject [
<category: 'accessing'>
next := aLinkedObject
]
]

View File

@ -91,6 +91,7 @@
</test>
<filein>Utilities/IliadObject.st</filein>
<filein>Utilities/Composite.st</filein>
<filein>Utilities/DynamicVariable.st</filein>
<filein>Utilities/Support.st</filein>
<filein>Utilities/Id.st</filein>
@ -195,6 +196,7 @@
<filein>RequestHandlers/RedirectHandler.st</filein>
<file>Utilities/IliadObject.st</file>
<file>Utilities/Composite.st</file>
<file>Utilities/DynamicVariable.st</file>
<file>Utilities/Support.st</file>
<file>Utilities/Id.st</file>