[Vm-dev] VM Maker: Cog-tpr.259.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Apr 15 02:21:41 UTC 2015


tim Rowledge uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-tpr.259.mcz

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

Name: Cog-tpr.259
Author: tpr
Time: 14 April 2015, 7:21:32.14 pm
UUID: 98c70518-1349-49e2-9ce3-0815c01a0cd0
Ancestors: Cog-tpr.258, Cog-eem.258

This should merge Cog-eem.258 but MC giveth and MC taketh away, so we'll see.

Remove a problematic usage of lookupAddress: until a better idea comes along.
Improve simulateCall... to actually, y'know, work.

=============== Diff against Cog-tpr.258 ===============

Item was changed:
  CogProcessorAlien variableByteSubclass: #BochsIA32Alien
  	instanceVariableNames: ''
+ 	classVariableNames: 'ExtendedOpcodeExceptionMap OpcodeExceptionMap PostBuildStackDelta'
- 	classVariableNames: 'OpcodeExceptionMap PostBuildStackDelta'
  	poolDictionaries: ''
  	category: 'Cog-Processors'!
  
  !BochsIA32Alien commentStamp: '<historical>' prior: 0!
  I am a wrapper around the Bochs C++ IA32 CPU emulator.  Note that currently I provide no access to the x87/mmx FPU state, only providing access to the SSE/xmm registers.
  
  Here is the configure script for the configuration this code assumes.  Offsets of fields will change with different configurations so they must agree.
  
  ----8<---- conf.COG ----8<----
  #!!/bin/sh
  
  # this sets up the compile for Cog.  Disable as much inessential stuff
  # as possible leaving only the cpu/fpu & memory interface
  
  set echo
  # CFLAGS="-pipe -O3 -fomit-frame-pointer -finline-functions -falign-loops=16 -falign-jumps=16 -falign-functions=16 -falign-labels=16 -falign-loops-max-skip=15 -falign-jumps-max-skip=15 -fprefetch-loop-arrays $CFLAGS"
  CFLAGS="-m32 $CFLAGS"
  CFLAGS="-Dlongjmp=_longjmp -Dsetjmp=_setjmp $CFLAGS"
  CFLAGS="-pipe -O3 -fomit-frame-pointer -finline-functions $CFLAGS"
  CFLAGS="-g $CFLAGS"
  CPATH="/sw/include"
  CPPFLAGS=""
  CXXFLAGS="$CFLAGS"
  LDFLAGS="-L/sw/lib"
  
  export CFLAGS
  export CPATH
  export CPPFLAGS
  export CXXFLAGS
  export LDFLAGS
  
  ./configure --enable-Cog \
  	--enable-cpu-level=6 \
  	--enable-sse=2 \
  	--enable-assert-checks \
  	--with-nogui \
  		--disable-x86-64 \
  		--disable-pae \
  		--disable-large-pages \
  		--disable-global-pages \
  		--disable-mtrr \
  		--disable-sb16 \
  		--disable-ne2000 \
  		--disable-pci \
  		--disable-acpi \
  		--disable-apic \
  		--disable-clgd54xx \
  		--disable-usb \
  		--disable-plugins \
  	${CONFIGURE_ARGS}
  
  # apic == Advanced programmable Interrupt Controller
  # acpi == Advanced Configuration and Power Interface
  # pci == Peripheral Component Interconnect local bus
  # clgd54xx == Cirrus Logic GD54xx video card
  ----8<---- conf.COG ----8<----!

Item was changed:
  ----- Method: BochsIA32Alien class>>initialize (in category 'class initialization') -----
  initialize
  	"BochsIA32Alien initialize"
+ 	| it |
+ 	it := self basicNew.
  	PostBuildStackDelta := 0.
  	OpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:.
  	OpcodeExceptionMap
+ 		at: 1 + it callOpcode			put: #handleCallFailureAt:in:;
+ 		at: 1 + it jmpOpcode			put: #handleJmpFailureAt:in:;
+ 		at: 1 + it retOpcode			put: #handleRetFailureAt:in:;
+ 		at: 1 + it movALObOpcode	put: #handleMovALObFailureAt:in:;
+ 		at: 1 + it movObALOpcode	put: #handleMovObALFailureAt:in:;
+ 		at: 1 + it movGvEvOpcode	put: #handleMovGvEvFailureAt:in:;
+ 		at: 1 + it movEvGvOpcode	put: #handleMovEvGvFailureAt:in:;
+ 		at: 1 + it movGbEbOpcode	put: #handleMovGbEbFailureAt:in:;
+ 		at: 1 + it movEbGbOpcode	put: #handleMovEbGbFailureAt:in:.
+ 	ExtendedOpcodeExceptionMap := Array new: 256 withAll: #handleExecutionPrimitiveFailureAt:in:.
+ 	ExtendedOpcodeExceptionMap
+ 		at: 1 + it movGvEbOpcode put: #handleMovGvEbFailureAt:in:!
- 		at: 1 + self basicNew callOpcode			put: #handleCallFailureAt:in:;
- 		at: 1 + self basicNew jmpOpcode			put: #handleJmpFailureAt:in:;
- 		at: 1 + self basicNew retOpcode			put: #handleRetFailureAt:in:;
- 		at: 1 + self basicNew movALObOpcode	put: #handleMovALObFailureAt:in:;
- 		at: 1 + self basicNew movObALOpcode	put: #handleMovObALFailureAt:in:;
- 		at: 1 + self basicNew movGvEvOpcode	put: #handleMovGvEvFailureAt:in:;
- 		at: 1 + self basicNew movEvGvOpcode	put: #handleMovEvGvFailureAt:in:;
- 		at: 1 + self basicNew movGbEbOpcode	put: #handleMovGbEbFailureAt:in:;
- 		at: 1 + self basicNew movEbGbOpcode	put: #handleMovEbGbFailureAt:in:!

