[View]  [Edit]  [Lock]  [References]  [Attachments]  [History]  [Home]  [Changes]  [Search]  [Help] 

Migrating StReader


StReader is a small tool used in VSE enviroment. Although not a visual application StReader uses UI minimal elements of VSE enviroment. Web based image is best suited on this scenary. Also you can benefit of a set of tools familiar to any Smalltalk developer in migration process. You can find detailed info about building a web based image . A complete migration project using web-mode enviroment (UI8) prepared for local development can be found here.

» Preparing for build.

Tipically you will start making a build.st file enumerating all source code, libraries and/or patches that will be compiled. The following is an example:

Code
"File: build.st
    __________________________________________________
    v1.0 Build sample file for migration project. 
    __________________________________________________
"!

"1-Compiles enviroment patches/libraries"!
self emmit: '..\lib\web\PatchLocalDev.st'.!

"2-Compiles migration-kit"!
self emmit: '..\VSECompat\VSECompat-Common.st'.!
self emmit: '..\VSECompat\VSECompat-Collections.st'.!
self emmit: '..\VSECompat\VSECompat-Stream.st'.!
self emmit: '..\VSECompat\VSECompat-Geometry.st'.!
self emmit: '..\VSECompat\VSECompat-Exceptions.st'.!
self emmit: '..\VSECompat\VSECompat-UI8.st'.!

"3-Compiles target source code pre-requisites"!
self emmit: 'stReader-VSECompat.st'.!

"4-Compiles target source code"!
self emmit: 'stReader.st'.!

"5-Compiles private specific target source code redefinitions"!
self emmit: 'stReader-Patch.st'.!

"6-Compiles launch target definitions"!
self emmit: 'stReaderTestApp.st'.!

(1) Compiles a patch for local development. This is a minimal modification that allows use a web enviroment in a offline fashion. More info about this in
(2) Compiles needed parts of migration-kit. In this exmaple most of the migration-kit is applied.
(3) Compiles pre-requisites for target source code. Sometimes it is needed to adapt things prior to target compilation. The StReader tool inherits from ARObject class that is not present in S8 image so this is the place to pre define such things.
(4) Compiles the target source code.
(5) Compiles post target source code re-definitions. Target source code should not be modified, so place where specific adaptations take place is in this stage. Next sections will show what is needed to redefine in StReader context.
(6) Compiles a small piece of code for launching the target itself or a set of tests for target. Next sections will shows how you can launch de StReader.

» Preparing pre-requisites

As mentioned earlier, sometimes it is needed to adapt things prior to target compilation. Doing quick manual revision of StReader code reveals that ARObject class is superclass of StReader and is not present in S8 core image (in this migration UI8 image is used, S8 core image is included in UI8 image). The following is a sample of stReader-VSECompat.st
Code
"File: stReader-VSECompat.st
    __________________________________________________
    v1.0 Defining support code for target compilation 
    __________________________________________________
"!
Object
   subclass: #ARObject
   instanceVariableNames: ''
   category: #stReader-VSECompat !

! ARObject class methodsFor: #instantiation!
new
   ^super new initialize! !


» Preparing re-definitions (adaptation)

Migration process is iterative. Most of adaptations will be done in this place. As a general form you start doing a manual revision looking for:
As a first step a String>>new: was found so must be changed. The first version of stReader-Patch.st could looks like:

Code
"File: stReader-Patch.st
    __________________________________________________
    v1.0 Defining code adaptations for target 
    __________________________________________________
"!

! StReader methodsFor: #VSECompat !
promptFileIn: aCollection as: aLabel
   " Private - Prompt for the collection to be filled in... "

   | stream |
   aCollection size = 0 ifTrue: [ ^self ].
   (MessageBox confirm: 'Perform fileIn of the ',aLabel,' ?')
      ifTrue: [
	aCollection do: [:each|
	   each classField
		addSelector: each selector
		withMethod: each.
	   SourceManager current
		logSource: each sourceString
		forSelector: each selector
		inClass: each classField.
	].
	MethodBrowser new
		label: aLabel;
		openOn: aCollection asArray.
      ]
      ifFalse: [
        "stream := WriteStream on: (String new: 10000)."
	stream := WriteStream on: (String new).
	self fileOutMethods: aCollection into: stream.
	TextWindow new
	   label: aLabel , ' sources (not filledIn Yet...)';
	   openOn: stream contents
	].! !

» Preparing launching/testing target

It is posible define a minimal application for target testing that will starts inmediatly after UI8 enviroment startup. Following code is a sample of launching StReader:
Code
"File: stReaderTestApp.st
    __________________________________________________
    v1.0 Testing target 
    __________________________________________________
"!
UI8Application
 subclass: #StReaderTestApp
 instanceVariableNames: ''
 category: 'StReaderTestApp'!

