Login

Ajax: How to Build Cascading Dialogs in Seaside with Scriptaculous

Cascading dialogs are a common thing web developers want to do. This is often a major pain in traditional web frameworks. Seaside and Scriptaculous make this a trivial task without posting back the form or pre-loading all the data at the client.

Let's build a simple component to demonstrate this. First, we need some data to put in these drop downs, lets play with Smalltalk reflection and use all the subclasses of WAComponent, and all their categories as our data sources.

For the first drop down list, the categories. We collect all the categories from all the subclasses, flush out the dupes by sending asSet. Since categories are just strings, we can sort them alphabetically by sending asSortedCollection.

componentCategories
    ^(WAComponent allSubclasses collect: [:each | each category])
        asSet asSortedCollection

Now, we'll need to store the currently selected category, so we create accessors for that...

currentCategory
    ^currentCategory

currentCategory: aCategory
    currentCategory := aCategory

Now we'll need a list of all the components in the currently selected category for the second drop down list...

components
    ^(WAComponent allSubclasses
        select: [:each | each category = self currentCategory])
            asSortedCollection: [:a :b | a name < b name]

So we select matching classes, and then alphabetize them with a sort block on the classes name. We'll also want to store the current component, so we'll create accessors for that as well...

currentComponent
    ^currentComponent

currentComponent: aComponent
    currentComponent := aComponent

OK, this gives us a model capable of having a currentCategory, currentComponent, and the data sources necessary for rendering the UI. Ordinarily you'd be getting this data from a database or something, but the Smalltalk class hierarchy will do for demonstration purposes. Now let's render the Seaside UI, which will consist of the following three methods. I like to factor down to very small methods, this comes in handy when you start wanting to re-render small parts of a page.

renderContentOn: html 
    super renderContentOn: html.
    html form: [self renderCategoriesOn: html]

renderCategoriesOn: html 
    (html select)
        id: #theCategory;
        list: self componentCategories;
        onChange: ((html updater)
                id: #theComponents;
                triggerFormElement: #theCategory;
                on: #renderComponentsOn: of: self);
        on: #currentCategory of: self.
    (html span)
        id: #theComponents;
        with: [self renderComponentsOn: html]

renderComponentsOn: html
    (html select)
        list: self components;
        on: #currentComponent of: self

That's it, we've rendered the form, the category list, bound it to the componentCategories we created earlier. Hooked an updater to the #onChange: event to make it re-render the contents of the span named #theComponents, which is the second drop down list.

The second list has its own render method, so that it can be rendered by itself, a necessity for binding the updater to it, and we simply call that method in the initial rendering when we first render the span that contains it. Now whenever the selected item changes, an Ajax callback is invoked, and the contents of the span are replaced with a re-rendered list after it updates the currentCategory.

If you tossed in a submit button, you could then post the form and do something useful with the data, but I'll leave that as an exercise for the reader. One last thing to note, we didn't write a lick of Javascript, it was all done in pure Smalltalk.

Comments (automatically disabled after 1 year)

Lidell 6366 days ago

This is really good stuff, the type of short and sweet recipe, that one can assemble for a Smalltlak cookbook.

One small favor though: Can you start at the very beginning,and describe the basic Seaside concepts and how they interact: What's a WAComponent, a Rendered, a WARenderCanvas, etc, and how do these pieces wotk together? Stuff like this should be in the tutorials, ut I still do't find the explanations clear.

Ramon Leon 6366 days ago

Absolutely, coming soon...

Carl Gundel 6348 days ago

This is great, but I have a question. I have a form that has a text area and also a checkbox (or it could just be an anchor) for hiding and showing the text area, and also a submit button for the form. I'd like the user to be able to type something into the text area and then before being ready to click the submit button to click on the checkbox and hide the text area (to have more space to work on something else). Then once the user is ready to do some more work in the text area he can click on the checkbox again and the text area reappears containing the same contents it did when it was hidden.

Can Scriptaculous help me to do this?

Ramon Leon 6348 days ago

Sure, simple, try something like this

html form: 
    [(html checkbox)
        on: #checked of: self;
        onChange: (html element id: #textAreaContainer; toggle).

    (html div)
        id: #textAreaContainer;
        with: [html textArea on: #someField of: self].

    self checked ifTrue: 
        [html script: ((html element) id: #textAreaContainer; hide)].

    html submitButton]
about me|good books|popular posts|atom|rss