[Vm-dev] VM Maker: GDB-bgs.4.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Jun 1 23:00:26 UTC 2020


Boris G. Shingarov uploaded a new version of GDB to project VM Maker:
http://source.squeak.org/VMMaker/GDB-bgs.4.mcz

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

Name: GDB-bgs.4
Author: bgs
Time: 1 June 2020, 7:00:25.45531 pm
UUID: 80860b50-a7b5-42db-b03c-a85e87a262ec
Ancestors: GDB-bgs.3

Add TargetAwareARM.
Simulated REPL works.

=============== Diff against GDB-bgs.3 ===============

Item was added:
+ FakeProcessorDescription subclass: #FakeProcessorDescriptionARM
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'GDB-Doodles'!

Item was added:
+ ----- Method: FakeProcessorDescriptionARM class>>endian (in category 'as yet unclassified') -----
+ endian 
+ 	^#little!

Item was added:
+ ----- Method: FakeProcessorDescriptionARM class>>fakeFeatures (in category 'as yet unclassified') -----
+ fakeFeatures
+ 	^self fakeFeaturesGem5!

Item was added:
+ ----- Method: FakeProcessorDescriptionARM class>>fakeFeaturesGem5 (in category 'as yet unclassified') -----
+ fakeFeaturesGem5
+ 	^#(
+ "org.gnu.gdb.arm.core"
+ #('r0' 32)  #('r1' 32)  #('r2' 32)  #('r3' 32)  #('r4' 32)  #('r5' 32)  #('r6' 32)  #('r7' 32)
+ #('r8' 32)  #('r9' 32)  #('r10' 32) #('r11' 32) #('r12' 32) #('sp' 32) #('lr' 32) #('pc' 32)
+ 
+ "The CPSR is register 25, rather than register 16, because
+  the FPA registers historically were placed between the PC
+  and the CPSR in the G packet."
+ #('cpsr' 32) "regnum=25????"
+ 
+ "org.gnu.gdb.arm.vfp"
+ #('d0' 64)  #('d1' 64)  #('d2' 64)  #('d3' 64)  #('d4' 64)  #('d5' 64)  #('d6' 64)  #('d7' 64)
+ #('d8' 64)  #('d9' 64)  #('d10' 64)  #('d11' 64)  #('d12' 64)  #('d13' 64)  #('d14' 64)  #('d15' 64)
+ #('d16' 64)  #('d17' 64)  #('d18' 64)  #('d19' 64)  #('d20' 64)  #('d21' 64)  #('d22' 64)  #('d23' 64)
+ #('d24' 64)  #('d25' 64)  #('d26' 64)  #('d27' 64)  #('d28' 64)  #('d29' 64)  #('d30' 64)  #('d31' 64)
+ #('fpscr' 32)
+ )
+ !

Item was added:
+ ----- Method: FakeProcessorDescriptionARM>>architectureName (in category 'as yet unclassified') -----
+ architectureName
+ 	^'arm'!

Item was added:
+ ----- Method: FakeProcessorDescriptionARM>>pcRegisterName (in category 'as yet unclassified') -----
+ pcRegisterName
+ 	^'pc'!

Item was changed:
+ ----- Method: FakeProcessorDescriptionX86>>architectureName (in category 'for DUI') -----
- ----- Method: FakeProcessorDescriptionX86>>architectureName (in category 'as yet unclassified') -----
  architectureName
  	^'x86'!

Item was changed:
+ ----- Method: FakeProcessorDescriptionX86>>z1kind (in category 'for HWBKPT') -----
- ----- Method: FakeProcessorDescriptionX86>>z1kind (in category 'as yet unclassified') -----
  z1kind
  	^1!

Item was changed:
  ----- Method: RemoteGDBSession>>pc (in category 'RSP commands') -----
  pc
+ 	^self getRegister: self processorDescription pcRegisterName !
- 	^self getRegisters at: self processorDescription pcRegisterName !

Item was changed:
  ----- Method: SharedRAM>>byteAtAddr:put: (in category 'writing') -----
  byteAtAddr: byteAddress put: byte
  	| ptr |
- byteAddress = 16r109014 ifTrue: [self halt].
  	ptr := self translate: byteAddress.
  	ptr unsignedByteAt: 1 put: byte!

Item was changed:
  ----- Method: SimulationAddressSpace class>>new: (in category 'as yet unclassified') -----
  new: bytes
  	"I really hate this design.
  	The only reason #new: is here is because there is no concept of conneciton
  	between the processor and memory."
  	| instance |
+ 	instance := self gdb: TargetAware current gdb.
- 	instance := self gdb: TargetAwareX86 current gdb.
  	instance shmemSize: 120*1024*1024.
+ 	TargetAware current class zeroROChunkIn: instance.
  	^instance!

Item was added:
+ Object subclass: #TargetAware
+ 	instanceVariableNames: 'gdb'
+ 	classVariableNames: 'Current'
+ 	poolDictionaries: ''
+ 	category: 'GDB-Cog'!

Item was added:
+ ----- Method: TargetAware class>>current (in category 'instance creation') -----
+ current
+ 	^Current !

Item was added:
+ ----- Method: TargetAware class>>new (in category 'instance creation') -----
+ new
+ 	"
+ 	TargetAwareX86 new
+ 	"
+ 	Current := super new connectGdb.
+ 	^Current !

Item was added:
+ ----- Method: TargetAware class>>nukeCurrent (in category 'instance creation') -----
+ nukeCurrent
+ 	Current := nil !

Item was added:
+ ----- Method: TargetAware class>>printTempNames (in category 'class initialization') -----
+ printTempNames
+ 	^false!

Item was added:
+ ----- Method: TargetAware class>>printTempNames: (in category 'class initialization') -----
+ printTempNames: x!

Item was added:
+ ----- Method: TargetAware class>>remoteMemoryClass (in category 'machine description') -----
+ remoteMemoryClass
+ 	^self isHardware
+ 		ifTrue: [SimpleSharedRAM]
+ 		ifFalse: [Gem5SharedRAM]!

Item was added:
+ ----- Method: TargetAware class>>setReceiverResultReg: (in category 'class initialization') -----
+ setReceiverResultReg:  x!

Item was added:
+ ----- Method: TargetAware class>>zeroROChunkIn: (in category 'machine description') -----
+ zeroROChunkIn: aMemory
+ 	| first last |
+ 	first := Cogit guardPageSize.
+ 	last := first + self nZoneSize - 1.
+ 	first to: last do: [ :addr | aMemory byteAtAddr: addr put: 0 ]
+ !

Item was added:
+ ----- Method: TargetAware>>accessorIsFramePointerSetter: (in category 'accessing-abstract') -----
+ accessorIsFramePointerSetter: accessor
+ 	"Answer if accessor is an accessor for the frame pointer.  Subclasses that don't call
+ 	 it fp must override to check for both names."
+ 	^#fp: == accessor!

Item was added:
+ ----- Method: TargetAware>>bogusRetPC (in category 'entering execution') -----
+ bogusRetPC
+ 	^16rBADF00D5!

Item was added:
+ ----- Method: TargetAware>>connectGdb (in category 'target connection') -----
+ connectGdb
+ 	gdb := self debuggerClass
+ 		host: self hostIP
+ 		port: self tcpPort
+ 		processorDescription: self pdl.
+ 	self runThinshellPrologue.
+ 	^self "not gdb; #new needs the instance"!

Item was added:
+ ----- Method: TargetAware>>convertIntegerToInternal: (in category 'tests support') -----
+ convertIntegerToInternal: anInteger
+ 	"Default conversion for 32-bit processors.  64-bit processors override."
+ 	^anInteger signedIntToLong!

Item was added:
+ ----- Method: TargetAware>>convertInternalToInteger: (in category 'tests support') -----
+ convertInternalToInteger: unsigned
+ 	"Default conversion for 32-bit processors.  64-bit processors override."
+ 	^unsigned signedIntFromLong!

Item was added:
+ ----- Method: TargetAware>>debuggerClass (in category 'target connection') -----
+ debuggerClass
+ 	^RemoteGDBSession!

Item was added:
+ ----- Method: TargetAware>>gdb (in category 'target connection') -----
+ gdb
+ 	^gdb!

Item was added:
+ ----- Method: TargetAware>>handleExecutionPrimitiveFailureAt:in: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Handle an execution primitive failure for an unhandled opcode."
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAware>>handleExecutionPrimitiveFailureIn:minimumAddress: (in category 'execution') -----
+ handleExecutionPrimitiveFailureIn: memoryArray minimumAddress: minimumAddress
+ 	"Execution stopped due to SIGSEGV.
+ 	Convert out-of-range call and absolute memory read-into-register instructions
+ 	into ProcessorSimulationTrap signals."
+ 
+ 	"The SEGV could be caused by Fetching from an unmapped address,
+ 	or a data operation with an unmapped address.
+ 	While a simulator such as gem5 could tell us what caused the fault,
+ 	real hardware such as silicon i386 doesn't provide an easy way;
+ 	therefore, we have to look at circumstancial evidence."
+ 	(self isWithinMappedRange: self pc)
+ 		ifTrue: [ ^self handleDataFailureIn: memoryArray ]
+ 		ifFalse: [ ^self handlePcOutOfRangeIn: memoryArray ]!

Item was added:
+ ----- Method: TargetAware>>handlePcOutOfRangeIn: (in category 'error handling') -----
+ handlePcOutOfRangeIn: memoryArray
+ 	| pc |
+ 	pc := self pc.
+ 	pc = self bogusRetPC ifTrue: [ ^self cResultRegister ].
+ 	^(ProcessorSimulationTrap
+ 			pc: nil
+ 			nextpc: nil
+ 			address: pc
+ 			type: #controlTransfer)
+ 		signal!

Item was added:
+ ----- Method: TargetAware>>hostIP (in category 'target connection') -----
+ hostIP
+ 	^'192.168.75.2'!

Item was added:
+ ----- Method: TargetAware>>isWithinMappedRange: (in category 'execution') -----
+ isWithinMappedRange: anAddress
+ 	| minimumAddress maximumAddress |
+ 	minimumAddress := 4096.
+ 	maximumAddress := 120*1024*1024 - 1.
+ 	^anAddress >= minimumAddress and: [ anAddress <= maximumAddress ]!

Item was added:
+ ----- Method: TargetAware>>pdl (in category 'target connection') -----
+ pdl
+ 	self subclassResponsibility!

Item was added:
+ ----- Method: TargetAware>>runInMemory:minimumAddress: (in category 'execution') -----
+ runInMemory: aMemory minimumAddress: minimumAddress
+ 	| stopReason |
+ 	stopReason := gdb c.
+ 	stopReason signal = #SIGSEGV ifTrue: [
+ 		^self
+ 			handleExecutionPrimitiveFailureIn: aMemory
+ 			minimumAddress: minimumAddress ].
+ 	stopReason signal = #SIGQUIT ifTrue: [ ^self halt ].
+ 
+ 	"There can be a number of other reasons to stop.
+ 	For example, a debug breakpoint."
+ 	self shouldBeImplemented!

