Login

A Simple File Based Wiki in Seaside

There can never be enough simple sample apps to help beginners learn Seaside. In that spirit, here's a simple file based Wiki written in pure Seaside (i.e. no Magritte and not overly abstracted to the point you can't figure out what's going on).

It has bookmarkable URLs, uses regex (regex package found on SqueakSource) to make WikiWords into links, keeps line breaks, and accepts raw HTML. Pages are stored on the file system under your image directory based upon the app name.

For a production quality Wiki, use Pier, this one is super simple and only intended for learning. It was written in about two hours (not counting some changes made during the writing of this article) as a single Seaside component.

OK, here we go, broken up into code sections by method category, first declare the class...

WAComponent subclass: #WikiPage
    instanceVariableNames: 'isEditing currentContent currentPage'
    classVariableNames: ''
    poolDictionaries: ''
    category: 'SimpleFileWiki'

Setup the app on the class side...

canBeRoot
    ^ true  

initialize
    self registerAsApplication: #wiki   

Initialize instances of the class...

initialize
    super initialize.
    currentPage := ''.
    isEditing := false

Create some accessing methods we'll need...

currentContent
    ^ currentContent ifNil: [currentContent := '']

currentContent: aString 
    currentContent := aString   

style
    ^ ' textarea {width:90%;height:500px;}' 

Then some fancier accessors that ensure our file system is setup and reads pages from it...

pageDirectory
    ^ (FileDirectory default 
        directoryNamed: self session application name , #Pages) assureExistence 

pageAt: aPage 
    isEditing := (self pageExists: aPage) not.
    isEditing ifTrue: [^ ''].
    ^ FileStream readOnlyFileNamed: (self pageDirectory fullNameFor: aPage)
        do: [:file | file contentsOfEntireFile]

If a page doesn't exist, the Wiki kicks into editing mode to create it. A testing method use by the above...

pageExists: match 
    ^ self pageDirectory fileExists: match  

A couple of actions (our controller methods)...

loadPage: aPage 
    isEditing := false.
    currentPage := aPage.
    self currentContent: (self pageAt: aPage)   

savePage
    self currentContent 
        ifEmpty: 
            [ (self pageExists: currentPage) ifTrue: 
                [ self pageDirectory deleteFileNamed: currentPage.
                self loadPage: #FrontPage ] ]
        ifNotEmpty: 
            [ FileStream 
                forceNewFileNamed: (self pageDirectory fullNameFor: currentPage)
                do: [ :file | file nextPutAll: self currentContent ].
            isEditing := false ]    

cancel
    isEditing := false

Deleting the contents of a page, deletes the page as well.

Now we're ready for rendering. Let's start with page title in the head...

updateRoot: aRoot 
    super updateRoot: aRoot.
    aRoot title: currentPage    

And setting up the url...

updateUrl: aUrl 
    super updateUrl: aUrl.
    aUrl addToPath: currentPage withFirstCharacterDownshifted   

Now that the URL looks valid, lets make it work by parsing new requests, those that don't include the session key (s) or includes an expired session key. Once the session key and the continuation key (k) are present, the URL is no longer necessary and will be ignored. Should this URL be bookmarked and returned to later, after the session has expired, #initialRequest: will be invoked, a new session started, and the correct page served...

initialRequest: aRequest 
    | page url |
    url := aRequest url stringAfter: self application basePath.
    page := (url beginsWith: '/') 
        ifTrue: [ url allButFirst copyAfterLast: $/ ]
        ifFalse: [ url copyAfterLast: $/ ].
    self loadPage: (page ifEmpty: [ 'FrontPage' ] ifNotEmpty: [ page ])

This uses an extension method #stringAfter that I have loaded in all my images, and it relies on another #split that is also in my images. Here they are...

String>>stringAfter: aDelim 
    | list |
    list := self split: aDelim.
    ^ list isEmpty ifTrue: [self] ifFalse: [list last withBlanksTrimmed]

String>>split: aString 
    | index lastIndex |
    index := lastIndex := 1.
    ^ Array streamContents: 
            [:stream | 
            [index <= self size] whileTrue: 
                    [index := self findString: aString startingAt: lastIndex.
                    index = 0 ifTrue: [index := self size + 1].
                    stream nextPut: (self copyFrom: lastIndex to: index - 1).
                    lastIndex := index + aString size]]

Now our main render method which decides which mode the Wiki is in...

renderContentOn: html 
    isEditing 
        ifTrue: [self renderEditorOn: html]
        ifFalse: [self renderViewerOn: html]    

And either edits the Wiki page...

renderEditorOn: html 
    (html heading)
        level1;
        with: ((self pageExists: currentPage) 
                    ifFalse: ['Page ' , currentPage , ' hasn''t been created yet, go for it!']
                    ifTrue: ['Editing ' , currentPage]).
    html form: 
            [html textArea on: #currentContent of: self.
            html break.
            html submitButton on: #savePage of: self.
            html text: ' or '.
            html anchor on: #cancel of: self]

Or renders the viewer which also parses the text for WikiWords and line breaks...

renderViewerOn: html 
    self withLineBreaks: (self currentContent 
                copyWithRegex: '[A-Z][a-z]+([A-Z][a-z]+)+'
                matchesTranslatedUsing: 
                    [:match | 
                    (self pageExists: match) 
                        ifTrue: ['<a href="' , (html urlForAction: [self loadPage: match]) displayString, '">', match , '</a>']
                        ifFalse: [match , '<a href="' , (html urlForAction: [self loadPage: match]) displayString, '">?</a>']])
        on: html.
    html paragraph: 
            [(html anchor)
                callback: [isEditing := true];
                text: 'Edit'.
            html space.
            (html anchor)
                callback: [self loadPage: #FrontPage];
                text: 'FrontPage']  

The editor and viewer could have been separate components, but I'm going for simple here, one class. And finally, the method for breaking lines...

withLineBreaks: aString on: html 
    | stream |
    stream := aString readStream.
    [stream atEnd] whileFalse: 
            [html html: stream nextLine.
            stream atEnd ifFalse: [html break]] 

And there we have it, a simple file based Wiki that covers quite a few things you'd want to do in a web app and should be easily digestible for the Seaside beginner. There are probably bugs, I didn't do a ton of testing and its only intended use is this blog post.

According to the message "WikiPage linesOfCode", that's 90 lines of code total (and that's including the HTML and CSS). Here's a file out of the code for anyone interested. Make sure to manually add the two extension methods to String for this to work.

Comments (automatically disabled after 1 year)

Miguel Cobá] 6050 days ago

I have the following error accesing http://localhost:8080/seaside/wiki

MessageNotUnderstood: ByteString>>stringAfter:

I have pulled Regex-sd from squeaksource but I can't find the implementation of stringAfter: nowhere in my image.

It is a custom method you created?

Ramon Leon 6050 days ago

Sorry, I didn't notice that #stringAfter: was one of my extensions to String, they're now included in the article. Thanks for catching that.

Miguel Cobá] 6050 days ago

One more thing. the message urlForAction is from class WAHtmlRenderer but in my Seaside 2.7a1-pc227, the object html is an instance of WARenderCanvas which doesn't respond to this message. It gives me the following error:

WARenderCanvas(Object)>>doesNotUnderstand: #urlForAction:

Is there some equivalent code from WARenderCanvas?

Ramon Leon 6050 days ago

This was written in Seaside 2.8, but it looks like the same code in both, just copy it into the WARenderCanvas and it should work. Here's mine...

urlForAction: aBlock
    ^ self context actionUrl withParameter: (self callbacks registerActionCallback: aBlock)
Miguel Cobá] 6050 days ago

It works now. Thank you. Excellent tutorial

[...] puts up a wiki example for Seaside Ramon Leon at On Smalltalk posted a tutorial wiki app. in Seaside. Give it a [...] ]

