Smallwiki Conversion Code

For the operational wiki, the setup is:

  • Root page - named Amdocs
    • Child page name Admin - containing Smallwiki specific commands
    • Child page name Champaign
      • OP Team page
      • Web team page
      • Dev team page
      • ... other teams ...

For the class SWUser, a password accessor had to be added, as well as the following:

  • Add a helper function to print the shorter path:

    SWStructure>>pathOfTitlesForPier
          "Return a wiki path based on the idea that the '/' would be removed"
          ^ self parents size >= 2
                  ifTrue: [self parents removeFirst; removeLast;
                                  inject: '/'
                                  into: [:output :structure | output , structure title , '/']]
                  ifFalse: [^ '/']

  • Change the path:

    SWVisitorRendererWiki>>acceptLinkInternal: aLink
          "Smallwiki is a little more leinient in the way links are created, for example:
                  root: This is the page at http://localhost:9090/ - Links to this are */*
                          parentFolder: links can be *childFolder* *childPage* *childFolder/childChildFolder*; or */parentFolder/childFolder* ...
                                  childFolder: links can be *childPage* *childchildFolder* */parentFolder*; or */parentFolder/childFolder* ...
                                          childChildFolder: Links must be absolute path, like */parentFolder/childFolder*
                                  childPage: links can be *childPage* *childFolder*"
          | linkTokens page folder |
          (JohnDebug isNil or: [aLink isBroken and: [JohnDebug isComposite]])
                  ifTrue: [^ self acceptLink: aLink].
          linkTokens := aLink reference findTokens: $/.
          self nextPut: $*.
          aLink text isNil
                  ifFalse: [self nextPutAll: aLink text;
                                   nextPut: $>].
          aLink isBroken ifTrue: [^ self nextPutAll: '../'; nextPutAll: aLink reference; nextPut: $*].
          aLink reference = '/'
                  ifTrue: [2
                                  to: JohnDebug parents size
                                  do: [:ndx | self nextPutAll: '../'].
                          ^ self nextPut: $*].
          aLink reference isEmpty ifTrue: [^ self nextPutAll: './*'].
          (aLink reference first = $/
                          and: [(page := JohnDebug root resolveTo: aLink reference) notNil])
                  ifTrue: ["Absolute Reference"
                          page parents removeFirst;
                                  do: [:parent | self nextPut: $/;
                                                   nextPutAll: parent title].
                          self nextPut: $*]
                  ifFalse: ["Relative Link"
                          folder := JohnDebug.
                          (JohnDebug isComposite
                                          and: [(JohnDebug at: linkTokens first) notNil])
                                  ifFalse: [self nextPutAll: '../'.
                                          folder := JohnDebug parent].
                          linkTokens
                                  do: [:pageName | self nextPutAll: (folder at: pageName) title.
                                          folder := folder at: pageName]
                                  separatedBy: [self nextPut: $/].
                          self nextPut: $*]

  • Wiki users may put absolute links on the web pages, the following correct those that point back to the wiki. This code has hard-coded machine names, other sites will need to change the machine named cmidashboard.

    SWVisitorRendererWiki>>acceptLinkExternal: aLinkExternal
          | page linkReference |
          (JohnDebug isNil
                          or: [(aLinkExternal reference includes: $#)
                                          or: [('http://cmidashboard:9090/*' match: aLinkExternal reference) not
                                                          or: [(JohnDebug root resolveTo: (linkReference := aLinkExternal reference copyFrom: 'http://cmidashboard:9090/' size to: aLinkExternal reference size)) isNil]]])
                  ifTrue: [^ super acceptLinkExternal: aLinkExternal].
          self nextPut: $*.
          aLinkExternal text isNil
                  ifFalse: [self nextPutAll: aLinkExternal text;
                                   nextPut: $>].
          page := JohnDebug root resolveTo: linkReference.
          page parents size < 2 ifTrue: [^ self nextPutAll: '/*'].
          page parents removeFirst;
                  do: [:parent | self nextPut: $/;
                                   nextPutAll: parent title].
          self nextPut: $*

  • For Smallwiki, each new line starts a new paragraph, for Pier, it is assumed that there will be an empty line between paragraphs. The following adds the empty line:

    SWVisitorRendererWiki>>acceptParagraph: aParagraph
          self cr.
          self visitCollection: aParagraph children.
          JohnDebug isNil
                  ifFalse: [(aParagraph ~= JohnDebug document children last
                                          and: [(JohnDebug document children
                                                          after: aParagraph
                                                          ifAbsent: []) class = aParagraph class])
                                  ifTrue: [self cr]]

  • From an inspector on the SWKom for the Smallwiki, add the following. When this code is executed, it will create a file wiki.test.st in the current working directory that contains doits for adding the wiki pages (it is a little hard to follow):

    | stream filename dir |
    filename := 'wiki.test.st'.
    #('/Champaign') do: [:path |
    stream := nil.
    JohnDebug := nil.
    [((dir := FileDirectory default) fileExists: filename)
     ifTrue: [stream := dir oldFileNamed: filename]
     ifFalse: [stream := dir newFileNamed: filename.
       stream nextPutAll: '| aKernel |
    aKernel := (PRKernel allInstances reject: [:e | e root name = ''root'']) detect: [:e | e name = ''pier'' or: [e name = ''Pier'']].
    Smalltalk at: #CreateAPageBlock put: [:path :owner :timeStamp :contents || aName aPage parentPage aContext |
     aName := (path subStrings: ''/'') last.
     aPage := ((PRPage named: aName) contents: contents).
     parentPage := PRPathLookup start: aKernel root path: (path copyFrom: 1 to: (path lastIndexOf: $/)).
     owner isNil ifTrue: [parentPage addChild: aPage]
       ifFalse: [aPage securityDecoration
         group: (aKernel groups detect: [:e | e name = ''Production'']).
         aPage securityDecoration owner: (aKernel users detect: [:e | e name = owner]).
         parentPage addChild: aPage.
         aContext := PRContext
           kernel: aKernel
           structure: aPage
           command: (PREditCommand new								
             timestamp: (TimeStamp fromString: timeStamp);
             propertyAt: #user put: (aKernel users detect: [:e | e name = owner]);
             isChecked;
             fields;
             yourself).
         aContext command setContext: aContext.
         aKernel persistency add: aContext]].'; cr; cr.
       self users do: [:e | (#('admin' 'anonymous') includes: e username) 
    	  ifFalse: [stream nextPutAll: 'aKernel userNamed: '; nextPutAll: e username printString; nextPutAll: ' ifNone: [aKernel users add: ((PUUser named: '; nextPutAll: e username printString; nextPut: $).
         e roles do: [:r | (#('anonymous') includes: r name) ifFalse: [stream cr; tab; tab; tab; nextPutAll: 'addGroup: (aKernel groupNamed: '; nextPutAll: r name printString; nextPutAll: ' ifNone: [aKernel groups add: (PUGroup named: '; nextPutAll: r name printString; nextPutAll: ')]);']].
       JohnDebug := 'Find the password'.
       stream cr; tab; tab; tab; nextPutAll: 'password: '; nextPutAll: e password printString; nextPutAll: ';
       superuser: false;
       yourself)].
       ]].
     ].
     stream setToEnd; cr; cr.
     SWVisitorStructure block: [:structure || parentPath |
      parentPath := (structure isRoot or: [structure parent isRoot]) ifTrue: ['/'] ifFalse: [structure pathOfTitlesForPier].
       stream nextPutAll: 'CreateAPageBlock value: ''';
         nextPutAll: parentPath;
         nextPutAll: structure title;
         nextPutAll: ''' value: '; nextPutAll: (self users values detect: [:u | | hp |  (hp := u personnalData at: #homepage 
    
    ifAbsent: []) notNil and: [self root ~~ hp and: [structure parents includes: hp]]] ifNone: [self users at: 'admin']) username printString;
       nextPutAll: ' value: ''';
       nextPutAll: (structure timestamp date mmddyyyy, ' ', structure timestamp time printString);
       nextPutAll: ''' value: '.
     JohnDebug := structure.
     (SWVisitorRendererWiki render: structure) contents printString
          do: [:c | stream nextPut: c].
     stream nextPut: $.; cr; cr] start: (self root resolveTo: path).
    ]
    ensure: [stream isNil ifFalse: [stream close].
     JohnDebug := nil].
    ]

Once the file wiki.test.st is created, this is complete, and ready for the next step.