Item was added:
+ ----- Method: TargetAware>>runInMemory:minimumAddress:readOnlyBelow: (in category 'execution') -----
+ runInMemory: aMemory minimumAddress: minimumAddress readOnlyBelow: minimumWritableAddress
+ 	^self runInMemory: aMemory minimumAddress: minimumAddress!

Item was added:
+ ----- Method: TargetAware>>runThinshellPrologue (in category 'target connection') -----
+ runThinshellPrologue
+ 	"Run the thinshell's _start to do whatever initialization it needs,
+ 	until it stops (usually indicates 'I am done' by segfaulting or trapping)"
+ 	gdb c!

Item was added:
+ ----- Method: TargetAware>>smashRegistersWithValuesFrom:by: (in category 'accessing-abstract') -----
+ smashRegistersWithValuesFrom: base by: step
+ 	self smashRegisterAccessors
+ 	   withIndexDo:
+ 		[:accessor :index|
+ 		self perform: accessor with: index - 1 * step + base]!

Item was added:
+ ----- Method: TargetAware>>tcpPort (in category 'target connection') -----
+ tcpPort
+ 	^7000!

Item was added:
+ TargetAware subclass: #TargetAwareARM
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'LongConstReg LongConstStep LongConstValue PostBuildStackDelta'
+ 	poolDictionaries: ''
+ 	category: 'GDB-Cog'!
+ 
+ !TargetAwareARM commentStamp: 'eem 12/15/2018 14:31' prior: 0!
+ I am a wrapper around the ARMulator CPU instance and emulator routines and I give access to disassembling using libopcodes. My C-part must be compiled with -DMODET, because otherwise my offsets are wrong by one field.!

Item was added:
+ ----- Method: TargetAwareARM class>>implementationClass (in category 'instance creation') -----
+ implementationClass
+ 	^TargetAwareARM!

Item was added:
+ ----- Method: TargetAwareARM class>>isHardware (in category 'machine description') -----
+ isHardware
+ 	"Answer true if we are running on an actual hardware target.
+ 	Browse senders to see all places where gem5 differs from silicon."
+ 
+ 	^false!

Item was added:
+ ----- Method: TargetAwareARM class>>nZoneSize (in category 'machine description') -----
+ nZoneSize
+ 	^16r140000!

Item was added:
+ ----- Method: TargetAwareARM class>>wordSize (in category 'machine description') -----
+ wordSize
+ 	^4!

Item was added:
+ ----- Method: TargetAwareARM>>XXXhandleExecutionPrimitiveFailureIn:minimumAddress: (in category 'error handling') -----
+ XXXhandleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>"
+ 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
+ 	 memory read into register instructions into ProcessorSimulationTrap signals."
+ 	"self printRegistersOn: Transcript"
+ 	| pcOnEntry pc instr |
+ 	pc := pcOnEntry := self pc.
+ 	self endCondition = #InstructionPrefetchError ifTrue:
+ 		[pc := self pc: self priorPc].
+ 
+ 	(pc between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
+ 		[instr := memoryArray unsignedLongAt:  pc + 1 bigEndian: false.
+ 
+ 		 (self endCondition = #InstructionPrefetchError) ifTrue:
+ 			[^self handleFailingBranch: instr to: pcOnEntry at: pc].
+ 
+ 		 (self instructionIsAnyLoadStore: instr) ifTrue:
+ 			[^self handleFailingLoadStore: instr at: pc].
+ 
+ 		 (self instructionIsAnyFPArithmetic: instr) ifTrue:
+ 			[^self handleFailingFPArithmetic: instr at: pc].
+ 
+ 		 ^self handleExecutionPrimitiveFailureAt: pc in: memoryArray].
+ 
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAwareARM>>abstractInstructionCompilerClass (in category 'Cog API') -----
+ abstractInstructionCompilerClass
+ 	^CogARMCompiler!

Item was added:
+ ----- Method: TargetAwareARM>>bitsInWord (in category 'Cog API') -----
+ bitsInWord
+ 	^32!

Item was added:
+ ----- Method: TargetAwareARM>>byteSwappedNopOpcode (in category 'opcodes') -----
+ byteSwappedNopOpcode
+ 	"For the Tsts class which keeps filling BitMaps with nop, provide one swapped so it turns out correct when disassembled
+ 	mov r0, r0 swapped -> "
+ 	^ 16r00000A0E1!

Item was added:
+ ----- Method: TargetAwareARM>>cResultRegister (in category 'accessing-abstract') -----
+ cResultRegister
+ 	^self r0!

Item was added:
+ ----- Method: TargetAwareARM>>cResultRegister: (in category 'accessing-abstract') -----
+ cResultRegister: aValue
+ 	self r0: aValue!

Item was added:
+ ----- Method: TargetAwareARM>>cflag (in category 'accessing-registers') -----
+ cflag
+ 	"Bit 29 in the cpsr: Carry condition code flag."
+ 	^self rawCPSR >> 29 bitAnd: 1.!

Item was added:
+ ----- Method: TargetAwareARM>>cflag: (in category 'accessing-registers') -----
+ cflag: unsignedInteger
+ 	^self setCPSRbit: 29 to: unsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>controlRegisterGetters (in category 'accessing-abstract') -----
+ controlRegisterGetters
+ 	^#(pc eflags)!

Item was added:
+ ----- Method: TargetAwareARM>>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| | string |
+ 		(value notNil
+ 		 and: [(string := aSymbolManager lookupAddress: value) notNil])
+ 			ifTrue: [ ' = ', value hex, ' = ', string]
+ 			ifFalse: ['']].
+ 	
+ 	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].
+ 			"We can't extract the offset from a  BX/BLX instructions register, unless we're at the current pc,
+ 			 because otherwise its current value has nothing to do with the value when this instruction is executed."
+ 			(self pc = address
+ 			 and: [(self instructionIsBX: word) or: [self instructionIsBLX: word]]) ifTrue:
+ 					[operand := (self perform: (self registerStateGetters at: (word bitAnd: 15) + 1))]]
+ 		ifFalse:
+ 			[(self instructionIsAnyLoadStore: word)
+ 				ifTrue:
+ 					[|baseR lit|
+ 					"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" 
+ 					operand := (baseR := (word >> 16 bitAnd: 15)) = CogARMCompiler VarBaseReg
+ 									ifTrue: [aSymbolManager varBaseAddress + (word bitAnd: 1 << 12 - 1)]
+ 									ifFalse: [self pc = address ifTrue:
+ 												[(self register: baseR) + (self extractOffsetFromLoadStore: word)]].
+ 					"See if this is a pc-relative literal load"
+ 					baseR = CogARMCompiler PCReg ifTrue:
+ 						[lit := memory longAt: (aSymbolManager backEnd pcRelativeAddressAt: address).
+ 						 ^(aSymbolManager lookupAddress: lit)
+ 							ifNotNil: [:label| anInstructionString, ' ', label]
+ 							ifNil: [anInstructionString, ' ', lit hex]].
+ 					"look for SP operations -pop/push"
+ 					 (self instructionIsPush: word) ifTrue: "push - "
+ 						[|srcR|
+ 						srcR := word >>12 bitAnd: 16rF.
+ 						^ (anInstructionString readStream upTo: $}), '}', (self pc = address ifTrue: ['  (', (self register: srcR) hex, ') to ',  (self sp - 4) hex] ifFalse: [''])].
+ 					(self instructionIsPop: word) ifTrue: "pop - " 
+ 						[^ (anInstructionString readStream upTo: $}), '}', (self pc = address ifTrue: ['  (', (memory longAt: self sp) hex, ') ' , ' from ' , self sp hex] ifFalse: [''])].
+ 
+ 					"look for a ld/st of the sp"
+ 					(self instructionIsLDRSP: word) ifTrue:
+ 						[^anInstructionString, '; Load SP from ', (addressinatorBlock value: operand)].
+ 					(self instructionIsSTRSP: word) ifTrue:
+ 						[^anInstructionString, '; Save SP to ', (addressinatorBlock value: operand)]]
+ 				ifFalse:
+ 					["check for SP changers not relating to read/writing data"
+ 					 (self instructionIsAlignSP: word) ifTrue:
+ 						[^anInstructionString, ' ALIGN SP ', (self pc = address ifTrue: [self sp hex] ifFalse: [''])].
+ 					 (self instructionIsAddSP: word) ifTrue:
+ 						[^anInstructionString, ' ADD ', (word bitAnd: 16rFF) asString,' to SP ', (self pc = address ifTrue: ['= ' , self sp hex] ifFalse: [''])].
+ 
+ 					 "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
+ 					  or: [aSymbolManager cogit backEnd literalLoadInstructionBytes = 4]) 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)!

