Pier 3.0 to Pier 3.1

As of 2015-Apr, Pier 3.1 was the active development version. For moving to Pharo 4.0, one of the main changes impacting Pier is that the TimeStamp class is being replaced by DateAndTime (code to switch).

Several smaller changes are:

  • It seems that the method parameterAt:ifPresent: is missing, when going to http://localhost:8080/pier - see Pier 3.1 Changes.
  • When opening a page with this type of link:

    *value:children|link*

    An error pops up about nil receiving #key. It seems that a loop is being performed over a dictionary which was previously an array in PRLinkRenderer>>attributesFor:, so adding a nil check can get past this error.

    This is very similar to Pier 2.0 to Pier 3.0 upgrades with a few differences:

    • From a Pharo 3 image, it simplifies the upgrade if TimeStamps are replaced by the parent class DateAndTime:

      PBPost allInstances do: [:post | post publication ifNotNil: [ post publication: (DateAndTime date: post publication asDate time: post publication asTime) ] ].

      In case the PierToDo is loaded:

      PRToDoTask allInstances do: [ :task | task due ifNotNil: [ task due: (DateAndTime date: task due asDate time: task due asTime) ] ].

    • Can use the newest version of Pier-Exporter-Code
    • Had issues with the emergency debugger, but was able to file-out the code.
    • After filling-in the code, when running:

      PRKernel instances size = 1 ifTrue: [ PRKernel instances anyOne name: 'pier_old' ].
      PRKernelCreatorForPier new createKernel.

      an error is raised from PRDocument>>parse::

      Pillar doesn't support this tag : ''OUT_LOG}  1>>${OUT_LOG} ...

      Debugging into the problem, about 100 steps higher give the cause coming from PRKernelCreatorForPier>>your_page where it calls: #contents:, found that the original page had this ksh variable listed on the past in non-preformatted text. Code to create a new file-out:

      | line count |
      count := 0.
      FileSystem workingDirectory / 'PRKernelCreatorForPier.old.st'
      	readStreamDo: [ :stream | 
      		| newStream |
      		[ newStream := (FileSystem workingDirectory / 'PRKernelCreatorForPier.newer.st')
      			writeStream.
      		[ stream atEnd ]
      			whileFalse: [ line := stream nextLine.
      				(line isNotEmpty and: [ line first ~~ $= and: [ '*${*' match: line ] ])
      					ifTrue: [ count := count + 1.
      						newStream
      							nextPutAll: (line copyReplaceAll: '${' with: '\$\{');
      							cr ]
      					ifFalse: [ newStream
      							nextPutAll: line;
      							cr ] ] ]
      			ensure: [ newStream ifNotNil: [ newStream close ] ] ].
      count

      Its also a good idea to look for $\{{{ and replace accordingly.