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

Merge remote-tracking branch 'iliad-stable/master'

This commit is contained in:
Holger Hans Peter Freyther 2012-10-21 16:03:29 +02:00
commit 97772d0834
360 changed files with 32397 additions and 0 deletions

10
iliad-stable/.gitignore vendored Normal file
View File

@ -0,0 +1,10 @@
Public/images/arrow_down.png
Public/images/arrow_right.png
Public/stylesheets/iliad-ui.css
gst.log
iliad.im
iliad.log
log.log
iliad.pidaproject
make_packages.log

View File

@ -0,0 +1,44 @@
Acknowledgements
----------------
The following parts of Iliad reuses portions of code from the Seaside framework:
- The Widget class and its decorators
- The HTTP abstraction library
- The Swazoo adapter
Seaside is licenced under the MIT Licence.
Copyright © 20012009 Avi Bryant, Julian Fitzell
Copyright © 20072009 Lukas Renggli, Michel Bany, Philippe Marschall
Copyright © Seaside Contributors
http://www.seaside.st/about/licence
----------------
The JSON library is adapted from http://www.squeaksource.com/Diplomacy/
written by Avi Bryant and licenced under the MIT licence.
----------------
The Application class reuses code from HttpView2.
HttpView2 is written by Göran Krampe and Giovanni Corriga and licenced
under the MIT licence.
http://www.squeaksource.com/HttpView2
----------------
The Element hierarchy is widely inspired from the Aida/Web web framework,
written by Janko Mivsek.
Aida/Web is licenced under the MIT licence
Copyright (c) 2000-2007 Janko Mivšek
Copyright (c) 2007-2009 Janko Mivšek, Nicolas Petton, contributors
http://www.aidaweb.si
----------------
The javascript layer is inspired by the LISP web framework Weblocks
http://weblocks.viridian-project.de/

View File

@ -0,0 +1,60 @@
"======================================================================
|
| Smalltalk Classes extensions
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
Object extend [
asResponse [
<category: 'converting'>
| response |
response := Iliad.ILResponse ok.
self respondOn: response.
^response
]
respondOn: aResponse [
<category: 'converting'>
self displayOn: aResponse
]
]
BlockClosure extend [
buildOn: anElement [
<category:'Iliad-Core'>
self value: anElement
]
]

View File

@ -0,0 +1,66 @@
"======================================================================
|
| Iliad.ILAnswerHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILDecorator subclass: ILAnswerHandler [
| action |
<category: 'Iliad-Core-Buildables'>
<comment: 'I am a special decorator for Widgets, used to handle widget answers.
See #handleAnswer: and ILWidget>>show:onAnswer:'>
action [
<category: 'accessing'>
^action
]
action: anAction [
<category: 'accessing'>
action := anAction
]
handleAnswer: anAnswer [
<category: 'decorations'>
(self action)
value: anAnswer;
evaluate
]
]

View File

@ -0,0 +1,53 @@
"======================================================================
|
| Iliad.ILAppendDelegator class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-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.
|
======================================================================"
ILDelegator subclass: ILAppendDelegator [
<comment: nil>
<category: 'Iliad-Core-Buildables'>
contents [
<category: 'building'>
^[:e | e
build: self decoratee contents;
build: super contents]
]
]

View File