Item was added:
+ ----- Method: TargetAwareARM>>disassembleFrom:to:in:for:labels:on: (in category 'disassembly') -----
+ disassembleFrom: startAddress to: endAddress in: memory for: aSymbolManager "<Cogit>" labels: labelDictionary on: aStream
+ 	| address |
+ 	address := startAddress.
+ 	[address <= endAddress] whileTrue:
+ 		[[:sizeArg :stringArg| | size string index offset |
+ 		size := sizeArg.
+ 		string := stringArg.
+ 		(aSymbolManager labelForPC: address) ifNotNil:
+ 			[:label| aStream nextPutAll: label; nextPut: $:; cr].
+ 		(labelDictionary at: address ifAbsent: []) ifNotNil:
+ 			[:label|
+ 			self printLabel: label on: aStream at: address for: aSymbolManager.
+ 			label isArray ifTrue:
+ 				[string := nil.
+ 				 size := label third]].
+ 		string ifNotNil:
+ 			[aStream nextPutAll: (self decorateDisassembly: string for: aSymbolManager fromAddress: address).
+ 			 (string includesSubstring: ': ldr	') ifTrue:"i.e. colon space 'ldr' tab" 
+ 				[(index := string indexOfSubCollection: ' [pc, #' startingAt: 1) > 0
+ 					ifTrue:
+ 						[offset := Integer readFrom: (ReadStream on: string from: index + 7 to: (string indexOf: $] startingAt: index + 7) - 1)]
+ 					ifFalse:
+ 						[(string indexOfSubCollection: ' [pc]' startingAt: 1) > 0 ifTrue:
+ 							[offset := 0]].
+ 				 offset ifNotNil:
+ 					[offset := address + 8 + offset.
+ 					 labelDictionary
+ 						at: offset
+ 						ifPresent:
+ 							[:entry|
+ 							entry isString
+ 								ifTrue: [labelDictionary at: offset put: {#literal. offset. 4. entry}]
+ 								ifFalse: [self assert: (entry isArray and: [entry first == #literal])]]
+ 						ifAbsentPut: [{#literal. offset. 4}]]]].
+ 		aStream cr; flush.
+ 		address := address + size]
+ 			valueWithArguments: (self
+ 									primitiveDisassembleAt: address
+ 									inMemory: memory)].
+ 	(labelDictionary at: address ifAbsent: []) ifNotNil:
+ 		[:label| self printLabel: label on: aStream at: address for: aSymbolManager]!

Item was added:
+ ----- Method: TargetAwareARM>>doesNotUnderstand: (in category 'accessing-registers') -----
+ doesNotUnderstand: msg
+ 	msg numArgs = 0 ifTrue: [^self doesNotUnderstandRegGetter: msg].
+ 	msg numArgs = 1 ifTrue: [^self doesNotUnderstandRegSetter: msg].
+ 	^super doesNotUnderstand: msg!

Item was added:
+ ----- Method: TargetAwareARM>>doesNotUnderstandRegGetter: (in category 'accessing-registers') -----
+ doesNotUnderstandRegGetter: msg
+ 	| regName |
+ 	regName := msg selector asString.
+ 	^self gdb getRegisters at: regName ifAbsent: [super doesNotUnderstand: msg].
+ !

Item was added:
+ ----- Method: TargetAwareARM>>doesNotUnderstandRegSetter: (in category 'accessing-registers') -----
+ doesNotUnderstandRegSetter: msg
+ 	| regName x |
+ 	regName := msg selector asString allButLast.
+ 	(gdb getRegisters includesKey: regName) ifFalse: [^super doesNotUnderstand: msg].
+ 	x := msg arguments first.
+ 	gdb setRegister: regName to: x.
+ 	^x!

Item was added:
+ ----- Method: TargetAwareARM>>eflags (in category 'accessing') -----
+ eflags
+ 	
+ 	^ (((self nflag << 5 bitOr: self zflag << 4) 
+ 			bitOr: self cflag << 3) 
+ 				bitOr: self vflag << 2)
+ 					bitOr: self ifflags!

Item was added:
+ ----- Method: TargetAwareARM>>eflags: (in category 'accessing') -----
+ eflags: anUnsignedInteger
+ 	"set the processor flags from the integer"
+ 	self nflag: (anUnsignedInteger >> 5 bitAnd: 1).
+ 	self zflag: (anUnsignedInteger >> 4 bitAnd: 1).
+ 	self cflag: (anUnsignedInteger >> 3 bitAnd: 1).
+ 	self vflag: (anUnsignedInteger >> 2 bitAnd: 1).
+ 	self ifflags: (anUnsignedInteger bitAnd: 3)!

Item was added:
+ ----- Method: TargetAwareARM>>endCondition (in category 'accessing') -----
+ endCondition
+ "why did the simulator stop?"
+ 	^self shouldBeImplemented!

Item was added:
+ ----- Method: TargetAwareARM>>endianness (in category 'accessing-abstract') -----
+ endianness
+ 	^#little!

Item was added:
+ ----- Method: TargetAwareARM>>errorCode (in category 'accessing') -----
+ errorCode
+ "simulator error code"
+ 	^self shouldBeImplemented!

Item was added:
+ ----- Method: TargetAwareARM>>extractOffsetFromBL: (in category 'testing') -----
+ extractOffsetFromBL: instr
+ "we are told this is a BL <offset> instruction, so work out the offset it encodes"
+ 	| relativeJump |
+ 	relativeJump := instr bitAnd: 16r00FFFFFF.
+ 	(relativeJump bitShift: -23) = 0 ifTrue:
+ 		[^relativeJump bitShift: 2].
+ 	^((relativeJump bitOr: 16r3F000000) bitShift: 2) signedIntFromLong!

Item was added:
+ ----- Method: TargetAwareARM>>extractOffsetFromLoadStore: (in category 'accessing-abstract') -----
+ extractOffsetFromLoadStore: instr
+ "work out the address offset implied by instr.
+ We assume it has been determined it is actually a load store before attaching any meaning to the result.
+ If it is post-indexed, then the offset must be 0, no matter what else is encoded.
+ If the instr is immediate-offset, pull the relevent bits out of instr.
+ If it is register-offset, pull the value from the indicated register."
+ 	|offset shiftAmt shiftType |
+ 
+ 	"post-indexed means no offset to the read address"
+ 	(instr bitAnd: 1 << 24) = 0 ifTrue:[^0].
+ 	
+ 	(self instructionIsImmediateOffsetLoadStore: instr)
+ 		ifTrue:["two cases apply - a 12bit immediate for 010 group instructions and an 8bit for 000 group ldrh stuff"
+ 			(instr >> 25 bitAnd: 7) = 2
+ 				ifTrue:[ "immed word or byte op, with 12bit offset"
+ 					offset := instr bitAnd: 16rFFF]
+ 				ifFalse:["halfword 8bit offset"
+ 					offset := (instr bitAnd: 16rF00)>>4 bitOr: (instr bitAnd: 16rF)]].
+ 
+ 	(self instructionIsRegisterOffsetLoadStore: instr)
+ 		ifTrue:["both forms use same offset-reg encoding"
+ 			offset := self perform:(self registerStateGetters at:(instr bitAnd: 16rF) + 1).
+ 			(instr >> 25 bitAnd: 7) = 3
+ 				ifTrue:[ "register offset with assorted modifiers"
+ 					"sort out modifiers"
+ 					shiftType := instr >> 5 bitAnd: 3.
+ 					shiftAmt := instr  >>7 bitAnd: 16r1F.
+ 					shiftType = 0"lsl" ifTrue:[offset := offset << shiftAmt.].
+ 					shiftType = 1"lsr" ifTrue:[offset := offset >> shiftAmt].
+ 					shiftType = 2"asr" ifTrue:[offset := offset  >>> shiftAmt].
+ 					"I refuse to countenance using ROR or RRX here. Just Say No" ]
+ 				"halfword stuff register offset uses no modifiers in the form we suport. See ARM DDI0406A p. A8-156"].
+ 
+ 	"all forms have the bit 23 up/down flag to account for"
+ 	(instr bitAnd: 1<<23) = 0
+ 						ifTrue:["-ve offset" ^offset negated]
+ 						ifFalse:["+ve offset" ^offset]	!

Item was added:
+ ----- Method: TargetAwareARM>>floatingPointRegisterStateGetters (in category 'accessing-abstract') -----
+ floatingPointRegisterStateGetters
+ 	^#(d0 d1 d2 d3 d4 d5 d6 d7 d8 d9 d10 d11 d12 d13 d14 d15)!

Item was added:
+ ----- Method: TargetAwareARM>>flushICacheFrom:to: (in category 'Cog API') -----
+ flushICacheFrom: anInteger to: anInteger2 
+ !

Item was added:
+ ----- Method: TargetAwareARM>>fp (in category 'accessing') -----
+ fp
+ 	^self r11!

Item was added:
+ ----- Method: TargetAwareARM>>fp: (in category 'accessing') -----
+ fp: anUnsignedInteger
+ 	^self r11: anUnsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>fpCPSR (in category 'accessing') -----
+ fpCPSR
+ 	"The VFP cpsr flags.  Return just the top 4 bits, the actual flags"
+ 	^self rawFPCPSR >>28!

Item was added:
+ ----- Method: TargetAwareARM>>handleBasicDoubleArithmetic:at: (in category 'floating-point emulation') -----
+ handleBasicDoubleArithmetic: instr at: pc
+ 	"Emulate a basic math - add/sub/mul/div -  VFP instruction."
+ 	| rn rd rm vn vm |
+ 	rn := instr >> 16 bitAnd: 15.
+ 	rd := instr >> 12 bitAnd: 15.
+ 	rm := instr bitAnd: 15.
+ 	vn := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rn + 18)). "Assume accesses fp regs"
+ 	vm := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rm + 18)). "Assume accesses fp regs"
+ 
+ 	"simplest to match the entire instruction pattern rather than mess around shifting and masking and merging"
+ 	(instr  bitAnd: 16rFF00FF0)
+ 		caseOf: {
+ 		[16rE200B00 "FMULD"]	->
+ 			[| r |
+ 			 r := vn * vm.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].
+ 		[16rE300B00 "FADDD"]	->
+ 			[| r |
+ 			 r := vn + vm.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].
+ 		[16rE300B40 "FSUBD"]	->
+ 			[| r |
+ 			 r := vn - vm.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].
+ 		[16rE800B00"FDIVD"]	->
+ 			[| r |
+ 			 r := vn / vm.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].}
+ 		otherwise: [self reportPrimitiveFailure].
+ 	self pc: pc + 4!

Item was added:
+ ----- Method: TargetAwareARM>>handleDataFailureIn: (in category 'error handling') -----
+ handleDataFailureIn: aMemory 
+ 	^self handleFailingLoadStore: aMemory currentInstructionEncoding at: self gdb pc!

Item was added:
+ ----- Method: TargetAwareARM>>handleExecutionPrimitiveFailureAt:in: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
+ 	"Handle an execution primitive failure for an otherwise unhandled opcode."
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAwareARM>>handleExecutionPrimitiveFailureIn:minimumAddress:code: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>"code: errorCode "<Integer>"
+ 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
+ 	 memory read into register instructions into ProcessorSimulationTrap signals."
+ 	"self printRegistersOn: Transcript"
+ 	| pcOnEntry pc instr |
+ 	pc := pcOnEntry := self pc.
+ 	errorCode = InstructionPrefetchError ifTrue:
+ 		[pc := self pc: self priorPc].
+ 
+ 	(pc between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
+ 		[instr := memoryArray unsignedLongAt:  pc + 1 bigEndian: false.
+ 
+ 		 errorCode = InstructionPrefetchError ifTrue:
+ 			[^self handleFailingBranch: instr to: pcOnEntry at: pc].
+ 
+ 		 (self instructionIsAnyLoadStore: instr) ifTrue:
+ 			[^self handleFailingLoadStore: instr at: pc].
+ 
+ 		 (self instructionIsAnyFPArithmetic: instr) ifTrue:
+ 			[^self handleFailingFPArithmetic: instr at: pc].
+ 
+ 		 ^self handleExecutionPrimitiveFailureAt: pc in: memoryArray].
+ 
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAwareARM>>handleExtendedDoubleArithmetic:at: (in category 'floating-point emulation') -----
+ handleExtendedDoubleArithmetic: instr at: pc
+ 	"Emulate an extended math - cmp/sqrt/sitod -  VFP instruction."
+ 	| rn rd rm vn vm vd |
+ 	rn := instr >> 16 bitAnd: 15.
+ 	rd := instr >> 12 bitAnd: 15.
+ 	rm := instr bitAnd: 15.
+ 	vn := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rn + 18)). "Assume accesses fp regs"
+ 	vm := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rm + 18)). "Assume accesses fp regs"
+ 
+ 	"simplest to match the entire instruction pattern rather than mess around shifting and masking and merging"
+ 	(instr  bitAnd: 16rFF00FF0)
+ 		caseOf: {
+ 		[16rEB80B80 "FCMPD"]	->
+ 			["read rd, compare with rm (ignore rn) and set FPSCR NZCV flags. Sigh"
+ 				vd := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rd + 18)).
+ 				self break].
+ 		[16rEB80BC0 "FSITOD"]	->
+ 			[| r |
+ 			 r := vm asFloat.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].
+ 		[16rEB10BC0 "FSQRTD"]	->
+ 			[| r |
+ 			 r := vm sqrt.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].
+ 		}
+ 		otherwise: [self reportPrimitiveFailure].
+ 	self pc: pc + 4!

Item was added:
+ ----- Method: TargetAwareARM>>handleFPLoadStore:at: (in category 'floating-point emulation') -----
+ handleFPLoadStore: instr at: pc
+ 	"Emulate a VFP load/store instruction."
+ 	| rn rd offset |
+ 	rn := instr >> 16 bitAnd: 15.
+ 	rd := instr >> 12 bitAnd: 15.
+ 	offset := instr bitAnd: 16rFF.
+ 
+ 	"examine the U and Lbits"
+ 	(instr >>20  bitAnd: 16rF)
+ 		caseOf: {
+ 		[0"Store neg"]	->
+ 			[| r addr|
+ 			addr := (self register: rn) - (offset<<2).
+ 			 r := self perform: (self registerStateGetters at: rd + 18).
+ 			 self unsignedLongLongAt: addr put: r].
+ 		[1"Load neg"]	->
+ 			[| r addr|
+ 			addr := (self register: rn) - (offset<<2).
+ 			r := self unsignedLongLongAt: addr.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r ].
+ 		[8"Store pos"]	->
+ 			[| r addr|
+ 			addr := (self register: rn) + (offset<<2).
+ 			 r := self perform: (self registerStateGetters at: rd + 18).
+ 			 self unsignedLongLongAt: addr put: r].
+ 		[9"Load pos"]	->
+ 			[| r addr|
+ 			addr := (self register: rn) + (offset<<2).
+ 			r := self unsignedLongLongAt: addr.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r ].}
+ 		otherwise: [self reportPrimitiveFailure].
+ 	self pc: pc + 4!

Item was added:
+ ----- Method: TargetAwareARM>>handleFPStatus:at: (in category 'floating-point emulation') -----
+ handleFPStatus: instr at: pc
+ 	"Emulate transferring the FP status to the ARM CPSR."
+ 	| fpcpsr |
+ 	fpcpsr := self fpCPSR.
+ 	self vflag: (fpcpsr bitAnd: 1).
+ 	self cflag: ((fpcpsr >>1) bitAnd: 1).
+ 	self zflag: ((fpcpsr >>2) bitAnd: 1).
+ 	self nflag: ((fpcpsr >>3) bitAnd: 1).
+ 	self pc: pc + 4!

Item was added:
+ ----- Method: TargetAwareARM>>handleFailingBranch:to:at: (in category 'error handling') -----
+ handleFailingBranch: instr to: address at: pc
+ 	(self instructionIsBL: instr) ifTrue:
+ 		[self assert: address = (pc + 8 + (self extractOffsetFromBL: instr)) signedIntToLong.
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: (pc + 8 + (self extractOffsetFromBL: instr)) signedIntToLong
+ 				type: #call)
+ 			signal].
+ 	(self instructionIsBLX: instr) ifTrue:
+ 		[self assert: address = (self perform: (self registerStateGetters at: (instr bitAnd: 15) + 1)).
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: address
+ 				type: #call)
+ 			signal].
+ 	(self instructionIsBX: instr) ifTrue:
+ 		[self assert: address = (self perform: (self registerStateGetters at: (instr bitAnd: 15) + 1)).
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: address
+ 				type: #jump)
+ 			signal].
+ 	(self instructionIsB: instr) ifTrue:
+ 		[self assert: address = (pc + 8 + (self extractOffsetFromBL: instr)) signedIntToLong.
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: address
+ 				type: #jump)
+ 			signal].
+ 	(self instructionIsReturnViaLR: instr) ifTrue:
+ 		[self assert: address = self lr.
+ 		 ^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: self lr
+ 				type: #return)
+ 			signal].
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAwareARM>>handleFailingFPArithmetic:at: (in category 'error handling') -----
+ handleFailingFPArithmetic: instr at: pc
+ 	
+ 	"basic arithmetic"
+ 	(instr bitAnd: 16rF400FB0) = 16rE000B00 ifTrue:
+ 		[^self handleBasicDoubleArithmetic: instr at: pc].
+ 	
+ 	"extension instructions sqrt/cmp/sitod"
+ 	(instr bitAnd: 16rFF00F70) = 16rEB00B40 ifTrue:
+ 		[^self handleExtendedDoubleArithmetic: instr at: pc].
+ 	
+ 	"move ARM reg to coproc reg. "
+ 	(instr bitAnd: 16rFF00FFF) = 16rE000A10 ifTrue:
+ 		[^self handleRegToDoubleTransfer: instr at: pc].
+ 
+ 	"move FPSCR reg to ARM CPSR"
+ 	(instr bitAnd: 16rFFFFFFF) = 16rEF1FA10 ifTrue:
+ 		[^self handleFPStatus: instr at: pc].
+ 
+ 	"load and store ops. All doubles; we only use FLDD & FSTD"
+ 	(instr bitAnd: 16rF600F00) = 16rD000B00 ifTrue:
+ 		[^self handleFPLoadStore: instr at: pc].
+ 	
+ 	
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAwareARM>>handleFailingLoadStore:at: (in category 'error handling') -----
+ handleFailingLoadStore: instr at: pc
+ 	"See e.g. ARM DDI0406A pp. A8-120, 124, 128, 132, 152, 156, etc. etc"
+ 	| baseReg regIdx destReg srcReg offset |
+ 
+ 	"find the register used as the base of the address and the register to load into or store from"
+ 	baseReg := self registerStateGetters at: ((instr bitShift: -16) bitAnd: 15) + 1.
+ 	srcReg :=  self registerStateGetters at: (regIdx := ((instr bitShift: -12) bitAnd: 15) + 1).
+ 	destReg := self registerStateSetters at: regIdx.
+ 
+ 	"work out the relevant offset, whether an immediate or register value"
+ 	offset := self extractOffsetFromLoadStore: instr.
+ 	
+ 	(self instructionIsLDR: instr) ifTrue:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4 
+ 				address: (self perform: baseReg) + offset
+ 				type: #read
+ 				accessor: destReg)
+ 			signal].
+ 	(self instructionIsSTR: instr) ifTrue:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4 
+ 				address: (self perform: baseReg) + offset
+ 				type: #write
+ 				accessor: srcReg)
+ 			signal].
+ 	(self instructionIsLDRB: instr) ifTrue:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4 
+ 				address: (self perform: baseReg) + offset
+ 				type: #read
+ 				accessor: destReg)
+ 			signal].
+ 	(self instructionIsSTRB: instr) ifTrue:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4 
+ 				address: (self perform: baseReg) + offset
+ 				type: #write
+ 				accessor: srcReg)
+ 			signal].
+ 	(self instructionIsLDRH: instr) ifTrue:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4 
+ 				address: (self perform: baseReg) + offset
+ 				type: #read
+ 				accessor: destReg)
+ 			signal].
+ 	(self instructionIsSTRH: instr) ifTrue:
+ 		[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4 
+ 				address: (self perform: baseReg) + offset
+ 				type: #write
+ 				accessor: srcReg)
+ 			signal].
+ 
+ 	self error: 'handleFailingLoadStore:at: invoked for non-load/store?'!

