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

Introduced ActionRegistry

This commit is contained in:
Nicolas Petton 2009-07-20 22:46:10 +00:00
parent 0d1ca62c34
commit e04d763730
11 changed files with 289 additions and 57 deletions

View File

@ -67,10 +67,16 @@ My subclasses must override the #build method, which should return an instance o
]
build [
"Override this method in subclasses.
It must answer an element"
<category: 'building'>
self withActionRegistry: [
^self buildContents]
]
buildContents [
"Override this method in subclasses.
It must answer an Element"
<category: 'building'>
self subclassResponsibility
]
@ -93,6 +99,15 @@ My subclasses must override the #build method, which should return an instance o
<category: 'converting'>
self build respondOn: aResponse
]
withActionRegistry: aBlock [
<category: 'private'>
CurrentActionRegistry
use: ((self session actionRegistryFor: self)
unregisterAllActions;
yourself)
during: aBlock
]
]

View File

@ -110,7 +110,7 @@ added to the decoration chain with #addDecoration:.'>
^self
]
build [
buildContents [
"Do *not* override this method. Use #contents instead"
<category: 'building'>

View File

@ -55,7 +55,7 @@ Buildable subclass: XHTMLPage [
^self attributeAt: #html ifAbsentPut: [HtmlElement new]
]
build [
buildContents [
<category: 'building'>
^self html
add: self head;

View File

@ -70,7 +70,7 @@ RequestHandler subclass: ApplicationHandler [
self session
clearDirtyWidgets;
clearNextId;
unregisterAllActions.
clearActionRegistries.
(self shouldRedirect)
ifTrue: [RedirectHandler new handleRequest]
ifFalse: [self produceResponse]

View File

@ -0,0 +1,108 @@
"======================================================================
|
| Iliad.ActionRegistry class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2009
| Nicolas Petton <petton.nicolas@gmail.com>,
| Sébastien Audier <sebastien.audier@gmail.com>
|
|
| 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: ActionRegistry [
| actions owner |
<category: 'Iliad-Core-Sessions'>
<comment: 'I implement a registry of actions.
My <owner> is responsible for registering actions,
and unregister them when they are obsolete.
Action registries should always be stored in Iliad sessions. '>
ActionRegistry class >> owner: aWidget [
<category: 'instance creation'>
^self basicNew
owner: aWidget;
initialize;
yourself
]
actionAt: aKeyString [
<category: 'accessing'>
^self actions
detect: [:each | each key = aKeyString]
ifNone: [nil]
]
actions [
<category: 'accessing'>
^actions ifNil: [actions := OrderedCollection new]
]
owner [
<category: 'accessing'>
^owner
]
owner: anObject [
<category: 'accessing'>
owner := anObject
]
evaluate: anAction [
<category: 'actions'>
(self actions includes: anAction) ifTrue: [
anAction evaluate]
]
evaluateActionKey: aString [
<category: 'actions'>
| action |
action := self actionAt: aString.
action ifNotNil: [self evaluate: action]
]
register: anAction [
<category: 'actions'>
self actions add: anAction
]
unregister: anAction [
<category: 'actions'>
(self actions includes: anAction) ifTrue: [
self actions remove: anAction]
]
unregisterAllActions [
<category: 'actions'>
actions := nil
]
]

View File

@ -0,0 +1,45 @@
"======================================================================
|
| Iliad.CurrentActionRegistry class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2009
| Nicolas Petton <petton.nicolas@gmail.com>,
| Sébastien Audier <sebastien.audier@gmail.com>
|
|
| 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.
|
======================================================================"
DynamicVariable subclass: CurrentActionRegistry [
<category: 'Iliad-Core-Sessions'>
<comment: nil>
]

View File

@ -38,28 +38,8 @@
Notification subclass: CurrentContext [
<category: 'Iliad-Core-Contexts'>
DynamicVariable subclass: CurrentContext [
<category: 'Iliad-Core-Sessions'>
<comment: nil>
CurrentContext class >> defaultValue [
<category: 'defaults'>
^nil
]
CurrentContext class >> use: aContext during: aBlock [
<category: 'evaluating'>
^aBlock on: self do: [:notification | notification resume: aContext]
]
CurrentContext class >> value [
<category: 'evaluating'>
^self signal
]
defaultAction [
<category: 'defaults'>
^self class defaultValue
]
]

View File

@ -37,7 +37,7 @@
IliadObject subclass: Session [
| id preferences timestamps expired redirectUrl applications actions dirtyWidgets nextId token |
| id preferences timestamps expired redirectUrl applications actionRegistries dirtyWidgets nextId token |
<category: 'Iliad-Core-Sessions'>
<comment: 'I represent a session in Iliad.
@ -82,7 +82,7 @@ IliadObject subclass: Session [
<category: 'accessing'>
nextId ifNil: [nextId := (Random new next * 100000) asInteger].
nextId := nextId + 1.
^nextId
^nextId printString
]
clearNextId [
@ -90,11 +90,6 @@ IliadObject subclass: Session [
nextId := nil
]
actions [
<category: 'accessing'>
^actions ifNil: [actions := Dictionary new]
]
applications [
<category: 'accessing'>
^applications ifNil: [applications := IdentityDictionary new]
@ -246,14 +241,41 @@ IliadObject subclass: Session [
^'en'
]
actionRegistries [
<category: 'actions'>
^actionRegistries ifNil:
[actionRegistries := OrderedCollection new]
]
actionRegistryFor: aWidget [
<category: 'actions'>
^self actionRegistries
detect: [:each | each owner = aWidget]
ifNone: [self addActionRegistryFor: aWidget]
]
addActionRegistryFor: aWidget [
<category: 'actions'>
^self actionRegistries add: (ActionRegistry owner: aWidget)
]
clearActionRegistries [
<category: 'actions'>
actionRegistries := OrderedCollection new
]
actionAt: aKeyString [
<category: 'actions'>
^self actions at: aKeyString ifAbsent: [nil]
| action |
self actionRegistries do: [:each |
action := each actionAt: aKeyString.
action ifNotNil: [^action]].
^nil
]
registerAction: anAction [
<category: 'actions'>
self actions at: anAction key printString put: anAction
CurrentActionRegistry value register: anAction
]
registerActionFor: aBlock [
@ -264,25 +286,12 @@ IliadObject subclass: Session [
block: aBlock;
yourself.
self registerAction: action.
^action key
]
evaluateActionKey: aString [
<category: 'actions'>
| action |
action := (self actionAt: aString) ifNil: [^nil].
action evaluate
]
unregisterAction: anAction [
<category: 'actions'>
(self actions includesKey: anAction key printString) ifFalse: [^nil].
self actions removeKey: anAction key printString
]
unregisterAllActions [
<category: 'actions'>
actions := Dictionary new
self actionRegistries do: [:each |
each evaluateActionKey: aString]
]
urlForAction: anAction [
@ -294,9 +303,9 @@ IliadObject subclass: Session [
<category: 'actions'>
^self baseUrl
addParameter: self sessionManager actionKey
value: aKey printString;
value: aKey;
addParameter: self sessionManager tokenKey
value: self token asString;
value: self token;
yourself
]

View File

@ -0,0 +1,65 @@
"======================================================================
|
| Iliad.DynamicVariable class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2009
| Nicolas Petton <petton.nicolas@gmail.com>,
| Sébastien Audier <sebastien.audier@gmail.com>
|
|
| 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.
|
======================================================================"
Notification subclass: DynamicVariable [
<category: 'Iliad-Core-Utilities'>
<comment: nil>
DynamicVariable class >> defaultValue [
<category: 'defaults'>
^nil
]
DynamicVariable class >> use: aContext during: aBlock [
<category: 'evaluating'>
^aBlock on: self do: [:notification | notification resume: aContext]
]
DynamicVariable class >> value [
<category: 'evaluating'>
^self signal
]
defaultAction [
<category: 'defaults'>
^self class defaultValue
]
]

View File

@ -88,10 +88,14 @@ LinkableElement subclass: AnchorElement [
action: aBlock [
<category: 'links'>
| actionKey |
actionKey := self session registerActionFor: aBlock.
self href: (self session urlForActionKey: actionKey).
self onClick: ('Iliad.evaluateAnchorAction(this); return false;')
| action |
action := Action new
block: aBlock;
key: self session nextId;
yourself.
self session registerAction: action.
self href: (self session urlForAction: action).
self onClick: ('Iliad.evaluateAnchorAction(this); return false;')
]
]

View File

@ -91,6 +91,7 @@
</test>
<filein>Utilities/IliadObject.st</filein>
<filein>Utilities/DynamicVariable.st</filein>
<filein>Utilities/Support.st</filein>
<filein>Utilities/Id.st</filein>
<filein>Utilities/Encoder.st</filein>
@ -109,6 +110,8 @@
<filein>Sessions/Context.st</filein>
<filein>Sessions/Action.st</filein>
<filein>Sessions/CurrentContext.st</filein>
<filein>Sessions/CurrentActionRegistry.st</filein>
<filein>Sessions/ActionRegistry.st</filein>
<filein>Sessions/Session.st</filein>
<filein>Sessions/SessionManager.st</filein>
@ -192,6 +195,7 @@
<filein>RequestHandlers/RedirectHandler.st</filein>
<file>Utilities/IliadObject.st</file>
<file>Utilities/DynamicVariable.st</file>
<file>Utilities/Support.st</file>
<file>Utilities/Id.st</file>
<file>Utilities/Encoder.st</file>
@ -210,6 +214,8 @@
<file>Sessions/Context.st</file>
<file>Sessions/Action.st</file>
<file>Sessions/CurrentContext.st</file>
<file>Sessions/CurrentActionRegistry.st</file>
<file>Sessions/ActionRegistry.st</file>
<file>Sessions/Session.st</file>
<file>Sessions/SessionManager.st</file>