"====================================================================== | | Iliad.ILApplication class definition | ======================================================================" "====================================================================== | | Copyright (c) 2008-2010 | Nicolas Petton , | Sébastien Audier | | 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 | 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" ^'' ] absolutePath [ ^String streamContents: [:stream | (self path startsWith: '/') ifFalse: [stream nextPut: $/]. stream nextPutAll: self path] ] selectorFilter [ ^selectorFilter ifNil: [self defaultSelectorFilter] ] selectorFilter: aBlock [ selectorFilter := aBlock ] defaultSelectorFilter [ "Override this method to supply your own selectorFilter or plug it in using #selectorFilter:" ^[:selector | (self canUnderstand: selector) and: [ (self categoryOfElement: selector inClassOrSuperclass: self) = 'controllers']] ] categoryOfElement: aSelector inClassOrSuperclass: aClass [ "Find the first category of up the superclass chain." ^aClass ifNotNil: [ ^(aClass whichCategoryIncludesSelector: aSelector) ifNil: [ self categoryOfElement: aSelector inClassOrSuperclass: aClass superclass]] ] ] model [ ^model ] model: anObject [ model := anObject ] page [ ^page ] selectorFilter [ ^self class selectorFilter ] widgetFor: aBuildable [ "Convenience method. This is useful for building anonymous widgets. ex: myWidget := self widgetFor: [:e | e h1: 'Hello world!']" ^ILPluggableWidget new contentsBlock: aBuildable; yourself ] buildContents [ "Call #dispatch. A buildable is expected from #dispatch" ^self newRootElement build: self dispatch; yourself ] allowedSelector: aSelector [ "Answer true if is ok to call from a URL. Default implementation is to use the pluggable filter block." ^self selectorFilter copy value: aSelector ] dispatch [ "Dispatch to correct controller method. If dispatchOverride returns something different from nil, consider it handled." ^self dispatchOverride ifNil: [ self dispatchOn: self router controller] ] dispatchOn: aMethod [ "Dispatch to correct method: - If is empty we call #index - If the selector is allowed to be executed then we just call it" | 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." ^nil ] updatePage: aPage [ "Override to add elements to aPage. super should always be called" aPage head javascript src: '/javascripts/jquery-1.8.3.min.js'. aPage head javascript src: '/javascripts/no_conflict.js'. aPage head javascript src: '/javascripts/iliad.js'. ] updateFromRoute: aRoute [ "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 [ "Update the base url used for the current context" ] respond: aBlock [ "Abort all other request handling" | response | response := ILResponse new. aBlock value: response. self returnResponse: response ] returnResponse: aResponse [ "Abort all other request handling" ILResponseNotification new response: aResponse; signal ] index [ "default view method" ^[:e | ] ] respondOn: aResponse [ page := self defaultPageClass new. page body build: self. self updatePage: page. self context builtWidgets do: [:each | each buildHead: page head]. page respondOn: aResponse ] defaultPageClass [ ^ILHTMLPage ] rootElementClass [ ^ILHTMLBuilderElement ] newRootElement [ ^self rootElementClass new ] ]