Item was added:
+ ----- Method: TargetAwareARM>>handleOneRegTransferDoubleArithmetic:at: (in category 'floating-point emulation') -----
+ handleOneRegTransferDoubleArithmetic: instr at: pc
+ 	"Emulate a one-register transfer VFP instruction."
+ 	| rn rd rm vn vm |
+ 	rn := instr >> 16 bitAnd: 15.
+ 	rd := instr >> 12 bitAnd: 15.
+ 	rm := instr bitAnd: 15.
+ 	vn := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rn + 18)). "Assume accesses fp regs"
+ 	vm := Float fromIEEE64BitWord: (self perform: (self registerStateGetters at: rm + 18)). "Assume accesses fp regs"
+ 	(instr >> 18 bitAnd: 31)
+ 		caseOf: {
+ 		[8 "FMULD"]	->
+ 			[| r |
+ 			 r := vn * vm.
+ 			 self perform: (self registerStateSetters at: rd + 18) with: r asIEEE64BitWord].
+ 		[12"FADDD/FSUBD"]	->
+ 			[self shouldBeImplemented].
+ 		[32"FDIVD"]	->
+ 			[self shouldBeImplemented].
+ 		[45"FCMPD"]	->
+ 			[self shouldBeImplemented]. }
+ 		otherwise: [self reportPrimitiveFailure].
+ 	self pc: pc + 4!

Item was added:
+ ----- Method: TargetAwareARM>>handleRegToDoubleTransfer:at: (in category 'floating-point emulation') -----
+ handleRegToDoubleTransfer: instr at: pc
+ 	"Emulate an ARM to VFP instruction."
+ 	| rn rd vn |
+ 	rn := (instr >> 16 bitAnd: 15) << 1 bitOr: (instr >>6 bitAnd: 1).
+ 	rd := instr >> 12 bitAnd: 15.
+ 	vn := self register: rn.
+ 
+ 	self perform: (self registerStateSetters at: rd + 18) with: vn.
+ 	self pc: pc + 4!

