Squeak
  links to this page:    
View this PageEdit this PageUploads to this PageHistory of this PageTop of the SwikiRecent ChangesSearch the SwikiHelp Guide
DoubleArray Plugin Tutorial
Last updated at 3:59 am UTC on 20 May 2009
DoubleArray is a plugin that uses 64-bit Double precision floating point data type.


Part I: Setting up the VM and plugin generation environment


Get the following three zip files and unzip it to the specified location:
  1. Squeak VM source release http://www.squeakvm.org/win32/release/SqueakVM-Win32-3.10.7-src.zip
  2. Tools for VM compilation http://www.squeakvm.org/win32/release/Squeak-Win32-Tools-1.2.zip
  3. Sqeauk 3.10 executable and image http://ftp.squeak.org/3.10/win/Squeak3.10.2-7179-win32.zip

Part II: Writing the DoubleArray Class and Plugin


DoubleArray Class

  1. On the Browser Create the DoubleArray Class as a subclass of ByteArray
            ByteArray variableByteSubclass: #DoubleArray
    	instanceVariableNames: ''
    	classVariableNames: ''
    	poolDictionaries: ''
    	category: 'ADoubleArrayPackage'
  2. We start of by writing the class side method.
    new: n
    ^ self basicNew: 8 * n
  3. Overide the size method.
    size
    	^ self basicSize / 8
  4. The accessing methods.
    at: i 
    	<primitive: 'primitiveAtDoubleArray' module: 'DoubleArrayPlugin'>
            ^ self
    
    at: i put: value
    	<primitive: 'primitiveAtPutDoubleArray' module: 'DoubleArrayPlugin'>
            ^ self
    .

