[Vm-dev] VM Maker: Cog-eem.367.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Nov 21 21:16:37 UTC 2019


Eliot Miranda uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-eem.367.mcz

==================== Summary ====================

Name: Cog-eem.367
Author: eem
Time: 21 November 2019, 1:16:35.3169 pm
UUID: 4336175b-c10d-44b9-a6b3-58e72c0c83e9
Ancestors: Cog-eem.366

Add GdbARMv8AlienTests and get it to execute nfib.  All nfib tests pass except testNfib1 because this requires error handling in GdbARMv8Alien which isn't implemented yet.

Revise saving of simulator register state on snapshot.  Add new instances to SavedState to avoid allGeneralInstancesDo:.

This demonstrates the VM bug in running GC in snapshot; the system can't run finalization/nil weak arrays for the GC done in snapshot, and any objects that need to be finalized won't get finalized on startup because on image start-up the finlization queue state is missing, not being saved in the image.

The simple implementation is /not/ to GC in snapshot, just compact.

=============== Diff against Cog-eem.366 ===============

Item was changed:
  Alien variableByteSubclass: #CogProcessorAlien
  	instanceVariableNames: ''
  	classVariableNames: 'BadCPUInstance ExecutionError InstructionPrefetchError MemoryBoundsError NoError PanicError PostBuildStackDelta PrintCodeBytes PrintTempNames ReceiverResultRegDereference SavedState SomethingLoggedError UnsupportedOperationError'
  	poolDictionaries: ''
  	category: 'Cog-Processors'!
  
+ !CogProcessorAlien commentStamp: 'eem 11/21/2019 11:17' prior: 0!
+ I am the superclass for the Simulation CPU instance wrappers. I ensure that methods used in both/all of them need not be copied.
+ 
+ Class Variables
+ 	error codes answered by the execution primitives, primitiveRunInMemory:minimumAddress:maximumAddress:readOnlyBelow: et al
+ 	NoError
+ 	BadCPUInstance				the receiver Alien does not appear to reference a valid underlying CPU object/struct/c++ instance, etc
+ 	ExecutionError					something went wrong when executing an instruction
+ 	InstructionPrefetchError		an attempt was made to fetch an instruction from an invalid address, e.g. below the minimum executable address
+ 	MemoryBoundsError			an attempt was made to access memory outside the bounds of the memory byte array.  This is key to how the simulator accesses Smalltalk variables
+ 	PanicError						the simulator "panicked", i.e. hit an error from which no propgress, such as delivering an exception, is possible
+ 	SomethingLoggedError			the simulator logged something, presumably an error, to its error log
+ 	UnsupportedOperationError	an attempt was made to do something currently unsupported or unimplemented (a lazy man's deferral)
+ 
+ 	simulation
+ 	PostBuildStackDelta			the amount to decrement the stack pointer after a simulated call
+ 
+ 	disassembly
+ 	PrintCodeBytes					when disassembling, whether to include the bytes comprising an insruction, false for faster single-stepping
+ 	PrintTempNames				when disassembling, whether to attempt to decorate temp var references with Smalltalk temp var names
+ 	ReceiverResultRegDereference	the concrete register holding ReceiverResultReg, used to decorate this register with ReceiverResultReg during disassembly
+ 
+ 	restart
+ 	SavedState						a Dictionary from processor to saved register state used to restore processor Aliens to their sate at snapshot, hence enabling continuing simulation after a snapshot, e.g. to save set-up time by advancing simulation to a given point and then saving and quitting!
- !CogProcessorAlien commentStamp: 'lw 8/23/2012 19:15' prior: 0!
- I am the superclass for the Simulation CPU instance wrappers. I ensure that methods used in both/all of them need not be copied.!

Item was changed:
  ----- Method: CogProcessorAlien class>>new (in category 'instance creation') -----
  new
+ 	| sim |
+ 	sim := self implementationClass atAddress: self primitiveNewCPU.
+ 	sim reset.
+ 	SavedState at: sim put: nil.
+ 	^sim!
- 	^(self implementationClass atAddress: self primitiveNewCPU) reset!

Item was changed:
  ----- Method: CogProcessorAlien class>>shutDown: (in category 'system startup') -----
  shutDown: quitting
+ 	SavedState keysDo:
+ 		[:processorOrNil|
+ 		 processorOrNil ifNotNil:
+ 			[SavedState at: processorOrNil put: processorOrNil registerState]]!
- 	self allSubInstancesDo:
- 		[:processor|
- 		SavedState at: processor put: processor registerState]!

Item was changed:
  ----- Method: CogProcessorAlien class>>startUp: (in category 'system startup') -----
  startUp: resuming
  	resuming ifTrue:
  		[SavedState keysAndValuesDo:
+ 			[:processorOrNil :stateOrNil|
+ 			 (processorOrNil notNil and: [stateOrNil notNil]) ifTrue:
- 			[:processorOrNil :state|
- 			 processorOrNil ifNotNil:
  				[processorOrNil addressFieldPut: processorOrNil class primitiveNewCPU.
+ 				 stateOrNil with: processorOrNil registerStateSetters do:
- 				 state with: processorOrNil registerStateSetters do:
  					[:value :setter|
+ 					processorOrNil perform: setter with: value]]]]!
- 					processorOrNil perform: setter with: value]]]].
- 	SavedState removeAll!