Item was added:
+ ----- Method: TargetAwareARM>>ifflags (in category 'accessing') -----
+ ifflags
+ 	"Bits 26:25 in the cpsr: If-Then execution state bits for the Thumb IT (If-Then) instruction."
+ 	^self rawCPSR >> 25 bitAnd: 3.!

Item was added:
+ ----- Method: TargetAwareARM>>ifflags: (in category 'accessing') -----
+ ifflags: unsignedInteger
+ 	| x y |
+ 	x := unsignedInteger >> 1 bitAnd: 1.
+ 	y := unsignedInteger bitAnd: 1.
+ 	self setCPSRbit: 26 to: x; setCPSRbit: 25 to: y!

Item was added:
+ ----- Method: TargetAwareARM>>initializeStackFor: (in category 'processor setup') -----
+ initializeStackFor: aCogit
+ 	"Different cpus need different stack alignment etc, so handle the details here."
+ 	aCogit setStackAlignment: 8 expectedSPOffset: 0 expectedFPOffset: 0.
+ 	PostBuildStackDelta := 0 !

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsAddSP: (in category 'testing') -----
+ instructionIsAddSP: instr
+ 	"is this an add sp, sp, #? -  instruction?"
+ 	^(instr bitShift: -28) < 16rF "test for allowed condcode - 0xF is extension"
+ 	  and: [(instr bitAnd: 16rFFFFF00) = 16r28DD000]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsAlignSP: (in category 'testing') -----
+ instructionIsAlignSP: instr
+ "is this a subs sp, sp, #4 -  instruction?"
+ 	^(instr bitShift: -28) < 16rF "test for allowed condcode - 0xF is extension"
+ 	  and: [(instr bitAnd: 16rFFFFFFF) = 16r2DDD004]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsAnyB: (in category 'testing') -----
+ instructionIsAnyB: instr 
+ 	"is this any of the B BX BL or BLX <offset> instructions?"
+ 	^ (self instructionIsB: instr)
+ 		or: [self instructionIsBL: instr]
+ 		or: [self instructionIsBLX: instr]
+ 		or: [self instructionIsBX: instr]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsAnyFPArithmetic: (in category 'testing') -----
+ instructionIsAnyFPArithmetic: instr
+ 	"Identify VFP instructions.
+ 	 See C3.1 - C3.4 in the ARM ARM v5 DDI01001."
+ 	| cp isFP |
+ 	
+ 	"All FP instructions are coprocessor instructions on coproc 10 or 11"
+ 	cp := (instr bitShift: -8) bitAnd: 16rF.
+ 	isFP := cp = 10 or:[cp = 11].
+ 	(isFP and: [((instr bitShift: -25) bitAnd: 7) = 6]) ifTrue: [^true].
+ 	(isFP and: [((instr bitShift: -24) bitAnd: 16rF) = 16rE]) ifTrue: [^true].
+ 	
+ 	"nope"
+ 	^false!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsAnyLoadStore: (in category 'testing') -----
+ instructionIsAnyLoadStore: instr
+ 	"is this any of the LDR,STR instructions?
+ 	We handle byte, word, and halfword versions but NOT NOT signed extend, double or privileged versions"
+ 	
+ 	^(self instructionIsImmediateOffsetLoadStore: instr) or:[self instructionIsRegisterOffsetLoadStore: instr]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsB: (in category 'testing') -----
+ instructionIsB: instr
+ "is this a B <offset> instruction?"
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	^(instr bitShift: -28) < 16rF
+ 	"See ARM DDI0406A p. A8-44"
+ 	 and: [((instr bitShift: -24) bitAnd: 16rF) = 16rA]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsBL: (in category 'testing') -----
+ instructionIsBL: instr
+ "is this a BL <offset> instruction?"
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	^(instr bitShift: -28) < 16rF
+ 	"see ARM DDI0406A p. A8-58"
+ 	  and: [((instr bitShift: -24) bitAnd: 16rF) = 16rB]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsBLX: (in category 'testing') -----
+ instructionIsBLX: instr
+ "is this a BLX <targetReg> instruction? We DO NOT support the BLX immed version"
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p A8-60"
+  	^(instr bitAnd: 16r0FFFFFF0) = 16r12FFF30!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsBX: (in category 'testing') -----
+ instructionIsBX: instr
+ "is this a BX <targetReg> instruction?"
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-62"
+  	^(instr bitAnd: 16r0FFFFFF0) = 16r12FFF10!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsImmediateOffsetLoadStore: (in category 'testing') -----
+ instructionIsImmediateOffsetLoadStore: instr
+ 	"is this any of the immediate offset LDR,STR instructions?"
+ 	| op1 |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"test for 010 group of load/stores"
+ 	op1 := (instr bitShift: -25) bitAnd: 7.
+ 	op1 = 2 ifTrue:[^true].
+ 
+ 	"test for the ridiculously muddled 000 group"
+ 	op1 > 0 ifTrue:[^false].
+ 	"bit 21 must not be 1 and bit 22 must be 1"
+ 	((instr bitShift: -21) bitAnd: 3) = 2 ifFalse:[^false].
+ 	"bits 4:7need to be 16rB for our purpose"
+ 	^(instr bitAnd: 16rF0) = 16rB0!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsLDR: (in category 'testing') -----
+ instructionIsLDR: instr
+ "is this a LDR instruction?"
+ 	| foo |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-120"
+ 	foo := (instr bitShift: -20) bitAnd: 16rE5.
+ 	^foo = 16r41 "ldr r1, [r2, #+/-imm]"
+ 		or:[foo = 16r61 "ldr r1, [r2, r3]"]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsLDRB: (in category 'testing') -----
+ instructionIsLDRB: instr
+ "is this a LDRB instruction?"
+ 	| foo |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-128"
+ 	foo := (instr bitShift: -20) bitAnd: 16rE5.
+ 	^foo = 16r45 "ldrb r1, [r2, #+/-imm]"
+ 		or:[foo = 16r65 "ldrb r1, [r2, r3]"]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsLDRH: (in category 'testing') -----
+ instructionIsLDRH: instr
+ "is this a LDRH instruction?"
+ 	| foo |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-154"
+ 	(instr bitAnd: 16rF0) = 16rB0 ifFalse:[^false].
+ 	foo := (instr bitShift: -20) bitAnd: 16rE3.
+ 	^foo = 16r3 "ldrh r1, [r2, #+/-imm]"
+ 		or:[foo = 16r1 "ldrh r1, [r2, r3]"]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsLDRSP: (in category 'testing') -----
+ instructionIsLDRSP: instr
+ "is this a LDR sp, [??] instruction? Special case to detect LDR sp, [] affecting stack pointer"
+ 	^(self instructionIsLDR: instr)  and:[((instr bitShift: -12) bitAnd: 16rF) = 13]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsPop: (in category 'testing') -----
+ instructionIsPop: instr
+ "is this a pop - ldr r??, [sp], #4 -  instruction?"
+ 	^(instr bitShift: -28) < 16rF "test for allowed condcode - 0xF is extension" and: [(instr bitAnd: (16rFFF0FFF)) = (16r49D0004)]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsPush: (in category 'testing') -----
+ instructionIsPush: instr
+ "is this a push -str r??, [sp, #-4] -  instruction?"
+ 	^(instr bitShift: -28) < 16rF "test for allowed condcode - 0xF is extension" and: [(instr bitAnd: (16rFFF0FFF)) = (16r52D0004)]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsRegisterOffsetLoadStore: (in category 'testing') -----
+ instructionIsRegisterOffsetLoadStore: instr
+ 	"is this any of the register offset LDR,STR instructions?"
+ 	| op1 |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	
+ 	op1 := (instr bitShift: -25) bitAnd: 7.
+ 	"test for the 011 group - check bit 4 as well"
+ 	(op1 = 3 and:[(instr bitAnd: 16r10) = 0]) ifTrue:[^true].
+ 	"test for the ridiculously muddled 000 group"
+ 	op1 > 0 ifTrue:[^false].
+ 	"bit 21 & 22 must not be 1"
+ 	((instr bitShift: -21) bitAnd: 3) = 0 ifFalse:[^false].
+ 	"bits 4:7need to be 16rB for our purpose"
+ 	^(instr bitAnd: 16rF0) = 16rB0!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsReturnViaLR: (in category 'testing') -----
+ instructionIsReturnViaLR: instr
+ "is this a MOV pc, lr instruction?"
+ 	^instr =  16rE1A0F00E!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsSTR: (in category 'testing') -----
+ instructionIsSTR: instr
+ "is this a STR instruction?"
+ 	| foo |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-382"
+  	foo := (instr bitShift: -20) bitAnd: 16rE5. 
+ 	^foo = 16r40 "str r1, [r2, #+/-imm]" 
+ 		or:[foo = 16r60] "str r1, [r2, #-imm]"!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsSTRB: (in category 'testing') -----
+ instructionIsSTRB: instr
+ "is this a STRB instruction?"
+ 	| foo |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-388"
+  	foo := (instr bitShift: -20) bitAnd: 16rE5. 
+ 	^foo = 16r44 "strb r1, [r2, #+/-imm]" 
+ 		or:[foo = 16r64] "strb r1, [r2, #-imm]"!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsSTRH: (in category 'testing') -----
+ instructionIsSTRH: instr
+ "is this a STRH instruction?"
+ 	| foo |
+ 	"first test for non-NV condition code; some important instructions use it"
+ 	(instr bitShift: -28) = 16rF ifTrue:[^false].
+ 	"See ARM DDI0406A p. A8-154"
+ 	(instr bitAnd: 16rF0) = 16rB0 ifFalse:[^false].
+ 	foo := (instr bitShift: -20) bitAnd: 16rE3.
+ 	^foo = 16r4 "strh r1, [r2, #+/-imm]"
+ 		or:[foo = 16r0 "strh r1, [r2, r3]"]!

Item was added:
+ ----- Method: TargetAwareARM>>instructionIsSTRSP: (in category 'testing') -----
+ instructionIsSTRSP: instr
+ "is this a STR sp, [??] instruction? Special case to detect STR sp, [] affecting stack pointer"
+ 	^(self instructionIsSTR: instr)  and:[((instr bitShift: -12) bitAnd: 16rF) = 13]!