Item was changed:
  ----- Method: BochsIA32Alien>>handleExecutionPrimitiveFailureIn:minimumAddress: (in category 'error handling') -----
  handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress
  	"Handle an execution primitive failure.  Convert out-of-range call and absolute
  	 memory read into register instructions into ProcessorSimulationTrap signals."
  	"self printIntegerRegistersOn: Transcript"
  	"self printRegistersOn: Transcript"
  	| pc opcode |
  	((pc := self eip) between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
  		[opcode := memoryArray byteAt: pc + 1.
+ 		 opcode ~= 16r0f ifTrue:
+ 			[^self
+ 				perform: (OpcodeExceptionMap at: opcode + 1)
+ 				with: pc
+ 				with: memoryArray].
+ 		 opcode := memoryArray byteAt: pc + 2.
+ 		 ^self
+ 				perform: (ExtendedOpcodeExceptionMap at: opcode + 1)
+ 				with: pc
+ 				with: memoryArray].
- 		^self
- 			perform: (OpcodeExceptionMap at: opcode + 1)
- 			with: pc
- 			with: memoryArray].
  	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsIA32Alien>>handleMovGvEbFailureAt:in: (in category 'error handling') -----
+ handleMovGvEbFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Convert an execution primitive failure for a register load into a ProcessorSimulationTrap signal."
+ 	| modrmByte mode srcIsSP srcVal dst offset |
+ 	modrmByte := memoryArray byteAt: pc + 3.
+ 	mode := modrmByte >> 6 bitAnd: 3.
+ 	srcIsSP := (modrmByte bitAnd: 7) = 4.
+ 	srcVal := self perform: (#(eax ecx edx ebx esp ebp esi edi) at: (modrmByte bitAnd: 7) + 1).
+ 	dst := #(eax: ecx: edx: ebx: esp: ebp: esi: edi:) at: ((modrmByte >> 3 bitAnd: 7) + 1).
+ 	mode = 1 ifTrue: "ModRegRegDisp8"
+ 		[offset := memoryArray byteAt: pc + (srcIsSP ifTrue: [5] ifFalse: [4]). "1-relative"
+ 		 offset > 127 ifTrue: [offset := offset - 256].
+ 		 ^(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + (srcIsSP ifTrue: [5] ifFalse: [4])
+ 					address: ((srcVal + offset) bitAnd: 16rFFFFFFFF)
+ 					type: #read
+ 					accessor: dst)
+ 				signal].
+ 	mode = 2 ifTrue: "ModRegRegDisp32"
+ 		[offset := memoryArray unsignedLongAt: pc + (srcIsSP ifTrue: [5] ifFalse: [4]). "1-relative"
+ 		 ^(ProcessorSimulationTrap
+ 					pc: pc
+ 					nextpc: pc + (srcIsSP ifTrue: [8] ifFalse: [7])
+ 					address: ((srcVal + offset) bitAnd: 16rFFFFFFFF)
+ 					type: #read
+ 					accessor: dst)
+ 				signal].
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: BochsIA32Alien>>movGvEbOpcode (in category 'opcodes') -----
+ movGvEbOpcode
+ 	"[1] IA-32 Intel® Architecture Software Developer's Manual Volume 2B: Instruction Set Reference, N-Z.
+ 		table A3, pA14"
+ 	^16rB6!

Item was changed:
  ----- Method: GdbARMAlien>>decorateDisassembly:for:fromAddress: (in category 'disassembly') -----
  decorateDisassembly: anInstructionString for: aSymbolManager fromAddress: address
  "Decode what we can of the instruction and decorate it with useful stuff"
  	| word opcode rotate mode operand memory addressinatorBlock|
  	addressinatorBlock := [:value|
  		(aSymbolManager lookupAddress: value)
  		ifNotNil: [:string| ' = ', value hex, ' = ', string]
  		ifNil: [' = ', value hex]].
  	
  	word := (memory:= aSymbolManager objectMemory) longAt: address.
  	(self instructionIsAnyB: word)
  		ifTrue:
  			[((self instructionIsB: word) or: [self instructionIsBL: word])
  				ifTrue:["We can extract the offset from a plain B/BL instruction"
  					operand := self extractOffsetFromBL: word..
  					 operand := operand + address + 8 bitAnd: aSymbolManager addressSpaceMask].
  			((self instructionIsBX: word) or: [self instructionIsBLX: word])
  				ifTrue:["We can extract the offset from a  BX/BLX instructions register"			
  					operand := (self perform: (self registerStateGetters at: (word bitAnd: 15) + 1))]]
  		ifFalse:
  			[(self instructionIsAnyLoadStore: word)
  				ifTrue: [|baseR|
  					"first see if this is a load via the varBase register - quick access globals. We'll trust
  					that nobody makes a nasty instruction that uses this reg in a mean way" 
  					(baseR := (word >> 16 bitAnd: 15)) = CogARMCompiler VarBaseReg
  						ifTrue:[ operand := aSymbolManager varBaseAddress + (word bitAnd: 1 << 12 - 1)]
  						ifFalse:[ operand := (self register: baseR) + (self extractOffsetFromLoadStore: word)].
  
  					"look for SP operations -pop/push"
  					 (self instructionIsPush: word) ifTrue: ["push - "
  						|srcR|
  						srcR := word >>12 bitAnd: 16rF.
  						^ (anInstructionString readStream upTo: $}), '}  (', (self register: srcR) hex, ') to ',  (self sp - 4) hex ].
  					(self instructionIsPop: word) ifTrue: ["pop - " 
  						^ (anInstructionString readStream upTo: $}), '}  (', (memory longAt: self sp) hex, ') ' , ' from ' , self sp hex ].
  
  					"look for a ld/st of the sp"
  					(self instructionIsLDRSP: word) ifTrue:[| val |
  						val := operand > memory memory size
  											ifTrue: [aSymbolManager simulatedVariableAt: operand ]
  											ifFalse: [memory longAt: operand].
+ 						^anInstructionString, '; Load SP (', (val ifNil:['unknown'] ifNotNil:[:v| v hex]) , ') from ', (addressinatorBlock value: operand)].
- 						^anInstructionString, '; Load SP (', val hex, ') from ', (addressinatorBlock value: operand)].
  					(self instructionIsSTRSP: word) ifTrue:[
  						^anInstructionString, '; Save SP (', self sp hex, ') to ',  (addressinatorBlock value: operand)].
  					]
  				ifFalse:
  					["check for SP changers not relating to read/writing data"
  					(self instructionIsAlignSP: word)
  						ifTrue: [^anInstructionString, ' ALIGN SP ' , self sp hex; cr].
  					(self instructionIsAddSP: word)
  						ifTrue:[^anInstructionString, ' ADD ', (word bitAnd: 16rFF) asString,' to SP = ' , self sp hex].				
  
  					"check for the end of a mov/orr/orr/orr set filling a reg with a const"
  					opcode := word >> 21 bitAnd: 16rF.
  					 opcode ~= CogARMCompiler orOpcode ifTrue:
  						[^anInstructionString].
  					 rotate := word >> 8 bitAnd: 16rF.
  					 mode := word >> 25 bitAnd: 7.
  					 "CogARMCompiler always uses a 0 rotate in the last operand of the final ORR when building long constants."
  					 (mode = 1 and: [rotate ~= 0]) ifTrue:
  						[^anInstructionString].
  					 operand := aSymbolManager backEnd literalBeforeFollowingAddress: address + 4]].
  	"is there an interesting address with this?"