! StReaderTestApp class methodsFor: #gui !
open
	
   " Private - Launch. "
   | source |	
   source := File pathName: 'http://MySERVER/Colors.st'.	
   StReader fileIn: source.! !

Colors.st is a small sample for testing StReader. Note that it is posible to open a file referenced as an URL (see more in VSE2S8Stream.st file).
Last step preparing a building involves making an HTML page invoking the resulting compiled image. This HTML page looks like:
Code

File: stReaderTestApp.html
<html>
<head>
   <title>StReader Application with S8 environment + U8 tools</title>
   <style type="text/css">
      html { height: 100% }
      body { height: 100%; margin: 0; padding: 0;
         font-family: Helvetica, Arial,sans-serif}
      textarea {font-family: inherit; font-size: inherit}
   </style>
   <script type="text/javascript" src="prologue.js"></script>
   <script type="text/javascript" src="stReader.web.snapshot.js"></script>
</head>
<body onLoad="  'U8 install: #u8.  U8Toolbar open. StReaderTestApp open.'.doIt(); " >
   <div id="u8"></div>
   <div id="playground" style="color:darkblue;background-color:#d0e4fe;"></div>
</body>
</html>

The resulting final image is marked in brown color (see more in First build section). Also, in dark green color, UI8 startup and the testing application openinig in HTML/javascript context, is marked.

» First build

A complete migration project using web-mode enviroment (UI8) prepared for local development can be found here.
Typically building a S8 project implies using s8vm.exe so you must operate with console commands to launch the compilation. You should have a build.bat (DOS batch file in Windows platform) invoking s8vm.exe with a main director script (a javascript file) as argument. At this point your build.bat should looks like this:
Code
File: build.bat
del *.snapshot.js
s8vm.exe --shell build.js


build.js is used to preload a certain flavor of S8 image (in this case an UI8 image).
Code
File: build.js
(function() {
   try	{
        load("../somepath/ui8.image.js");
        load("../somepath/util.js");
	smalltalk.LoadFromSources = true;
	fileIn("build.st");
	smalltalk.Snapshot.outputToFile_("stReader.web.snapshot.js");
	print('=====Build OK=====');
	quit();	
	}
   catch (err) {
	print('====Error===='+err);
	print(err.stack);
	quit();
    }	
})();

The command fileIn("build.st") activate all compilation defined in section Preparing for build.
At this point you should be able to build the migration project by executing in build.bat command in console context.





Pointing your web browser to a local URL will force serving stReaderTestApp.html so stReader.web.snapshot.js will be loaded, UI8 enviroment started up and StReaderTestApp triggered for opening.
StReader works doing file in of source code; whenever a Smalltalk chunck is founded StReader prompts a confirmation with "Parsing source...File in this code chunck?". Once all chunck are prompted and confirmed you should see this screen.





Nothing happends apparently; Colors.st is a small sample consisting in three classes (RGBColor, HSVColor, HSLColor) plus a set of helper additional methods in Number class. If StReader is working ok you should be able to see these classes and methods in the System Browser. At this point Colors' classes are not present in the system, so an error happened.
As a general recomendation after first build (first migration attempt) is: you should make sure wich global names are present in target and not defined in current S8 image.
Opening system references window and selecting 'missing globals' will shows this kind of issue:






Adapting this things in stReader-Patch.st results in:

Code
"File: stReader-Patch.st
    __________________________________________________
    v1.1 Defining code adaptations for target 
    __________________________________________________
"!

! StReader methodsFor: #VSECompat !
fileIn: aStream
   "File in the contents of aStream into this image..."

   | cursor toBeFiledIn chunk |
   "cursor := Cursor."
   CursorManager execute change.
   [aStream atEnd or: [aStream peek isSeparator not ]] whileFalse: [aStream next].
   [aStream atEnd] whileFalse: [
			
	toBeFiledIn := aStream peekFor: $!!.
	chunk := aStream nextChunk.
	toBeFiledIn
		ifTrue: [ self fileIn: chunk from: aStream ]
		ifFalse: [ self evaluate: chunk ]
	].
   self performRealFileIn.
   CursorManager normal change.! !

! StReader methodsFor: #VSECompat !
promptFileIn: aCollection as: aLabel
   " Private - Prompt for the collection to be filled in... "

   | stream |
   aCollection size = 0 ifTrue: [ ^self ].
   (MessageBox confirm: 'Perform fileIn of the ',aLabel,' ?')
      ifTrue: [
	aCollection do: [:each|
	   each classField addCompiledMethod: each
	   "	addSelector: each selector
		withMethod: each.
	   SourceManager current
		logSource: each sourceString
		forSelector: each selector
		inClass: each classField."
	].
	"MethodBrowser new
		label: aLabel;
		openOn: aCollection asArray."
      ]
      ifFalse: [
        "stream := WriteStream on: (String new: 10000)."
	stream := WriteStream on: (String new).
	self fileOutMethods: aCollection into: stream.
	TextWindow new
	   label: aLabel , ' sources (not filledIn Yet...)';
	   openOn: stream contents
	].! !