@ -0,0 +1,298 @@
"======================================================================
|
| Iliad.ILApplication class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| Nicolas Petton <petton.nicolas@gmail.com>,
| Sébastien Audier <sebastien.audier@gmail.com>
|
| Some parts of this file reuse code from HttpView2 written by Giovanni
| Corriga and Göran Krampe http://www.squeaksource.com/HttpView2/
|
| 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.
|
======================================================================"
ILBuildable subclass: ILApplication [
| model page |
<category: 'Iliad-Core-Buildables'>
<comment: 'I am the Iliad implementation of an application.
I am is the root object of a buildable object tree. Applications have a
set of controllers, methods used to dispatch requests to the corresponding
sub-tree of buildable objects (oftenly a composition of stateful widgets).
In concrete subclasses, the class method #path should return the base path
(string) for the application.
"""""""""""""""""""""""""""
" Applications & UI state "
"""""""""""""""""""""""""""
You don''t have to bother about instantiating applications, the framework
will handle session and application instances. Application instances are stored
in sessions. Each session stores one instance of the same application class.
Root widgets should be stored in applications to keep their state across requests.
""""""""""""""""""""""
" Controller methods "
""""""""""""""""""""""
Like widgets, I am stateful.
Unlike widgets I know how to dispatch a request with #dispatch :
the controller method corresponding to the url will be called.
Controller methods must:
- answer a buildable object (a block closure or an instance of ILWidget for example).
- be in the ''controllers'' method protocol (with the default selector filter)
The default controller method is #index.
""""""""""""""""""
" selectorFilter "
""""""""""""""""""
The class inst var <selectorFilter> is used to filter controller methods.
By default it allows all methods in the ''controllers'' protocol.
Alternatively, you can override the class method #defaultSelectorFilter to supply
your own selectorFilter or plug it in using the class method #selectorFilter:'>
ILApplication class [
| selectorFilter |
path [
"Base path of the application.
Override this method in concrete subclasses.
It should return a string"
<category: 'accessing'>
^''
]
absolutePath [
<category: 'accessing'>
^String streamContents: [:stream |
(self path startsWith: '/') ifFalse: [stream nextPut: $/].
stream nextPutAll: self path]
]
selectorFilter [
<category: 'accessing'>
^selectorFilter ifNil: [self defaultSelectorFilter]
]
selectorFilter: aBlock [
<category: 'accessing'>
selectorFilter := aBlock
]
defaultSelectorFilter [
"Override this method to supply your own selectorFilter
or plug it in using #selectorFilter:"
<category: 'defaults'>
^[:selector |
(self canUnderstand: selector) and: [
(self
categoryOfElement: selector
inClassOrSuperclass: self) = 'controllers']]
]
categoryOfElement: aSelector inClassOrSuperclass: aClass [
"Find the first category of <aSelector> up the superclass chain."
<category: 'private'>
^aClass ifNotNil: [
^(aClass whichCategoryIncludesSelector: aSelector) ifNil: [
self
categoryOfElement: aSelector
inClassOrSuperclass: aClass superclass]]
]
]
model [
<category: 'accessing'>
^model
]
model: anObject [
<category: 'accessing'>
model := anObject
]
page [
<category: 'accessing'>
^page
]
selectorFilter [
<category: 'accessing'>
^self class selectorFilter
]
widgetFor: aBuildable [
"Convenience method. This is useful for building anonymous widgets.
ex: myWidget := self widgetFor: [:e | e h1: 'Hello world!']"
<category: 'accessing'>
^ILPluggableWidget new
contentsBlock: aBuildable;
yourself
]
buildContents [
"Call #dispatch. A buildable is expected from #dispatch"
<category: 'building'>
^self newRootElement
build: self dispatch;
yourself
]
allowedSelector: aSelector [
"Answer true if <aSelector> is ok to call from a URL.
Default implementation is to use the pluggable filter block."
<category: 'dispatching'>
^self selectorFilter copy value: aSelector
]
dispatch [
"Dispatch to correct controller method.
If dispatchOverride returns something
different from nil, consider it handled."
<category: 'dispatching'>
^self dispatchOverride ifNil: [
self dispatchOn: self router controller]
]
dispatchOn: aMethod [
"Dispatch to correct method:
- If <aMethod> is empty we call #index
- If the selector is allowed to be executed then we just call it"
<category: 'dispatching'>
| m |
(aMethod isNil or: [aMethod isEmpty])
ifTrue: [m := #index]
ifFalse: [m := aMethod asSymbol].
(self allowedSelector: m)
ifTrue: [^self perform: m]
ifFalse: [ILDispatchError signal]
]
dispatchOverride [
"Handle special urls. Subclass implementors
should call super first and see if it was handled."
<category: 'dispatching'>
^nil
]
updatePage: aPage [
"Override to add elements to aPage.
super should always be called"
<category: 'updating'>
aPage head javascript src: '/javascripts/jquery132min.js'.
aPage head javascript src: '/javascripts/no_conflict.js'.
aPage head javascript src: '/javascripts/iliad.js'.
]
updateFromRoute: aRoute [
<category: 'updating'>
"Override this method to update to state of the application
from the request url route.
This method will be called for each new request"
]
updateBaseUrl: anUrl [
<category: 'updating'>
"Update the base url used for the current context"
]
respond: aBlock [
"Abort all other request handling"
<category: 'redirecting'>
| response |
response := ILResponse new.
aBlock value: response.
self returnResponse: response
]
returnResponse: aResponse [
"Abort all other request handling"
<category: 'redirecting'>
ILResponseNotification new
response: aResponse;
signal
]
index [
"default view method"
<category: 'controllers'>
^[:e | ]
]
respondOn: aResponse [
<category: 'converting'>
page := self defaultPageClass new.
page body build: self.
self updatePage: page.
self context builtWidgets do: [:each | each buildHead: page head].
page respondOn: aResponse
]
defaultPageClass [
<category: 'defaults'>
^ILHTMLPage
]
rootElementClass [
<category: 'defaults'>
^ILHTMLBuilderElement
]
newRootElement [
<category: 'private'>
^self rootElementClass new
]
]

View File

@ -0,0 +1,195 @@
"======================================================================
|
| Iliad.ILBuildable class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILObject subclass: ILBuildable [
| attributes children |
<category: 'Iliad-Core-Buildables'>
<comment: 'I am an abstract buildable object.
My subclasses must override #build method, which should return an instance of a subclass of Iliad.ILElement.'>
children [
<category: 'accessing'>
^children ifNil: [children := OrderedCollection new]
]
router [
<category: 'accessing'>
^self context router
]
attributeAt: aSymbol [
<category: 'accessing attributes'>
^self attributes at: aSymbol ifAbsent: [nil]
]
attributeAt: aSymbol ifAbsentPut: aBlock [
<category: 'accessing attributes'>
^self attributes at: aSymbol ifAbsentPut: aBlock
]
attributeAt: aSymbol put: anObject [
<category: 'accessing attributes'>
^self attributes at: aSymbol put: anObject
]
attributes [
<category: 'accessing attributes'>
^attributes ifNil: [attributes := Dictionary new]
]
send: aSymbol [
<category: 'actions'>
^self send: aSymbol to: self
]
send: aSymbol to: anObject [
<category: 'actions'>
^self send: aSymbol to: anObject arguments: #()
]
send: aSymbol to: anObject arguments: anArray [
<category: 'actions'>
^Grease.GRDelayedSend
receiver: anObject
selector: aSymbol
arguments: anArray
]
build [
<category: 'building'>
self withChildrenRegistrationDo: [
^self buildContents
]
]
buildContents [
"Override this method in subclasses.
It must answer an Element"
<category: 'building'>
self subclassResponsibility
]
buildOn: anElement [
<category: 'building'>
anElement add: self build
]
registerChild: aBuildable [
<category: 'building'>
(self children includes: aBuildable) ifFalse: [
self children add: aBuildable]
]
redirectTo: anUrlString [
"Abort all other request handling.
Redirect to anUrlString"
<category: 'redirecting'>
self session
redirectUrl: anUrlString;
redirect
]
redirectToIndex [
"Abort all other request handling.
Redirect to the index method of this class"
<category: 'redirecting'>
self redirectToLocal: 'index'
]
redirectToLocal: aString [
"Abort all other request handling.
Make a redirection to another controller method in this application"
<category: 'redirecting'>
self
redirectToApplication: self application class
controller: aString
]
redirectToApplication: aClass [
"Abort all other request handling.
Redirect to the index method of <aClass>"
<category: 'redirecting'>
self redirectToApplication: aClass controller: ''
]
redirectToApplication: aClass controller: aString [
"Abort all other request handling.
Redirect to the controller named <aString> of <aClass>"
<category: 'redirecting'>
self redirectTo:
(self context urlBuilder urlFor: aClass path, '/', aString)
greaseString
]
redirectToCurrentController [
"Abort all other request handling.
Redirect to the current controller method"
<category: 'redirecting'>
self redirectTo:
(self context urlBuilder urlFor: self router route pathString)
greaseString
]
respondOn: aResponse [
<category: 'converting'>
self build respondOn: aResponse
]
printHtmlString [
<category: 'printing'>
^String streamContents: [:str |
self build printHtmlOn: str]
]
withChildrenRegistrationDo: aBlock [
<category: 'private'>
ILCurrentBuildable value ifNotNil: [:parent |
parent registerChild: self].
ILCurrentBuildable use: self during: aBlock
]
]

View File

@ -0,0 +1,67 @@
"======================================================================
|
| Iliad.ILConfirmationWidget class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILWidget subclass: ILConfirmationWidget [
| confirmationString |
<category: 'Iliad-Core-Buildables'>
<comment: nil>
confirmationString [
<category: 'accessing'>
^confirmationString
]
confirmationString: aString [
<category: 'accessing'>
confirmationString := aString
]
contents [
<category: 'building'>
^[:e |
e text: self confirmationString.
e form build: [:form |
form button
action: [self answer: true];
text: 'Yes'.
form button
action: [self answer: false];
text: 'No']]
]
]

View File

@ -0,0 +1,43 @@
"======================================================================
|
| Iliad.ILCurrentBuildable class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILDynamicVariable subclass: ILCurrentBuildable [
<category: 'Iliad-Core-Buildables'>
<comment: nil>
]

View File

@ -0,0 +1,116 @@
"======================================================================
|
| Iliad.ILDecorator class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILBuildable subclass: ILDecorator [
| decoratee |
<category: 'Iliad-Core-Buildables'>
<comment: 'I am a decorator for Widgets. I can be added to a widget by calling #decorateWith: from a widget.
Subclasses can be used to modify the building process of a widget, or change its behavior'>
ILDecorator class >> decoratee: aDecoratee [
<category: 'instance creation'>
^self basicNew
decoratee: aDecoratee;
initialize;
yourself
]
decoratee [
<category: 'accessing'>
^decoratee
]
decoratee: aDecoratee [
<category: 'accessing'>
decoratee := aDecoratee
]
widget [
<category: 'accessing'>
^self decoratee widget
]
contents [
<category: 'building'>
^self decoratee contents
]
updateHead: aHead [
<category: 'building'>
self decoratee updateHead: aHead
]
styles [
<category: 'building'>
^#()
]
scripts [
<category: 'building'>
^#()
]
handleAnswer: anAnswer [
<category: 'decorations'>
^self decoratee handleAnswer: anAnswer
]
removeDecorator: aDecorator [
<category: 'decorations'>
self decoratee removeDecorator: aDecorator
]
removeYourself [
<category: 'decorations'>
self decoratee removeDecorator: self
]
isDelegator [
<category: 'testing'>
^false
]
isGlobal [
<category: 'testing'>
^false
]
]

View File

@ -0,0 +1,87 @@
"======================================================================
|
| Iliad.ILDelegator class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILDecorator subclass: ILDelegator [
| widget |
<comment: nil>
<category: 'Iliad-Core-Buildables'>
widget [
<category: 'accessing'>
^widget
]
widget: aWidget [
<category: 'accessing'>
widget := aWidget
]
newRootElement [
<category: 'accessing'>
^self widget newRootElement
]
contents [
<category: 'building'>
^self widget
]
updateHead: aHead [
<category: 'building'>
self widget updateHead: aHead
]
handleAnswer: anAnswer [
<category: 'decorations'>
self widget handleAnswer: anAnswer
]
isDelegator [
<category: 'testing'>
^true
]
isGlobal [
<category: 'testing'>
^true
]
]

View File

@ -0,0 +1,66 @@
"======================================================================
|
| Iliad.ILHTMLPage class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILBuildable subclass: ILHTMLPage [
<comment: nil>
<category: 'Iliad-Core-Buildables'>
body [
<category: 'accessing attributes'>
^self attributeAt: #body ifAbsentPut: [ILBodyElement new]
]
head [
<category: 'accessing attributes'>
^self attributeAt: #head ifAbsentPut: [ILHeadElement new]
]
html [
<category: 'accessing attributes'>
^self attributeAt: #html ifAbsentPut: [ILHtmlElement new]
]
build [
<category: 'building'>
^self html
add: self head;
add: self body;
yourself
]
]

View File

@ -0,0 +1,63 @@
"======================================================================
|
| Iliad.ILInformationWidget class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILWidget subclass: ILInformationWidget [
| informationString |
<category: 'Iliad-Core-Buildables'>
<comment: nil>
informationString [
<category: 'accessing'>
^informationString
]
informationString: aString [
<category: 'accessing'>
informationString := aString
]
contents [
<category: 'building'>
^[:e |
e text: self informationString.
e form button
action: [self answer];
text: 'Ok']
]
]

View File

@ -0,0 +1,58 @@
"======================================================================
|
| Iliad.ILPluggableWidget class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILWidget subclass: ILPluggableWidget [
| contentsBlock |
<comment: nil>
<category: 'Iliad-Core-Buildables'>
contentsBlock [
<category: 'accessing'>
^contentsBlock ifNil: [[:e | ]]
]
contentsBlock: aBlock [
<category: 'accessing'>
contentsBlock := aBlock
]
contents [
<category: 'building'>
^self contentsBlock
]
]

View File

@ -0,0 +1,53 @@
"======================================================================
|
| Iliad.ILPrependDelegator class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-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.
|
======================================================================"
ILDelegator subclass: ILPrependDelegator [
<comment: nil>
<category: 'Iliad-Core-Buildables'>
contents [
<category: 'building'>
^[:e | e
build: super contents;
build: self decoratee contents]
]
]

View File

@ -0,0 +1,85 @@
"======================================================================
|
| Iliad.ILProfiler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILDecorator subclass: ILProfiler [
<comment: nil>
<category: 'Iliad-Core-Buildables'>
contents [
<category: 'building'>
^[:e |
Transcript
show: '-- Iliad Profiler on: ', self widget greaseString , ' --';
cr.
[e build: self decoratee contents] profile do: [:each |
Transcript show: each greaseString; cr].
]
]
]
BlockClosure extend [
profile [
<category: 'profiling'>
| results workProcess finished s profProcess |
s := Semaphore new.
results := IdentityBag new.
workProcess := Processor activeProcess.
finished := false.
profProcess := [
[(Delay forMilliseconds: 2) wait.
finished] whileFalse: [
results add: workProcess suspendedContext method].
s signal]
forkAt: Processor highIOPriority.
self ensure: [
finished := true.
s wait.
^results sortedByCount]
]
]
Bag subclass: IdentityBag [
<category: nil>
<comment: nil>
dictionaryClass [
^IdentityDictionary
]
]

View File

@ -0,0 +1,72 @@
"======================================================================
|
| Iliad.ILSequence class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILWidget subclass: ILSequence [
<category: 'Iliad-Core-Buildables'>
<comment: nil>
build [
<category: 'building'>
self shouldStart ifTrue: [self start].
^super build
]
contents [
<category: 'building'>
"Do not override. The purpose of a sequence is to display other buildables"
self shouldNotImplement
]
start [
<category: 'control flow'>
"Override this method in subclasses"
]
restart [
<category: 'control flow'>
self
retrieveControl;
markDirty
]
shouldStart [
<category: 'testing'>
^decorator widget = self
]
]

View File

@ -0,0 +1,460 @@
"======================================================================
|
| Iliad.ILWidget class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILBuildable subclass: ILWidget [
| id state decorator owner dependentWidgets |
<category: 'Iliad-Core-Buildables'>
<comment: 'I am a stateful graphical component.
""""""""""""""""""""""""""""""
" Building HTML with widgets "
""""""""""""""""""""""""""""""
To build HTML override the #contents method, which should always
return a view block, ie, a block which takes an element as parameter.
Example:
contents
^[:e || div |
div := e div class: ''foo''.
div h1: ''Bar''.
div a
text: ''do something'';
action: [self doSomething]]
See Iliad.ILElement hierarchy (Especially Iliad.ILHTMLBuilderElement ) for more information
about building HTML with elements.
#contents method should *never* be called from the outside. Use #build instead.
For instance, to build a sub-widget in a view block, you should write something like:
contents [
^[:e | e build: mySubWidget]
]
""""""""""""""""
" Control flow "
""""""""""""""""
I can show (display instead of me) other widgets with #show* methods or answer
to widgets that called me with #answer.
When using the javascript layer, call #markDirty whenever my state change,
so I will be updated on AJAX requests.
Widgets which states depend on me can be automatically rebuilt whenever I am
marked as dirty (see #addDependentWidget:).
""""""""""""""
" Decorators "
""""""""""""""
I can also have decorators that may modify my behavior. A decorator can be
added to the decoration chain with #decorateWith:.'>
initialize [
<category: 'initialization'>
super initialize.
decorator := ILDecorator decoratee: self.
dependentWidgets := OrderedCollection new.
]
postCopy [
<category: 'copying'>
super postCopy.
decorator := ILDecorator decoratee: self.
dependentWidgets := OrderedCollection new.
state := nil.
id := nil
]
state [
<category: 'accessing'>
^state copy
]
id: aString [
<category: 'accessing'>
id := aString
]
id [
<category: 'accessing'>
^id ifNil: [id := self session nextId]
]
owner: aWidget [
<category: 'accessing'>
owner := aWidget
]
owner [
"Answer the widget which shows me. if any"
<category: 'accessing'>
^owner
]
dependentWidgets [
<category: 'accessing'>
^dependentWidgets copy
]
widget [
<category: 'accessing'>
^self
]
widgetFor: aBuildable [
"Convenience method. This is useful for building anonymous widgets.
ex: myWidget := self widgetFor: [:e | e h1: 'Hello world!']"
<category: 'accessing'>
^ILPluggableWidget new
contentsBlock: aBuildable;
yourself
]
stateRegistry [
<category: 'accessing'>
^self context stateRegistry
]
buildContents [
"Do *not* override this method. Use #contents instead"
<category: 'building'>
self registerState.
self context addBuiltWidget: self.
^self newRootElement
class: self id;
build: self fullContents;
yourself
]
fullContents [
"Do *not* override this method. Use #contents instead"
<category: 'building'>
^decorator contents
]
buildHead: aHead [
<category: 'building'>
decorator updateHead: aHead
]
contents [
"Override this method to add contents to your widget"
<category: 'building'>
^[:e | ]
]
scripts [
"Answer a collection of strings.
Override in subclasses to add scripts to load with the widget"
<category: 'building'>
^#()
]
styles [
"Answer a collection of strings.
Override in subclasses to add styles to load with the widget"
<category: 'building'>
^#()
]
decorateWith: aDecorator [
<category: 'decorators'>
| dec1 dec2 |
dec1 := nil.
dec2 := decorator.
[dec2 = self or: [
aDecorator isGlobal]] whileFalse: [
dec1 := dec2.
dec2 := dec2 decoratee].
aDecorator decoratee: dec2.
dec1 isNil
ifTrue: [decorator := aDecorator]
ifFalse: [dec1 decoratee: aDecorator]
]
decorateWith: aDecorator during: aBlock [
<category: 'decorators'>
self decorateWith: aDecorator.
aBlock value.
aDecorator removeYourself
]
decoratorsDo: aBlock [
<category: 'decorators'>
| dec |
dec := decorator.
[dec ~= self] whileTrue: [
aBlock value: dec.
dec := dec decoratee]
]
withDecoratorsDo: aBlock [
<category: 'decorators'>
aBlock value: self.
self decoratorsDo: aBlock
]
removeDecorator: aDecorator [
"Remove <aDecorator> from the decoration chain,
except if <aDecorator> is the initial one"
<category: 'decorators'>
decorator = aDecorator
ifTrue: [
decorator decoratee = self ifFalse: [
decorator := aDecorator decoratee]]
ifFalse: [| dec1 dec2 |
dec1 := decorator.
[dec1 = aDecorator] whileFalse: [
dec2 := dec1.
dec1 := dec1 decoratee].
dec2 decoratee: dec1 decoratee]
]
rootElementClass [
<category: 'defaults'>
^ILDivElement
]
answer [
"Give the control back to the owner, i.e, the widget which showed the receiver.
Answer self"
<category: 'control flow'>
^self answer: self
]
answer: anAnswer [
"Give the control back to the owner, i.e, the widget which showed the receiver.
Answer <anAnswer>"
<category: 'control flow'>
decorator handleAnswer: anAnswer
]
handleAnswer: anAnswer [
<category: 'control flow'>
^nil
]
retrieveControl [
"Give the control back to the receiver, and make any showed widget answer nil"
<category: 'control flow'>
self decoratorsDo: [:each |
each isDelegator ifTrue: [
each widget answer: nil]]
]
show: aWidget [
"Show another widget instead of the receiver.
The receiver is also implicitely marked dirty"
<category: 'control flow'>
self show: aWidget onAnswer: [:ans | ]
]
show: aWidget onAnswer: aBlock [
"Show another widget instead of the receiver and catch the answer in <aBlock>.
The receiver is also implicitely marked dirty"
<category: 'control flow'>
self
show: aWidget
onAnswer: aBlock
delegator: (ILDelegator new widget: aWidget)
]
append: aWidget [
"Insert <aWidget> after the receiver"
<category: 'control flow'>
self append: aWidget onAnswer: [:ans |]
]
append: aWidget onAnswer: aBlock [
"Insert <aWidget> after the receiver"
<category: 'control flow'>
self
show: aWidget
onAnswer: aBlock
delegator: (ILAppendDelegator new widget: aWidget)
]
prepend: aWidget [
"Insert <aWidget> before the receiver"
<category: 'control flow'>
self prepend: aWidget onAnswer: [:ans |]
]
prepend: aWidget onAnswer: aBlock [
"Insert <aWidget> before the receiver"
<category: 'control flow'>
self
show: aWidget
onAnswer: aBlock
delegator: (ILPrependDelegator new widget: aWidget)
]
show: aWidget onAnswer: aBlock delegator: aDelegator [
<category: 'control flow'>
| answerHandler |
answerHandler := ILAnswerHandler new.
self
decorateWith: aDelegator;
markDirty.
answerHandler action: (self session actionFor: [:value |
aDelegator removeYourself.
self markDirty.
aWidget owner: nil.
answerHandler removeYourself.
aBlock value: value]).
aWidget
owner: self;
decorateWith: answerHandler
]
inform: aString [
<category: 'control flow'>
self show: (ILInformationWidget new
informationString: aString;
yourself)
]
confirm: aString ifTrue: aBlock [
<category: 'control flow'>
self
confirm: aString
ifTrue: aBlock
ifFalse: []
]
confirm: aString ifTrue: aBlock ifFalse: anotherBlock [
<category: 'control flow'>
self
show: (ILConfirmationWidget new
confirmationString: aString;
yourself)
onAnswer: [:boolean |
boolean ifTrue: aBlock ifFalse: anotherBlock]
]
addDependentWidget: aWidget [
"Add <aWidget> to my dependent widgets.
Each dependent widget will be rebuilt on AJAX requests whenever
I am rebuilt"
<category: 'control flow'>
(dependentWidgets includes: aWidget) ifFalse: [
dependentWidgets add: aWidget]
]
removeDependentWidget: aWidget [
<category: 'control flow'>
(dependentWidgets includes: aWidget) ifTrue: [
dependentWidgets remove: aWidget]
]
registerState [
<category: 'states'>
self stateRegistry register: self
]
markDirty [
"Mark the receiver as 'dirty',
so the widget will be rebuilt on Ajax requests.
You do not need to mark subwidgets as dirty,
they will be rebuilt together with the receiver"
<category: 'states'>
self owner
ifNil: [self beDirty]
ifNotNil: [self owner markDirty].
dependentWidgets do: [:each | each markDirty]
]
printJsonOn: aStream [
<category: 'printing'>
self build printJsonOn: aStream
]
newRootElement [
<category: 'private'>
^self rootElementClass new
]
updateHead: aHead [
<category: 'private'>
self withDecoratorsDo: [:each |
each scripts do: [:script || e |
e := ILHTMLBuilderElement new javascript src: script.
(aHead children includes: e) ifFalse: [
aHead add: e]].
each styles do: [:script || e |
e := ILHTMLBuilderElement new stylesheet href: script.
(aHead children includes: e) ifFalse: [
aHead add: e]]]
]
beDirty [
<category: 'private'>
state := self session nextId
]
]

View File

@ -0,0 +1,47 @@
"======================================================================
|
| Iliad.ILDispatchError class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
Grease.GRError subclass: ILDispatchError [
<category: 'Iliad-Core-Dispatching'>
<comment: nil>
]

View File

@ -0,0 +1,110 @@
"======================================================================
|
| Iliad.ILDispatcher class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILObject subclass: ILDispatcher [
<category: 'Iliad-Core-Dispatching'>
<comment: 'I am the entry point of requests.
I dispatch them with the #dispatch: method to an ILApplicationHandler or a
ILFileHandler.
Web server adapters should use the #dispatch: method on the current instance
of ILDispatcher - returned by ILDispatcher class>>current - to handle requests,
and wait for a ILResponseNotification to respond to them.'>
ILDispatcher class [
| current |
current [
<category: 'instance creation'>
^current ifNil: [current := super new]
]
new [
<category: 'instance creation'>
self shouldNotImplement
]
]
dispatch: aRequest [
"Entry point of requests"
<category: 'dispatching'>
self withErrorHandling: [
ILCurrentContext
use: (self createContextFor: aRequest)
during: [
self withDispatchErrorHandling: [
self context router dispatchRequest]]]
]
withDispatchErrorHandling: aBlock [
"Catch dispatch errors"
<category: 'error-handling'>
aBlock
on: ILDispatchError
do: [:error |
ILNotFoundHandler new handleRequest]
]
withErrorHandling: aBlock [
"Catch errors and use an ILErrorHandler to handle them"
<category: 'error-handling'>
aBlock
on: Error
do: [:error |
ILErrorHandler new
error: error;
handleRequest]
]
createContextFor: aRequest [
<category: 'private'>
^ILContext new
request: aRequest;
session: (self findSessionFor: aRequest);
yourself
]
findSessionFor: aRequest [
<category: 'private'>
^ILSessionManager current sessionFor: aRequest
]
]

View File

@ -0,0 +1,155 @@
"======================================================================
|
| Iliad.ILRoute class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILObject subclass: ILRoute [
| path stream |
<category: 'Iliad-Core-Dispatching'>
<comment: 'I represent a route, used to dispatch a request.
My path is a collection of string, representing each part of the path of an url,
and can be streamed with methods in the <streaming> protocol.'>
ILRoute class >> delimiters [
<category: 'accessing'>
^Array with: $/
]
ILRoute class >> path: aCollection [
<category: 'instance creation'>
^self basicNew
initializeWithPath: aCollection;
yourself
]
basePath [
<category: 'accessing'>
self path isEmpty ifTrue: [^'/'].
^'/' , self path first
]
delimiter [
<category: 'accessing'>
^self delimiters first
]
delimiters [
<category: 'accessing'>
^self class delimiters
]
path [
<category: 'accessing'>
^path ifNil: [path := OrderedCollection new]
]
initializeWithPath: aCollection [
<category:'initialization'>
path := aCollection.
stream := ReadStream on: path
]
currentPath [
"Return an absolute url of the current streamed path
separated with delimiters, like this:
/foo/bar/baz"
<category: 'iterating'>
| part |
^String streamContents: [:s |
1 to: stream position do: [:i |
part := path at: i.
s nextPut: $/; nextPutAll: part]]
]
atEnd [
<category: 'streaming'>
^stream atEnd
]
next [
<category: 'streaming'>
^stream atEnd
ifTrue: [nil]
ifFalse: [stream next]
]
peek [
<category: 'streaming'>
^stream peek
]
position [
<category: 'streaming'>
^stream position
]
position: anInteger [
<category: 'streaming'>
stream position: anInteger
]
reset [
<category: 'streaming'>
stream reset
]
pathString [
<category: 'converting'>
| str |
str := WriteStream on: String new.
str nextPut: $/.
self path
do: [:each | str nextPutAll: each]
separatedBy: [str nextPut: self delimiter].
^str contents
]
uriString [
<category: 'converting'>
^self pathString
]
printOn: aStream [
<category: 'printing'>
super printOn: aStream.
aStream
nextPut: Character space;
nextPutAll: self uriString
]
]

View File

@ -0,0 +1,131 @@
"======================================================================
|
| Iliad.ILRouter class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILObject subclass: ILRouter [
| route hashRoute application controller |
<category: 'Iliad-Core-Dispatching'>
<comment: nil>
initialize [
<category: 'initialization'>
super initialize.
self
setApplication;
setRoutePosition;
setController;
updateApplicationFromRoute
]
dispatchRequest [
<category: 'dispatching'>
self shouldRedirect ifTrue: [
ILRedirectHandler new handleRequest].
self application
ifNil: [ILFileHandler new handleRequest]
ifNotNil: [ILApplicationHandler new handleRequest]
]
route [
<category: 'accessing'>
^route ifNil: [route := ILRoute path: self request url path]
]
hashRoute [
<category: 'accessing'>
| hash |
hash := self request hashLocationField ifNil: [''].
^hashRoute ifNil: [hashRoute := ILRoute path: (hash tokenize: '/')]
]
application [
<category: 'accessing'>
^application
]
controller [
<category: 'accessing'>
^controller
]
shouldRedirect [
<category: 'testing'>
self request isTypeOfRequestForJson ifTrue: [^false].
^self request sessionField notNil and: [self request hasCookies]
]
setApplication [
<category: 'private'>
application := self applicationClass
ifNotNil: [:applicationClass |
self session applications
at: applicationClass
ifAbsentPut: [applicationClass new]]
]
setRoutePosition [
<category: 'private'>
self application ifNotNil: [
self route position:
(ILUrl absolute: self application class path) path size]
]
setController [
<category: 'private'>
self route atEnd ifFalse: [
controller := self route next]
]
applicationClass [
<category: 'private'>
| applicationClass |
applicationClass := nil.
[self route atEnd not] whileTrue: [
self route next.
applicationClass := ILApplication allSubclasses
detect: [:each | each absolutePath = self route currentPath]
ifNone: [applicationClass]].
^applicationClass
]
updateApplicationFromRoute [
<category: 'updating'>
self application ifNotNil: [
self application updateFromRoute: self route]
]
]

View File

@ -0,0 +1,12 @@
Object extend [
printHtmlOn: aStream [
<category: '*Iliad-Core'>
self displayOn: aStream
]
printEncodedOn: aStream [
<category: '*Iliad-Core'>
Iliad.ILEncoder encodeForHTTP: self greaseString on: aStream
]
]

View File

@ -0,0 +1,177 @@
"======================================================================
|
| Iliad.ILElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILComposite subclass: ILElement [
| 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'>
= anObject [
<category: 'comparing'>
^super = anObject and: [
self attributes = anObject attributes]
]
hash [
<category: 'comparing'>
^super hash bitXor: self attributes hash
]
attributes [
<category: 'accessing'>
^attributes ifNil: [attributes := Grease.GRSmallDictionary new]
]
attributeAt: akey [
<category: 'accessing'>
^self attributes at: akey ifAbsent: [nil]
]
attributeAt: akey ifAbsent: aBlock [
<category: 'accessing'>
^self attributes at: akey ifAbsent: aBlock
]
attributeAt: akey ifAbsentPut: aBlock [
<category: 'accessing'>
^self attributes at: akey ifAbsentPut: aBlock
]
attributeAt: aKey put: aValue [
<category: 'accessing'>
^self attributes at: aKey put: aValue
]
contentType [
<category: 'accessing'>
self subclassResponsibility
]
tag [
<category: 'accessing'>
^nil
]
printJsonOn: aStream [
<category: 'printing'>
| str |
str := WriteStream on: String new.
self printHtmlOn: str.
str contents printJsonOn: aStream
]
printHtmlOn: aStream [
<category: 'printing'>
self beforePrintHtml.
self printOpenTagOn: aStream.
self childrenDo: [:each |
each printHtmlOn: aStream].
self printCloseTagOn: aStream.
self afterPrintHtml
]
afterPrintHtml [
<category: 'printing'>
]
beforePrintHtml [
<category: 'printing'>
]
printAttribute: anAttribute on: aStream [
<category: 'printing'>
aStream
nextPut: Character space;
nextPutAll: anAttribute key;
nextPutAll: '="'.
anAttribute value printEncodedOn: aStream.
aStream nextPut: $"
]
printCloseTagOn: aStream [
<category: 'printing'>
self tag ifNotNil: [aStream nextPutAll: '</' , self tag , '>']
]
printOpenTagOn: aStream [
<category: 'printing'>
self tag ifNotNil: [
aStream nextPutAll: '<' , self tag.
self attributes associationsDo: [:each |
each value ifNotNil: [
self printAttribute: each on: aStream]].
aStream nextPutAll: '>']
]
build: aBuildable [
<category: 'building'>
aBuildable buildOn: self
]
text: aString [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
contents: aString;
yourself)
]
xml [
<category: 'adding-conveniance'>
^self add: ILXmlElement new
]
attributeError: key [
<category: 'error handling'>
ILAttributeError signal: key
]
doesNotUnderstandAttribute: aString [
<category: 'error handling'>
^(AttributeNotUnderstood element: self attribute: aString) signal
]
respondOn: aResponse [
<category: 'converting'>
self printHtmlOn: aResponse.
aResponse contentType: self contentType
]
]

View File

@ -0,0 +1,68 @@
Grease.GRError subclass: ILAttributeError [
<category: 'Iliad-Core-Elements'>
<comment: nil>
]
Grease.GRError subclass: ILAttributeNotUnderstood [
| element attribute |
<category: 'Iliad-Core-Elements'>
<comment: nil>
ILAttributeNotUnderstood class >> element: anElement attribute: aString [
<category: 'instance creation'>
^(self new)
element: anElement;
attribute: aString;
yourself
]
attribute [
<category: 'accessing'>
^attribute
]
attribute: anObject [
<category: 'accessing'>
attribute := anObject
]
element [
<category: 'accessing'>
^element
]
element: anElement [
<category: 'accessing'>
element := anElement
]
defaultAction [
<category: 'exceptionDescription'>
]
isResumable [
<category: 'exceptionDescription'>
^true
]
messageText [
<category: 'printing'>
^'Tag ''{1}'' does not understand attribute ''{2}''' format:
{self element tag.
self attribute}
]
]
Grease.GRError subclass: ILElementError [
<comment: nil>
<category: 'Iliad-Core-Elements'>
]

View File

@ -0,0 +1,82 @@
"======================================================================
|
| Iliad.ILTextElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILElement subclass: ILTextElement [
| contents tag |
<comment: nil>
<category: 'Iliad-Core-Elements'>
add: anElement [
<category: 'adding'>
ILElementError signal: 'Can''t add an element to a ' , self class name
]
text: aString [
<category: 'adding'>
self contents: aString
]
contents [
<category: 'accessing'>
^contents ifNil: [contents := String new]
]
contents: aString [
<category: 'accessing'>
contents := aString
]
tag [
<category: 'accessing'>
^tag
]
tag: aString [
<category: 'accessing'>
tag := aString
]
printHtmlOn: aStream [
<category: 'printing'>
self printOpenTagOn: aStream.
ILEncoder encodeForHTTP: self contents on: aStream.
self printCloseTagOn: aStream
]
]

View File

@ -0,0 +1,71 @@
"======================================================================
|
| Iliad.ILXmlElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2010
| 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.
|
======================================================================"
ILElement subclass: ILXmlElement [
| tag |
<comment: nil>
<category: 'Iliad-Core-Elements'>
contentType [
<category: 'accessing'>
^'text/xml; charset=', self session charset
]
xmlTag [
<category: 'accessing'>
^'<?xml version="1.0" encoding="', self session encoding, '"?>'
]
tag [
<category: 'accessing'>
^tag
]
tag: aString [
<category: 'accessing'>
tag := aString
]
respondOn: aResponse [
<category: 'converting'>
aResponse nextPutAll: self xmlTag.
super respondOn: aResponse
]
]

View File

@ -0,0 +1,12 @@
Grease.GRGSTPlatform extend [
asMethodReturningString: aByteArrayOrString named: aSymbol [
"Generates the source of a method named aSymbol that returns aByteArrayOrString as a String"
<category: '*Iliad-Core-GST'>
^String streamContents: [ :stream |
stream nextPutAll: aSymbol; nextPutAll: ' [ '; nl.
stream tab; nextPutAll: ' ^'.
aByteArrayOrString storeLiteralOn: stream.
stream nl; nextPutAll: ']' ]
]
]

View File

@ -0,0 +1,49 @@
ILDirectory subclass: ILDiskDirectory [
| directory |
<category: 'Iliad-Core-GST'>
<comment: 'An ILDiskDirectory allows files to be served by Iliad directly from directories of even archives like .star files.
I shouldn''t be used in production.
Usage example:
Iliad.ILFileHandler addDirectory:
(Iliad.ILDiskDirectory new
directory: (PackageLoader packageAt: ''SomePackage'') directory / ''Public'';
'>
fileContentsFor: aString [
<category: 'accessing'>
| file stream |
file := self fileNamed: (self adjustPath: aString).
file isNil ifTrue: [^nil].
stream := file readStream.
^[stream contents] ensure: [stream close]
]
directory [
<category: 'accessing'>
^directory
]
directory: aDirectory [
<category: 'accessing'>
directory := aDirectory
]
fileNamed: aFilename [
"Try to find a file named <aFileName> in the directory"
<category: 'private'>
| file |
aFilename isEmpty ifTrue: [^nil].
file := self directory / aFilename.
(file notNil and: [file exists]) ifTrue: [^file].
^nil
]
adjustPath: aFilename [
<category: 'private'>
^aFilename copyReplacingRegex: '^\/' with: ''
]
]

View File

@ -0,0 +1,99 @@
"======================================================================
|
| Iliad.ILAnchorElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILLinkableElement subclass: ILAnchorElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
action: aBlock [
<category: 'accessing'>
self action: aBlock hash: ''
]
action: aBlock hash: aString [
<category: 'accessing'>
| action |
action := self session registerActionFor: aBlock.
self href: (self context urlBuilder
urlForAction: action
hash: aString)
]
tag [
<category: 'accessing'>
^'a'
]
tabindex: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'tabindex' put: anInteger greaseString
]
circleShape [
<category: 'accessing attributes-imagemap'>
self shape: 'circle'
]
coords: aString [
<category: 'accessing attributes-imagemap'>
self attributeAt: 'coords' put: aString
]
defaultShape [
<category: 'accessing attributes-imagemap'>
self shape: 'default'
]
polyShape [
<category: 'accessing attributes-imagemap'>
self shape: 'poly'
]
rectShape [
<category: 'accessing attributes-imagemap'>
self shape: 'rect'
]
shape: aString [
<category: 'accessing attributes-imagemap'>
self attributeAt: 'shape' put: aString
]
]