Item was added:
+ ----- Method: TargetAwareARM>>integerRegisterState (in category 'accessing-abstract') -----
+ integerRegisterState
+ 	"Answer a WordArray of the integer registers, the pc and the flags."
+ 	^{	self r0. self r1. self r2. self r3. self r4. self r5. self r6. self r7. self r8. 
+ 		self r9. self sl. self fp. self r12. self sp. self lr. self pc. self rawCPSR}!

Item was added:
+ ----- Method: TargetAwareARM>>leafRetpcIn: (in category 'accessing-abstract') -----
+ leafRetpcIn: aMemory
+ 	"Answer the retpc assuming that the processor is in a simulated call established
+ 	 by simulateLeafCallOf:nextpc:memory:"
+ 	^self lr!

Item was added:
+ ----- Method: TargetAwareARM>>lr (in category 'accessing') -----
+ lr
+ 	^gdb getRegister: 'lr'
+ !

Item was added:
+ ----- Method: TargetAwareARM>>lr: (in category 'accessing') -----
+ lr: anUnsignedInteger
+ 	gdb setRegister: 'lr' to: anUnsignedInteger.
+ 	^anUnsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>nflag (in category 'accessing') -----
+ nflag
+ 	"Bit 31 in the cpsr: Negative condition code flag."
+ 	^self rawCPSR >> 31 bitAnd: 1.!

Item was added:
+ ----- Method: TargetAwareARM>>nflag: (in category 'accessing') -----
+ nflag: unsignedInteger
+ 	^self setCPSRbit: 31 to: unsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>nopOpcode (in category 'opcodes') -----
+ nopOpcode
+ 	"mov r0, r0"
+ 	^ 16rE1A00000!

Item was added:
+ ----- Method: TargetAwareARM>>pc (in category 'accessing') -----
+ pc
+ 	^gdb getRegister: 'pc'
+ !

Item was added:
+ ----- Method: TargetAwareARM>>pc: (in category 'accessing') -----
+ pc: anUnsignedInteger
+ 	gdb setRegister: 'pc' to: anUnsignedInteger.
+ 	^anUnsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>pdl (in category 'target connection') -----
+ pdl
+ 	^FakeProcessorDescriptionARM new!

Item was added:
+ ----- Method: TargetAwareARM>>popPcOpcode (in category 'opcodes') -----
+ popPcOpcode
+ "See also CogARMCompiler>concretizePopR"
+ 	^16rE49DF004!

Item was added:
+ ----- Method: TargetAwareARM>>popWordIn: (in category 'execution') -----
+ popWordIn: aMemory 
+ 	| sp word |
+ 	word := aMemory unsignedLongAt: (sp := self sp) + 1 bigEndian: false.
+ 	self sp: sp + 4.
+ 	^word!

Item was added:
+ ----- Method: TargetAwareARM>>postCallArgumentsNumArgs:in: (in category 'execution') -----
+ postCallArgumentsNumArgs: numArgs "<Integer>" in: memory "<ByteArray|Bitmap>"
+ 	"Answer an argument vector of the requested size after a vanilla
+ 	 ABI call. For ARM the Procedure Calling Specification can be found in IHI0042D_aapcs.pdf.
+ 	On ARM this typically means accessing r0 through r3 and fetching additional arguments from the stack, acording to pages 20f. aapcs.
+ 	We assume that all arguments are single word arguments, which can not be supplied on co-processor-registers.
+ 	 For compatibility with Cog/Slang we answer unsigned values."
+ 	^(1 to: numArgs) collect: [:i |
+ 		i < 5 
+ 			ifTrue: [self perform: (self registerStateGetters at: i)]
+ 			"ARM uses a full descending stack. Directly after calling a procedure, nothing but the arguments are pushed."
+ 			ifFalse: [memory unsignedLongAt: self sp + (i-5)*4 bigEndian: false]].!

Item was added:
+ ----- Method: TargetAwareARM>>primitiveDisassembleAt:inMemory: (in category 'primitives') -----
+ primitiveDisassembleAt: address inMemory: memory
+ 	| prefix theseBytes |
+ 	prefix := ByteArray new: address.
+ 	theseBytes := (address to: address + 16) collect: [ :addr | memory byteAtAddr: addr ].
+ 	^GdbARMAlien new
+ 		primitiveDisassembleAt: address inMemory: prefix, theseBytes!

Item was added:
+ ----- Method: TargetAwareARM>>primitiveErrorAndLog (in category 'primitives') -----
+ primitiveErrorAndLog
+ 	"Answer an array of the current error code and log contents"
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: TargetAwareARM>>primitiveFlushICacheFrom:To: (in category 'primitives') -----
+ primitiveFlushICacheFrom: startAddress "<Integer>" To: endAddress "<Integer>"
+ 	"Flush the icache in the requested range"
+ 	^self primitiveFailed!

Item was added:
+ ----- Method: TargetAwareARM>>primitiveResetCPU (in category 'primitives') -----
+ primitiveResetCPU
+ 	"Reset the receiver to registers all zero, and protected 32-bit mode."
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: TargetAwareARM>>primitiveRunInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
+ primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
+ 	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
+ 	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
+ 	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals.
+ 	Note that minWriteMaxExecAddress is both the minimum writeable address AND the maximum executable address"
+ 	| ec |
+ 	ec := #ZZZZZ.
+ 	self shouldBeImplemented.
+ 	^ec isPrimitiveError
+ 		ifTrue:
+ 			[self handleExecutionPrimitiveFailureIn: memoryArray
+ 				minimumAddress: minimumAddress
+ 				code: ec errorCode]
+ 		ifFalse:
+ 			[ec == #'inappropriate operation'
+ 				ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 							minimumAddress: minimumAddress]
+ 				ifFalse: [self reportPrimitiveFailure]]!

Item was added:
+ ----- Method: TargetAwareARM>>primitiveSingleStepInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
+ primitiveSingleStepInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
+ 	"Single-step the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
+ 	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
+ 	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals."
+ 	| ec |
+ 	ec := #ZZZZZ.
+ 	self shouldBeImplemented.
+ 	^ec isPrimitiveError
+ 		ifTrue:
+ 			[self handleExecutionPrimitiveFailureIn: memoryArray
+ 				minimumAddress: minimumAddress
+ 				code: ec errorCode]
+ 		ifFalse:
+ 			[ec == #'inappropriate operation'
+ 				ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 							minimumAddress: minimumAddress]
+ 				ifFalse: [self reportPrimitiveFailure]]!

Item was added:
+ ----- Method: TargetAwareARM>>printFields:inRegisterState:on: (in category 'printing') -----
+ printFields: fields inRegisterState: registerStateVector on: aStream
+ 	| rsvs |
+ 	aStream ensureCr.
+ 	rsvs := registerStateVector readStream.
+ 	fields withIndexDo:
+ 		[:sym :index| | val |
+ 		sym = #cr
+ 			ifTrue: [aStream cr]
+ 			ifFalse:
+ 				[(val := rsvs next) isNil ifTrue: [^self].
+ 				aStream nextPutAll: sym; nextPut: $:; space.
+ 				val printOn: aStream base: 16 length: 8 padded: true.
+ 				#eflags == sym
+ 					ifTrue:
+ 						[aStream space.
+ 						 "'FIVCZN'"'--VCZN' withIndexDo:
+ 							[:flag :bitIndex|
+ 							flag ~= $- ifTrue:
+ 								[aStream nextPut: flag; nextPutAll: 'F='; print: (val bitAnd: 1 << (bitIndex - 1)) >> (bitIndex - 1); space]]]
+ 					ifFalse:
+ 						[val > 16 ifTrue:
+ 							[aStream space; nextPut: $(.
+ 							 val printOn: aStream base: 10 length: 1 padded: false.
+ 							 aStream nextPut: $)]].
+ 				(fields at: index + 1) ~~ #cr ifTrue:
+ 					[aStream tab]]]!

Item was added:
+ ----- Method: TargetAwareARM>>printLabel:on:at:for: (in category 'printing') -----
+ printLabel: label on: aStream at: address for: aSymbolManager
+ 	"Print label on aStream.  The label is either a triple of {type, printer, size} or a simple string."
+ 	label isArray
+ 		ifTrue: [label first == #literal
+ 					ifTrue:
+ 						[label size = 4 ifTrue:
+ 							[aStream nextPutAll: label last; nextPut: $:; cr].
+ 						 aStream
+ 							nextPutAll: (address printStringBase: 16 length: 8 padded: true) asLowercase;
+ 							nextPut: $:; space;
+ 							nextPutAll: ((aSymbolManager objectMemory longAt: address) printStringBase: 16 length: 8 padded: true) asLowercase.
+ 						 (aSymbolManager lookupAddress: (aSymbolManager objectMemory longAt: address)) ifNotNil:
+ 							[:name| aStream space; nextPutAll: name]]
+ 					ifFalse:
+ 						[aStream
+ 							nextPutAll: label first;
+ 							nextPut: $:; cr;
+ 							nextPutAll: (address printStringBase: 16 length: 8 padded: true) asLowercase;
+ 							nextPut: $:; space;
+ 							nextPutAll: (aSymbolManager perform: label second with: address) asString]]
+ 		ifFalse: [aStream nextPutAll: label; nextPut: $:; cr]!

Item was added:
+ ----- Method: TargetAwareARM>>printNameOn: (in category 'printing') -----
+ printNameOn: aStream 
+ 	super printOn: aStream!

Item was added:
+ ----- Method: TargetAwareARM>>printRegisterState:on: (in category 'printing') -----
+ printRegisterState: registerStateVector on: aStream
+ 	self printFields: #(	r0 r1 r2 r3 cr
+ 						r4 r5 r6 r7 cr
+ 						r8 r9 sl fp cr
+ 						r12 sp lr pc eflags cr)
+ 		inRegisterState: registerStateVector
+ 		on: aStream!

Item was added:
+ ----- Method: TargetAwareARM>>printRegisterStateExceptPC:on: (in category 'printing') -----
+ printRegisterStateExceptPC: registerStateVector on: aStream
+ 	self printFields: #(	r0 r1 r2 r3 cr
+ 						r4 r5 r6 r7 cr
+ 						r8 r9 sl fp cr
+ 						r12 sp lr eflags cr)
+ 		inRegisterState: registerStateVector
+ 		on: aStream!

Item was added:
+ ----- Method: TargetAwareARM>>priorPc (in category 'accessing') -----
+ priorPc
+ "where did the simulator stop just before a prefetch abort?"
+ 	^self shouldNotImplement!