Primitive Accessors

  1. In order to save execution time, primitive accessors are created for DoubleArray Plugin. primitiveAtDoubleArray and primitiveAtPutDoubleArray are created:
    primitiveAtDoubleArray
    	| size arrayC arraySq indexC index value |
    	self export: true.
    	self inline: false.
    	self var: #arrayC type: 'double *'.
    	self var: #indexC type: 'int'.
    	self var: #size type: 'int'.
    	index := interpreterProxy stackIntegerValue: 0.
    	arrayC := self loadDoubleArray: (arraySq := interpreterProxy stackObjectValue: 1).
    	"Check for the validity of index"
    	(index >= 1
    			and: [index <= (size := (interpreterProxy stSizeOf: arraySq)
    								/ 8)])
    		ifFalse: [interpreterProxy primitiveFail.
    			^ nil].
    	interpreterProxy failed
    		ifTrue: [^ nil].
    	indexC := index - 1.
    	interpreterProxy pop: 2.
    	interpreterProxy
    		pushFloat: (self
    				cCoerce: (arrayC at: indexC)
    				to: 'double')
    primitiveAtPutDoubleArray
    	| size arrayC arraySq indexC valueC |
    	self export: true.
    	self inline: false.
    	self var: #arrayC type: 'double *'.
    	self var: #indexC type: 'int'.
    	self var: #valueC type: 'double'.
    	self var: #size type: 'int'.
    	value := interpreterProxy stackValue: 0.
    	(interpreterProxy isFloatObject: value)
    		ifTrue: [valueC := interpreterProxy floatValueOf: value]
    		ifFalse: [valueC := (interpreterProxy integerValueOf: value) asFloat].
    	indexC := interpreterProxy stackIntegerValue: 1.
    	arrayC := self loadDoubleArray: (arraySq := interpreterProxy stackObjectValue: 2).
    	"Check for the validity of index"
    	(indexC >= 1
    			and: [indexC <= (size := (interpreterProxy stSizeOf: arraySq)
    								/ 8)])
    		ifFalse: [interpreterProxy primitiveFail.
    			^ nil].
    	interpreterProxy failed
    		ifTrue: [^ nil].
    	arrayC
    		at: indexC - 1
    		put: (self cCoerce: valueC to: 'double').
    	interpreterProxy pop: 3.
    	interpreterProxy
    		pushFloat: (self
    				cCoerce: (arrayC at: indexC - 1)
    				to: 'double')
  2. These methods will be translated to the following respectively:
    EXPORT(sqInt) primitiveAtDoubleArray(void) {
        int size;
        double * arrayC;
        sqInt arraySq;
        int indexC;
        sqInt indexSq;
        sqInt array;
    
    	indexSq = interpreterProxy->stackIntegerValue(0);
    	/* begin loadDoubleArray: */
    	array = arraySq = interpreterProxy->stackObjectValue(1);
    	if (interpreterProxy->failed()) {
    		arrayC = null;
    		goto l1;
    	}
    	if (!(interpreterProxy->isBytes(array))) {
    		interpreterProxy->primitiveFail();
    		arrayC = null;
    		goto l1;
    	}
    	arrayC = ((double *) (interpreterProxy->firstIndexableField(array)));
    l1:	/* end loadDoubleArray: */;
    	if (!((indexSq >= 1) && (indexSq <= (size = ((sqInt) (interpreterProxy->stSizeOf(arraySq)) >> 3))))) {
    		interpreterProxy->primitiveFail();
    		return null;
    	}
    	if (interpreterProxy->failed()) {
    		return null;
    	}
    	indexC = indexSq - 1;
    	interpreterProxy->pop(2);
    	interpreterProxy->pushFloat(((double) (arrayC[indexC])));
    }
    EXPORT(sqInt) primitiveAtPutDoubleArray(void) {
        double valueC;
        int size;
        double * arrayC;
        sqInt arraySq;
        int indexC;
        sqInt valueSq;
        sqInt array;
    
    	valueSq = interpreterProxy->stackValue(0);
    	if (interpreterProxy->isFloatObject(valueSq)) {
    		valueC = interpreterProxy->floatValueOf(valueSq);
    	} else {
    		valueC = ((double) ((valueSq >> 1)) );
    	}
    	indexC = interpreterProxy->stackIntegerValue(1);
    	/* begin loadDoubleArray: */
    	array = arraySq = interpreterProxy->stackObjectValue(2);
    	if (interpreterProxy->failed()) {
    		arrayC = null;
    		goto l1;
    	}
    	if (!(interpreterProxy->isBytes(array))) {
    		interpreterProxy->primitiveFail();
    		arrayC = null;
    		goto l1;
    	}
    	arrayC = ((double *) (interpreterProxy->firstIndexableField(array)));
    l1:	/* end loadDoubleArray: */;
    	if (!((indexC >= 1) && (indexC <= (size = ((sqInt) (interpreterProxy->stSizeOf(arraySq)) >> 3))))) {
    		interpreterProxy->primitiveFail();
    		return null;
    	}
    	if (interpreterProxy->failed()) {
    		return null;
    	}
    	arrayC[indexC - 1] = (((double) valueC));
    	interpreterProxy->pop(3);
    	interpreterProxy->pushFloat(((double) (arrayC[indexC - 1])));
    }

DoubleArrayPlugin

  1. Create a plugin module that is going to store the primitive as 'DoubleArrayPlugin'
            InterpreterPlugin subclass: #DoubleArrayPlugin
    	instanceVariableNames: ''
    	classVariableNames: ''
    	poolDictionaries: ''
    	category: 'ADoubleArrayPackage'
  2. Now, a method has to be written to load the DoubleArray type array and cast it to a 'double *' type in the DoubleArrayPlugin Class.
    loadDoubleArray: array 
	"Load the DoubleArray array "
	self returnTypeC: 'double*'.
	interpreterProxy failed
		ifTrue: [^ nil].
	(interpreterProxy isBytes: array )
		ifFalse: [interpreterProxy primitiveFail.
			^ nil].
	^ self
		cCoerce: (interpreterProxy firstIndexableField: array )
		to: 'double *'


Part III: Some DoubleArray plugin examples


A DoubleArray addition plugin


    add: array into: answer
	primitive: 'primitiveAddArray' module: 'DoubleArrayPlugin'
	1
		to: self size
		do: [:i | answer at: i put: ((self at: i)
					+ (array at: i)) asFloat].
	^ answer


