Importing History

At a high level, the plan for copying the history is:

  1. export the history from the older image after running all of the modification code - this creates a text file named history.txt
  2. After bringing up the image and importing all of the pages, read the text file into a collection, that is kept as the history

This plan only includes a single copy of each page's history (the current copy). This also assumes that the kernel is named Pier.

The code for writing out the history can be ran from any workspace:

| history fileStream recorded |
history := ((PRKernel instances reject: [:e | e root name = 'root']) detect: [:e | e name = 'pier' or: [e name = 'Pier']]) persistency history.
recorded := Set new: history size.
file := (File named: 'history.txt').
fileStream := ZnCharacterWriteStream on: file writeStream encoding: 'utf8'.
(history reject: [:e | e command timestamp isNil or: [e user isNil]]) reverseDo: [:e || collection | 
	(recorded includes: e structure absolutePath)
		ifFalse: [
			fileStream nextPutAll: e structure absolutePath.
			fileStream tab.
			fileStream nextPutAll: e user name.
			fileStream tab.
			fileStream nextPutAll: e command timestamp printString.
			fileStream cr.			
			recorded add: e structure absolutePath] ].
fileStream close.

The code for reading in the history into the Pier kernel persistence can also be ran from any workspace:

| fileStream aKernel path owner timeStamp listOfTuples aPage aContext aCommand |
aKernel := (PRKernel instances reject: [:e | e root name = 'root']) detect: [:e | e name = 'pier' or: [e name = 'Pier']].
listOfTuples := OrderedCollection new: 1024 * 8.
(file := File named: 'history.txt') exists ifFalse: [ self error: 'Missing history.txt in this directory.' ].
fileStream := ZnCharacterReadStream on: file readStream encoding: 'utf8'.
[
	[fileStream atEnd] whileFalse: 
		[path :=  (fileStream upTo: Character tab).
		owner := (fileStream upTo: Character tab).
		timeStamp := (fileStream upTo: Character cr).
		listOfTuples add: (Array with: path with: owner with: timeStamp).
	].
	listOfTuples reverseDo: [ :array | path := array first.
		owner := array second.
		timeStamp := array third.
		aPage := PRPathLookup start: aKernel root path: path.
		aPage ifNotNil: [
			(aKernel users contains: [ :e | e name = owner ]) ifTrue: [ 
				aContext := PRContext
			 		kernel: aKernel
 			 		structure: aPage.
				aContext := aContext user: (aKernel users detect: [:e | e name = owner]).
				aCommand := (PREditCommand context: aContext)
					timestamp: (GRPlatform current magritteTimeStampClass fromString: timeStamp);
					propertyAt: #user put: (aKernel users detect: [:e | e name = owner]);
					isChecked;
					fields;
					yourself.
				aKernel persistency add: (aContext command: aCommand)]]
		]
] ensure: [ fileStream ifNotNil: [ fileStream close ] ]