View File

@ -0,0 +1,103 @@
"======================================================================
|
| Iliad.ILAreaElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILClosingElement subclass: ILAreaElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'area'
]
accesskey: aCharacter [
<category: 'accessing attributes'>
self attributeAt: 'accesskey' put: aCharacter greaseString
]
alt: aString [
<category: 'accessing attributes'>
self attributeAt: 'alt' put: aString
]
href: aString [
<category: 'accessing attributes'>
self attributeAt: 'href' put: aString
]
nohref [
<category: 'accessing attributes'>
self attributeAt: 'nohref' put: 'nohref'
]
tabindex: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'tabindex' put: anInteger greaseString
]
circleShape [
<category: 'accessing attributes-imagemap'>
self shape: 'circle'
]
coords: aString [
<category: 'accessing attributes-imagemap'>
self attributeAt: 'coords' put: aString
]
defaultShape [
<category: 'accessing attributes-imagemap'>
self shape: 'default'
]
polyShape [
<category: 'accessing attributes-imagemap'>
self shape: 'poly'
]
rectShape [
<category: 'accessing attributes-imagemap'>
self shape: 'rect'
]
shape: aString [
<category: 'accessing attributes-imagemap'>
self attributeAt: 'shape' put: aString
]
]

View File

@ -0,0 +1,59 @@
"======================================================================
|
| Iliad.ILBodyElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILBodyElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'body'
]
onLoad: aString [
<category: 'addessing attributes-events'>
self onEvent: 'Load' add: aString
]
onUnload: aString [
<category: 'addessing attributes-events'>
self onEvent: 'Unload' add: aString
]
]

View File

@ -0,0 +1,53 @@
"======================================================================
|
| Iliad.ILBreakElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILClosingElement subclass: ILBreakElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'br'
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
]

View File

@ -0,0 +1,79 @@
"======================================================================
|
| Iliad.ILButtonElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILFormElementElement subclass: ILButtonElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'button'
]
beButton [
<category: 'accessing attributes'>
self type: 'button'
]
beReset [
<category: 'accessing attributes'>
self type: 'reset'
]
beSubmit [
<category: 'accessing attributes'>
self type: 'submit'
]
type: aString [
<category: 'accessing attributes'>
self attributeAt: 'type' put: aString
]
value: aString [
<category: 'accessing attributes'>
self attributeAt: 'value' put: aString
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'type' ifAbsentPut: ['submit']
]
]

View File

@ -0,0 +1,82 @@
"======================================================================
|
| Iliad.ILCheckboxElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILFormElementElement subclass: ILCheckboxElement [
| value hiddenAction |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'input'
]
action: aBlock [
<category: 'accessing attributes'>
| action |
hiddenAction := aBlock.
value := false.
action := self session registerActionFor: [:val | value := true].
self name: action key.
self addHiddenInput
]
beChecked [
<category: 'accessing attributes'>
self checked: true
]
checked: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue: [self attributeAt: 'checked' put: 'checked']
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'type' put: 'checkbox'
]
addHiddenInput [
<category: 'printing'>
self input
beHidden;
action: [:val | hiddenAction value: value. value := false]
]
]

View File

@ -0,0 +1,52 @@
"======================================================================
|
| Iliad.ILClosingElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILClosingElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
printHtmlOn: aStream [
<category: 'printing'>
aStream nextPutAll: '<' , self tag.
self attributes
associationsDo: [:each | self printAttribute: each on: aStream].
aStream nextPutAll: '/>'
]
]

View File