Note: first statement call the primitive, second statement will execute when primitive fail, or if primitive not found.
    primitiveAddArray
	| resultC secondOperandC firstOperandC result operand rcvr size |
	self export: true.
	self inline: false.
	self var: #resultC type: 'double*'.
	self var: #secondOperandC type: 'double*'.
	self var: #firstOperandC type: 'double*'.
	self var: #size type: 'int'.
	resultC := self loadDoubleArray: (result := interpreterProxy stackObjectValue: 0).
	secondOperandC := self loadDoubleArray: (operand := interpreterProxy stackObjectValue: 1).
	firstOperandC := self loadDoubleArray: (rcvr := interpreterProxy stackObjectValue: 2).
	"Check for size of both the operands"
	(size := interpreterProxy stSizeOf: operand)
			= (interpreterProxy stSizeOf: rcvr)
		ifFalse: [interpreterProxy primitiveFail.
			^ nil].
	interpreterProxy failed
		ifTrue: [^ nil].
	"Computation"
	0
		to: size / 8 - 1
		do: [:i | resultC at: i put: (firstOperandC at: i)
					+ (secondOperandC at: i)].
	interpreterProxy pop: 3.
	interpreterProxy push: result

A positive array test

    positive
	primitive: 'primitiveArrayIsPositive' module: 'DoubleArrayPlugin'
	1
		to: self size
		do: [:i | (self at: i) positive
				ifFalse: [^ false]].
	^ true

    primitiveArrayIsPositive
	| rcvrC rcvr result |
	self export: true.
	self inline: false.
	self var: #rcvrC type: 'double*'.
	rcvrC := self loadDoubleArray: (rcvr := interpreterProxy stackObjectValue: 0).
	interpreterProxy failed
		ifTrue: [^ nil].
	result := true.
	0
		to: (interpreterProxy stSizeOf: rcvr)
				/ 8 - 1
		do: [:i | (rcvrC at: i)
					>= 0
				ifFalse: [result := false]].
	interpreterProxy pop: 1.
	interpreterProxy pushBool: result


A plugin to round the array to a factor.



Part IV: Generating and test the plugin

  1. Drag a workspace from the Tools tab. We can now test the primitive. Type the following in the workspace.
    VMMakerTool openInWorld
    ctrl + d to open the VMMaker GUI and fill in the text fields with the following:
    Interpreter class name: Interpreter
    Path to platform code: C:\SqueakVM-Win32-3.10.7\platforms
    Platform name: Win32
    Path to generate sources: C:\SqueakVM-Win32-3.10.7\platforms\win32\build\src
  2. Right click in the Plugins not built pane and select make all internal. From Internal Plugins pane, drag DoubleArrayPlugin to the External Plugins pane. Then, click on Entire to translate the files into .C equivalent for compilation.

Test Run

  1. In the workspace, type in the following to test for the addition plugin:
    | m1 m2 dm1 |
    	m1 := DoubleArray new: 3.
    	m1 at: 1 put: 1.0.
    	m1 at: 2 put: 2.000000000003.
    	m1 at: 3 put: 1/3.
    	m2 := DoubleArray new: 3.
    	m2 at: 1 put: 1.0.
    	m2 at: 2 put: 1.0.
    	m2 at: 3 put: 1.0.
            m3 := DoubleArray new: 3.
    	m1 add: m2 into: m3
  2. For the positive test, type in the following:
    	| m1 dm1 |
    	m1 := DoubleArray new: 3.
    	m1 at: 1 put: 1.00000000002.
    	m1 at: 2 put: 1.00000000003.
    	m1 at: 3 put: 5.5.
    	m1 positive.
  3. For the rounding test, type in the following:
    | m1 dm1 |
    	m1 := DoubleArray new: 3.
    	m1 at: 1 put: 1.00000000002.
    	m1 at: 2 put: 4.9.
    	m1 at: 3 put: 5.5.
    	m1 roundTo: 5 into: m2.