+ 	^anInstructionString", (addressinatorBlock value: operand) <-------------- NEEDS FIXING BETTERER"!
- 	^anInstructionString, (addressinatorBlock value: operand)!

Item was changed:
  ----- Method: GdbARMAlien>>simulateCallOf:nextpc:memory: (in category 'execution simulation') -----
  simulateCallOf: address nextpc: nextpc memory: aMemory
  	"Simulate a frame-building call of address.  Build a frame since
  	a) this is used for calls into the run-time which are unlikely to be leaf-calls"
  	"This method builds a stack frame as expected by the simulator, not as defined by ARM aapcs-abi.
  	In ARM aapcs, every method can define for itself, wether it wants to push lr (nextpc), and wether it 
  	uses a frame pointer. The standard never mentions a fp. It merely defines r4-r11 to be callee-saved."
  
+ 	self pushWord: self lr in: aMemory.
- 	self pushWord: nextpc in: aMemory.
  	self pushWord: self fp in: aMemory.
  	self fp: self sp.
  	PostBuildStackDelta ~= 0 ifTrue:
  		[self sp: self sp - PostBuildStackDelta]. "In order to satisfy the CStackAlignment check by cogit, which is only valid on IA32 platforms."
  	self pc: address!



More information about the Vm-dev mailing list