Item was added:
+ ----- Method: TargetAwareARM>>priorPc: (in category 'accessing') -----
+ priorPc: val
+ 	^self shouldNotImplement!

Item was added:
+ ----- Method: TargetAwareARM>>pushWord:in: (in category 'execution') -----
+ pushWord: aValue in: aMemory
+ 	aMemory longAt: (self sp: self sp - 4) + 1 put: aValue bigEndian: false!

Item was added:
+ ----- Method: TargetAwareARM>>qflag (in category 'accessing') -----
+ qflag
+ 	"Bit 27 in the cpsr: Cumulative saturation bit."
+ 	^self rawCPSR >> 27 bitAnd: 1.!

Item was added:
+ ----- Method: TargetAwareARM>>qflag: (in category 'accessing') -----
+ qflag: unsignedInteger
+ 	^self setCPSRbit: 27 to: unsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>rawCPSR (in category 'accessing') -----
+ rawCPSR
+ 	^gdb getRegister: 'cpsr'!

Item was added:
+ ----- Method: TargetAwareARM>>rawCPSR: (in category 'accessing') -----
+ rawCPSR: anUnsignedInteger
+ 	gdb setRegister: 'cpsr' to: anUnsignedInteger.
+ 	^anUnsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>rawFPCPSR (in category 'accessing') -----
+ rawFPCPSR
+ 	"The VFP cpsr register as seen by gdb."
+ 	^gdb getRegister: 'fpscr'!

Item was added:
+ ----- Method: TargetAwareARM>>rawFPCPSR: (in category 'accessing') -----
+ rawFPCPSR: anUnsignedInteger
+ 	gdb setRegister: 'fpscr' to: anUnsignedInteger.
+ 	^anUnsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>register: (in category 'accessing') -----
+ register: int0to15
+ "return the value of register"
+ 	self assert:[int0to15 between: 0 and:15].
+ 	^self shouldBeImplemented!

Item was added:
+ ----- Method: TargetAwareARM>>registerState (in category 'accessing-abstract') -----
+ registerState
+ 	^{	self r0. self r1. self r2. self r3. self r4. self r5. self r6. self r7.
+ 		self r8. self r9. self sl. self fp. self r12. self sp. self lr. self pc. self eflags.
+ 		self d0. self d1. self d2. self d3. self d4. self d5. self d6. self d7.
+ 		self d8. self d9. self d10. self d11. self d12. self d13. self d14. self d15 }!

Item was added:
+ ----- Method: TargetAwareARM>>registerStateGetters (in category 'accessing-abstract') -----
+ registerStateGetters
+ 	^#(	r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 sl fp r12 sp lr pc eflags
+ 		d0 d1 d2 d3 d4 d5 d6 d7 d8 d9 d10 d11 d12 d13 d14 d15)!

Item was added:
+ ----- Method: TargetAwareARM>>registerStatePCIndex (in category 'accessing-abstract') -----
+ registerStatePCIndex
+ 	"Answer the index of the PC register in the Array answered by integerRegisterState"
+ 	^16!

Item was added:
+ ----- Method: TargetAwareARM>>registerStateSetters (in category 'accessing-abstract') -----
+ registerStateSetters
+ 	^#(	r0: r1: r2: r3: r4: r5: r6: r7: r8: r9: sl: fp: r12: sp: lr: pc: eflags:
+ 		d0: d1: d2: d3: d4: d5: d6: d7: d8: d9: d10: d11: d12: d13: d14: d15:)!

Item was added:
+ ----- Method: TargetAwareARM>>reset (in category 'processor setup') -----
+ reset
+ 	self priorPc: 0;
+ 		primitiveResetCPU!

Item was added:
+ ----- Method: TargetAwareARM>>retpcIn: (in category 'accessing-abstract') -----
+ retpcIn: aMemory
+ 	"The return address is on the stack, having been pushed by either
+ 	 simulateCallOf:nextpc:memory: or simulateJumpCallOf:memory:"
+ 	^aMemory unsignedLongAt: self fp + 5 bigEndian: false!

Item was added:
+ ----- Method: TargetAwareARM>>runThinshellPrologue (in category 'target connection') -----
+ runThinshellPrologue
+ 	"Right now, the thinshell prologue on ARM does not work well.
+ 	Nor is it needed at this stage.
+ 	So, do nothing instead of c."!

Item was added:
+ ----- Method: TargetAwareARM>>setCPSRbit:to: (in category 'accessing') -----
+ setCPSRbit: position to: oneOrZero
+ 	"Flip bit 'position' (counted from LSB=0 to MSB=31) in the CPSR to oneOrZero"
+ 	self rawCPSR: (self rawCPSR bitAt: position+1 put: oneOrZero).
+ 	^oneOrZero!

Item was added:
+ ----- Method: TargetAwareARM>>setFramePointer:stackPointer: (in category 'accessing-abstract') -----
+ setFramePointer: framePointer stackPointer: stackPointer
+ 	"Initialize the processor's frame and stack pointers"
+ 	self fp: framePointer.
+ 	self sp: stackPointer!

Item was added:
+ ----- Method: TargetAwareARM>>setRegisterState: (in category 'accessing-abstract') -----
+ setRegisterState: aRegisterStateArray
+ 	"N.B. keep in sync with voidRegisterState"
+ 
+ 	self r0:  (aRegisterStateArray at: 1).
+ 	self r1: (aRegisterStateArray at: 2).
+ 	self r2: (aRegisterStateArray at: 3).
+ 	self r3: (aRegisterStateArray at: 4).
+ 	self r4: (aRegisterStateArray at: 5).
+ 	self r5: (aRegisterStateArray at: 6).
+ 	self r6: (aRegisterStateArray at: 7).
+ 	self r7: (aRegisterStateArray at: 8).
+ 	self r8: (aRegisterStateArray at: 9).
+ 	self r9: (aRegisterStateArray at: 10).
+ 	self r10: (aRegisterStateArray at: 11).
+ 	self fp: (aRegisterStateArray at: 12).
+ 	self r12: (aRegisterStateArray at: 13).
+ 	self sp: (aRegisterStateArray at: 14).
+ 	self lr: (aRegisterStateArray at: 15).
+ 	self pc: (aRegisterStateArray at: 16).
+ 	self eflags:  (aRegisterStateArray at: 17).!

Item was added:
+ ----- Method: TargetAwareARM>>sflag (in category 'accessing') -----
+ sflag
+ "The ARM cpsr flags are kept as individual fields in the Alien structure. The address here is the 1-based byte offset into the ARMul_State structure"
+ 	^self shouldNotImplement!

Item was added:
+ ----- Method: TargetAwareARM>>sflag: (in category 'accessing') -----
+ sflag: unsignedInteger
+ "The ARM cpsr flags are kept as individual fields in the Alien structure. The address here is the 1-based byte offset into the ARMul_State structure"
+ self shouldNotImplement!

Item was added:
+ ----- Method: TargetAwareARM>>simulateBuildFrameIn:for: (in category 'execution') -----
+ simulateBuildFrameIn: aMemory for: evaluable
+ 	
+ 	self pushWord: self lr in: aMemory.
+ 	self pushWord: self fp in: aMemory.
+ 	self fp: self sp.!

Item was added:
+ ----- Method: TargetAwareARM>>simulateCallOf:nextpc:memory: (in category 'execution') -----
+ 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: 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!

Item was added:
+ ----- Method: TargetAwareARM>>simulateJumpCallOf:memory: (in category 'execution') -----
+ simulateJumpCallOf: address memory: aMemory
+ 	"Simulate a frame-building jump 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 assert: self sp \\ 8 = 0. "This check ensures, that we conform with ARM abi. Before doing anything to the stack, we ensure 2-word alignment."
+ 	self pushWord: self lr 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!

Item was added:
+ ----- Method: TargetAwareARM>>simulateLeafCallOf:nextpc:memory: (in category 'execution') -----
+ simulateLeafCallOf: address nextpc: nextpc memory: aMemory
+ 	self lr: nextpc.
+ 	self pc: address!

Item was added:
+ ----- Method: TargetAwareARM>>simulateLeafReturnIn: (in category 'execution') -----
+ simulateLeafReturnIn: aMemory
+ 	self pc: self lr!

Item was added:
+ ----- Method: TargetAwareARM>>simulateReturnIn: (in category 'execution') -----
+ simulateReturnIn: aMemory
+ 	PostBuildStackDelta ~= 0 ifTrue:
+ 		[self sp: self sp + PostBuildStackDelta].
+ 	self fp: (self popWordIn: aMemory).
+ 	"According to tpr, most C compilers implement return by simply
+ 	 popping into the pc, rather than popping through the link register."
+ 	self pc: (self popWordIn: aMemory)!

Item was added:
+ ----- Method: TargetAwareARM>>sl (in category 'accessing') -----
+ sl
+ 	^self r10!

Item was added:
+ ----- Method: TargetAwareARM>>sl: (in category 'accessing') -----
+ sl: anUnsignedInteger
+ self shouldNotImplement!

Item was added:
+ ----- Method: TargetAwareARM>>smashABICallerSavedRegistersWithValuesFrom:by: (in category 'accessing-abstract') -----
+ smashABICallerSavedRegistersWithValuesFrom: base by: step
+ 	"limited list of registers to clear out when simulating an ABI call.
+ 	 Smash neither R0 nor R1 since many abi calls return 2 results or a 64-bit dual-reg value.
+ 	 LR has to be left alone becasue a leaf call doesn't push it."
+ 
+ 	#(r2: r3: r9: r12:) withIndexDo:
+ 		[:accessor :index|
+ 		self perform: accessor with: index - 1 * step + base]!

Item was added:
+ ----- Method: TargetAwareARM>>smashCallerSavedRegistersWithValuesFrom:by:in: (in category 'accessing-abstract') -----
+ smashCallerSavedRegistersWithValuesFrom: base by: step in: aMemory
+ 	#(r0: r1: r2: r3: r9: r12: lr:) withIndexDo:
+ 		[:accessor :index|
+ 		self perform: accessor with: index - 1 * step + base]!

Item was added:
+ ----- Method: TargetAwareARM>>smashRegisterAccessors (in category 'accessing-abstract') -----
+ smashRegisterAccessors
+ 	^#(r0: r1: r2: r3: r4: r5: r6: r7: r8: r9: r10: "11=FP" r12: "13=SP, 14=LR, 15=PC")!

Item was added:
+ ----- Method: TargetAwareARM>>sp (in category 'accessing') -----
+ sp
+ 	^gdb getRegister: 'sp'
+ !

