[Vm-dev] [commit] r2554 - Fix the undeclared variable ref for the linux BochsIA32Plugin.

commits at squeakvm.org commits at squeakvm.org
Sat May 19 22:07:03 UTC 2012


Author: eliot
Date: 2012-05-19 15:07:03 -0700 (Sat, 19 May 2012)
New Revision: 2554

Removed:
   branches/Cog/image/BaseExtensionsForVMMaker.1.cs
Modified:
   branches/Cog/image/
   branches/Cog/platforms/unix/plugins/BochsIA32Plugin/Makefile.inc
Log:
Fix the undeclared variable ref for the linux BochsIA32Plugin.
Nuke an obsolete changeset.



Property changes on: branches/Cog/image
___________________________________________________________________
Modified: svn:ignore
   - prefs
special-dirs
package-cache

   + prefs
special-dirs
package-cache
SqueakDebug.log


Deleted: branches/Cog/image/BaseExtensionsForVMMaker.1.cs
===================================================================
--- branches/Cog/image/BaseExtensionsForVMMaker.1.cs	2012-05-19 21:41:17 UTC (rev 2553)
+++ branches/Cog/image/BaseExtensionsForVMMaker.1.cs	2012-05-19 22:07:03 UTC (rev 2554)
@@ -1,172 +0,0 @@
-'From Squeak4.1 of 17 April 2010 [latest update: #9957] on 21 May 2010 at 11:13:17 am'!
-
-!Character methodsFor: 'printing' stamp: 'eem 5/21/2010 11:11'!
-hex
-	^value printStringBase: 16! !
-
-
-!Collection methodsFor: 'enumerating' stamp: 'eem 1/11/2009 14:11'!
-fold: binaryBlock
-	"Evaluate the block with the first two elements of the receiver,
-	 then with the result of the first evaluation and the next element,
-	 and so on.  Answer the result of the final evaluation. If the receiver
-	 is empty, raise an error. If the receiver has a single element, answer
-	 that element."
-	"#('if' 'it' 'is' 'to' 'be' 'it' 'is' 'up' 'to' 'me') fold: [:a :b | a, ' ', b]"
-
-	| firstValue nextValue |
-	firstValue := nextValue := Object new. "something that can't be in the receiver"
-	self do:
-		[:each |
-		nextValue := firstValue == nextValue
-						ifTrue: [each]
-						ifFalse: [binaryBlock value: nextValue value: each]].
-	^nextValue == firstValue
-		ifTrue: [self errorEmptyCollection]
-		ifFalse: [nextValue]! !
-
-
-!HexTest methodsFor: 'as yet unclassified' stamp: 'eem 5/21/2010 11:12'!
-testIntegerHex
-	| result |
-	result := 15 asInteger hex.
-	self assert: result = '16rF'.
-	result := 0 asInteger hex.
-	self assert: result = '16r0'.
-	result := 255 asInteger hex.
-	self assert: result = '16rFF'.
-	result := 90 asInteger hex.
-	self assert: result = '16r5A'! !
-
-
-!Integer methodsFor: 'printing' stamp: 'eem 5/21/2010 11:06'!
-hex
-	"Print the receiver as hex, prefixed with 16r.  DO NOT CHANGE THIS!!  The Cog VMMaker depends on this.
-	 Consider using any of
-		printStringHex
-		printStringBase: 16
-		printStringBase: 16 length: 8 padded: true
-		storeStringHex
-		storeStringBase: 16
-		storeStringBase: 16 length: 11 padded: true"
-	^self storeStringBase: 16! !
-
-!Integer methodsFor: 'printing' stamp: 'eem 5/21/2010 11:09'!
-hex8
-	"Print the receiver in base 16 with prefixed base, using at least 8 digits.
-	 DO NOT CHANGE THIS!!  The Cog VMMaker depends on this.
-	 Consider using storeStringBase: 16 length: 11 padded: true instead."
-	  "16r3333 hex8"
-	| hex |
-	hex := self hex.  "16rNNN"
-	^hex size < 11
-		ifTrue: [hex copyReplaceFrom: 4 to: 3
-						 with: ('00000000' copyFrom: 1 to: 11-hex size)]
-		ifFalse: [hex]! !
-
-
-!SequenceableCollection methodsFor: 'copying' stamp: 'eem 2/10/2009 11:44'!
-copyUpThrough: anElement 
-	"Answer all elements up to and including anObject. If there
-	is no such object, answer a copy of the receiver."
-
-	^self first: (self indexOf: anElement ifAbsent: [^ self copy])! !
-
-
-!SmalltalkImage methodsFor: 'special objects' stamp: 'Igor.Stasenko 5/4/2010 17:01'!
-recreateSpecialObjectsArray
-	"Smalltalk recreateSpecialObjectsArray"
-	
-	"To external package developers:
-	**** DO NOT OVERRIDE THIS METHOD.  *****
-	If you are writing a plugin and need an additional special object(s) for own use, 
-	use addGCRoot() function and use own, separate special objects registry "
-	
-	"The Special Objects Array is an array of object pointers used
-	by the
-	Squeak virtual machine. Its contents are critical and
-	unchecked, so don't even think of playing here unless you
-	know what you are doing."
-	| newArray |
-	newArray := Array new: 55.
-	"Nil false and true get used throughout the interpreter"
-	newArray at: 1 put: nil.
-	newArray at: 2 put: false.
-	newArray at: 3 put: true.
-	"This association holds the active process (a ProcessScheduler)"
-	newArray at: 4 put: (self associationAt: #Processor).
-	"Numerous classes below used for type checking and instantiation"
-	newArray at: 5 put: Bitmap.
-	newArray at: 6 put: SmallInteger.
-	newArray at: 7 put: ByteString.
-	newArray at: 8 put: Array.
-	newArray at: 9 put: Smalltalk.
-	newArray at: 10 put: Float.
-	newArray at: 11 put: MethodContext.
-	newArray at: 12 put: BlockContext.
-	newArray at: 13 put: Point.
-	newArray at: 14 put: LargePositiveInteger.
-	newArray at: 15 put: Display.
-	newArray at: 16 put: Message.
-	newArray at: 17 put: CompiledMethod.
-	newArray at: 18 put: (self specialObjectsArray at: 18).
-	"(low space Semaphore)"
-	newArray at: 19 put: Semaphore.
-	newArray at: 20 put: Character.
-	newArray at: 21 put: #doesNotUnderstand:.
-	newArray at: 22 put: #cannotReturn:.
-	newArray at: 23 put: nil.
-	"An array of the 32 selectors that are compiled as special bytecodes,
-	 paired alternately with the number of arguments each takes."
-	newArray at: 24 put: #(	#+ 1 #- 1 #< 1 #> 1 #<= 1 #>= 1 #= 1 #~= 1
-							#* 1 #/ 1 #\\ 1 #@ 1 #bitShift: 1 #// 1 #bitAnd: 1 #bitOr: 1
-							#at: 1 #at:put: 2 #size 0 #next 0 #nextPut: 1 #atEnd 0 #== 1 #class 0
-							#blockCopy: 1 #value 0 #value: 1 #do: 1 #new 0 #new: 1 #x 0 #y 0 ).
-	"An array of the 255 Characters in ascii order."
-	newArray at: 25 put: ((0 to: 255) collect: [:ascii | Character value: ascii]).
-	newArray at: 26 put: #mustBeBoolean.
-	newArray at: 27 put: ByteArray.
-	newArray at: 28 put: Process.
-	"An array of up to 31 classes whose instances will have compact headers"
-	newArray at: 29 put: self compactClassesArray.
-	newArray at: 30 put: (self specialObjectsArray at: 30).
-	"(delay Semaphore)"
-	newArray at: 31 put: (self specialObjectsArray at: 31).
-	"(user interrupt Semaphore)"
-	"Prototype instances that can be copied for fast initialization"
-	newArray at: 32 put: (Float new: 2).
-	newArray at: 33 put: (LargePositiveInteger new: 4).
-	newArray at: 34 put: Point new.
-	newArray at: 35 put: #cannotInterpret:.
-	"Note: This must be fixed once we start using context prototypes (yeah, right)"
-	"(MethodContext new: CompiledMethod fullFrameSize)."
-	newArray at: 36 put: (self specialObjectsArray at: 36). "Is the prototype MethodContext (unused by the VM)"
-	newArray at: 37 put: BlockClosure.
-	"(BlockContext new: CompiledMethod fullFrameSize)."
-	newArray at: 38 put: (self specialObjectsArray at: 38). "Is the prototype BlockContext (unused by the VM)"
-	newArray at: 39 put: (self specialObjectsArray at: 39).	"preserve external semaphores"
-	"array of objects referred to by external code"
-	newArray at: 40 put: PseudoContext.
-	newArray at: 41 put: TranslatedMethod.
-	"finalization Semaphore"
-	newArray at: 42 put: ((self specialObjectsArray at: 42) ifNil: [Semaphore new]).
-	newArray at: 43 put: LargeNegativeInteger.
-	"External objects for callout.
-	 Note: Written so that one can actually completely remove the FFI."
-	newArray at: 44 put: (self at: #ExternalAddress ifAbsent: []).
-	newArray at: 45 put: (self at: #ExternalStructure ifAbsent: []).
-	newArray at: 46 put: (self at: #ExternalData ifAbsent: []).
-	newArray at: 47 put: (self at: #ExternalFunction ifAbsent: []).
-	newArray at: 48 put: (self at: #ExternalLibrary ifAbsent: []).
-	newArray at: 49 put: #aboutToReturn:through:.
-	newArray at: 50 put: #run:with:in:.
-	newArray at: 51 put: (self at: #WeakFinalizationList ifAbsent: []).
-	newArray at: 52 put: nil.
-	newArray at: 53 put: (self at: #Alien ifAbsent: []).
-	newArray at: 54 put: #invokeCallback:stack:registers:jmpbuf:.
-	newArray at: 55 put: (self at: #UnsafeAlien ifAbsent: []).
-	
-	"Now replace the interpreter's reference in one atomic operation"
-	self specialObjectsArray become: newArray
-	! !
-
Modified: branches/Cog/platforms/unix/plugins/BochsIA32Plugin/Makefile.inc
===================================================================
--- branches/Cog/platforms/unix/plugins/BochsIA32Plugin/Makefile.inc	2012-05-19 21:41:17 UTC (rev 2553)
+++ branches/Cog/platforms/unix/plugins/BochsIA32Plugin/Makefile.inc	2012-05-19 22:07:03 UTC (rev 2554)
@@ -7,4 +7,5 @@
 XLDFLAGS=	-L$(topdir)/processors/IA32/linuxbochs/cpu \
 			-L$(topdir)/processors/IA32/linuxbochs/fpu \
 			-L$(topdir)/processors/IA32/linuxbochs/disasm \
-			-lcpu -lfpu -ldisasm
+			-lcpu -lfpu -ldisasm \
+			-lstdc++



More information about the Vm-dev mailing list