Item was added:
+ ----- Method: GdbARMv8Alien>>nopOpcode (in category 'opcodes') -----
+ nopOpcode
+ 	^16rd503201f!

Item was added:
+ TestCase subclass: #GdbARMv8AlienTests
+ 	instanceVariableNames: 'processor'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Cog-Processors-Tests'!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>memory (in category 'accessing') -----
+ memory 
+ 	"build a memory for this test; a ByteArray of 1024 bytes, filled with NOPs"
+ 	| mem nop|
+ 	nop := self processor nopOpcode.
+ 	mem := ByteArray new: 1024.
+ 	1 to: 1024  by: 4 do:
+ 		[:i| mem unsignedLongAt: i put: nop bigEndian: false].
+ 	^mem!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>nfib (in category 'private') -----
+ nfib
+ 	"long fib(long n) { return n <= 1 ? 1 : fib(n-1) + fib(n-2) + 1; }
+ 	 as compiled by arm-elf-gnuabi-gcc fib.c -c -marm
+ 	also, the jumps are changed by hand."
+ 	"| bat nfib ip |
+ 	bat := GdbARMv8AlienTests new.
+ 	nfib := bat nfib asWordArray.
+ 	ip := 0.
+ 	23 timesRepeat:
+ 		[bat processor disassembleInstructionAt: ip In: nfib into:
+ 			[:da :len|
+ 			Transcript nextPutAll: da; cr; flush.
+ 			ip := ip + len]]"
+ 	^#("           	nfib:
+ 		00" 16rF100041F 		"cmp	x0, 1
+ 		04" 16r540002AD 		"ble	.L4
+ 		08" 16rA9BE53F3 		"stp	x19, x20, [sp, -32]!!
+ 		0c" 16rD1000801 		"sub	x1, x0, #2
+ 		10" 16r927FF821 		"and	x1, x1, -2
+ 		14" 16rD1000413 		"sub	x19, x0, #1
+ 		18" 16rA9017BF5 		"stp	x21, x30, [sp, 16]
+ 		1c" 16rD1000C15 		"sub	x21, x0, #3
+ 		20" 16rCB0102B5 		"sub	x21, x21, x1
+ 		24" 16rD2800014 		"mov	x20, 0
+ 			.L3:
+ 		28" 16rAA1303E0 		"mov	x0, x19
+ 		2c" 16rD1000A73 		"sub	x19, x19, #2
+ 		30" 16r97FFFFF4 		"bl	nfib
+ 		34" 16r91000400 		"add	x0, x0, 1
+ 		38" 16r8B000294 		"add	x20, x20, x0
+ 		3c" 16rEB15027F 		"cmp	x19, x21
+ 		40" 16r54FFFF41 		"bne	.L3
+ 		44" 16r91000680 		"add	x0, x20, 1
+ 		48" 16rA9417BF5 		"ldp	x21, x30, [sp, 16]
+ 		4c" 16rA8C253F3 		"ldp	x19, x20, [sp], 32
+ 		50" 16rD65F03C0 		"ret
+ 		54" 16rD503201F 		".p2align 3
+ 			.L4:
+ 		58" 16rD2800020 		"mov	x0, 1
+ 		5c" 16rD65F03C0 		"ret")!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>processor (in category 'accessing') -----
+ processor
+ 	processor ifNil:
+ 		[processor := GdbARMv8Alien new].
+ 	^processor!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>runNFib:disassemble:printRegisters: (in category 'private') -----
+ runNFib: n disassemble: disassemble printRegisters: printRegisters
+ 	"Run nfib wth the argument. Answer the result."
+ 	"self new runNFib: 5 disassemble: true printRegisters: true"
+ 	| memory |
+ 	memory := Bitmap new: 1024 * 2 withAll: self processor nopOpcode.
+ 	memory replaceFrom: 1 to: self nfib size with: self nfib asWordArray startingAt: 1.
+ 	self processor
+ 		r0: n;"argument n"
+ 		lr: memory size * 2; "return address"
+ 		pc: 0;
+ 		sp: (memory size * 4) - 16.
+ 	printRegisters ifTrue:
+ 		[self processor printRegistersOn: Transcript.
+ 		 Transcript cr; flush].
+ 	"run until something goes wrong."
+ 	self processor runInMemory: memory readExecuteOnlyBelow: memory size / 2.
+ 	printRegisters ifTrue:
+ 		[self processor printRegistersOn: Transcript.
+ 		 Transcript cr; flush].
+ 	^self processor r0!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>singleStepNFibFor:numTimes:on: (in category 'examples') -----
+ singleStepNFibFor: v numTimes: n on: aStream
+ 	"self new singleStepNFibFor: 2 numTimes: 32 on: Transcript"
+ 	| memory p state newState |
+ 	memory := Bitmap new: 1024 * 2 withAll: self processor nopOpcode.
+ 	memory replaceFrom: 1 to: self nfib size with: self nfib asWordArray startingAt: 1.
+ 	(p := self processor)
+ 		r0: n;
+ 		lr: memory size * 2; "return address"
+ 		pc: 0;
+ 		sp: (memory size * 4) - 16.
+ 	p printRegistersOn: aStream.
+ 	state := p registerState.
+ 	aStream cr; flush.
+ 	n timesRepeat:
+ 		[aStream nextPutAll: (p disassembleNextInstructionIn: memory); space.
+ 		p singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
+ 		 newState := p registerState.
+ 		 state doWithIndex:
+ 			[:rv :i| | nv |
+ 			rv ~= (nv := newState at: i) ifTrue:
+ 				[aStream nextPutAll: (p registerStateSetters at: i); space; print: rv; nextPutAll: ' -> '; print: nv; space]].
+ 		 aStream cr; flush.
+ 		 state := newState].
+ 	^p r0!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>testNfib1 (in category 'tests') -----
+ testNfib1
+ 	"self new testNfib1"
+ 	self should: [self runNFib: 1 disassemble: false printRegisters: false]
+ 		raise: Error
+ 		withExceptionDo: 
+ 			[:err| self assert: err messageText = 'Error 0: Illegal Instruction fetch address (0x1000).'].
+ 	self deny: (self processor pc between: 0 and: self nfib size).
+ 	self assert: self processor r0 = 1 benchFib!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>testNfib16 (in category 'tests') -----
+ testNfib16
+ 	"self new testNfib16"
+ 	self should: [self runNFib: 16 disassemble: false printRegisters: false]
+ 		raise: Error.
+ 	self deny: (self processor pc between: 0 and: self nfib size).
+ 	self assert: self processor r0 = 16 benchFib!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>testNfib2 (in category 'tests') -----
+ testNfib2
+ 	"self new testNfib2"
+ 	self should: [self runNFib: 2 disassemble: false printRegisters: false]
+ 		raise: Error.
+ 	self deny: (self processor pc between: 0 and: self nfib size).
+ 	self assert: self processor r0 = 2 benchFib!

Item was added:
+ ----- Method: GdbARMv8AlienTests>>testNfib4 (in category 'tests') -----
+ testNfib4
+ 	"self new testNfib4"
+ 	self should: [self runNFib: 4 disassemble: false printRegisters: false]
+ 		raise: Error.
+ 	self deny: (self processor pc between: 0 and: self nfib size).
+ 	self assert: self processor r0 = 4 benchFib!



More information about the Vm-dev mailing list