'From Squeak3.9.1 of 2 March 2008 [latest update: #7075] on 6 May 2008 at 8:16:37 pm'!
WAComponent subclass: #WikiPage
instanceVariableNames: 'isEditing currentContent currentPage'
classVariableNames: ''
poolDictionaries: ''
category: 'SimpleFileWiki'!
!WikiPage methodsFor: 'accessing' stamp: 'rjl 9/25/2007 19:29'!
currentContent
^ currentContent ifNil: [currentContent := '']! !
!WikiPage methodsFor: 'accessing' stamp: 'rjl 9/25/2007 19:30'!
currentContent: aString
currentContent := aString! !
!WikiPage methodsFor: 'accessing' stamp: 'rjl 5/6/2008 20:15'!
pageAt: aPage
isEditing := (self pageExists: aPage) not.
isEditing ifTrue: [ ^ '' ].
^ FileStream
readOnlyFileNamed: (self pageDirectory fullNameFor: aPage)
do: [ :file | file contentsOfEntireFile ]! !
!WikiPage methodsFor: 'accessing' stamp: 'rjl 5/6/2008 20:15'!
pageDirectory
^ (FileDirectory default directoryNamed: self session application name , #Pages) assureExistence! !
!WikiPage methodsFor: 'accessing' stamp: 'rjl 10/17/2007 20:22'!
style
^ 'textarea {width:90%;height:500px;}'! !
!WikiPage methodsFor: 'actions' stamp: 'rjl 10/17/2007 20:56'!
cancel
isEditing := false! !
!WikiPage methodsFor: 'actions' stamp: 'rjl 9/25/2007 19:53'!
loadPage: aPage
isEditing := false.
currentPage := aPage.
self currentContent: (self pageAt: aPage)! !
!WikiPage methodsFor: 'actions' stamp: 'rjl 5/6/2008 20:15'!
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 ]! !
!WikiPage methodsFor: 'initialize-release' stamp: 'rjl 9/25/2007 19:31'!
initialize
super initialize.
currentPage := ''.
isEditing := false! !
!WikiPage methodsFor: 'rendering' stamp: 'rjl 9/25/2007 18:04'!
renderContentOn: html
isEditing
ifTrue: [self renderEditorOn: html]
ifFalse: [self renderViewerOn: html ]! !
!WikiPage methodsFor: 'rendering' stamp: 'rjl 10/17/2007 20:57'!
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]! !
!WikiPage methodsFor: 'rendering' stamp: 'rjl 10/17/2007 20:23'!
renderViewerOn: html
self withLineBreaks: (self currentContent
copyWithRegex: '[A-Z][a-z]+([A-Z][a-z]+)+'
matchesTranslatedUsing:
[:match |
(self pageExists: match)
ifTrue: ['' , match , '']
ifFalse: [match , '?']])
on: html.
html paragraph:
[(html anchor)
callback: [isEditing := true];
text: 'Edit'.
html space.
(html anchor)
callback: [self loadPage: #FrontPage];
text: 'FrontPage']! !
!WikiPage methodsFor: 'rendering' stamp: 'rjl 10/17/2007 20:23'!
withLineBreaks: aString on: html
| stream |
stream := aString readStream.
[stream atEnd] whileFalse:
[html html: stream nextLine.
stream atEnd ifFalse: [html break]]! !
!WikiPage methodsFor: 'request processing' stamp: 'rjl 5/6/2008 20:11'!
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 ])! !
!WikiPage methodsFor: 'testing' stamp: 'rjl 9/25/2007 19:43'!
pageExists: match
^ self pageDirectory fileExists: match! !
!WikiPage methodsFor: 'updating' stamp: 'rjl 9/25/2007 19:55'!
updateRoot: aRoot
super updateRoot: aRoot.
aRoot title: currentPage ! !
!WikiPage methodsFor: 'updating' stamp: 'rjl 9/25/2007 19:55'!
updateUrl: aUrl
super updateUrl: aUrl.
aUrl addToPath: currentPage withFirstCharacterDownshifted ! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
WikiPage class
instanceVariableNames: ''!
!WikiPage class methodsFor: 'testing' stamp: 'rjl 9/25/2007 16:58'!
canBeRoot
^true! !
!WikiPage class methodsFor: 'class initialization' stamp: 'rjl 9/25/2007 16:58'!
initialize
"self initialize"
self registerAsApplication: #wiki! !
WikiPage initialize!