Item was added:
+ ----- Method: TargetAwareARM>>sp: (in category 'accessing') -----
+ sp: anUnsignedInteger
+ 	gdb setRegister: 'sp' to: anUnsignedInteger.
+ 	^anUnsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>tflag (in category 'accessing') -----
+ tflag
+ "The ARM cpsr flags are kept as individual fields in the Alien structure. The address here is the 1-based byte offset into the ARMul_State structure"
+ "This would be the Thumb flag if we have it -which depends rather oddly on the compiletime flags used to build the ARMulator. Sigh"
+ 	^0!

Item was added:
+ ----- Method: TargetAwareARM>>tflag: (in category 'accessing') -----
+ tflag: unsignedInteger
+ "The ARM cpsr flags are kept as individual fields in the Alien structure. The address here is the 1-based byte offset into the ARMul_State structure"
+ "This would be the Thumb flag if we have it -which depends rather oddly on the compiletime flags used to build the ARMulator. Sigh"
+ self shouldNotImplement!

Item was added:
+ ----- Method: TargetAwareARM>>vflag (in category 'accessing') -----
+ vflag
+ 	"Bit 28 in the cpsr: Overflow condition code flag."
+ 	^self rawCPSR >> 28 bitAnd: 1.!

Item was added:
+ ----- Method: TargetAwareARM>>vflag: (in category 'accessing') -----
+ vflag: unsignedInteger
+ 	^self setCPSRbit: 28 to: unsignedInteger!

Item was added:
+ ----- Method: TargetAwareARM>>voidRegisterState (in category 'accessing-abstract') -----
+ voidRegisterState
+ 	"N.B. keep in sync with setRegisterState:"
+ 	self setRegisterState: (Array new: 17 withAll: 0)!

Item was added:
+ ----- Method: TargetAwareARM>>zflag (in category 'accessing') -----
+ zflag
+ 	"Bit 30 in the cpsr: Zero condition code flag."
+ 	^self rawCPSR >> 30 bitAnd: 1.!

Item was added:
+ ----- Method: TargetAwareARM>>zflag: (in category 'accessing') -----
+ zflag: unsignedInteger
+ 	^self setCPSRbit: 30 to: unsignedInteger!

Item was changed:
+ TargetAware subclass: #TargetAwareX86
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'ExtendedOpcodeExceptionMap OpcodeExceptionMap PostBuildStackDelta'
- Object subclass: #TargetAwareX86
- 	instanceVariableNames: 'gdb'
- 	classVariableNames: 'Current ExtendedOpcodeExceptionMap OpcodeExceptionMap PostBuildStackDelta'
  	poolDictionaries: ''
  	category: 'GDB-Cog'!

Item was removed:
- ----- Method: TargetAwareX86 class>>current (in category 'instance creation') -----
- current
- 	^Current!

Item was added:
+ ----- Method: TargetAwareX86 class>>nZoneSize (in category 'machine description') -----
+ nZoneSize
+ 	^16r100000!

Item was removed:
- ----- Method: TargetAwareX86 class>>new (in category 'instance creation') -----
- new
- 	"
- 	TargetAwareX86 new
- 	"
- 	Current := super new connectGdb.
- 	^Current!

Item was removed:
- ----- Method: TargetAwareX86 class>>printTempNames (in category 'class initialization') -----
- printTempNames
- 	^false!

Item was removed:
- ----- Method: TargetAwareX86 class>>printTempNames: (in category 'class initialization') -----
- printTempNames: x!

Item was removed:
- ----- Method: TargetAwareX86 class>>remoteMemoryClass (in category 'machine description') -----
- remoteMemoryClass
- 	^self isHardware
- 		ifTrue: [SimpleSharedRAM]
- 		ifFalse: [Gem5SharedRAM]!

Item was removed:
- ----- Method: TargetAwareX86 class>>setReceiverResultReg: (in category 'class initialization') -----
- setReceiverResultReg:  x!

Item was added:
+ ----- Method: TargetAwareX86 class>>wordSize (in category 'machine description') -----
+ wordSize
+ 	^4!

Item was removed:
- ----- Method: TargetAwareX86>>bogusRetPC (in category 'entering execution') -----
- bogusRetPC
- 	^16rBADF00D5!

Item was removed:
- ----- Method: TargetAwareX86>>connectGdb (in category 'target connection') -----
- connectGdb
- 	gdb := self debuggerClass
- 		host: self hostIP
- 		port: self tcpPort
- 		processorDescription: self pdl.
- 	self runThinshellPrologue.
- 	^self "not gdb; #new needs the instance"!

Item was removed:
- ----- Method: TargetAwareX86>>convertIntegerToInternal: (in category 'tests support') -----
- convertIntegerToInternal: anInteger
- 	"Default conversion for 32-bit processors.  64-bit processors override."
- 	^anInteger signedIntToLong!

Item was removed:
- ----- Method: TargetAwareX86>>debuggerClass (in category 'target connection') -----
- debuggerClass
- 	^RemoteGDBSession!

Item was added:
+ ----- Method: TargetAwareX86>>fp: (in category 'accessing-abstract') -----
+ fp: newFP
+ 	^self ebp: newFP!

Item was removed:
- ----- Method: TargetAwareX86>>gdb (in category 'target connection') -----
- gdb
- 	^gdb!

Item was changed:
+ ----- Method: TargetAwareX86>>handleDataFailureIn: (in category 'error handling') -----
- ----- Method: TargetAwareX86>>handleDataFailureIn: (in category 'execution') -----
  handleDataFailureIn: memoryArray
  	| pc opcode |
  	pc := self eip.
  	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!

Item was removed:
- ----- Method: TargetAwareX86>>handleExecutionPrimitiveFailureAt:in: (in category 'error handling') -----
- handleExecutionPrimitiveFailureAt: pc "<Integer>" in: memoryArray "<Bitmap|ByteArray>"
- 	"Handle an execution primitive failure for an unhandled opcode."
- 	^self reportPrimitiveFailure!

Item was removed:
- ----- Method: TargetAwareX86>>handleExecutionPrimitiveFailureIn:minimumAddress: (in category 'execution') -----
- handleExecutionPrimitiveFailureIn: memoryArray minimumAddress: minimumAddress
- 	"Execution stopped due to SIGSEGV.
- 	Convert out-of-range call and absolute memory read-into-register instructions
- 	into ProcessorSimulationTrap signals."
- 
- 	"The SEGV could be caused by Fetching from an unmapped address,
- 	or a data operation with an unmapped address.
- 	While a simulator such as gem5 could tell us what caused the fault,
- 	real hardware such as silicon i386 doesn't provide an easy way;
- 	therefore, we have to look at circumstancial evidence."
- 	(self isWithinMappedRange: self eip)
- 		ifTrue: [ ^self handleDataFailureIn: memoryArray ]
- 		ifFalse: [ ^self handlePcOutOfRangeIn: memoryArray ]!

Item was removed:
- ----- Method: TargetAwareX86>>handlePcOutOfRangeIn: (in category 'execution') -----
- handlePcOutOfRangeIn: memoryArray
- 	| pc |
- 	pc := self pc.
- 	pc = self bogusRetPC ifTrue: [ ^self cResultRegister ].
- 	^(ProcessorSimulationTrap
- 			pc: nil
- 			nextpc: nil
- 			address: pc
- 			type: #controlTransfer)
- 		signal!

Item was removed:
- ----- Method: TargetAwareX86>>hostIP (in category 'target connection') -----
- hostIP
- 	^'192.168.75.2'!

Item was removed:
- ----- Method: TargetAwareX86>>isWithinMappedRange: (in category 'execution') -----
- isWithinMappedRange: anAddress
- 	| minimumAddress maximumAddress |
- 	minimumAddress := 4096.
- 	maximumAddress := 120*1024*1024 - 1.
- 	^anAddress >= minimumAddress and: [ anAddress <= maximumAddress ]!

Item was removed:
- ----- Method: TargetAwareX86>>runInMemory:minimumAddress: (in category 'execution') -----
- runInMemory: aMemory minimumAddress: minimumAddress
- 	| stopReason |
- 	stopReason := gdb c.
- 	stopReason signal = #SIGSEGV ifTrue: [
- 		^self
- 			handleExecutionPrimitiveFailureIn: aMemory
- 			minimumAddress: minimumAddress ].
- 	stopReason signal = #SIGQUIT ifTrue: [ ^self halt ].
- 
- 	"There can be a number of other reasons to stop.
- 	For example, a debug breakpoint."
- 	self shouldBeImplemented!

Item was removed:
- ----- Method: TargetAwareX86>>runInMemory:minimumAddress:readOnlyBelow: (in category 'execution') -----
- runInMemory: aMemory minimumAddress: minimumAddress readOnlyBelow: minimumWritableAddress
- 	^self runInMemory: aMemory minimumAddress: minimumAddress!

Item was removed:
- ----- Method: TargetAwareX86>>runThinshellPrologue (in category 'target connection') -----
- runThinshellPrologue
- 	"Run the thinshell's _start to do whatever initialization it needs,
- 	until it stops (usually indicates 'I am done' by segfaulting or trapping)"
- 	gdb c!

Item was changed:
  ----- Method: TargetAwareX86>>simulateBuildFrameIn:for: (in category 'execution') -----
  simulateBuildFrameIn: aMemory for: evaluable
  	"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, and
  	b) stack alignment needs to be realistic for assert checking for platforms such as Mac OS X"
+ 	
+ 	"NB: do not push the return address here.
+ 	Unlike Bochs, which fails atomically so the return address doesn't end up pushed,
+ 	the Intel CPU faults on fetch after the return address has already been pushed."
+ 	self break.
+ 	self pushWord: self sp in: aMemory.
+ 	self fp: self sp.
- 	| sp |
- 	sp := self esp.
- 	self pushWord: sp in: aMemory.
- 	sp := sp - 4.
- 	self ebp: sp.
  	PostBuildStackDelta ~= 0 ifTrue:
+ 		[self sp: self sp - PostBuildStackDelta].
- 		[self esp: sp - PostBuildStackDelta].
  !

Item was removed:
- ----- Method: TargetAwareX86>>smashRegistersWithValuesFrom:by: (in category 'accessing-abstract') -----
- smashRegistersWithValuesFrom: base by: step
- 	self smashRegisterAccessors
- 	   withIndexDo:
- 		[:accessor :index|
- 		self perform: accessor with: index - 1 * step + base]!

Item was removed:
- ----- Method: TargetAwareX86>>tcpPort (in category 'target connection') -----
- tcpPort
- 	^7000!



More information about the Vm-dev mailing list