Pier 3.1 to Pier 3.2

As of 2017-October, active development in Pier is going into version 3.2. At the time, there are some issues loading this version, but generally proceeding through the errors resolves the problems. Before upgrading, check Pier 3.0 to Pier 3.1.

There are several changes for Pier 3.2 are:

  • Links enclosed in italics can be expressed in Pier 3.1 as:

    Normal text ''italics text *link text>link location* more italics ==italics pre-formatted text== other'' more normal text

    Unfortunately the link is not be represented as a link, the text will appear the same for Pier 3.2, it will appear as:

    Normal text italics text *link text>link location* more italics italics pre-formatted text other more normal text
    This can be corrected with:

    Normal text {{{html: <i>}}}italics text *link text>link location* more italics ==italics pre-formatted text== other{{{html: </i>}}} more normal text

  • Dealing with empty table cells is not too straightforward. In Pier 3.1, it was possible to simply add an empty space, like:

    |next cell is empty| |the last cell had a space before editing

    However for Pier 3.2, the spaces are removed when editing, so the above turns into:

    |next cell is empty||the last cell had a space

    and is displayed as a table to 2 cells (the second cell's text is centered). For now it appears that using a dash may be a good convention, like:

    |Middle cell should be empty||-|Second cell had a dash

    which is displayed as:

    Middle cell should be empty-Second cell had a dash
  • Another change is that PRRaw (unformatted text in between triplets of brackets) now has a type option, instead of being direct HTML. An example is pictures:

    {{{<div style="clear: both"><img src="https://saysborden.s3.us-east-2.amazonaws.com/BlackTieToDo.png" alt="Black Tie" /></div>}}}

    For Pier 3.2, this should be:

    {{{html: <div style="clear: both"><img src="https://saysborden.s3.us-east-2.amazonaws.com/BlackTieToDo.png" alt="Black Tie" /></div>}}}

    For Pier 3.1 this is valid syntax for embedded a page in a table:

    | +An Embedded Page+

    For Pier 3.2 the embedding is done with:

    *An Embedded Page|embedded=true*

    Unfortunately the bar is parsed as part of the table, so an HTML table is required. This code makes the changes in the file out of the wiki:

    | newFileStream line tableLines tableHtmlLines isNeedingTableToHtml lineConverterBlock |
    isNeedingTableToHtml := false.
    lineConverterBlock := [ :aString |
    | copyString |
    (aString size < 3 or: [ aString first = $= and: [ aString second = Character space ] ])
    	ifTrue: [ aString ]
    	ifFalse: [ ('*{{{*' match: aString)
    			ifTrue: [ copyString := aString
    					copyWithRegex: '\{\{\{'
    					matchesTranslatedUsing: [ :string | string , 'html: ' ] ]
    			ifFalse: [ copyString := aString copy ].
    		((copyString includes: $+) not
    			or: [ (copyString allRegexMatches: '\+[^+]*\+') size
    					= (copyString allRegexMatches: '\*[^+]*http[^+*]*\+[^+*]*\+[^*]*\*') size ])
    			ifFalse: [ copyString := copyString
    					copyWithRegex: '\+value\:[a-zA-Z0-9]*\+'
    					matchesTranslatedUsing: [ :string | string copyReplaceAll: '+' with: '*' ].
    				copyString := copyString
    					copyWithRegex: '\+http[s]*\:[^+]*\+'
    					matchesTranslatedUsing: [ :string | string copyReplaceAll: '+' with: '*' ].
    				copyString := copyString
    					copyWithRegex: '\+[^>+]*\+'
    					matchesTranslatedUsing: [ :string |
    						(((copyString allRegexMatches: 'http[^ ]*')
    							contains: [ :httpString | httpString includesSubstring: string ])
    							or: [ (string at: string size - 1) = $\ ])
    							ifTrue: [ string ]
    							ifFalse: [ "self halt: 'What is ', string."
    								isNeedingTableToHtml := true.
    								'*' , (string copyFrom: 2 to: string size - 1) , '|embedded=true*' ] ] ].
    		copyString ] ].
    tableLines := OrderedCollection new.
    tableHtmlLines := OrderedCollection new.
    [ newFileStream := (FileSystem disk workingDirectory / 'new.st') writeStream.
    (FileSystem disk workingDirectory / 'Pier-Exported-Code.st') exists
    	ifFalse: [ self error: 'Missing file Pier-Exported-Code.st' ].
    FileSystem disk workingDirectory / 'Pier-Exported-Code.st'
    	readStreamDo: [ :stream |
    		[ stream atEnd ]
    			whileFalse: [ | htmlTableLine |
    				line := stream nextLine.
    				(line isEmpty not and: [ line first = $| ])
    					ifTrue: [ htmlTableLine := String
    							streamContents: [ :tableStream |
    								| convertedBars |
    								tableStream nextPutAll: '<tr>'.
    								convertedBars := line
    									copyWithRegex: '\|[^|][^|]*'
    									matchesTranslatedUsing: [ :barText |
    										barText second = $!
    											ifTrue: [barText third = $! ifFalse: [ self halt ].
    												(barText allButFirst allButFirst allSatisfy: [:c | c isAlphaNumeric or: [ c isSeparator ] ])
    													ifTrue: [ '<th>' , (barText copyFrom: 4 to: barText size), '</th>'
    														 ]
    													ifFalse: [ '<th>}}}' , (lineConverterBlock value: (barText copyFrom: 4 to: barText size))
    													, '{{{html: </th>' ]
    												 ]
    											ifFalse: [
    												(barText allButFirst allSatisfy: [:c | c isAlphaNumeric or: [ c isSeparator ] ])
    													ifTrue: [ '<td>' , (barText copyFrom: 2 to: barText size), '</td>' ]
    													ifFalse: [ '<td>}}}' , (lineConverterBlock value: (barText copyFrom: 2 to: barText size))
    													, '{{{html: </td>' ] ] ].
    								tableStream nextPutAll: convertedBars.
    								tableStream nextPutAll: '</tr>' ].
    						tableHtmlLines add: htmlTableLine.
    						tableLines add: (lineConverterBlock value: line) ]
    					ifFalse: [ line := lineConverterBlock value: line ].
    				tableHtmlLines isEmpty
    					ifTrue: [ isNeedingTableToHtml := false.
    						newFileStream
    							nextPutAll: line;
    							nextPut: Character lf ]
    					ifFalse: [ (line isEmpty or: [ line first ~~ $| ])
    							ifTrue: [ isNeedingTableToHtml
    									ifTrue: [ newFileStream nextPutAll: '{{{html:<table class="prtable">'.
    										tableHtmlLines
    											do: [ :htmlLine |
    												htmlLine = tableHtmlLines last ifFalse: [
    													newFileStream
    														nextPutAll: htmlLine;
    														nextPut: Character lf ]
    													ifTrue: [
    														(htmlLine matchesRegex: '.*''[)]*\..*') ifTrue: [ | indexOfDot |
    																	newFileStream
    																		nextPutAll:
    																	(htmlLine copyFrom: 1 to: ((indexOfDot := htmlLine findString: '''') - 1)).
    																	newFileStream
    																		nextPutAll: '{{{html: </td></tr></table>}}}'.
    																	newFileStream
    																		nextPutAll: (htmlLine copyFrom: indexOfDot to: ((htmlLine findString: '{{{html:' startingAt: indexOfDot) - 1)).
    																 ]
    															ifFalse: [
    																newFileStream
    																	nextPutAll: htmlLine;
    																	nextPut: Character lf.
    																newFileStream
    																	nextPutAll: '</table>}}}';
    																	nextPut: Character lf ]
    														 ]].
    ]
    									ifFalse: [ tableLines
    											do: [ :wikiLine |
    												newFileStream
    													nextPutAll: wikiLine;
    													nextPut: Character lf ] ].
    								isNeedingTableToHtml := false.
    								tableHtmlLines := OrderedCollection new.
    								tableLines := OrderedCollection new.
    								newFileStream
    									nextPutAll: line;
    									nextPut: Character lf ] ] ] ] ]
    	ensure: [ newFileStream isNil
    			ifFalse: [ newFileStream close ] ].

  • For very large wikis, there can be problems with importing due to the WideString special characters. These can be converted in the old image with:

    "Replace the wide chars with reasonable replacements. This runs in a few seconds."
    | problemChars |
    (problemChars := Dictionary new)
    	at: (Character value: 8217) put: $';
    	at: (Character value: 8220) put: $";
    	at: (Character value: 8221) put: $";
    	at: (Character value: 8211) put: $-.
    PRText allInstancesDo: [ :prText | (prText text includesAnyOf: problemChars keys) ifTrue: [ prText text: (prText text collect: [ :char | problemChars at: char ifAbsent: [ char ] ] ) ] ].