» Second build

After a second build you should see again this screen
By clicking U8 icon (bottom right) you gain acces to S8 Transcript. It should looks like this:





RGBColor class is already filled in but S8 parser is failing in processing the first method. Keep in mind StReader is a tool for fileIn VSE Smalltalk code. Colors.st is developed for S8 so chunk format is different, S8 chunk format is similar to Squeak chunk format.

VSE chunk format sample:

!StReader methods!
method1
   "method body"!

method2
   "method body"! !

S8 chunk format sample:

!StReader methodsFor: #aspect!
method1
   "method body"! !

!StReader methodsFor: #otherAspect!
method2
   "method body"! !

Every time StReader finds a new method list definition expects in in first place a methods keyword. Migration should not involve modification of the target, however contradicting the issue, we slightly change the StReader to also understand S8 chunk format. The following is the final version of stReader-Patch.st:
Code
"File: stReader-Patch.st
    __________________________________________________
    v1.2 Defining code adaptations for target 
    __________________________________________________
"!

! StReader methodsFor: #VSECompat !
collectMethod: aCompiledMethod into: aCollection as: sourceCode
   " Private - Scan a collection for a method similar to aCompiledMethod,
   if found replaces it by aCompiledMethod if not add it at end of aCollection. "

   "aCompiledMethod sourceString: sourceCode."
   ^self collectMethod: aCompiledMethod into: aCollection! !

! StReader methodsFor: #VSECompat !
fileIn: aString from: aFile

   " Private - Scan aString for selected class and fileIn aFile contents upTo nul chunk... "

   | stream chunk answer old |
   "self getClassFrom: aString."
   self getClassFrom: (aString upTo: #For: ).
   [(chunk := aFile nextChunk) isEmpty]	whileFalse: [
	answer := Compiler compile: chunk in: selectedClass.
	answer notNil ifTrue: [
		old := answer isNil ifTrue: [ "do nothing" ]
				ifFalse: [ selectedClass compiledMethodAt: answer key ].
		old isNil
			ifTrue: [ self collectMethod: answer value into: contents as: chunk ]
			ifFalse: [
				(self isSource: old sourceString equalTo: chunk)
					ifFalse: [ self collectMethod: answer value into: contents as: chunk ]
			]
	]
   ].! !

! StReader methodsFor: #VSECompat !
fileIn: aStream
   "File in the contents of aStream into this image..."

   | cursor toBeFiledIn chunk |
   "cursor := Cursor."
   CursorManager execute change.
   [aStream atEnd or: [aStream peek isSeparator not ]] whileFalse: [aStream next].
   [aStream atEnd] whileFalse: [
			
	"toBeFiledIn := aStream peekFor: $!!."
        toBeFiledIn := aStream skipSeparators;peekFor: $!!.
	chunk := aStream nextChunk.
	toBeFiledIn
		ifTrue: [ self fileIn: chunk from: aStream ]
		ifFalse: [ self evaluate: chunk ]
	].
   self performRealFileIn.
   CursorManager normal change.! !

! StReader methodsFor: #VSECompat !
promptFileIn: aCollection as: aLabel
   " Private - Prompt for the collection to be filled in... "

   | stream |
   aCollection size = 0 ifTrue: [ ^self ].
   (MessageBox confirm: 'Perform fileIn of the ',aLabel,' ?')
      ifTrue: [
	aCollection do: [:each|
	   each classField addCompiledMethod: each
	   "	addSelector: each selector
		withMethod: each.
	   SourceManager current
		logSource: each sourceString
		forSelector: each selector
		inClass: each classField."
	].
	"MethodBrowser new
		label: aLabel;
		openOn: aCollection asArray."
      ]
      ifFalse: [
        "stream := WriteStream on: (String new: 10000)."
	stream := WriteStream on: (String new).
	self fileOutMethods: aCollection into: stream.
	TextWindow new
	   label: aLabel , ' sources (not filledIn Yet...)';
	   openOn: stream contents
	].! !


Last Build

After third build, and all chunk prompted and confirmed StReader asks confirmation about performing the filein whith label: 'Perform fileIn of the New filledIn methods?'. You should see again this screen but this time open a System Browser and look for RGBColor, HSLColor, HSVColor. It should looks like this:





DONE!
A complete migration project using web-mode enviroment (UI8) prepared for local development can be found here.