[...] Ramon Leon’s blog, always a great resource for tips on Squeak and Seaside, has a nice post on how to build a simple file-based wiki using Seaside using only one class and 98 lines of code. It’s intended as a learning tool, so it [...] ]

[...] Leon escribió un post detallando la construcción de un Wiki básico usando Seaside. [...] ]]>

[...] wrote an interesting post today on A Simple File Based Wiki in SeasideHere’s a quick [...]

Bill 6041 days ago

Great example!

"Initialize the class" should be "initialize objects/instances of the class" ?

Ramon Leon 6039 days ago

Ah, good catch, fixed! Thanks!

[...] le Wiki en 98 lignes écrit par Ramon Leon, voila une nouvelle application-jouet Seaside, une liste de choses à faire [...] ]]>

jared 5873 days ago

Thanks a lot for putting this on the web. It's the first useful Seaside coding example I've run across. It's actually up to date, gives good hints for a smalltalk beginner (who'd think that the phrase "setup the app on the class side" would be a crucial reminder?), and it's short enough that I can wrap my head around it. (Really short! All the good stuff Alan Kay's been advertising is true!)

Now that I'm getting comfortable with the system browser, I don't know how I'm going to go back to writing php in vim...

Ramon Leon 5872 days ago

You're welcome.

Justin 5827 days ago

Hey Ramon,

I'm trying to follow your tutorial but keep coming up with a InvalidDirectoryError [see below]; sorry to bother but was wondering if you knew how it might be arising ? Was wondering if it was some problem with relative vs absolute path names ? The wikiPages directory is getting created fine btw. I am a Rails guy trying to see what all the fuss is re Seaside, so any help would be mucho appreciated.

Many thanks,

Justin

Ramon Leon 5827 days ago

OK, there was a bug in the #initialRequest: method concerning the trailing / on the root page, I fixed it, updated the article and the fileOut at the end with the new code. Should work fine now.

[...] le Wiki en 98 lignes écrit par Ramon Leon, voila une nouvelle application-jouet Seaside, une liste de choses à faire [...] ]]

about me|good books|popular posts|atom|rss