@ -0,0 +1,124 @@
"======================================================================
|
| Iliad.ILConditionalCommentElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILConditionalCommentElement [
| conditions |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
printOpenTagOn: aStream [
<category: 'printing'>
aStream nextPutAll: '<!--[if '.
self conditions
do: [:each | aStream nextPutAll: each]
separatedBy: [aStream nextPut: Character space].
aStream nextPutAll: ']>'
]
printCloseTagOn: aStream [
<category: 'printing'>
aStream nextPutAll: '<![endif]-->'
]
conditions [
<category: 'accessing'>
^conditions ifNil: [conditions := OrderedCollection new]
]
ie [
<category: 'conditions'>
self conditions add: 'IE'
]
ie5 [
<category: 'conditions'>
self conditions add: 'IE 5'
]
ie50 [
<category: 'conditions'>
self conditions add: 'IE 5.0'
]
ie55 [
<category: 'conditions'>
self conditions add: 'IE 5.5'
]
ie6 [
<category: 'conditions'>
self conditions add: 'IE 6'
]
ie7 [
<category: 'conditions'>
self conditions add: 'IE 7'
]
ie8 [
<category: 'conditions'>
self conditions add: 'IE 8'
]
gt [
"Greater than"
<category: 'conditions'>
self conditions add: 'gt'
]
lt [
"Less than"
<category: 'conditions'>
self conditions add: 'lt'
]
not [
"Not"
<category: 'conditions'>
self conditions add: '!'
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
]

View File

@ -0,0 +1,69 @@
"======================================================================
|
| Iliad.ILDirectionElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILDirectionElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'bdo'
]
xmlLang: aString [
<category: 'accessing'>
self doesNotUnderstandAttribute: 'xml:lang'
]
dir: aString [
<category: 'acessing attributes'>
self attributeAt: 'dir' put: aString
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'dir' ifAbsent: [self attributeError: '''dir'' not set']
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILDivElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILDivElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'div'
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILFieldsetElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILFieldsetElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'fieldset'
]
]

View File

@ -0,0 +1,174 @@
"======================================================================
|
| Iliad.ILFormElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILFormElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
ILFormElement class >> encodingType [
<category: 'defaults'>
^'application/x-www-form-urlencoded'
]
ILFormElement class >> multipartFormData [
<category: 'defaults'>
^'multipart/form-data'
]
tag [
<category: 'accessing'>
^'form'
]
url [
<category: 'accessing'>
^self context baseUrl greaseString
]
accept: aString [
<category: 'accessing attributes'>
self attributeAt: 'accept' put: aString
]
acceptCharset: aString [
<category: 'accessing attributes'>
self attributeAt: 'accept-charset' put: aString
]
acceptCharsets: aCollection [
<category: 'accessing attributes'>
| encodings |
encodings := WriteStream on: String new.
aCollection do: [:each | encodings nextPutAll: each]
separatedBy: [encodings nextPutAll: ' '].
self acceptCharset: encodings contents
]
accepts: aCollection [
<category: 'accessing attributes'>
| contentTypes |
contentTypes := WriteStream on: String new.
aCollection do: [:each | contentTypes nextPutAll: each]
separatedBy: [contentTypes nextPutAll: ' '].
self accept: contentTypes contents
]
beMultipart [
<category: 'accessing attributes'>
self enctype: self class multipartFormData
]
enctype [
<category: 'accessing attributes'>
^self attributeAt: 'enctype'
]
enctype: aString [
<category: 'accessing attributes'>
self attributeAt: 'enctype' put: aString
]
multipart: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue:
[self beMultipart]
]
useGet [
<category: 'accessing attributes'>
self attributeAt: 'method' put: 'get'
]
usePost [
<category: 'accessing attributes'>
self attributeAt: 'method' put: 'post'
]
onReset: aString [
<category: 'accessing attributes-events'>
self onEvent: 'reset' add: aString
]
onSubmit: aString [
<category: 'accessing attributes-events'>
self onEvent: 'submit' add: aString
]
onResetDo: aBlock [
<category: 'accessing attributes-events'>
self onEvent: 'reset' do: aBlock
]
onSubmitDo: aBlock [
<category: 'accessing attributes-events'>
self onEvent: 'submit' do: aBlock
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'action' ifAbsentPut: [self context baseUrl withoutParameters greaseString].
self attributeAt: 'method' ifAbsent: [self usePost].
self attributeAt: 'accept-charset' ifAbsentPut: [self session charset].
self addHiddenParameters
]
isMultipart [
<category: 'testing'>
^self enctype = self class multipartFormData
]
addHiddenParameters [
<category: 'private'>
self context urlBuilder baseUrl parameters keysAndValuesDo: [:key :value |
self input
beHidden;
name: key;
value: value].
self input
beHidden;
name: self context urlBuilder stateKey;
value: self session stateRegistry key.
self isMultipart ifTrue: [
self input
beHidden;
name: '_callback';
value: (self context urlBuilder urlForAction: (self session registerActionFor: [])) greaseString]
]
]

View File

@ -0,0 +1,98 @@
"======================================================================
|
| Iliad.ILFormElementElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILFormElementElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
accesskey: aCharacter [
<category: 'accessing'>
self attributeAt: 'accesskey' put: aCharacter greaseString
]
action: aBlock [
<category: 'accessing attributes'>
| action |
action := self session registerActionFor: aBlock.
self name: action key
]
name [
<category: 'accessing attributes'>
^self attributeAt: 'name'
]
name: aString [
<category: 'accessing attributes'>
self attributeAt: 'name' put: aString
]
readonly: aBoolean [
<category: 'accessing attributes'>
self attributeAt: 'readonly' put: aBoolean greaseString
]
beSubmitOnChange [
<category: 'accessing attributes'>
self beSubmitOnEvent: 'change'
]
beSubmitOnClick [
<category: 'accessing attributes'>
self beSubmitOnEvent: 'click'
]
beSubmitOnEvent: aString [
<category: 'accessing attributes'>
self onEvent: aString add: 'iliad.evaluateFormElementAction(this)'
]
disabled: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue: [
self attributeAt: 'disabled' put: 'disabled']
]
disabled [
<category: 'accessing attributes'>
self disabled: true
]
]

View File

@ -0,0 +1,841 @@
"======================================================================
|
| Iliad.ILHTMLBuilderElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILElement subclass: ILHTMLBuilderElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
contentType [
<category: 'accessing'>
^'text/html; charset=', self session charset
]
title [
<category: 'accessing attributes'>
^self attributeAt: 'title'
]
title: aString [
<category: 'accessing attributes'>
^self attributeAt: 'title' put: aString
]
cssClass: aString [
<category: 'accessing attributes'>
self attributeAt: 'class' put: aString
]
cssClass [
<category: 'accessing attributes'>
^self attributeAt: 'class'
]
class: aString [
<category: 'accessing'>
self cssClass: aString
]
id [
<category: 'accessing attributes'>
^self attributeAt: 'id'
]
id: aString [
<category: 'accessing attributes'>
self attributeAt: 'id' put: aString
]
lang: aString [
<category: 'accessing attributes'>
self attributeAt: 'lang' put: aString
]
xmlLang: aString [
<category: 'accessing attributes'>
self attributeAt: 'xml:lang' put: aString
]
style [
<category: 'accessing attributes'>
^self attributeAt: 'style'
]
style: aString [
<category: 'accessing attibutes'>
^self attributeAt: 'style' put: aString
]
onBlur: aString [
<category: 'accessing attributes-events'>
self onEvent: 'blur' add: aString
]
onChange: aString [
<category: 'accessing attributes-events'>
self onEvent: 'change' add: aString
]
onClick: aString [
<category: 'accessing attributes-events'>
self onEvent: 'click' add: aString
]
onDoubleClick: aString [
<category: 'accessing attributes-events'>
self onEvent: 'dblclick' add: aString
]
onFocus: aString [
<category: 'accessing attributes-events'>
self onEvent: 'focus' add: aString
]
onKeyDown: aString [
<category: 'accessing attributes-events'>
self onEvent: 'keydown' add: aString
]
onKeyPress: aString [
<category: 'accessing attributes-events'>
self onEvent: 'keypress' add: aString
]
onKeyUp: aString [
<category: 'accessing attributes-events'>
self onEvent: 'keyup' add: aString
]
onMouseOut: aString [
<category: 'accessing attributes-events'>
self onEvent: 'mouseout' add: aString
]
onMouseOver: aString [
<category: 'accessing attributes-events'>
self onEvent: 'mouseover' add: aString
]
onSelect: aString [
<category: 'accessing attributes-events'>
self onEvent: 'select' add: aString
]
onBlurDo: aBlock [
<category: 'accessing attributes-events'>
self onEvent: 'blur' do: aBlock
]
onChangeDo: aBlock [
<category: 'accessing attributes-events'>
self onEvent: 'change' do: aBlock
]
onClickDo: aBlock [
<category: 'accessing attributes-events'>
self onEvent: 'click' do: aBlock
]
onDoubleClickDo: aBlock [
<category: 'accessing attributes-events'>
self onEvent: 'dblclick' do: aBlock
]
onFocusDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'focus' do: aBlock
]
onKeyDownDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'keydown' do: aBlock
]
onKeyPressDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'keypress' do: aBlock
]
onKeyUpDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'keyup' do: aBlock
]
onMouseOutDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'mouseout' do: aBlock
]
onMouseOverDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'mouseover' do: aBlock
]
onSelectDo: aBlock [
<categoryDo: 'accessing attributes-events'>
self onEvent: 'select' do: aBlock
]
onEvent: aString add: anotherString [
<category: 'accessing attributes-events'>
| oldString |
oldString := (self attributeAt: 'on', aString) ifNil: [''].
self attributeAt: 'on', aString put: (oldString, anotherString)
]
onEvent: aString do: aBlock [
<category: 'accessing attributes-events'>
| actionUrl |
actionUrl := (self context urlBuilder urlForAction:
(self session registerActionFor: aBlock)) greaseString.
self
onEvent: aString
add: 'iliad.evaluateAction("', actionUrl, '");'
]
a [
<category: 'adding-conveniance'>
^self add: ILAnchorElement new
]
area [
<category: 'adding-conveniance'>
^self add: ILAreaElement new
]
bdo [
<category: 'adding-conveniance'>
^self add: ILDirectionElement new
]
big [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'big';
yourself)
]
big: aString [
<category: 'adding-conveniance'>
^self big
contents: aString;
yourself
]
blockquote [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'blockquote';
yourself)
]
blockquote: aString [
<category: 'adding-conveniance'>
^self blockquote
contents: aString;
yourself
]
b [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'b';
yourself)
]
b: aString [
<category: 'adding-conveniance'>
^self b
contents: aString;
yourself
]
br [
<category: 'adding-conveniance'>
^self add: ILBreakElement new
]
button [
<category: 'adding-conveniance'>
^self add: ILButtonElement new
]
checkbox [
<category: 'adding-conveniance'>
^self add: ILCheckboxElement new
]
cite [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'cite';
yourself)
]
cite: aString [
<category: 'adding-conveniance'>
^self cite
contents: aString;
yourself
]
code [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'code';
yourself)
]
code: aString [
<category: 'adding-conveniance'>
^self code
contents: aString;
yourself
]
dd [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'dd';
yourself)
]
dfn [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'dfn';
yourself)
]
dl [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'dl';
yourself)
]
dt [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'dt';
yourself)
]
div [
<category: 'adding-conveniance'>
^self add: ILDivElement new
]
em [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'em';
yourself)
]
em: aString [
<category: 'adding-conveniance'>
^self em
contents: aString;
yourself
]
favicon [
<category: 'adding-conveniance'>
^self link
beFavicon;
yourself
]
favicon: aString [
<category: 'adding-conveniance'>
^self favicon
href: aString;
yourself
]
fieldset [
<category: 'adding-conveniance'>
^self add: ILFieldsetElement new
]
file [
<category: 'adding-conveniance'>
^self input
beFile;
yourself
]
form [
<category: 'adding-conveniance'>
^self add: ILFormElement new
]
h1 [
<category: 'adding-conveniance'>
^self add: (ILHeadingElement new
level: 1;
yourself)
]
h1: aString [
<category: 'adding-conveniance'>
^self h1
text: aString;
yourself
]
h2 [
<category: 'adding-conveniance'>
^self add: (ILHeadingElement new
level: 2;
yourself)
]
h2: aString [
<category: 'adding-conveniance'>
^self h2
text: aString;
yourself
]
h3 [
<category: 'adding-conveniance'>
^self add: (ILHeadingElement new
level: 3;
yourself)
]
h3: aString [
<category: 'adding-conveniance'>
^self h3
text: aString;
yourself
]
h4 [
<category: 'adding-conveniance'>
^self add: (ILHeadingElement new
level: 4;
yourself)
]
h4: aString [
<category: 'adding-conveniance'>
^self h4
text: aString;
yourself
]
h5 [
<category: 'adding-conveniance'>
^self add: (ILHeadingElement new
level: 5;
yourself)
]
h5: aString [
<category: 'adding-conveniance'>
^self h5
text: aString;
yourself
]
h6 [
<category: 'adding-conveniance'>
^self add: (ILHeadingElement new
level: 6;
yourself)
]
h6: aString [
<category: 'adding-conveniance'>
^self h6
text: aString;
yourself
]
h [
<category: 'adding-conveniance'>
^self add: ILHeadingElement new
]
hr [
<category: 'adding-conveniance'>
^self add: ILHorizontalRuleElement new
]
html: aString [
<category: 'adding-conveniance'>
^self add: (ILRawHtmlElement new
contents: aString;
yourself)
]
if [
<category: 'accessing'>
^self add: (ILConditionalCommentElement new)
]
img [
<category: 'adding-conveniance'>
^self add: ILImageElement new
]
img: aString [
<category: 'adding-conveniance'>
^self img
src: aString;
yourself
]
input [
<category: 'adding-conveniance'>
^self add: ILInputElement new
]
i [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'i';
yourself)
]
i: aString [
<category: 'adding-conveniance'>
^self i
contents: aString;
yourself
]
javascript [
<category: 'adding-conveniance'>
^self script
beJavascript;
yourself
]
label [
<category: 'adding-conveniance'>
^self add: ILLabelElement new
]
legend [
<category: 'adding-conveniance'>
^self add: ILLegendElement new
]
legend: aString [
<category: 'adding-conveniance'>
^self legend
text: aString;
yourself
]
link [
<category: 'adding-conveenience'>
^self add: ILLinkElement new
]
li [
<category: 'adding-conveniance'>
^self add: ILListItemElement new
]
map [
<category: 'adding-conveniance'>
^self add: ILMapElement new
]
meta [
<category: 'adding-conveniance'>
^self add: ILMetaElement new
]
nbsp [
^self add: (ILRawHtmlElement new
contents: '&nbsp;';
yourself)
]
object [
<category: 'adding-conveniance'>
^self add: ILObjectElement new
]
option [
<category: 'adding-conveniance'>
^self add: ILOptionElement new
]
optgroup [
<category: 'adding-conveniance'>
^self add: ILOptionGroupElement new
]
ol [
<category: 'adding-conveniance'>
^self add: (ILListElement new
beOrdered;
yourself)
]
p [
<category: 'adding-conveniance'>
^self add: ILParagraphElement new
]
param [
<category: 'adding-conveniance'>
^self add: ILParameterElement new
]
password [
<category: 'adding-conveniance'>
^self input
bePassword;
yourself
]
pre [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'pre';
yourself)
]
pre: aString [
<category: 'adding-conveniance'>
^self pre
contents: aString;
yourself
]
quote [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'quote';
yourself)
]
quote: aString [
<category: 'adding-conveniance'>
^self quote
contents: aString;
yourself
]
radio [
<category: 'adding-conveniance'>
^self add: ILRadioButtonElement new
]
reset [
<category: 'adding-conveniance'>
^self input
beReset;
yourself
]
script [
<category: 'adding-conveniance'>
^self add: ILScriptElement new
]
script: aString [
<category: 'adding-conveniance'>
^self script
contents: aString;
yourself
]
select [
<category: 'adding-conveniance'>
^self add: ILSelectElement new
]
small [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'small';
yourself)
]
small: aString [
<category: 'adding-conveniance'>
^self small
contents: aString;
yourself
]
space [
<category: 'adding-conveniance'>
^self text: ' '
]
span [
<category: 'adding-conveniance'>
^self add: ILSpanElement new
]
strong [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'strong';
yourself)
]
strong: aString [
<category: 'adding-conveniance'>
^self strong
contents: aString;
yourself
]
stylesheet [
<category: 'adding-conveniance'>
^self link
beStylesheet;
yourself
]
submit [
<category: 'adding-conveniance'>
^self input
beSubmit;
yourself
]
subscript [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'subscript';
yourself)
]
subscript: aString [
<category: 'adding-conveniance'>
^self subscript
contents: aString;
yourself
]
superscript [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'superscript';
yourself)
]
superscript: aString [
<category: 'adding-conveniance'>
^self superscript
contents: aString;
yourself
]
table [
<category: 'adding-conveniance'>
^self add: ILTableElement new
]
tbody [
<category: 'adding-conveniance'>
^self add: ILTableBodyElement new
]
td [
<category: 'adding-conveniance'>
^self add: ILTableDataElement new
]
tfoot [
<category: 'adding-conveniance'>
^self add: ILTableFootElement new
]
thead [
<category: 'adding-conveniance'>
^self add: ILTableHeadElement new
]
th [
<category: 'adding-conveniance'>
^self add: ILTableHeaderElement new
]
tr [
<category: 'adding-conveniance'>
^self add: ILTableRowElement new
]
tt [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'tt';
yourself)
]
textarea [
<category: 'adding-conveniance'>
^self add: ILTextAreaElement new
]
ul [
<category: 'adding-conveniance'>
^self
add: (ILListElement new beUnordered;
yourself)
]
var [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'var';
yourself)
]
var: aString [
<category: 'adding-conveniance'>
^self var
contents: aString;
yourself
]
]

View File

@ -0,0 +1,101 @@
"======================================================================
|
| Iliad.ILHeadElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILHeadElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'head'
]
profile: aString [
<category: 'accessing attributes'>
self attributeAt: 'profile' put: aString
]
profiles: aCollection [
<category: 'accessing attributes'>
| profiles |
profiles := WriteStream on: String new.
aCollection do: [:each | profiles nextPutAll: each]
separatedBy: [profiles nextPutAll: ' '].
self attributeAt: 'profile' put: profiles contents
]
title [
<category: 'accessing attributes'>
^self add: ILTitleElement new
]
title: aString [
<category: 'accessing attributes'>
^self add: (ILTitleElement new
text: aString;
yourself)
]
style [
<category: 'adding-conveniance'>
^self add: (ILTextElement new
tag: 'style';
attributeAt: 'type' put: 'text/css';
yourself)
]
style: aString [
<category: 'adding-conveniance'>
^self style
contents: aString;
yourself
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
beforePrintHtml [
<category: 'printing'>
(self meta)
httpEquiv: 'Content-Type';
content: self contentType
]
]

View File

@ -0,0 +1,65 @@
"======================================================================
|
| Iliad.ILHeadingElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILHeadingElement [
| level |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
level [
<category: 'accessing'>
^level
]
level: anInteger [
<category: 'accessing'>
level := anInteger greaseString
]
tag [
<category: 'accessing'>
^'h' , self level
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
]

View File

@ -0,0 +1,54 @@
"======================================================================
|
| Iliad.ILHorizontalRuleElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILClosingElement subclass: ILHorizontalRuleElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'hr'
]
onEvent: anEvent add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , aString
]
]

View File

@ -0,0 +1,144 @@
"======================================================================
|
| Iliad.ILHtmlElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILHtmlElement [
| doctype xmlTag |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
defaultXmlns [
<category: 'defaults'>
^'http://www.w3.org/1999/xhtml'
]
beXhtml10Strict [
<category: 'accessing'>
self setXmlTag.
self doctype: '<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Strict//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-strict.dtd">'
]
beXhtml10Transitional [
<category: 'accessing'>
self setXmlTag.
self doctype: '<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.0 Transitional//EN" "http://www.w3.org/TR/xhtml1/DTD/xhtml1-transitional.dtd">'
]
beXhtml11 [
<category: 'accessing'>
self setXmlTag.
self doctype: '<!DOCTYPE html PUBLIC "-//W3C//DTD XHTML 1.1//EN" "http://www.w3.org/TR/xhtml11/DTD/xhtml11.dtd">'
]
beHtml5 [
<category: 'accessing'>
self doctype: '<!DOCTYPE html>'
]
doctype [
<category: 'accessing'>
^doctype
]
doctype: aString [
<category: 'accessing'>
doctype := aString
]
xmlTag [
<category: 'accessing'>
^xmlTag
]
xmlTag: aString [
<category: 'accessing'>
xmlTag := aString
]
setXmlTag [
<category: 'accessing'>
self xmlTag: ('<?xml version="1.0" encoding="', self session encoding, '"?>')
]
tag [
<category: 'accessing'>
^'html'
]
version: aNumber [
<category: 'accessing attributes'>
self attributeAt: 'version' put: aNumber greaseString
]
xmlns: aString [
<category: 'accessing attributes'>
self attributeAt: 'xmlns' put: aString
]
xmlns [
<category: 'accessing attributes'>
^self attributeAt: 'xmlns'
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'lang' ifAbsentPut: [self session language greaseString].
self hasXmlTag ifFalse: [^self].
self attributeAt: 'xmlns' ifAbsentPut: [self defaultXmlns].
self attributeAt: 'xml:lang' ifAbsentPut: [self session language greaseString]
]
printHtmlOn: aStream [
<category: 'printing'>
self doctype ifNil: [self beXhtml10Strict].
self hasXmlTag ifTrue: [
aStream nextPutAll: self xmlTag].
aStream nextPutAll: self doctype.
super printHtmlOn: aStream
]
hasXmlTag [
<category: 'testing'>
^self xmlTag notNil
]
]

View File

@ -0,0 +1,97 @@
"======================================================================
|
| Iliad.ILImageElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILClosingElement subclass: ILImageElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'img'
]
alt: aString [
<category: 'accessing attributes'>
self attributeAt: 'alt' put: aString
]
height: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'height' put: anInteger greaseString
]
ismap [
<category: 'accessing attributes'>
self attributeAt: 'ismap' put: 'ismap'
]
longdesc: aString [
<category: 'accessing attributes'>
self attributeAt: 'longdesc' put: aString
]
src: aString [
<category: 'accessing attributes'>
self attributeAt: 'src' put: aString
]
src: src alt: alt [
<category: 'accessing attributes'>
self
src: src;
alt: alt
]
usemap: aString [
<category: 'accessing attributes'>
self attributeAt: 'usemap' put: aString
]
width: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'width' put: anInteger greaseString
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'src' ifAbsent: [self attributeError: 'src not set'].
self attributeAt: 'alt' ifAbsentPut: ['']
]
]

View File

@ -0,0 +1,149 @@
"======================================================================
|
| Iliad.ILInputElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILFormElementElement subclass: ILInputElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'input'
]
accept: aString [
<category: 'accessing attributes'>
self attributeAt: 'accept' put: aString
]
accepts: aCollection [
<category: 'accessing attributes'>
| contentTypes |
contentTypes := WriteStream on: String new.
aCollection do: [:each | contentTypes nextPutAll: each]
separatedBy: [contentTypes nextPutAll: ' '].
self accept: contentTypes contents
]
alt: aString [
<category: 'accessing attributes'>
self attributeAt: 'alt' put: aString
]
ismap [
<category: 'accessing attributes'>
self attributeAt: 'ismap' put: 'ismap'
]
maxlength: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'maxlength' put: anInteger greaseString
]
size: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'size' put: anInteger greaseString
]
usemap: aString [
<category: 'accessing attributes'>
self attributeAt: 'usemap' put: aString
]
value: aString [
<category: 'accessing attributes'>
self attributeAt: 'value' put: aString
]
beFile [
<category: 'accessing attributes-types'>
self type: 'file'
]
beHidden [
<category: 'accessing attributes-types'>
self type: 'hidden'
]
beImage [
<category: 'accessing attributes-types'>
self type: 'image'
]
bePassword [
<category: 'accessing attributes-types'>
self type: 'password'
]
beReset [
<category: 'accessing attributes-types'>
self type: 'reset'
]
beSubmit [
<category: 'accessing attributes-types'>
self type: 'submit'
]
beText [
<category: 'accessing attributes-types'>
self type: 'text'
]
type: aString [
<category: 'accessing attributes-types'>
self attributeAt: 'type' put: aString
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'type' ifAbsentPut: ['text'].
]
printHtmlOn: aStream [
<category: 'printing'>
self beforePrintHtml.
aStream
nextPut: $<;
nextPutAll: self tag.
self attributes
associationsDo: [:each | self printAttribute: each on: aStream].
aStream nextPutAll: '/>'
]
]

View File

@ -0,0 +1,59 @@
"======================================================================
|
| Iliad.ILLabelElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILLabelElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'label'
]
accesskey: aCharacter [
<category: 'accessing attributes'>
self attributeAt: 'accesskey' put: aCharacter greaseString
]
for: aString [
<category: 'accessing attributes'>
self attributeAt: 'for' put: aString
]
]

View File

@ -0,0 +1,54 @@
"======================================================================
|
| Iliad.ILLegendElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILLegendElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'legend'
]
accesskey: aCharacter [
<category: 'accessing attributes'>
self attributeAt: 'accesskey' put: aCharacter greaseString
]
]

View File

@ -0,0 +1,112 @@
"======================================================================
|
| Iliad.ILLinkElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILLinkableElement subclass: ILLinkElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'link'
]
allMedia [
<category: 'accessing attributes'>
self media: 'all'
]
auralMedia [
<category: 'accessing attributes'>
self media: 'aural'
]
brailleMedia [
<category: 'accessing attributes'>
self media: 'braille'
]
handheldMedia [
<category: 'accessing attributes'>
self media: 'handheld'
]
media: aString [
<category: 'accessing attributes'>
self attributeAt: 'media' put: aString
]
printMedia [
<category: 'accessing attributes'>
self media: 'print'
]
projectionMedia [
<category: 'accessing attributes'>
self media: 'projection'
]
screenMedia [
<category: 'accessing attributes'>
self media: 'screen'
]
ttyMedia [
<category: 'accessing attributes'>
self media: 'tty'
]
tvMedia [
<category: 'accessing attributes'>
self media: 'tv'
]
type: aString [
<category: 'accessing attributes'>
self attributeAt: 'type' put: aString
]
printHtmlOn: aStream [
<category: 'printing'>
aStream nextPutAll: '<' , self tag.
self attributes
associationsDo: [:each | self printAttribute: each on: aStream].
aStream nextPutAll: '/>'
]
]

View File

@ -0,0 +1,275 @@
"======================================================================
|
| Iliad.ILLinkableElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILLinkableElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
accesskey: aCharacter [
<category: 'accessing attributes'>
self attributeAt: 'accesskey' put: aCharacter greaseString
]
charset: aString [
<category: 'accessing attributes'>
self attributeAt: 'charset' put: aString
]
contentType: aString [
<category: 'accessing attributes'>
self type: aString
]
href: aString [
<category: 'accessing attributes'>
self attributeAt: 'href' put: aString
]
hreflang: aString [
<category: 'accessing attributes'>
self attributeAt: 'hreflang' put: aString
]
target: aString [
<category: 'accessing attributes'>
self attributeAt: 'target' put: aString
]
linkToLocal: aString [
<category: 'accessing attributes'>
self linkToApplication: self application class controller: aString
]
linkToApplication: anApplicationClass [
<category: 'accessing attributes'>
self linkToApplication: anApplicationClass controller: ''
]
linkToApplication: anApplicationClass controller: aString [
<category: 'accessing attributes'>
self href: (self context urlBuilder urlFor: anApplicationClass path, '/', aString)
]
type: aString [
<category: 'accessing attributes'>
self attributeAt: 'type' put: aString
]
beAlternate [
<category: 'accessing attributes-relationships'>
self rel: 'Alternate'
]
beAppendix [
<category: 'accessing attributes-relationships'>
self rel: 'Appendix'
]
beBookmark [
<category: 'accessing attributes-relationships'>
self rel: 'Bookmark'
]
beChapter [
<category: 'accessing attributes-relationships'>
self rel: 'Chapter'
]
beContents [
<category: 'accessing attributes-relationships'>
self rel: 'Contents'
]
beCopyright [
<category: 'accessing attributes-relationships'>
self rel: 'Copyright'
]
beFavicon [
<category: 'accessing attributes-relationships'>
self rel: 'shortcut icon'
]
beGlossary [
<category: 'accessing attributes-relationships'>
self rel: 'Glossary'
]
beHelp [
<category: 'accessing attributes-relationships'>
self rel: 'Help'
]
beIndex [
<category: 'accessing attributes-relationships'>
self rel: 'Index'
]
beNext [
<category: 'accessing attributes-relationships'>
self rel: 'Next'
]
bePrev [
<category: 'accessing attributes-relationships'>
self rel: 'Prev'
]
bePrevious [
<category: 'accessing attributes-relationships'>
self rel: 'Prev'
]
beRss [
<category: 'accessing attributes-relationships'>
self rel: 'alternate'.
self type: 'application/rss+xml'
]
beSection [
<category: 'accessing attributes-relationships'>
self rel: 'Section'
]
beStart [
<category: 'accessing attributes-relationships'>
self rel: 'Start'
]
beStylesheet [
<category: 'accessing attributes-relationships'>
self rel: 'Stylesheet'.
self type: 'text/css'
]
beSubsection [
<category: 'accessing attributes-relationships'>
self rel: 'Subsection'
]
rel: aString [
<category: 'accessing attributes-relationships'>
self attributeAt: 'rel' put: aString
]
fromAlternate [
<category: 'accessing attributes-reverse links'>
self rev: 'Alternate'
]
fromAppendix [
<category: 'accessing attributes-reverse links'>
self rev: 'Appendix'
]
fromBookmark [
<category: 'accessing attributes-reverse links'>
self rev: 'Bookmark'
]
fromChapter [
<category: 'accessing attributes-reverse links'>
self rev: 'Chapter'
]
fromContents [
<category: 'accessing attributes-reverse links'>
self rev: 'Contents'
]
fromCopyright [
<category: 'accessing attributes-reverse links'>
self rev: 'Copyright'
]
fromGlossary [
<category: 'accessing attributes-reverse links'>
self rev: 'Glossary'
]
fromHelp [
<category: 'accessing attributes-reverse links'>
self rev: 'Help'
]
fromIndex [
<category: 'accessing attributes-reverse links'>
self rev: 'Index'
]
fromNext [
<category: 'accessing attributes-reverse links'>
self rev: 'Next'
]
fromPrev [
<category: 'accessing attributes-reverse links'>
self rev: 'Prev'
]
fromPrevious [
<category: 'accessing attributes-reverse links'>
self rev: 'Prev'
]
fromSection [
<category: 'accessing attributes-reverse links'>
self rev: 'Section'
]
fromStart [
<category: 'accessing attributes-reverse links'>
self rev: 'Start'
]
fromStylesheet [
<category: 'accessing attributes-reverse links'>
self rev: 'Stylesheet'
]
fromSubsection [
<category: 'accessing attributes-reverse links'>
self rev: 'Subsection'
]
rev: aString [
<category: 'accessing attributes-reverse links'>
self attributeAt: 'rev' put: aString
]
]

View File

@ -0,0 +1,65 @@
"======================================================================
|
| Iliad.ILListElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILListElement [
| tag |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
beOrdered [
<category: 'accessing'>
self tag: 'ol'
]
beUnordered [
<category: 'accessing'>
self tag: 'ul'
]
tag [
<category: 'accessing'>
^tag
]
tag: aString [
<category: 'accessing'>
tag := aString
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILListItemElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILListItemElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'li'
]
]

View File

@ -0,0 +1,54 @@
"======================================================================
|
| Iliad.ILMapElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILMapElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'map'
]
classes: aCollection [
<category: 'accessing attributes'>
ILAttributeError signal: 'map tag can have one class only'
]
]

View File

@ -0,0 +1,115 @@
"======================================================================
|
| Iliad.ILMetaElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILClosingElement subclass: ILMetaElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'meta'
]
class: aString [
<category: 'accessing attributes'>
self doesNotUnderstandAttribute: 'class'
]
classes: aCollection [
<category: 'accessing attributes'>
self doesNotUnderstandAttribute: 'class'
]
content: aString [
<category: 'accessing attributes'>
self attributeAt: 'content' put: aString
]
contentType [
<category: 'accessing attributes'>
self httpEquiv: 'content-type'
]
expires [
<category: 'accessing attributes'>
self httpEquiv: 'expires'
]
httpEquiv: aString [
<category: 'accessing attributes'>
self attributeAt: 'http-equiv' put: aString
]
name: aString [
<category: 'accessing attributes'>
self attributeAt: 'name' put: aString
]
refresh [
<category: 'accessing attributes'>
self httpEquiv: 'refresh'
]
scheme: aString [
<category: 'accessing attributes'>
self attributeAt: 'scheme' put: aString
]
setCookie [
<category: 'accessing attributes'>
self httpEquiv: 'set-cookie'
]
title: aString [
<category: 'accessing attributes'>
self doesNotUnderstandAttribute: 'title'
]
onEvent: event add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , event
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'content'
ifAbsent: [self attributeError: 'content not set']
]
]

View File

@ -0,0 +1,128 @@
"======================================================================
|
| Iliad.ILObjectElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILObjectElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'object'
]
archive: aString [
<category: 'accessing attributes'>
self attributeAt: 'archive' put: aString
]
archives: aCollection [
<category: 'accessing attributes'>
| archives |
archives := WriteStream on: String new.
aCollection do: [:each | archives nextPutAll: each]
separatedBy: [archives nextPutAll: ' '].
self attributeAt: 'archive' put: archives contents
]
classid: aString [
<category: 'accessing attributes'>
self attributeAt: 'classid' put: aString
]
codebase: aString [
<category: 'accessing attributes'>
self attributeAt: 'codebase' put: aString
]
codetype: aString [
<category: 'accessing attributes'>
self attributeAt: 'codetype' put: aString
]
data: aString [
<category: 'accessing attributes'>
self attributeAt: 'data' put: aString
]
declare [
<category: 'accessing attributes'>
self attributeAt: 'declare' put: 'declare'
]
declareOnly [
<category: 'accessing attributes'>
self declare
]
height: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'height' put: anInteger greaseString
]
name: aString [
<category: 'accessing attributes'>
self attributeAt: 'name' put: aString
]
standby: aString [
<category: 'accessing attributes'>
self attributeAt: 'standby' put: aString
]
tabindex: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'tabindex' put: anInteger greaseString
]
type: aString [
<category: 'accessing attributes'>
self attributeAt: 'type' put: aString
]
usemap: aString [
<category: 'accessing attributes'>
self attributeAt: 'usemap' put: aString
]
width: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'width' put: anInteger greaseString
]
]

View File

@ -0,0 +1,91 @@
"======================================================================
|
| Iliad.ILOptionElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILOptionElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'option'
]
action: aBlock [
<category: 'accessing-attributes'>
| action |
action := self session registerActionFor: aBlock.
self value: action key
]
selected: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue: [self selected]
]
label: aString [
<category: 'accessing attributes'>
self attributeAt: 'label' put: aString
]
selected [
<category: 'accessing attributes'>
self attributeAt: 'selected' put: 'selected'
]
selected: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue: [self selected]
]
disabled [
<category: 'accessing attributes'>
self attributeAt: 'disabled' put: 'disabled'
]
disabled: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue: [self disabled]
]
value: aString [
<category: 'accessing attributes'>
self attributeAt: 'value' put: aString
]
]

View File

@ -0,0 +1,65 @@
"======================================================================
|
| Iliad.ILOptionGroupElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILOptionGroupElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'optgroup'
]
label: aString [
<category: 'accessing attributes'>
self attributeAt: 'label' put: aString
]
disabled [
<category: 'accessing attributes'>
self attributeAt: 'disabled' put: 'disabled'
]
disabled: aBoolean [
<vategory: 'accessing attributes'>
aBoolean ifTrue: [self disabled]
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILParagraphElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILParagraphElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'p'
]
]

View File

@ -0,0 +1,96 @@
"======================================================================
|
| Iliad.ILParameterElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILClosingElement subclass: ILParameterElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'param'
]
beData [
<category: 'accessing attributes'>
self valuetype: 'data'
]
beObject [
<category: 'accessing attributes'>
self valuetype: 'object'
]
beReference [
<category: 'accessing attributes'>
self valuetype: 'ref'
]
name: aString [
<category: 'accessing attributes'>
self attributeAt: 'name' put: aString
]
type: aString [
<category: 'accessing attributes'>
self attributeAt: 'type' put: aString
]
value: aString [
<category: 'accessing attributes'>
self attributeAt: 'value' put: aString
]
valuetype: aString [
<category: 'accessing attributes'>
self attributeAt: 'valuetype' put: aString
]
add: anElement [
<category: 'adding'>
ILElementError signal: 'Can''t add an element to a' , self class name
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'name'
ifAbsent: [self attributeError: 'name can''t be null']
]
]

View File

@ -0,0 +1,76 @@
"======================================================================
|
| Iliad.ILRadioButtonElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILFormElementElement subclass: ILRadioButtonElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'input'
]
action: aBlock [
<category: 'accessing attributes'>
| action |
action := self session registerActionFor: aBlock.
self value: action key
]
beSelected [
<category: 'accessing attributes'>
self selected: true
]
selected: aBoolean [
<category: 'accessing attributes'>
aBoolean ifTrue: [self attributeAt: 'checked' put: 'checked']
]
value: aString [
<category: 'accessing attributes'>
self attributeAt: 'value' put: aString
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'type' put: 'radio'
]
]

View File

@ -0,0 +1,60 @@
"======================================================================
|
| Iliad.ILRawHtmlElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILElement subclass: ILRawHtmlElement [
| contents |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
contents [
<category: 'accessing'>
^contents ifNil: ['']
]
contents: aString [
<category: 'accessing'>
contents := aString
]
printHtmlOn: aStream [
<category: 'printing'>
aStream nextPutAll: self contents
]
]

View File

@ -0,0 +1,54 @@
"======================================================================
|
| Iliad.ILRubyTextElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILRubyTextElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'rt'
]
rbspan: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'rbspan' put: anInteger greaseString
]
]

View File

@ -0,0 +1,103 @@
"======================================================================
|
| Iliad.ILScriptElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILScriptElement [
| contents |
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
contents [
<category: 'accessing'>
^contents ifNil: ['']
]
contents: aString [
<category: 'accessing'>
contents := aString
]
tag [
<category: 'accessing'>
^'script'
]
beJavascript [
<category: 'accessing attributes'>
self type: 'text/javascript'
]
charset: aString [
<category: 'accessing attributes'>
self attributeAt: 'charset' put: aString
]
defer [
<category: 'accessing attributes'>
self attributeAt: 'defer' put: 'defer'
]
language: aString [
<category: 'accessing attributes'>
self attributeAt: 'language' put: aString
]
src: aString [
<category: 'accessing attributes'>
self attributeAt: 'src' put: aString
]
type: aString [
<category: 'accessing attributes'>
self attributeAt: 'type' put: aString
]
beforePrintHtml [
<category: 'printing'>
self attributeAt: 'type' ifAbsent: [self beJavascript]
]
printHtmlOn: aStream [
"do not encode contents!!"
<category: 'printing'>
self printOpenTagOn: aStream.
aStream nextPutAll: self contents.
self printCloseTagOn: aStream
]
]

View File

@ -0,0 +1,72 @@
"======================================================================
|
| Iliad.ILSelectElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILFormElementElement subclass: ILSelectElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
initialize [
<category: 'initialize release'>
super initialize.
super action: [:val |
val do: [:each |
self session evaluateActionKey: each]]
]
tag [
<category: 'accessing'>
^'select'
]
action: aBlock [
<category: 'accessing attributes'>
self shouldNotImplement
]
beMultiple [
<category: 'accessing attributes'>
self attributeAt: 'multiple' put: 'multiple'
]
size: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'size' put: anInteger greaseString
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILSpanElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILSpanElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'span'
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILTableBodyElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableElementElement subclass: ILTableBodyElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'tbody'
]
]

View File

@ -0,0 +1,98 @@
"======================================================================
|
| Iliad.ILTableCellElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableElementElement subclass: ILTableCellElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
abbr: aString [
<category: 'accessing attributes-table'>
self attributeAt: 'abbr' put: aString
]
axis: aString [
<category: 'accessing attributes-table'>
self attributeAt: 'axis' put: aString
]
colgroupScope [
<category: 'accessing attributes-table'>
self scope: 'colgroup'
]
colScope [
<category: 'accessing attributes-table'>
self scope: 'col'
]
colspan: anInteger [
<category: 'accessing attributes-table'>
self attributeAt: 'colspan' put: anInteger greaseString
]
headers: aCollection [
<category: 'accessing attributes-table'>
| headers |
headers := WriteStream on: String new.
aCollection do: [:each | headers nextPutAll: each]
separatedBy: [headers nextPutAll: ','].
self attributeAt: 'headers' put: headers contents
]
rowgroupScope [
<category: 'accessing attributes-table'>
self scope: 'rowgroup'
]
rowScope [
<category: 'accessing attributes-table'>
self scope: 'row'
]
rowspan: anInteger [
<category: 'accessing attributes-table'>
self attributeAt: 'rowspan' put: anInteger greaseString
]
scope: aString [
<category: 'accessing attributes-table'>
self attributeAt: 'scope' put: aString
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILTableDataElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableCellElement subclass: ILTableDataElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'td'
]
]

View File

@ -0,0 +1,154 @@
"======================================================================
|
| Iliad.ILTableElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILTableElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'table'
]
aboveFrame [
<category: 'accessing attributes'>
self frame: 'above'
]
allRules [
<category: 'accessing attributes'>
self rules: 'all'
]
belowFrame [
<category: 'accessing attributes'>
self frame: 'below'
]
border: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'border' put: anInteger greaseString
]
borderFrame [
<category: 'accessing attributes'>
self frame: 'border'
]
boxFrame [
<category: 'accessing attributes'>
self frame: 'box'
]
cellpadding: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'cellpadding' put: anInteger greaseString
]
cellspacing: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'cellspacing' put: anInteger greaseString
]
colsRules [
<category: 'accessing attributes'>
self rules: 'cols'
]
frame: aString [
<category: 'accessing attributes'>
self attributeAt: 'frame' put: aString
]
groupRules [
<category: 'accessing attributes'>
self rules: 'groups'
]
hsidesFrame [
<category: 'accessing attributes'>
self frame: 'hsides'
]
lhsFrame [
<category: 'accessing attributes'>
self frame: 'lhs'
]
noRules [
<category: 'accessing attributes'>
self rules: 'none'
]
rhsFrame [
<category: 'accessing attributes'>
self frame: 'rhs'
]
rowsRules [
<category: 'accessing attributes'>
self rules: 'rows'
]
rules: aString [
<category: 'accessing attributes'>
self attributeAt: 'rules' put: aString
]
summary: aString [
<category: 'accessing attributes'>
self attributeAt: 'summary' put: aString
]
vsidesFrame [
<category: 'accessing attributes'>
self frame: 'vsides'
]
voidFrame [
<category: 'accessing attributes'>
self frame: 'void'
]
width: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'width' put: anInteger greaseString
]
]

View File

@ -0,0 +1,115 @@
"======================================================================
|
| Iliad.ILTableElementElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILTableElementElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
align: aString [
<category: 'accessing attributes-table'>
self attributeAt: 'align' put: aString
]
baselineValign [
<category: 'accessing attributes-table'>
self valign: 'baseline'
]
bottomValign [
<category: 'accessing attributes-table'>
self valign: 'bottom'
]
centerAlign [
<category: 'accessing attributes-table'>
self align: 'center'
]
character: aCharacter [
<category: 'accessing attributes-table'>
| alignment |
alignment := self attributeAt: 'align' ifAbsent: ['left'].
alignment = 'char'
ifFalse: [self attributeError: 'Alignment must be "char"'].
self attributeAt: 'char' put: aCharacter greaseString
]
characterAlign [
<category: 'accessing attributes-table'>
self align: 'char'
]
charoff: anInteger [
<category: 'accessing attributes-table'>
self attributeAt: 'char'
ifAbsent: [self attributeError: 'Must specify alignment character'].
self attributeAt: 'charoff' put: anInteger greaseString
]
justifyAlign [
<category: 'accessing attributes-table'>
self align: 'justify'
]
leftAlign [
<category: 'accessing attributes-table'>
self align: 'left'
]
middleValign [
<category: 'accessing attributes-table'>
self valign: 'middle'
]
rightAlign [
<category: 'accessing attributes-table'>
self align: 'right'
]
topValign [
<category: 'accessing attributes-table'>
self valign: 'top'
]
valign: aString [
<category: 'accessing attributes-table'>
self attributeAt: 'valign' put: aString
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILTableFootElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableElementElement subclass: ILTableFootElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'tfoot'
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILTableHeadElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableElementElement subclass: ILTableHeadElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'thead'
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILTableHeaderElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableCellElement subclass: ILTableHeaderElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'th'
]
]

View File

@ -0,0 +1,49 @@
"======================================================================
|
| Iliad.ILTableRowElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILTableCellElement subclass: ILTableRowElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'tr'
]
]

View File

@ -0,0 +1,64 @@
"======================================================================
|
| Iliad.ILTextAreaElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILFormElementElement subclass: ILTextAreaElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'textarea'
]
cols: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'cols' put: anInteger greaseString
]
rows: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'rows' put: anInteger greaseString
]
tabindex: anInteger [
<category: 'accessing attributes'>
self attributeAt: 'tabindex' put: anInteger greaseString
]
]

View File

@ -0,0 +1,54 @@
"======================================================================
|
| Iliad.ILTitleElement class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILHTMLBuilderElement subclass: ILTitleElement [
<comment: nil>
<category: 'Iliad-Core-XHTMLElements'>
tag [
<category: 'accessing'>
^'title'
]
onEvent: anEvent add: aString [
<category: 'accessing attributes-events'>
self doesNotUnderstandAttribute: 'on' , anEvent
]
]

Binary file not shown.

After

Width:  |  Height:  |  Size: 3.9 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 49 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 82 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 52 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 130 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 20 KiB

Binary file not shown.

After

Width:  |  Height:  |  Size: 7.7 KiB

View File

@ -0,0 +1,395 @@
/* ====================================================================
|
| iliad.js
|
======================================================================
======================================================================
|
| 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.
|
==================================================================== */
var iliad = (function() {
/* ---
* Variables
* -------------------------------------------------------------- */
var hash = "";
var actionsLocked = false;
var ajax_enabled = true;
var ie67 = false;
var ajaxLoader = false;
/* ---
* Initialization
* -------------------------------------------------------------- */
function initialize() {
ie67 = jQuery.browser.msie && parseInt(jQuery.browser.version) < 8;
if(ie67) {
var iDoc = jQuery("<iframe id='_iliad_ie_history_iframe'" +
"src='/javascripts/iliad_ie_history.html'" +
"style='display: none'></iframe>").prependTo("body")[0];
var iframe = iDoc.contentWindow.document || iDoc.document;
if(window.location.hash) {
hash = window.location.hash.substr(1);
iframe.location.hash = hash;
evaluateAction(window.location.pathname + '?_hash=' + hash);
}
iframe.location.title = window.title;
}
checkHashChange();
enableAjaxActions()
}
function enableAjaxActions() {
jQuery('body').click(function(event) {
if (event.metaKey)
return;
var anchor = jQuery(event.target).closest("a");
if(anchor.length == 1) {
if(hasActionUrl(anchor)) {
evaluateAnchorAction(anchor, event);
}
}
var button = jQuery(event.target).closest("button");
if(button.length == 1) {
addHiddenInput(button);
evaluateFormElementAction(button, event);
removeHiddenInput(button);
}
})
}
/* ---
* Action evaluation
* -------------------------------------------------------------- */
function evaluateAnchorAction(anchor, event) {
if(hasActionUrl(anchor) && ajax_enabled) {
var actionUrl = jQuery(anchor).attr('href');
evaluateAction(actionUrl);
if(hasHashUrl(anchor)) {
setHash(hashUrl(anchor));
};
if(event) event.preventDefault();
}
}
function evaluateFormElementAction(formElement, event) {
var form = jQuery(formElement).closest("form");
if(ajax_enabled) {
if(isMultipart(form)) {
evaluateMultipartFormAction(form);
} else {
evaluateFormAction(form);
if(event) event.preventDefault();
}
}
}
function addHiddenInput(button) {
var name = jQuery(button).attr("name");
if(name) {
var hidden = "<input type='hidden' name='" +
name + "'></input>";
var form = jQuery(button).closest("form");
jQuery(form).append(hidden);
}
}
function removeHiddenInput(button) {
var name = jQuery(button).attr("name");
if(name) {
jQuery(button).closest("form")
.find("input:hidden[name="+ name + "]")
.replaceWith("");
}
}
function evaluateFormAction(form) {
var actionUrl = getFormActionUrl(form);
var data = jQuery(form).serialize();
evaluateAction(actionUrl, "post", data);
}
function evaluateMultipartFormAction(form) {
if(!actionsLocked) {
var hidden = "<input type='hidden' name='_ajax_upload'></input>";
var upload_target = jQuery('#_upload_target');
if(upload_target.size() == 0) {
upload_target = jQuery(
"<iframe id='_upload_target' name='_upload_target' " +
"src='#' style='display:none'></iframe>");
upload_target.appendTo('body');
}
upload_target.one('load', function(e) {
evaluateAction(jQuery(form).children("input[name=_callback]").val());
});
jQuery(form).append(hidden);
jQuery(form).attr('target', '_upload_target');
startUpload(form);
}
else {return false}
}
function evaluateAction(actionUrl, method, data, lock) {
if(!actionsLocked) {
if(!method) method = 'get';
if(lock == null) lock = true;
if(lock) lockActions();
jQuery.ajax({
url: actionUrl,
type: method,
processUpdates: true,
dataType: 'json',
data: data,
beforeSend: function(xhr) {
if(ajaxLoader) insertAjaxLoader();},
success: function(json) {
processUpdates(json);
if(ajaxLoader) removeAjaxLoader();
unlockActions();
},
error: function(err) {
showError(err, actionUrl);
unlockActions();
}
});
}
}
function lockActions() {
actionsLocked = true;
}
function unlockActions() {
actionsLocked = false;
}
function disableAjax() {
ajax_enabled = false
}
function enableAjax() {
ajax_enabled = true
}
function hasActionUrl(anchor) {
if(anchor && jQuery(anchor).attr('href')) {
return (/_action?=(.*)$/).test(jQuery(anchor).attr('href'));
}
}
function hasHashUrl(anchor) {
if(anchor && jQuery(anchor).attr('href')) {
return (/_hash?=(.*)$/).test(jQuery(anchor).attr('href'));
}
}
function hashUrl(anchor) {
return /_hash=([^\#|\&]+)/.exec(anchor.attr('href'))[1]
}
function isMultipart(form) {
return jQuery(form).attr('enctype') == "multipart/form-data";
}
function getFormActionUrl(form) {
return jQuery(form).attr('action');
}
/* ---
* Enable bookmarking for ajax actions
* and fix the back button
* -------------------------------------------------------------- */
function checkHashChange() {
var newHash = getHash();
if(hash != newHash) {
hash = newHash;
if(ie67) window.location.hash = hash;
evaluateAction(window.location.pathname + '?_hash=' + hash);
}
}
function setHash(hashString) {
hash = hashString;
window.location.hash = hash;
//IE is different, as usual....
if(ie67) fixHistoryForIE();
}
function getHash() {
if(ie67) {
var newHash = getIframe().location.hash;
return newHash.substr(1);
}
return window.location.hash.substr(1);
}
function getIframe() {
return jQuery('#_iliad_ie_history_iframe')[0].contentWindow.document;
}
//Special hack for IE < 8.
//Else IE won't add an entry to the history
function fixHistoryForIE() {
//Add history entry
getIframe().open();
getIframe().close();
getIframe().location.hash = hash;
}
/* ---
* Page updates
* -------------------------------------------------------------- */
function processUpdates(json) {
var script_extractor= /<script(.|\s)*?\/script>/ig;
var scripts = [];
/* handle redirect if any */
if(json.redirect) {
return (window.location.href = json.redirect);
}
/* update head */
for (var i in json.head) {
jQuery('head').append(json.head[i]);
}
/* update application */
if(json.application) {
jQuery('body').html(json.application)
}
/* update dirty widgets */
var dirtyWidgets = json.widgets;
for(var i in dirtyWidgets) {
var script = dirtyWidgets[i].match(script_extractor);
if(script) {
for(var j = 0; j < script.length; j++) {
scripts.push(script[j]);
}
}
updateWidget(i, dirtyWidgets[i].replace(script_extractor, ''));
}
/* evaluate scripts */
//var scripts = json.scripts;
for(var i in scripts) {
evalScript(scripts[i]);
}
}
function updateWidget(id, contents) {
jQuery("."+id).replaceWith(contents);
}
function evalScript(script) {
eval(jQuery(script).html());
}
/* ---
* Various
* -------------------------------------------------------------- */
function showAjaxLoader(bool) {
ajaxLoader = bool
}
function insertAjaxLoader() {
jQuery('body').append(
"<div class='ajax_loader'" +
"style='position: fixed; _position: absolute;" +
"top: 10px; right: 10px; z-index: 9999'>" +
"<img src='/images/ajax_loader.gif'/></div>");
}
function showError(error, actionUrl){
//jQuery("body").html("<h1>Error 500: Internal server error</h1>");
}
function removeAjaxLoader() {
jQuery(".ajax_loader, .ajax_upload").replaceWith("");
}
function sizeOf(obj) {
var size = 0, key;
for (key in obj) {
if (obj[key] !== Object.prototype[key]) size++;
//if (obj.hasOwnProperty(key)) size++;
}
return size;
}
function startUpload(form){
var fileInputs = jQuery(form).find('input:file');
jQuery.each(fileInputs, function(){
if(jQuery(this).val()) {
jQuery(this).after(
'<div class="ajax_upload">loading...<br/>' +
'<img src="/images/ajax_loader.gif"/></div>');
}
})
}
/* ---
* Public API
* -------------------------------------------------------------- */
return {
evaluateAnchorAction: evaluateAnchorAction,
evaluateFormAction: evaluateFormAction,
evaluateMultipartFormAction: evaluateMultipartFormAction,
evaluateFormElementAction: evaluateFormElementAction,
evaluateAction: evaluateAction,
checkHashChange: checkHashChange,
showAjaxLoader: showAjaxLoader,
disableAjax: disableAjax,
enableAjax: enableAjax,
initialize: initialize
};
})();
jQuery(document).ready(function() {
iliad.initialize();
setInterval(iliad.checkHashChange, 200);
});

View File

@ -0,0 +1,12 @@
<html xmlns="http://www.w3.org/1999/xhtml">
<head>
<script language="JavaScript">
if (window.parent) {
document.title = window.parent.document.title;
}
</script>
</head>
<body>
</body>
</html>

File diff suppressed because one or more lines are too long

View File

@ -0,0 +1,2 @@
jQuery.noConflict();

View File

@ -0,0 +1,93 @@
body {
background-color: #f4f1f1;
font-family: "Verdana", "DejaVu Sans", sans-serif;
color: #636363;
font-size: 12px;
text-align: center;
}
img {
border: 0 none
}
.wrapper {
margin: 0 auto;
text-align: left;
width: 600px;
}
.logo {
text-align: center;
}
h1, h2, h3 {
font-weight: normal;
}
h1 {
color: #3B3B3B;
font-size: 32px;
}
h2 {
font-size: 22px;
}
h3 {
font-size: 18px;
margin-top: 5px;
margin-bottom: 5px;
}
a, a:visited {
color: #660e7b;
font-weight: bold;
text-decoration: none;
}
a:hover {
color: #111;
}
table {
margin: 10px;
padding: 10px;
line-height: 1.5em;
border: 1px solid #ccc;
background: #fcfcfc
}
thead {
font-size: 1.4em
}
td {
padding-left: 14px;
padding-right: 14px;
}
pre {
margin: 10px;
padding: 10px;
line-height: 1.5em;
background-color: #fafafa;
border: 1px solid #cef6c9;
}
input, textarea {
border: 1px solid #444;
}
.error, .errors {
color: #d51a2c;
font-weight: bold
}
.errors {margin-bottom: 10px}
.error input,
.error textarea {
background-color: #f4e5e6;
border: 1px solid #d51a2c}
.required:after {content: ' *'; color: #d51a2c; font-weight: bold}

View File

@ -0,0 +1,122 @@
"======================================================================
|
| Iliad.ILApplicationHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILRequestHandler subclass: ILApplicationHandler [
| actions |
<comment: nil>
<category: 'Iliad-Core-RequestHandlers'>
initialize [
<category: 'initialization'>
super initialize.
actions := OrderedCollection new
]
evaluateActions [
<category: 'request handling'>
self getActionsFromRequest.
(actions asSortedCollection: [:a :b | a key asInteger < b key asInteger])
do: [:each | each evaluate]
]
handleRequest [
<category: 'request handling'>
self session isExpired ifTrue: [self session onExpire].
self isRequestValid
ifTrue: [self evaluateActions]
ifFalse: [ILRedirectHandler new handleRequest].
self shouldReturnEmptyResponse ifTrue: [
self returnResponse: ILResponse ok].
self shouldRespondInJson ifTrue: [
ILJsonHandler new handleRequest].
self shouldRedirect
ifTrue: [ILRedirectHandler new handleRequest]
ifFalse: [self produceResponse]
]
produceResponse [
<category: 'responding'>
self respond: [:response |
self addAllowHeaderTo: response.
self session useCookies ifTrue: [self addCookieHeaderTo: response].
self session refreshOnBacktrack ifTrue: [self addNoCacheHeaderTo: response]]
]
isRequestValid [
<category: 'testing'>
^self context previousStateRegistry notNil
or: [self request actionField isNil and: [self request isGet]]
]
shouldRedirect [
<category: 'testing'>
^self request isTypeOfRequestForRedirect
]
shouldRespondInJson [
<category: 'testing'>
^self request isTypeOfRequestForJson
]
shouldReturnEmptyResponse [
<category: 'testing'>
^self request ajaxUploadField notNil
]
newResponse [
<category: 'private'>
^self application asResponse
]
getActionsFromRequest [
<category: 'private'>
| action |
actions := OrderedCollection new.
self request isGet ifTrue: [
| actionField |
actionField := self request actionField.
action := self session actionAt: actionField.
action ifNotNil: [actions add: action]].
self request isPost ifTrue: [
self request fields associations do: [:asso |
(action := self session actionAt: asso value) ifNil: [
action := self session actionAt: asso key.
action ifNotNil: [action value: asso value]].
action ifNotNil: [actions add: action]]]
]
]

View File

@ -0,0 +1,10 @@
ILObject subclass: ILDirectory [
<category: 'Iliad-Core-RequestHandlers'>
<comment: nil>
fileContentsFor: aFilename [
<category: 'accessing'>
self subclassResponsibility
]
]

View File

@ -0,0 +1,173 @@
"======================================================================
|
| Iliad.ILErrorHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILRequestHandler subclass: ILErrorHandler [
| error |
<category: 'Iliad-Core-RequestHandlers'>
<comment: '
""""""""""""""""""""""""
" Error handling modes "
""""""""""""""""""""""""
Error handlers can be in one of the following modes: deployment, verbose or
debug. The default mode is verbose.
You can switch between modes with class methods in the <accessing modes>
protocol.
When errors occur, the framework with handle them differently depending on
the application mode:
- in deployment mode, it will respond an error 500;
- in verbose mode, it will also respond an error 500, but with error details;
- in debug mode, a debugger window will be opened on the error;'>
ILErrorHandler class [
| mode |
mode [
<category: 'accessing'>
^mode ifNil: [mode := #verbose]
]
mode: aSymbol [
<category: 'accessing'>
mode := aSymbol
]
verboseMode [
<category: 'accessing modes'>
self mode: #verbose
]
debugMode [
<category: 'accessing modes'>
self mode: #debug
]
deploymentMode [
<category: 'accessing modes'>
self mode: #deployment
]
]
error [
<category: 'accessing'>
^error
]
error: anError [
<category: 'accessing'>
error := anError
]
mode [
<category: 'accessing'>
^self class mode
]
newResponse [
<category: 'accessing'>
^ILResponse new
status: 500;
yourself
]
produceResponse [
<category: 'responding'>
self isDebugMode ifTrue: [
self produceDebugResponse].
self isVerboseMode ifTrue: [
self produceVerboseResponse].
self isDeploymentMode ifTrue: [
self produceDeploymentResponse]
]
produceDeploymentResponse [
<category: 'responding'>
self respond: [:response |
response nextPutAll: '<html><h1>Error 500: Internal server error</h1></html>']
]
produceDebugResponse [
<category: 'responding'>
self error resignalAsUnhandled: self error messageText
]
produceVerboseResponse [
<category: 'responding'>
| info |
info := WriteStream on: ''.
self respond: [:response || page e |
response nextPutAll: (String streamContents: [:stream |
page := ILHTMLPage new.
page body h1: 'Internal Error';
h2: self error description;
h3: self error messageText.
self error examineOn: info.
info nextPut: Character cr.
self error resumeContext backtraceOn: info.
page body pre: info contents.
Transcript show: info contents; cr.
page build printHtmlOn: stream])]
]
isDebugMode [
<category: 'testing'>
^self mode = #debug
]
isVerboseMode [
<category: 'testing'>
^self mode = #verbose
]
isDeploymentMode [
<category: 'testing'>
^self isDebugMode not and: [
self isVerboseMode not]
]
]
Exception extend [
resumeContext [
^resumeBlock outerContext home
]
]

View File

@ -0,0 +1,559 @@
"======================================================================
|
| Iliad.ILFileHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILRequestHandler subclass: ILFileHandler [
| file |
<comment: nil>
<category: 'Iliad-Core-RequestHandlers'>
MimeTypes := nil.
Directories := nil.
ILFileHandler class >> defaultMimeType [
<category: 'accessing'>
^'application/octet-stream'
]
ILFileHandler class >> defaultMimeTypes [
<category: 'accessing'>
^ #(
'%' 'application/x-trash'
'323' 'text/h323'
'abw' 'application/x-abiword'
'ai' 'application/postscript'
'aif' 'audio/x-aiff'
'aifc' 'audio/x-aiff'
'aiff' 'audio/x-aiff'
'alc' 'chemical/x-alchemy'
'art' 'image/x-jg'
'asc' 'text/plain'
'asf' 'video/x-ms-asf'
'asn' 'chemical/x-ncbi-asn1-spec'
'aso' 'chemical/x-ncbi-asn1-binary'
'asx' 'video/x-ms-asf'
'au' 'audio/basic'
'avi' 'video/x-msvideo'
'b' 'chemical/x-molconn-Z'
'bak' 'application/x-trash'
'bat' 'application/x-msdos-program'
'bcpio' 'application/x-bcpio'
'bib' 'text/x-bibtex'
'bin' 'application/octet-stream'
'bmp' 'image/x-ms-bmp'
'book' 'application/x-maker'
'bsd' 'chemical/x-crossfire'
'c' 'text/x-csrc'
'c++' 'text/x-c++src'
'c3d' 'chemical/x-chem3d'
'cac' 'chemical/x-cache'
'cache' 'chemical/x-cache'
'cascii' 'chemical/x-cactvs-binary'
'cat' 'application/vnd.ms-pki.seccat'
'cbin' 'chemical/x-cactvs-binary'
'cc' 'text/x-c++src'
'cdf' 'application/x-cdf'
'cdr' 'image/x-coreldraw'
'cdt' 'image/x-coreldrawtemplate'
'cdx' 'chemical/x-cdx'
'cdy' 'application/vnd.cinderella'
'cef' 'chemical/x-cxf'
'cer' 'chemical/x-cerius'
'chm' 'chemical/x-chemdraw'
'chrt' 'application/x-kchart'
'cif' 'chemical/x-cif'
'class' 'application/java-vm'
'cls' 'text/x-tex'
'cmdf' 'chemical/x-cmdf'
'cml' 'chemical/x-cml'
'cod' 'application/vnd.rim.cod'
'com' 'application/x-msdos-program'
'cpa' 'chemical/x-compass'
'cpio' 'application/x-cpio'
'cpp' 'text/x-c++src'
'cpt' 'image/x-corelphotopaint'
'crl' 'application/x-pkcs7-crl'
'crt' 'application/x-x509-ca-cert'
'csf' 'chemical/x-cache-csf'
'csh' 'text/x-csh'
'csm' 'chemical/x-csml'
'csml' 'chemical/x-csml'
'css' 'text/css'
'csv' 'text/comma-separated-values'
'ctab' 'chemical/x-cactvs-binary'
'ctx' 'chemical/x-ctx'
'cu' 'application/cu-seeme'
'cub' 'chemical/x-gaussian-cube'
'cxf' 'chemical/x-cxf'
'cxx' 'text/x-c++src'
'dat' 'chemical/x-mopac-input'
'dcr' 'application/x-director'
'deb' 'application/x-debian-package'
'dif' 'video/dv'
'diff' 'text/plain'
'dir' 'application/x-director'
'djv' 'image/vnd.djvu'
'djvu' 'image/vnd.djvu'
'dl' 'video/dl'
'dll' 'application/x-msdos-program'
'dmg' 'application/x-apple-diskimage'
'dms' 'application/x-dms'
'doc' 'application/msword'
'dot' 'application/msword'
'dv' 'video/dv'
'dvi' 'application/x-dvi'
'dx' 'chemical/x-jcamp-dx'
'dxr' 'application/x-director'
'emb' 'chemical/x-embl-dl-nucleotide'
'embl' 'chemical/x-embl-dl-nucleotide'
'ent' 'chemical/x-pdb'
'eps' 'application/postscript'
'etx' 'text/x-setext'
'exe' 'application/x-msdos-program'
'ez' 'application/andrew-inset'
'fb' 'application/x-maker'
'fbdoc' 'application/x-maker'
'fch' 'chemical/x-gaussian-checkpoint'
'fchk' 'chemical/x-gaussian-checkpoint'
'fig' 'application/x-xfig'
'flac' 'application/x-flac'
'fli' 'video/fli'
'fm' 'application/x-maker'
'frame' 'application/x-maker'
'frm' 'application/x-maker'
'gal' 'chemical/x-gaussian-log'
'gam' 'chemical/x-gamess-input'
'gamin' 'chemical/x-gamess-input'
'gau' 'chemical/x-gaussian-input'
'gcd' 'text/x-pcs-gcd'
'gcf' 'application/x-graphing-calculator'
'gcg' 'chemical/x-gcg8-sequence'
'gen' 'chemical/x-genbank'
'gf' 'application/x-tex-gf'
'gif' 'image/gif'
'gjc' 'chemical/x-gaussian-input'
'gjf' 'chemical/x-gaussian-input'
'gl' 'video/gl'
'gnumeric' 'application/x-gnumeric'
'gpt' 'chemical/x-mopac-graph'
'gsf' 'application/x-font'
'gsm' 'audio/x-gsm'
'gtar' 'application/x-gtar'
'h' 'text/x-chdr'
'h++' 'text/x-c++hdr'
'hdf' 'application/x-hdf'
'hh' 'text/x-c++hdr'
'hin' 'chemical/x-hin'
'hpp' 'text/x-c++hdr'
'hqx' 'application/mac-binhex40'
'hs' 'text/x-haskell'
'hta' 'application/hta'
'htc' 'text/x-component'
'htm' 'text/html'
'html' 'text/html'
'hxx' 'text/x-c++hdr'
'ica' 'application/x-ica'
'ice' 'x-conference/x-cooltalk'
'ico' 'image/x-icon'
'ics' 'text/calendar'
'icz' 'text/calendar'
'ief' 'image/ief'
'iges' 'model/iges'
'igs' 'model/iges'
'iii' 'application/x-iphone'
'inp' 'chemical/x-gamess-input'
'ins' 'application/x-internet-signup'
'iso' 'application/x-iso9660-image'
'isp' 'application/x-internet-signup'
'ist' 'chemical/x-isostar'
'istr' 'chemical/x-isostar'
'jad' 'text/vnd.sun.j2me.app-descriptor'
'jar' 'application/java-archive'
'java' 'text/x-java'
'jdx' 'chemical/x-jcamp-dx'
'jmz' 'application/x-jmol'
'jng' 'image/x-jng'
'jnlp' 'application/x-java-jnlp-file'
'jpe' 'image/jpeg'
'jpeg' 'image/jpeg'
'jpg' 'image/jpeg'
'js' 'application/x-javascript'
'kar' 'audio/midi'
'key' 'application/pgp-keys'
'kil' 'application/x-killustrator'
'kin' 'chemical/x-kinemage'
'kpr' 'application/x-kpresenter'
'kpt' 'application/x-kpresenter'
'ksp' 'application/x-kspread'
'kwd' 'application/x-kword'
'kwt' 'application/x-kword'
'latex' 'application/x-latex'
'lha' 'application/x-lha'
'lhs' 'text/x-literate-haskell'
'lsf' 'video/x-la-asf'
'lsx' 'video/x-la-asf'
'ltx' 'text/x-tex'
'lzh' 'application/x-lzh'
'lzx' 'application/x-lzx'
'm3u' 'audio/x-mpegurl'
'm4a' 'audio/mpeg'
'maker' 'application/x-maker'
'man' 'application/x-troff-man'
'mcif' 'chemical/x-mmcif'
'mcm' 'chemical/x-macmolecule'
'mdb' 'application/msaccess'
'me' 'application/x-troff-me'
'mesh' 'model/mesh'
'mid' 'audio/midi'
'midi' 'audio/midi'
'mif' 'application/x-mif'
'mm' 'application/x-freemind'
'mmd' 'chemical/x-macromodel-input'
'mmf' 'application/vnd.smaf'
'mml' 'text/mathml'
'mmod' 'chemical/x-macromodel-input'
'mng' 'video/x-mng'
'moc' 'text/x-moc'
'mol' 'chemical/x-mdl-molfile'
'mol2' 'chemical/x-mol2'
'moo' 'chemical/x-mopac-out'
'mop' 'chemical/x-mopac-input'
'mopcrt' 'chemical/x-mopac-input'
'mov' 'video/quicktime'
'movie' 'video/x-sgi-movie'
'mp2' 'audio/mpeg'
'mp3' 'audio/mpeg'
'mp4' 'video/mp4'
'mpc' 'chemical/x-mopac-input'
'mpe' 'video/mpeg'
'mpeg' 'video/mpeg'
'mpega' 'audio/mpeg'
'mpg' 'video/mpeg'
'mpga' 'audio/mpeg'
'ms' 'application/x-troff-ms'
'msh' 'model/mesh'
'msi' 'application/x-msi'
'mvb' 'chemical/x-mopac-vib'
'mxu' 'video/vnd.mpegurl'
'nb' 'application/mathematica'
'nc' 'application/x-netcdf'
'nwc' 'application/x-nwc'
'o' 'application/x-object'
'oda' 'application/oda'
'odb' 'application/vnd.oasis.opendocument.database'
'odc' 'application/vnd.oasis.opendocument.chart'
'odf' 'application/vnd.oasis.opendocument.formula'
'odg' 'application/vnd.oasis.opendocument.graphics'
'odi' 'application/vnd.oasis.opendocument.image'
'odm' 'application/vnd.oasis.opendocument.text-master'
'odp' 'application/vnd.oasis.opendocument.presentation'
'ods' 'application/vnd.oasis.opendocument.spreadsheet'
'odt' 'application/vnd.oasis.opendocument.text'
'ogg' 'application/ogg'
'old' 'application/x-trash'
'oth' 'application/vnd.oasis.opendocument.text-web'
'oza' 'application/x-oz-application'
'p' 'text/x-pascal'
'p7r' 'application/x-pkcs7-certreqresp'
'pac' 'application/x-ns-proxy-autoconfig'
'pas' 'text/x-pascal'
'pat' 'image/x-coreldrawpattern'
'pbm' 'image/x-portable-bitmap'
'pcf' 'application/x-font'
'pcf.Z' 'application/x-font'
'pcx' 'image/pcx'
'pdb' 'chemical/x-pdb'
'pdf' 'application/pdf'
'pfa' 'application/x-font'
'pfb' 'application/x-font'
'pgm' 'image/x-portable-graymap'
'pgn' 'application/x-chess-pgn'
'pgp' 'application/pgp-signature'
'pk' 'application/x-tex-pk'
'pl' 'text/x-perl'
'pls' 'audio/x-scpls'
'pm' 'text/x-perl'
'png' 'image/png'
'pnm' 'image/x-portable-anymap'
'pot' 'text/plain'
'ppm' 'image/x-portable-pixmap'
'pps' 'application/vnd.ms-powerpoint'
'ppt' 'application/vnd.ms-powerpoint'
'prf' 'application/pics-rules'
'prt' 'chemical/x-ncbi-asn1-ascii'
'ps' 'application/postscript'
'psd' 'image/x-photoshop'
'psp' 'text/x-psp'
'py' 'text/x-python'
'pyc' 'application/x-python-code'
'pyo' 'application/x-python-code'
'qt' 'video/quicktime'
'qtl' 'application/x-quicktimeplayer'
'ra' 'audio/x-realaudio'
'ram' 'audio/x-pn-realaudio'
'rar' 'application/rar'
'ras' 'image/x-cmu-raster'
'rd' 'chemical/x-mdl-rdfile'
'rdf' 'application/rdf+xml'
'rgb' 'image/x-rgb'
'rm' 'audio/x-pn-realaudio'
'roff' 'application/x-troff'
'ros' 'chemical/x-rosdal'
'rpm' 'application/x-redhat-package-manager'
'rss' 'application/rss+xml'
'rtf' 'text/rtf'
'rtx' 'text/richtext'
'rxn' 'chemical/x-mdl-rxnfile'
'sct' 'text/scriptlet'
'sd' 'chemical/x-mdl-sdfile'
'sd2' 'audio/x-sd2'
'sda' 'application/vnd.stardivision.draw'
'sdc' 'application/vnd.stardivision.calc'
'sdd' 'application/vnd.stardivision.impress'
'sdf' 'chemical/x-mdl-sdfile'
'sdp' 'application/vnd.stardivision.impress'
'sdw' 'application/vnd.stardivision.writer'
'ser' 'application/java-serialized-object'
'sgf' 'application/x-go-sgf'
'sgl' 'application/vnd.stardivision.writer-global'
'sh' 'text/x-sh'
'shar' 'application/x-shar'
'shtml' 'text/html'
'sid' 'audio/prs.sid'
'sik' 'application/x-trash'
'silo' 'model/mesh'
'sis' 'application/vnd.symbian.install'
'sit' 'application/x-stuffit'
'skd' 'application/x-koan'
'skm' 'application/x-koan'
'skp' 'application/x-koan'
'skt' 'application/x-koan'
'smf' 'application/vnd.stardivision.math'
'smi' 'application/smil'
'smil' 'application/smil'
'snd' 'audio/basic'
'spc' 'chemical/x-galactic-spc'
'spl' 'application/x-futuresplash'
'src' 'application/x-wais-source'
'stc' 'application/vnd.sun.xml.calc.template'
'std' 'application/vnd.sun.xml.draw.template'
'sti' 'application/vnd.sun.xml.impress.template'
'stl' 'application/vnd.ms-pki.stl'
'stw' 'application/vnd.sun.xml.writer.template'
'sty' 'text/x-tex'
'sv4cpio' 'application/x-sv4cpio'
'sv4crc' 'application/x-sv4crc'
'svg' 'image/svg+xml'
'svgz' 'image/svg+xml'
'sw' 'chemical/x-swissprot'
'swf' 'application/x-shockwave-flash'
'swfl' 'application/x-shockwave-flash'
'sxc' 'application/vnd.sun.xml.calc'
'sxd' 'application/vnd.sun.xml.draw'
'sxg' 'application/vnd.sun.xml.writer.global'
'sxi' 'application/vnd.sun.xml.impress'
'sxm' 'application/vnd.sun.xml.math'
'sxw' 'application/vnd.sun.xml.writer'
't' 'application/x-troff'
'tar' 'application/x-tar'
'taz' 'application/x-gtar'
'tcl' 'text/x-tcl'
'tex' 'text/x-tex'
'texi' 'application/x-texinfo'
'texinfo' 'application/x-texinfo'
'text' 'text/plain'
'tgf' 'chemical/x-mdl-tgf'
'tgz' 'application/x-gtar'
'tif' 'image/tiff'
'tiff' 'image/tiff'
'tk' 'text/x-tcl'
'tm' 'text/texmacs'
'torrent' 'application/x-bittorrent'
'tr' 'application/x-troff'
'ts' 'text/texmacs'
'tsp' 'application/dsptype'
'tsv' 'text/tab-separated-values'
'txt' 'text/plain'
'udeb' 'application/x-debian-package'
'uls' 'text/iuls'
'ustar' 'application/x-ustar'
'val' 'chemical/x-ncbi-asn1-binary'
'vcd' 'application/x-cdlink'
'vcf' 'text/x-vcard'
'vcs' 'text/x-vcalendar'
'vmd' 'chemical/x-vmd'
'vms' 'chemical/x-vamas-iso14976'
'vor' 'application/vnd.stardivision.writer'
'vrm' 'x-world/x-vrml'
'vrml' 'x-world/x-vrml'
'vsd' 'application/vnd.visio'
'wad' 'application/x-doom'
'wav' 'audio/x-wav'
'wax' 'audio/x-ms-wax'
'wbmp' 'image/vnd.wap.wbmp'
'wbxml' 'application/vnd.wap.wbxml'
'wk' 'application/x-123'
'wm' 'video/x-ms-wm'
'wma' 'audio/x-ms-wma'
'wmd' 'application/x-ms-wmd'
'wml' 'text/vnd.wap.wml'
'wmlc' 'application/vnd.wap.wmlc'
'wmls' 'text/vnd.wap.wmlscript'
'wmlsc' 'application/vnd.wap.wmlscriptc'
'wmv' 'video/x-ms-wmv'
'wmx' 'video/x-ms-wmx'
'wmz' 'application/x-ms-wmz'
'wp5' 'application/wordperfect5.1'
'wpd' 'application/wordperfect'
'wrl' 'x-world/x-vrml'
'wsc' 'text/scriptlet'
'wvx' 'video/x-ms-wvx'
'wz' 'application/x-wingz'
'xbm' 'image/x-xbitmap'
'xcf' 'application/x-xcf'
'xht' 'application/xhtml+xml'
'xhtml' 'application/xhtml+xml'
'xlb' 'application/vnd.ms-excel'
'xls' 'application/vnd.ms-excel'
'xlt' 'application/vnd.ms-excel'
'xml' 'application/xml'
'xpi' 'application/x-xpinstall'
'xpm' 'image/x-xpixmap'
'xsl' 'application/xml'
'xtel' 'chemical/x-xtel'
'xul' 'application/vnd.mozilla.xul+xml'
'xwd' 'image/x-xwindowdump'
'xyz' 'chemical/x-xyz'
'zip' 'application/zip'
'zmt' 'chemical/x-mopac-input'
'~' 'application/x-trash'
)
]
ILFileHandler class >> mimeTypeFor: aString [
<category: 'accessing'>
^self mimeTypes at: aString ifAbsent: [self defaultMimeType]
]
ILFileHandler class >> mimeTypes [
<category: 'accessing'>
MimeTypes ifNil: [self initMimeTypes].
^MimeTypes
]
ILFileHandler class >> directories [
<category: 'acccessing'>
^Directories ifNil: [Directories := OrderedCollection new]
]
ILFileHandler class >> directories: aCollection [
<category: 'accessing'>
Directories := aCollection
]
ILFileHandler class >> addDirectory: aDirectory [
<category: 'accessing'>
self directories add: aDirectory
]
ILFileHandler class >> initMimeTypes [
<category: 'defaults'>
MimeTypes := Dictionary new.
1 to: self defaultMimeTypes size by: 2 do: [:index |
MimeTypes
at: (self defaultMimeTypes at: index)
put: (self defaultMimeTypes at: index + 1)]
]
ILFileHandler class >> isBinary: aFilename [
<category: 'testing'>
| tokens type |
tokens := (ILFileHandler mimeTypeFor: (aFilename copyAfterLast: $.)) subStrings: '/'.
type := tokens first.
type = 'text' ifTrue: [^false].
type = 'application' ifFalse: [^true].
tokens size = 1 ifTrue: [^true].
^(tokens second subStrings: '+') noneSatisfy: [:each |
#('x-javascript' 'xml') includes: each]
]
directories [
<category: 'accessing'>
^self class directories
]
mimeTypeFor: aFilename [
<category: 'accessing'>
^self class mimeTypeFor: (aFilename copyAfterLast: $.)
]
newResponse [
<category: 'accessing'>
^ILResponse ok
]
handleRequest [
<category: 'request handling'>
file := self fileContentsFor: self request url greaseString.
file isNil ifTrue: [
ILDispatchError signal].
super handleRequest
]
produceResponse [
<category: 'responding'>
self respond: [:response || stream |
stream := file readStream.
[response nextPutAll: stream contents]
ensure: [stream close].
response contentType: (self mimeTypeFor: self request url greaseString).
self addAllowHeaderTo: response.
self addCacheHeaderTo: response]
]
fileContentsFor: aFileName [
"Try to find a file with <aFileName> in one of the directories"
<category: 'private'>
aFileName isEmpty ifTrue: [^nil].
self directories do: [:each || fileContents |
fileContents := (each fileContentsFor: aFileName).
(fileContents notNil) ifTrue: [^fileContents]].
^nil
]
]

View File

@ -0,0 +1,117 @@
"======================================================================
|
| Iliad.ILJsonHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILRequestHandler subclass: ILJsonHandler [
| jsonContents widgets scripts head |
<comment: nil>
<category: 'Iliad-Core-RequestHandlers'>
initialize [
<category: 'initialization'>
super initialize.
jsonContents := Dictionary new.
head := OrderedCollection new.
widgets := Dictionary new
]
produceResponse [
<category: 'responding'>
self respond: [:response |
self shouldRedirect
ifTrue: [
jsonContents
at: 'redirect'
put: self session redirectUrl greaseString]
ifFalse: [
self shouldUpdateApplication
ifFalse: [
self updateHead.
self updateWidgets]
ifTrue: [self updateApplication]].
response nextPutAll: (String streamContents: [:stream |
jsonContents printJsonOn: stream]).
self session clearRedirectUrl.
self addNoCacheHeaderTo: response]
]
shouldRedirect [
<category: 'testing'>
^self session redirectUrl notNil
]
shouldUpdateApplication [
<category: 'testing'>
^self request hashLocationField notNil and: [
self request actionField isNil]
]
newResponse [
<category: 'private'>
^ILResponse ok
contentType: 'application/json';
yourself
]
updateHead [
<category: 'private'>
| headElement |
headElement := ILElement new.
self session dirtyWidgets do: [:each | each buildHead: headElement].
headElement childrenDo: [:each |
(self application page head children includes: each) ifFalse: [
head add: each]].
jsonContents at: 'head' put: head
]
updateWidgets [
<category: 'private'>
self session dirtyWidgets do: [:each || e |
e := each build.
widgets at: each id put: e].
jsonContents
at: 'widgets' put: widgets
]
updateApplication [
<category: 'private'>
jsonContents
at: 'application'
put: self application build
]
]

View File

@ -0,0 +1,130 @@
ILDirectory subclass: ILMemoryDirectory [
<category: 'Iliad-Core-RequestHandlers'>
<comment: nil>
ILMemoryDirectory class [
addAllFilesIn: aPathString [
<category: 'maintenance'>
"adds all files in the directory specified by aPathString to the current file library"
(Grease.GRPlatform current filesIn: aPathString) do: [:each | self addFileAt: each]
]
addFileAt: aPath [
<category: 'maintenance'>
"adds the file specified by aFilename to the current file library"
self
addFileAt: aPath
contents: (Grease.GRPlatform current
contentsOfFile: aPath
binary: (ILFileHandler isBinary: aPath))
]
addFileAt: aPath contents: aByteArrayOrString [
<category: 'private'>
self
addFileNamed: (Grease.GRPlatform current localNameOf: aPath)
contents: aByteArrayOrString
]
addFileNamed: aFilename contents: aByteArrayOrString [
<category: 'private'>
| selector |
selector := self convertToSelector: aFilename.
(ILFileHandler isBinary: aFilename)
ifTrue: [self compileBinary: aByteArrayOrString selector: selector]
ifFalse: [self compileText: aByteArrayOrString selector: selector]
]
compileText: aByteArrayOrString selector: aSymbol [
"Compiles aByteArrayOrString into a method named aSymbol that returns aByteArrayOrString as a string literal."
<category: 'private'>
Grease.GRPlatform current
compile: (Grease.GRPlatform current asMethodReturningString: aByteArrayOrString named: aSymbol)
into: self
classified: self methodCategory
]
compileBinary: aByteArrayOrString selector: aSymbol [
"Compiles aByteArrayOrString into a method named aSymbol that returns aByteArrayOrString as a string literal."
<category: 'private'>
Grease.GRPlatform current
compile: (Grease.GRPlatform current asMethodReturningByteArray: aByteArrayOrString named: aSymbol)
into: self
classified: 'files'
]
convertToSelector: aString [
<category: 'private'>
| mainPart extension |
mainPart := (aString copyUpToLast: $.)
reject: [:each | each isAlphaNumeric not].
mainPart isEmpty not ifTrue: [
[mainPart first isDigit]
whileTrue: [mainPart := mainPart allButFirst]].
extension := (aString copyAfterLast: $.) asLowercase capitalized.
^(mainPart , extension) asSymbol
]
]
fileContentsFor: aString [
<category: 'accessing'>
| fileSelector |
fileSelector := self convertToSelector: (self adjustPath: aString).
(self isFileSelector: fileSelector) ifFalse: [^nil].
^(self perform: fileSelector)
]
path [
"answer the base path of the memory directory"
<category: 'accessing'>
^self subclassResponsibility
]
fileSelectors [
<category: 'accessing'>
^self class selectors select: [:each |
self isFileSelector: each]
]
isFileSelector: aSelector [
"Only methods in 'files' protocol are allowed to be served as files"
<category: 'testing'>
^(self class whichCategoryIncludesSelector: aSelector) = 'files'
]
adjustPath: aString [
<category: 'private'>
^aString copyReplacingRegex: '^\/', self path, '\/' with: ''
]
convertToSelector: aString [
<category: 'private'>
^self class convertToSelector: aString
]
removeFile: aFilename [
<category: 'maintenence'>
Grease.GRPlatform current
removeSelector: (self asSelector: aFilename)
from: self class
]
deployFiles [
"Write to disk the files that the receiver use to serve as methods.
The files are stored in a subfolder named like the classname of the receiver in a subfolder of Smalltalk image folder."
<category: 'maintenence'>
Grease.GRPlatform current ensureExistenceOfFolder: self path.
self fileSelectors do: [:each |
Grease.GRPlatform current
write: (self perform: each)
toFile: (self asFilename: each)
inFolder: self path]
]
]

View File

@ -0,0 +1,57 @@
"======================================================================
|
| Iliad.ILNotFoundHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILRequestHandler subclass: ILNotFoundHandler [
<comment: nil>
<category: 'Iliad-Core-RequestHandlers'>
produceResponse [
<category: 'responding'>
self respond: [:response |
response
nextPutAll: '<h1>404 Not Found: ';
nextPutAll: self request url greaseString;
nextPutAll: '</h1>']
]
newResponse [
<category: 'private'>
^ILResponse notFound
]
]

View File

@ -0,0 +1,70 @@
"======================================================================
|
| Iliad.ILRedirectHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILRequestHandler subclass: ILRedirectHandler [
<comment: nil>
<category: 'Iliad-Core-RequestHandlers'>
produceResponse [
<category: 'responding'>
self setRedirectUrl.
self shouldRespondInJson ifTrue: [
ILJsonHandler new handleRequest].
self respond: [:response |
response redirectTo: self session redirectUrl greaseString.
self session clearRedirectUrl.
self addCookieHeaderTo: response]
]
shouldRespondInJson [
<category: 'testing'>
^self request isTypeOfRequestForJson
]
setRedirectUrl [
<category: 'private'>
self session redirectUrl ifNil: [
self session redirectUrl: self context baseUrl greaseString]
]
newResponse [
<category: 'private'>
^ILResponse redirect
]
]

View File

@ -0,0 +1,107 @@
"======================================================================
|
| Iliad.ILRequestHandler class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2008-2010
| 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.
|
======================================================================"
ILObject subclass: ILRequestHandler [
<category: 'Iliad-Core-RequestHandlers'>
<comment: 'I implement the basic behavior needed to handle requests.
My sublcasses must override #newResponse to handle requests, and most likely #produceResponse.
The current handled request is answered by the #request method inherited from ILObject'>
handleRequest [
<category: 'request handling'>
self produceResponse
]
produceResponse [
<category: 'responding'>
self respond: [:response | ]
]
respond: aBlock [
<category: 'private'>
| response |
response := self newResponse.
aBlock value: response.
self returnResponse: response
]
returnResponse: aResponse [
<category: 'private'>
ILResponseNotification new
response: aResponse;
signal
]
newResponse [
<category: 'private'>
self subclassResponsibility
]
addCacheHeaderTo: aResponse [
<category: 'private'>
aResponse
headerAt: 'expires'
put: ((Grease.GRPrinter rfc822WithTimeZone: 'GMT')
print: (DateTime fromSeconds: DateTime now asSeconds + (24*3600*365)))
]
addAllowHeaderTo: aResponse [
<category: 'private'>
| methods |
methods := 'OPTIONS,GET,HEAD,POST,DELETE,TRACE,PROPFIND,PROPPATCH,MKCOL,PUT,COPY,MOVE,LOCK,UNLOCK'.
aResponse headerAt: 'Allow' put: methods
]
addCookieHeaderTo: aResponse [
<category: 'private'>
aResponse
addCookie: (ILCookie new
key: self session sessionManager cookieName;
value: self session id;
expireIn: (Duration days: 600);
yourself)
]
addNoCacheHeaderTo: aResponse [
aResponse
headerAt: 'expires'
put: ((Grease.GRPrinter rfc822WithTimeZone: 'GMT') print: DateTime now).
aResponse headerAt: 'Cache-Control' put: 'no-store, no-cache, must-revalidate'
]
]

Some files were not shown because too many files have changed in this diff Show More