[Vm-dev] VM Maker: Cog-rmacnak.294.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Nov 12 04:49:43 UTC 2015


Ryan Macnak uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-rmacnak.294.mcz

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

Name: Cog-rmacnak.294
Author: rmacnak
Time: 11 November 2015, 8:49:29.983 pm
UUID: 474cf204-cc7d-4c72-bf46-806f7a8095f9
Ancestors: Cog-eem.293

Initial commit of MIPSEL simulator.

=============== Diff against Cog-eem.293 ===============

Item was added:
+ SharedPool subclass: #MIPSConstants
+ 	instanceVariableNames: ''
+ 	classVariableNames: 'A0 A1 A2 A3 ADDIU ADDU AND ANDI AT BEQ BGEZ BGTZ BLEZ BLTZ BNE BREAK FP GP J JAL JALR JR K0 K1 LB LBU LH LHU LUI LW OR ORI OneInstruction R0 R1 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R2 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R3 R30 R31 R4 R5 R6 R7 R8 R9 RA REGIMM S0 S1 S2 S3 S4 S5 S6 S7 SB SH SLL SLLV SLT SLTI SLTIU SLTU SP SPECIAL SRA SRAV SRL SRLV SUBU SW T0 T1 T2 T3 T4 T5 T6 T7 T8 T9 TwoInstructions V0 V1 XOR XORI ZR'
+ 	poolDictionaries: ''
+ 	category: 'Cog-Processors'!
+ 
+ !MIPSConstants commentStamp: 'rmacnak 11/11/2015 20:29:59' prior: 0!
+ MIPS opcodes and register names.!

Item was added:
+ ----- Method: MIPSConstants class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	super initialize.
+ 	
+ 	OneInstruction := 4.
+ 	TwoInstructions := 8.
+ 	
+ 	self initializeRegisters.
+ 	self initializeOpcodes.
+ 	self initializeSpecialFunctions.
+ 	self initializeRegImmRts.!

Item was added:
+ ----- Method: MIPSConstants class>>initializeOpcodes (in category 'as yet unclassified') -----
+ initializeOpcodes
+ 	SPECIAL := 0.
+ 	REGIMM := 1.
+ 	J := 2.
+ 	JAL := 3.
+ 	BEQ := 4.
+ 	BNE := 5.
+ 	BLEZ := 6.
+ 	BGTZ := 7.
+ 	ADDIU := 9.
+ 	SLTI := 10.
+ 	SLTIU := 11.
+ 	ANDI := 12.
+ 	ORI := 13.
+ 	XORI := 14.
+ 	LUI := 15.
+ 	LB := 32.
+ 	LH := 33.
+ 	LW := 35.
+ 	LBU := 36.
+ 	LHU := 37.
+ 	SB := 40.
+ 	SH := 41.
+ 	SW := 43.!

Item was added:
+ ----- Method: MIPSConstants class>>initializeRegImmRts (in category 'as yet unclassified') -----
+ initializeRegImmRts
+ 	BLTZ := 0.
+ 	BGEZ := 1.!

Item was added:
+ ----- Method: MIPSConstants class>>initializeRegisters (in category 'as yet unclassified') -----
+ initializeRegisters
+ 	self flag: #OABI.
+ 	R0 := ZR := 0. "Hardwired zero"
+ 	R1 := AT := 1. "Assembler temp - used to expand psuedo instructions"
+ 	R2 := V0 := 2. "ABI: result register"
+ 	R3 := V1 := 3. "ABI: result register"
+ 	R4 := A0 := 4. "ABI: argument register"
+ 	R5 := A1 := 5. "ABI: argument register"
+ 	R6 := A2 := 6. "ABI: argument register"
+ 	R7 := A3 := 7. "ABI: argument register"
+ 	R8 := T0 := 8. "ABI: volatile"
+ 	R9 := T1 := 9. "ABI: volatile"
+ 	R10 := T2 := 10. "ABI: volatile"
+ 	R11 := T3 := 11. "ABI: volatile"
+ 	R12 := T4 := 12. "ABI: volatile"
+ 	R13 := T5 := 13. "ABI: volatile"
+ 	R14 := T6 := 14. "ABI: volatile"
+ 	R15 := T7 := 15. "ABI: volatile"
+ 	R16 := S0 := 16. "ABI: preserved"
+ 	R17 := S1 := 17. "ABI: preserved"
+ 	R18 := S2 := 18. "ABI: preserved"
+ 	R19 := S3 := 19. "ABI: preserved"
+ 	R20 := S4 := 20. "ABI: preserved"
+ 	R21 := S5 := 21. "ABI: preserved"
+ 	R22 := S6 := 22. "ABI: preserved"
+ 	R23 := S7 := 23. "ABI: preserved"
+ 	R24 := T8 := 24. "ABI: volatile"
+ 	R25 := T9 := 25. "Special use in some position-independent code"
+ 	R26 := K0 := 26. "Reserved for OS"
+ 	R27 := K1 := 27. "Reserved for OS"
+ 	R28 := GP := 28. "Special use in some position-independent code"
+ 	R29 := SP := 29. "Stack pointer"
+ 	R30 := FP := 30. "Frame pointer"
+ 	R31 := RA := 31. "Link register"
+ 
+ 	!

Item was added:
+ ----- Method: MIPSConstants class>>initializeSpecialFunctions (in category 'as yet unclassified') -----
+ initializeSpecialFunctions
+ 	SLL := 0.
+ 	SRL := 2.
+ 	SRA := 3.
+ 	SLLV := 4.
+ 	SRLV := 6.
+ 	SRAV := 7.
+ 	JR := 8.
+ 	JALR := 9.
+ 	BREAK := 13.
+ 	ADDU := 33.
+ 	SUBU := 35.
+ 	AND := 36.
+ 	OR := 37.
+ 	XOR := 38.
+ 	SLT := 42.
+ 	SLTU := 43.!

Item was added:
+ ----- Method: MIPSConstants class>>nameForRegister: (in category 'as yet unclassified') -----
+ nameForRegister: registerNumber
+ 	^#(zr at v0 v1 a0 a1 a2 a3
+ 		t0 t1 t2 t3 t4 t5 t6 t7
+ 		s0 s1 s2 s3 s4 s5 s6 s7
+ 		t8 t9 k0 k1 gp sp fp ra) at: registerNumber + 1!

Item was added:
+ Object subclass: #MIPSDisassembler
+ 	instanceVariableNames: 'pc'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'MIPSConstants'
+ 	category: 'Cog-Processors'!

Item was added:
+ ----- Method: MIPSDisassembler>>addImmediateUnsigned: (in category 'instructions - arithmetic') -----
+ addImmediateUnsigned: instruction
+ 	^'addiu ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(instruction signedImmediate printString)!

Item was added:
+ ----- Method: MIPSDisassembler>>addUnsigned: (in category 'instructions - arithmetic') -----
+ addUnsigned: instruction
+ 	^'addu ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>andImmediate: (in category 'instructions - arithmetic') -----
+ andImmediate: instruction
+ 	^'andi ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(instruction unsignedImmediate printString)!

Item was added:
+ ----- Method: MIPSDisassembler>>bitwiseAnd: (in category 'instructions - arithmetic') -----
+ bitwiseAnd: instruction
+ 	^'and ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>bitwiseOr: (in category 'instructions - arithmetic') -----
+ bitwiseOr: instruction
+ 	^'or ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>bitwiseXor: (in category 'instructions - arithmetic') -----
+ bitwiseXor: instruction
+ 	^'xor ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>branchEqual: (in category 'instructions - control') -----
+ branchEqual: instruction
+ 	| offset target |
+ 	offset := instruction signedImmediate << 2.
+ 	target := pc + offset + OneInstruction. "Offset is relative to the delay slot"
+ 	^'beq ', 
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(offset > 0 ifTrue: ['+'] ifFalse: ['']), offset printString, ' ; =', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>branchGreaterEqualZero: (in category 'instructions - control') -----
+ branchGreaterEqualZero: instruction
+ 	| offset target |
+ 	offset := instruction signedImmediate << 2.
+ 	target := pc + offset + OneInstruction. "Offset is relative to the delay slot"
+ 	^'bgez ', 
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(offset > 0 ifTrue: ['+'] ifFalse: ['']), offset printString, ' ; =', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>branchGreaterThanZero: (in category 'instructions - control') -----
+ branchGreaterThanZero: instruction
+ 	| offset target |
+ 	offset := instruction signedImmediate << 2.
+ 	target := pc + offset + OneInstruction. "Offset is relative to the delay slot"
+ 	^'bgtz ', 
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(offset > 0 ifTrue: ['+'] ifFalse: ['']), offset printString, ' ; =', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>branchLessEqualZero: (in category 'instructions - control') -----
+ branchLessEqualZero: instruction
+ 	| offset target |
+ 	offset := instruction signedImmediate << 2.
+ 	target := pc + offset + OneInstruction. "Offset is relative to the delay slot"
+ 	^'blez ', 
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(offset > 0 ifTrue: ['+'] ifFalse: ['']), offset printString, ' ; =', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>branchLessThanZero: (in category 'instructions - control') -----
+ branchLessThanZero: instruction
+ 	| offset target |
+ 	offset := instruction signedImmediate << 2.
+ 	target := pc + offset + OneInstruction. "Offset is relative to the delay slot"
+ 	^'bltz ', 
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(offset > 0 ifTrue: ['+'] ifFalse: ['']), offset printString, ' ; =', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>branchNotEqual: (in category 'instructions - control') -----
+ branchNotEqual: instruction
+ 	| offset target |
+ 	offset := instruction signedImmediate << 2.
+ 	target := pc + offset + OneInstruction. "Offset is relative to the delay slot"
+ 	^'bne ', 
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(offset > 0 ifTrue: ['+'] ifFalse: ['']), offset printString, ' ; =', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>break: (in category 'instructions - control') -----
+ break: instruction
+ 	^'break'!

Item was added:
+ ----- Method: MIPSDisassembler>>disassemble:from:to: (in category 'as yet unclassified') -----
+ disassemble: memory from: startPC to: limitPC
+ 	| stream |
+ 	stream := WriteStream on: ''.
+ 	self disassemble: memory from: startPC to: limitPC for: nil labels: nil on: stream.
+ 	^stream contents!

Item was added:
+ ----- Method: MIPSDisassembler>>disassemble:from:to:for:labels:on: (in category 'as yet unclassified') -----
+ disassemble: memory from: startPC to: limitPC for: aSymbolManager "<Cogit>" labels: labelDictionary on: aStream
+ 	pc := startPC.
+ 	[pc < limitPC] whileTrue:
+ 		[ | word instruction |
+ 		pc printOn: aStream base: 16 nDigits: 8.
+ 		aStream space; space.
+ 		word := memory unsignedLongAt: pc + 1.
+ 		word printOn: aStream base: 16 nDigits: 8.
+ 		aStream space; space.
+ 		instruction := MIPSInstruction new value: word.
+ 		aStream nextPutAll: (instruction decodeFor: self).
+ 		aStream cr.
+ 		pc := pc + OneInstruction].!

Item was added:
+ ----- Method: MIPSDisassembler>>jump: (in category 'instructions - control') -----
+ jump: instruction
+ 	| target |
+ 	target := (pc + OneInstruction) bitAnd: 16rF0000000. "Region is that of the delay slot"
+ 	target := target + (instruction target << 2).
+ 	^'j ', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>jumpAndLink: (in category 'instructions - control') -----
+ jumpAndLink: instruction
+ 	| target |
+ 	target := (pc + OneInstruction) bitAnd: 16rF0000000. "Region is that of the delay slot"
+ 	target := target + (instruction target << 2).
+ 	^'jal ', (target printStringBase: 16)!

Item was added:
+ ----- Method: MIPSDisassembler>>jumpAndLinkRegister: (in category 'instructions - control') -----
+ jumpAndLinkRegister: instruction
+ 	instruction rd = 31 ifTrue: [^'jalr ', (MIPSConstants nameForRegister: instruction rs)].
+ 	^'jalr ',
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs)!

Item was added:
+ ----- Method: MIPSDisassembler>>jumpRegister: (in category 'instructions - control') -----
+ jumpRegister: instruction
+ 	^'jr ', (MIPSConstants nameForRegister: instruction rs)!

Item was added:
+ ----- Method: MIPSDisassembler>>loadByte: (in category 'instructions - memory') -----
+ loadByte: instruction
+ 	^'lb ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>loadByteUnsigned: (in category 'instructions - memory') -----
+ loadByteUnsigned: instruction
+ 	^'lbu ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>loadHalfword: (in category 'instructions - memory') -----
+ loadHalfword: instruction
+ 	^'lh ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>loadHalfwordUnsigned: (in category 'instructions - memory') -----
+ loadHalfwordUnsigned: instruction
+ 	^'lhu ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>loadUpperImmediate: (in category 'instructions - arithmetic') -----
+ loadUpperImmediate: instruction
+ 	^'lui ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString)!

Item was added:
+ ----- Method: MIPSDisassembler>>loadWord: (in category 'instructions - memory') -----
+ loadWord: instruction
+ 	^'lw ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>orImmediate: (in category 'instructions - arithmetic') -----
+ orImmediate: instruction
+ 	^'ori ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(instruction unsignedImmediate printString)!

Item was added:
+ ----- Method: MIPSDisassembler>>setOnLessThan: (in category 'instructions - arithmetic') -----
+ setOnLessThan: instruction
+ 	^'slt ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>setOnLessThanImmediate: (in category 'instructions - arithmetic') -----
+ setOnLessThanImmediate: instruction
+ 	^'slti ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(instruction signedImmediate printString)!

Item was added:
+ ----- Method: MIPSDisassembler>>setOnLessThanImmediateUnsigned: (in category 'instructions - arithmetic') -----
+ setOnLessThanImmediateUnsigned: instruction
+ 	"The immediate is still sign-extended; it is the comparison that is unsigned."
+ 	^'sltiu ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(instruction signedImmediate printString) !

Item was added:
+ ----- Method: MIPSDisassembler>>setOnLessThanUnsigned: (in category 'instructions - arithmetic') -----
+ setOnLessThanUnsigned: instruction
+ 	^'sltu ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>shiftLeftLogical: (in category 'instructions - arithmetic') -----
+ shiftLeftLogical: instruction
+ 	instruction value = 0 ifTrue: [^'nop'].
+ 	^'sll ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	instruction sa printString!

Item was added:
+ ----- Method: MIPSDisassembler>>shiftLeftLogicalVariable: (in category 'instructions - arithmetic') -----
+ shiftLeftLogicalVariable: instruction
+ 	^'sllv ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs)!

Item was added:
+ ----- Method: MIPSDisassembler>>shiftRightArithmetic: (in category 'instructions - arithmetic') -----
+ shiftRightArithmetic: instruction
+ 	^'sra ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	instruction sa printString!

Item was added:
+ ----- Method: MIPSDisassembler>>shiftRightArithmeticVariable: (in category 'instructions - arithmetic') -----
+ shiftRightArithmeticVariable: instruction
+ 	^'srav ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs)!

Item was added:
+ ----- Method: MIPSDisassembler>>shiftRightLogical: (in category 'instructions - arithmetic') -----
+ shiftRightLogical: instruction
+ 	^'srl ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	instruction sa printString!

Item was added:
+ ----- Method: MIPSDisassembler>>shiftRightLogicalVariable: (in category 'instructions - arithmetic') -----
+ shiftRightLogicalVariable: instruction
+ 	^'srlv ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs)!

Item was added:
+ ----- Method: MIPSDisassembler>>storeByte: (in category 'instructions - memory') -----
+ storeByte: instruction
+ 	^'sb ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>storeHalfword: (in category 'instructions - memory') -----
+ storeHalfword: instruction
+ 	^'sh ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>storeWord: (in category 'instructions - memory') -----
+ storeWord: instruction
+ 	^'sw ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(instruction signedImmediate printString), '(',
+ 	(MIPSConstants nameForRegister: instruction rs), ')'!

Item was added:
+ ----- Method: MIPSDisassembler>>subtractUnsigned: (in category 'instructions - arithmetic') -----
+ subtractUnsigned: instruction
+ 	^'subu ', 
+ 	(MIPSConstants nameForRegister: instruction rd), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(MIPSConstants nameForRegister: instruction rt)!

Item was added:
+ ----- Method: MIPSDisassembler>>xorImmediate: (in category 'instructions - arithmetic') -----
+ xorImmediate: instruction
+ 	^'xori ', 
+ 	(MIPSConstants nameForRegister: instruction rt), ', ',
+ 	(MIPSConstants nameForRegister: instruction rs), ', ',
+ 	(instruction unsignedImmediate printString)!

Item was added:
+ MIPSSimulator subclass: #MIPSELSimulator
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'Cog-Processors'!
+ 
+ !MIPSELSimulator commentStamp: 'rmacnak 11/11/2015 20:33:13' prior: 0!
+ Simulator for little-endian 32-bit MIPS.!

Item was added:
+ ----- Method: MIPSELSimulator>>signedByte: (in category 'as yet unclassified') -----
+ signedByte: address
+ 	^memory signedByteAt: address + 1!

Item was added:
+ ----- Method: MIPSELSimulator>>signedByte:put: (in category 'memory') -----
+ signedByte: address put: value
+ 	^memory signedByteAt: address + 1 put: value!

Item was added:
+ ----- Method: MIPSELSimulator>>signedHalfword: (in category 'as yet unclassified') -----
+ signedHalfword: address
+ 	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory signedShortAt: address + 1!

Item was added:
+ ----- Method: MIPSELSimulator>>signedHalfword:put: (in category 'memory') -----
+ signedHalfword: address put: value
+ 	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory signedShortAt: address + 1 put: value!

Item was added:
+ ----- Method: MIPSELSimulator>>signedWord: (in category 'as yet unclassified') -----
+ signedWord: address
+ 	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory signedLongAt: address + 1!

Item was added:
+ ----- Method: MIPSELSimulator>>signedWord:put: (in category 'memory') -----
+ signedWord: address put: value
+ 	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory signedLongAt: address + 1 put: value!

Item was added:
+ ----- Method: MIPSELSimulator>>snsignedWord: (in category 'as yet unclassified') -----
+ snsignedWord: address
+ 	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory unsignedLongAt: address + 1 bigEndian: false!

Item was added:
+ ----- Method: MIPSELSimulator>>unsignedByte: (in category 'as yet unclassified') -----
+ unsignedByte: address
+ 	^memory at: address + 1!

Item was added:
+ ----- Method: MIPSELSimulator>>unsignedByte:put: (in category 'memory') -----
+ unsignedByte: address put: value
+ 	^memory at: address + 1 put: value!

Item was added:
+ ----- Method: MIPSELSimulator>>unsignedHalfword: (in category 'as yet unclassified') -----
+ unsignedHalfword: address
+ 	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory unsignedShortAt: address + 1 bigEndian: false!

Item was added:
+ ----- Method: MIPSELSimulator>>unsignedHalfword:put: (in category 'memory') -----
+ unsignedHalfword: address put: value
+ 	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory unsignedShortAt: address + 1 put: value!

Item was added:
+ ----- Method: MIPSELSimulator>>unsignedWord: (in category 'as yet unclassified') -----
+ unsignedWord: address
+ 	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory unsignedLongAt: address + 1 bigEndian: false!

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

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAddiu (in category 'tests - arithmetic') -----
+ testAddiu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 42).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  2402002A  addiu v0, zr, 42
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 42].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAddiuNegative (in category 'tests - arithmetic') -----
+ testAddiuNegative
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: -42).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  2402FFD6  addiu v0, zr, -42
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: -42].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAddiuOverflow (in category 'tests - arithmetic') -----
+ testAddiuOverflow
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler luiR: T0 C: 16r7FFF).
+ 			stream nextPut: (compiler oriR: T0 R: T0 C: 16rFFFF).
+ 			stream nextPut: (compiler addiuR: V0 R: T0 C: 1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3C087FFF  lui t0, 32767
+ 00000004  3508FFFF  ori t0, t0, 65535
+ 00000008  25020001  addiu v0, t0, 1
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: -1 << 31].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAddiuUnderflow (in category 'tests - arithmetic') -----
+ testAddiuUnderflow
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler luiR: T0 C: 16r8000).
+ 			stream nextPut: (compiler addiuR: V0 R: T0 C: -1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3C088000  lui t0, -32768
+ 00000004  2502FFFF  addiu v0, t0, -1
+ 00000008  03E00008  jr ra
+ 0000000C  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: (1 << 31) - 1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAddu (in category 'tests - arithmetic') -----
+ testAddu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler adduR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00851021  addu v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: 7.
+ 			result := simulator call: 0 with: 3 with: -4 with: 0 with: 0.
+ 			self assert: result equals: -1.
+ 			result := simulator call: 0 with: -3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 16r7FFFFFFF with: 1 with: 0 with: 0.
+ 			self assert: result equals: (-1 << 31).
+ 			result := simulator call: 0 with: (-1 << 31) with: -1 with: 0 with: 0.
+ 			self assert: result equals: (1 << 31) - 1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAnd (in category 'tests - arithmetic') -----
+ testAnd
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler andR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00851024  and v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 2r1101 with: 2r1011 with: 0 with: 0.
+ 			self assert: result equals: 2r1001.
+ 			result := simulator call: 0 with: -1 with: 42 with: 0 with: 0.
+ 			self assert: result equals: 42].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAndi (in category 'tests - arithmetic') -----
+ testAndi
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler andiR: V0 R: A0 C: 16rFF).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  308200FF  andi v0, a0, 255
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 16r12345678 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r78.
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rFF].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testAndiNegative (in category 'tests - arithmetic') -----
+ testAndiNegative
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler andiR: V0 R: A0 C: -1). "Immediate is zero-extended, so same as 16rFFFF"
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3082FFFF  andi v0, a0, 65535
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 16r12345678 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r5678.
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rFFFF].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBeq (in category 'tests - control') -----
+ testBeq
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler beqR: A0 R: A1 offset: 8).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020004  addiu v0, zr, 4
+ 00000004  10850002  beq a0, a1, +8 ; =10
+ 00000008  00000000  nop
+ 0000000C  24020003  addiu v0, zr, 3
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBeqDelaySlot (in category 'tests - control') -----
+ testBeqDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler beqR: A0 R: A1 offset: 8).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  10850002  beq a0, a1, +8 ; =C
+ 00000004  24020003  addiu v0, zr, 3
+ 00000008  24420004  addiu v0, v0, 4
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 7].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBgez (in category 'tests - control') -----
+ testBgez
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler bgezR: A0 offset: 8).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020004  addiu v0, zr, 4
+ 00000004  04810002  bgez a0, +8 ; =10
+ 00000008  00000000  nop
+ 0000000C  24020003  addiu v0, zr, 3
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBgezDelaySlot (in category 'tests - control') -----
+ testBgezDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler bgezR: A0 offset: 8).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  04810002  bgez a0, +8 ; =C
+ 00000004  24020004  addiu v0, zr, 4
+ 00000008  24020003  addiu v0, zr, 3
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBgtz (in category 'tests - control') -----
+ testBgtz
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler bgtzR: A0 offset: 8).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020004  addiu v0, zr, 4
+ 00000004  1C800002  bgtz a0, +8 ; =10
+ 00000008  00000000  nop
+ 0000000C  24020003  addiu v0, zr, 3
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBgtzDelaySlot (in category 'tests - control') -----
+ testBgtzDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler bgtzR: A0 offset: 8).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  1C800002  bgtz a0, +8 ; =C
+ 00000004  24020004  addiu v0, zr, 4
+ 00000008  24020003  addiu v0, zr, 3
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBlez (in category 'tests - control') -----
+ testBlez
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler blezR: A0 offset: 8).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020004  addiu v0, zr, 4
+ 00000004  18800002  blez a0, +8 ; =10
+ 00000008  00000000  nop
+ 0000000C  24020003  addiu v0, zr, 3
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBlezDelaySlot (in category 'tests - control') -----
+ testBlezDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler blezR: A0 offset: 8).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  18800002  blez a0, +8 ; =C
+ 00000004  24020004  addiu v0, zr, 4
+ 00000008  24020003  addiu v0, zr, 3
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBltz (in category 'tests - control') -----
+ testBltz
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler bltzR: A0 offset: 8).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020004  addiu v0, zr, 4
+ 00000004  04800002  bltz a0, +8 ; =10
+ 00000008  00000000  nop
+ 0000000C  24020003  addiu v0, zr, 3
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBltzDelaySlot (in category 'tests - control') -----
+ testBltzDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler bltzR: A0 offset: 8).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  04800002  bltz a0, +8 ; =C
+ 00000004  24020004  addiu v0, zr, 4
+ 00000008  24020003  addiu v0, zr, 3
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4.
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBne (in category 'tests - control') -----
+ testBne
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler bneR: A0 R: A1 offset: 8).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020004  addiu v0, zr, 4
+ 00000004  14850002  bne a0, a1, +8 ; =10
+ 00000008  00000000  nop
+ 0000000C  24020003  addiu v0, zr, 3
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 4].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBneDelaySlot (in category 'tests - control') -----
+ testBneDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler bneR: A0 R: A1 offset: 8).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  14850002  bne a0, a1, +8 ; =C
+ 00000004  24020003  addiu v0, zr, 3
+ 00000008  24420004  addiu v0, v0, 4
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 7.
+ 			result := simulator call: 0 with: 1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testBreak (in category 'tests - control') -----
+ testBreak
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler break: 0)]
+ 		disassembly:
+ '00000000  0000000D  break
+ '		run: 
+ 			[:simulator | 
+ 			self should: [simulator call: 0 with: 0 with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testGenerateInto:disassembly:run: (in category 'execution') -----
+ testGenerateInto: generateBlock disassembly: expectedDisassembly run: executeBlock
+ 	| actualDisassembly compiler memory stopInstr instructions simulator |	
+ 	MIPSConstants initialize.
+ 	compiler := CogMIPSELCompiler new.
+ 	
+ 	stopInstr := compiler stop.
+ 	memory := ByteArray new: 1024.
+ 	1 to: 1024 by: 4 do:
+ 		[:i | memory unsignedLongAt: i put: stopInstr bigEndian: false].
+ 
+ 	instructions := Array streamContents: [:stream | generateBlock value: stream value: compiler].
+ 	instructions withIndexDo: 
+ 		[:instr :i | memory unsignedLongAt: (4 * (i - 1)) + 1 put: instr bigEndian: false].
+ 	
+ 	actualDisassembly := MIPSDisassembler new disassemble: memory from: 0 to: instructions size * 4.
+ 	self assert: actualDisassembly equals: expectedDisassembly.
+ 	
+ 	simulator := MIPSELSimulator new initializeWithMemory: memory.
+ 	executeBlock value: simulator.!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJ (in category 'tests - control') -----
+ testJ
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler jA: 16r10).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020003  addiu v0, zr, 3
+ 00000004  08000004  j 10
+ 00000008  00000000  nop
+ 0000000C  24420004  addiu v0, v0, 4
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJDelaySlot (in category 'tests - control') -----
+ testJDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler jA: 16rC).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  08000003  j C
+ 00000004  24020003  addiu v0, zr, 3
+ 00000008  24420004  addiu v0, v0, 4
+ 0000000C  03E00008  jr ra
+ 00000010  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJal (in category 'tests - control') -----
+ testJal
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: T0 R: RA C: 0).
+ 			stream nextPut: (compiler jalA: 16r1C).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 3).
+ 			stream nextPut: (compiler jR: T0).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler stop).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  27E80000  addiu t0, ra, 0
+ 00000004  0C000007  jal 1C
+ 00000008  00000000  nop
+ 0000000C  24420003  addiu v0, v0, 3
+ 00000010  01000008  jr t0
+ 00000014  00000000  nop
+ 00000018  0000000D  break
+ 0000001C  24020004  addiu v0, zr, 4
+ 00000020  03E00008  jr ra
+ 00000024  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 7].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJalDelaySlot (in category 'tests - control') -----
+ testJalDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: T0 R: RA C: 0).
+ 			stream nextPut: (compiler jalA: 16r1C).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 11). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 3).
+ 			stream nextPut: (compiler jR: T0).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler stop).
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  27E80000  addiu t0, ra, 0
+ 00000004  0C000007  jal 1C
+ 00000008  2402000B  addiu v0, zr, 11
+ 0000000C  24420003  addiu v0, v0, 3
+ 00000010  01000008  jr t0
+ 00000014  00000000  nop
+ 00000018  0000000D  break
+ 0000001C  24420004  addiu v0, v0, 4
+ 00000020  03E00008  jr ra
+ 00000024  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 18].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJalr (in category 'tests - control') -----
+ testJalr
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: T0 R: RA C: 0).
+ 			stream nextPut: (compiler addiuR: T9 R: ZR C: 16r20).
+ 			stream nextPut: (compiler jalR: T9).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 3).
+ 			stream nextPut: (compiler jR: T0).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler stop).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  27E80000  addiu t0, ra, 0
+ 00000004  24190020  addiu t9, zr, 32
+ 00000008  0320F809  jalr t9
+ 0000000C  00000000  nop
+ 00000010  24420003  addiu v0, v0, 3
+ 00000014  01000008  jr t0
+ 00000018  00000000  nop
+ 0000001C  0000000D  break
+ 00000020  24020004  addiu v0, zr, 4
+ 00000024  03E00008  jr ra
+ 00000028  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 7].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJalrDelaySlot (in category 'tests - control') -----
+ testJalrDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: T0 R: RA C: 0).
+ 			stream nextPut: (compiler addiuR: T9 R: ZR C: 16r20).
+ 			stream nextPut: (compiler jalR: T9).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 11). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 3).
+ 			stream nextPut: (compiler jR: T0).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler stop).
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  27E80000  addiu t0, ra, 0
+ 00000004  24190020  addiu t9, zr, 32
+ 00000008  0320F809  jalr t9
+ 0000000C  2402000B  addiu v0, zr, 11
+ 00000010  24420003  addiu v0, v0, 3
+ 00000014  01000008  jr t0
+ 00000018  00000000  nop
+ 0000001C  0000000D  break
+ 00000020  24420004  addiu v0, v0, 4
+ 00000024  03E00008  jr ra
+ 00000028  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 18].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJr (in category 'tests - control') -----
+ testJr
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3).
+ 			stream nextPut: (compiler addiuR: T9 R: ZR C: 16r14).
+ 			stream nextPut: (compiler jR: T9).
+ 			stream nextPut: (compiler nop). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24020003  addiu v0, zr, 3
+ 00000004  24190014  addiu t9, zr, 20
+ 00000008  03200008  jr t9
+ 0000000C  00000000  nop
+ 00000010  24420004  addiu v0, v0, 4
+ 00000014  03E00008  jr ra
+ 00000018  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testJrDelaySlot (in category 'tests - control') -----
+ testJrDelaySlot
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler addiuR: T9 R: ZR C: 16r10).
+ 			stream nextPut: (compiler jR: T9).
+ 			stream nextPut: (compiler addiuR: V0 R: ZR C: 3). "Delay slot"
+ 			stream nextPut: (compiler addiuR: V0 R: V0 C: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  24190010  addiu t9, zr, 16
+ 00000004  03200008  jr t9
+ 00000008  24020003  addiu v0, zr, 3
+ 0000000C  24420004  addiu v0, v0, 4
+ 00000010  03E00008  jr ra
+ 00000014  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 3].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLb (in category 'tests - memory') -----
+ testLb
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lbR: V0 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  80820004  lb v0, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42.
+ 			result := simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 43.
+ 			result := simulator call: 0 with: 16rE2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 44.
+ 			result := simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 45.
+ 			result := simulator call: 0 with: 16rF0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -42.
+ 			result := simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -43.
+ 			result := simulator call: 0 with: 16rF2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -44.
+ 			result := simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLbNegativeOffset (in category 'tests - memory') -----
+ testLbNegativeOffset
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lbR: V0 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  8082FFFC  lb v0, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42.
+ 			result := simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 43.
+ 			result := simulator call: 0 with: 16rEA with: 0 with: 0 with: 0.
+ 			self assert: result equals: 44.
+ 			result := simulator call: 0 with: 16rEB with: 0 with: 0 with: 0.
+ 			self assert: result equals: 45.
+ 			result := simulator call: 0 with: 16rF8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -42.
+ 			result := simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -43.
+ 			result := simulator call: 0 with: 16rFA with: 0 with: 0 with: 0.
+ 			self assert: result equals: -44.
+ 			result := simulator call: 0 with: 16rFB with: 0 with: 0 with: 0.
+ 			self assert: result equals: -45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLbu (in category 'tests - memory') -----
+ testLbu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lbuR: V0 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  90820004  lbu v0, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42.
+ 			result := simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 43.
+ 			result := simulator call: 0 with: 16rE2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 44.
+ 			result := simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 45.
+ 			result := simulator call: 0 with: 16rF0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 42.
+ 			result := simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 43.
+ 			result := simulator call: 0 with: 16rF2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 44.
+ 			result := simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLbuNegativeOffset (in category 'tests - memory') -----
+ testLbuNegativeOffset
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lbuR: V0 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  9082FFFC  lbu v0, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42.
+ 			result := simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 43.
+ 			result := simulator call: 0 with: 16rEA with: 0 with: 0 with: 0.
+ 			self assert: result equals: 44.
+ 			result := simulator call: 0 with: 16rEB with: 0 with: 0 with: 0.
+ 			self assert: result equals: 45.
+ 			result := simulator call: 0 with: 16rF8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 42.
+ 			result := simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 43.
+ 			result := simulator call: 0 with: 16rFA with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 44.
+ 			result := simulator call: 0 with: 16rFB with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLh (in category 'tests - memory') -----
+ testLh
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lhR: V0 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  84820004  lh v0, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2B2A.
+ 			self should: [simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rE2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2D2C.
+ 			self should: [simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF0 with: 0 with: 0 with: 0.
+ 			self assert: result equals:  -16r2A2A.
+ 			self should: [simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -16r2C2C.
+ 			self should: [simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLhNegativeOffset (in category 'tests - memory') -----
+ testLhNegativeOffset
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lhR: V0 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  8482FFFC  lh v0, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2B2A.
+ 			self should: [simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rEA with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2D2C.
+ 			self should: [simulator call: 0 with: 16rEB with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF8 with: 0 with: 0 with: 0.
+ 			self assert: result equals:  -16r2A2A.
+ 			self should: [simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rFA with: 0 with: 0 with: 0.
+ 			self assert: result equals: -16r2C2C.
+ 			self should: [simulator call: 0 with: 16rFB with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLhu (in category 'tests - memory') -----
+ testLhu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lhuR: V0 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  94820004  lhu v0, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2B2A.
+ 			self should: [simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rE2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2D2C.
+ 			self should: [simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rD5D6.
+ 			self should: [simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rD3D4.
+ 			self should: [simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLhuNegativeOffset (in category 'tests - memory') -----
+ testLhuNegativeOffset
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lhuR: V0 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  9482FFFC  lhu v0, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2B2A.
+ 			self should: [simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rEA with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2D2C.
+ 			self should: [simulator call: 0 with: 16rEB with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rD5D6.
+ 			self should: [simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rFA with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rD3D4.
+ 			self should: [simulator call: 0 with: 16rFB with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLoadLargeLiteral (in category 'tests - arithmetic') -----
+ testLoadLargeLiteral
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler luiR: V0 C: 16r3FFF).
+ 			stream nextPut: (compiler oriR: V0 R: V0 C: 16rFFFF).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3C023FFF  lui v0, 16383
+ 00000004  3442FFFF  ori v0, v0, 65535
+ 00000008  03E00008  jr ra
+ 0000000C  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 16r3FFFFFFF].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLui (in category 'tests - arithmetic') -----
+ testLui
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler luiR: V0 C: 42).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3C02002A  lui v0, 42
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 42 << 16].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLuiNegative (in category 'tests - arithmetic') -----
+ testLuiNegative
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler luiR: V0 C: -42).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3C02FFD6  lui v0, -42
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: -42 << 16].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLw (in category 'tests - memory') -----
+ testLw
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lwR: V0 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  8C820004  lw v0, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2D2C2B2A.
+ 			self should: [simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rE2 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -16r2C2B2A2A.
+ 			self should: [simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rF2 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testLwNegativeOffset (in category 'tests - memory') -----
+ testLwNegativeOffset
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler lwR: V0 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  8C82FFFC  lw v0, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator memory at: 16rE4 + 1 put: 42.
+ 			simulator memory at: 16rE5 + 1 put: 43.
+ 			simulator memory at: 16rE6 + 1 put: 44.
+ 			simulator memory at: 16rE7 + 1 put: 45.
+ 			simulator memory at: 16rF4 + 1 put: 16r100 - 42.
+ 			simulator memory at: 16rF5 + 1 put: 16r100 - 43.
+ 			simulator memory at: 16rF6 + 1 put: 16r100 - 44.
+ 			simulator memory at: 16rF7 + 1 put: 16r100 - 45.
+ 			result := simulator call: 0 with: 16rE8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16r2D2C2B2A.
+ 			self should: [simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rEA with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rEB with: 0 with: 0 with: 0] raise: Error.
+ 			result := simulator call: 0 with: 16rF8 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -16r2C2B2A2A.
+ 			self should: [simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rFA with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rFB with: 0 with: 0 with: 0] raise: Error].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testOr (in category 'tests - arithmetic') -----
+ testOr
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler orR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00851025  or v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 2r101 with: 2r011 with: 0 with: 0.
+ 			self assert: result equals: 2r111.
+ 			result := simulator call: 0 with: -1 with: 42 with: 0 with: 0.
+ 			self assert: result equals: -1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testOri (in category 'tests - arithmetic') -----
+ testOri
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler oriR: V0 R: ZR C: 16rFFFF).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3402FFFF  ori v0, zr, 65535
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 16rFFFF].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testOriNegative (in category 'tests - arithmetic') -----
+ testOriNegative
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler oriR: V0 R: ZR C: -42).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3402FFD6  ori v0, zr, 65494
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0.
+ 			self assert: result equals: 16r10000 - 42].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSb (in category 'tests - memory') -----
+ testSb
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sbR: A1 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  A0850004  sb a1, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator call: 0 with: 16rE0 with: 42 with: 0 with: 0.
+ 			simulator call: 0 with: 16rE1 with: 43 with: 0 with: 0.
+ 			simulator call: 0 with: 16rE2 with: 44 with: 0 with: 0.
+ 			simulator call: 0 with: 16rE3 with: 45 with: 0 with: 0.
+ 			simulator call: 0 with: 16rF0 with: -42 with: 0 with: 0.
+ 			simulator call: 0 with: 16rF1 with: -43 with: 0 with: 0.
+ 			simulator call: 0 with: 16rF2 with: -44 with: 0 with: 0.
+ 			simulator call: 0 with: 16rF3 with: -45 with: 0 with: 0.
+ 			self assert: (simulator memory at: 16rE4 + 1) equals: 42.
+ 			self assert: (simulator memory at: 16rE5 + 1) equals: 43.
+ 			self assert: (simulator memory at: 16rE6 + 1) equals: 44.
+ 			self assert: (simulator memory at: 16rE7 + 1) equals: 45.
+ 			self assert: (simulator memory at: 16rF4 + 1) equals: 16r100 - 42.
+ 			self assert: (simulator memory at: 16rF5 + 1) equals: 16r100 - 43.
+ 			self assert: (simulator memory at: 16rF6 + 1) equals: 16r100 - 44.
+ 			self assert: (simulator memory at: 16rF7 + 1) equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSbNegativeOffset (in category 'tests - memory') -----
+ testSbNegativeOffset
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sbR: A1 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  A085FFFC  sb a1, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator call: 0 with: 16rE8 with: 42 with: 0 with: 0.
+ 			simulator call: 0 with: 16rE9 with: 43 with: 0 with: 0.
+ 			simulator call: 0 with: 16rEA with: 44 with: 0 with: 0.
+ 			simulator call: 0 with: 16rEB with: 45 with: 0 with: 0.
+ 			simulator call: 0 with: 16rF8 with: -42 with: 0 with: 0.
+ 			simulator call: 0 with: 16rF9 with: -43 with: 0 with: 0.
+ 			simulator call: 0 with: 16rFA with: -44 with: 0 with: 0.
+ 			simulator call: 0 with: 16rFB with: -45 with: 0 with: 0.
+ 			self assert: (simulator memory at: 16rE4 + 1) equals: 42.
+ 			self assert: (simulator memory at: 16rE5 + 1) equals: 43.
+ 			self assert: (simulator memory at: 16rE6 + 1) equals: 44.
+ 			self assert: (simulator memory at: 16rE7 + 1) equals: 45.
+ 			self assert: (simulator memory at: 16rF4 + 1) equals: 16r100 - 42.
+ 			self assert: (simulator memory at: 16rF5 + 1) equals: 16r100 - 43.
+ 			self assert: (simulator memory at: 16rF6 + 1) equals: 16r100 - 44.
+ 			self assert: (simulator memory at: 16rF7 + 1) equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSh (in category 'tests - memory') -----
+ testSh
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler shR: A1 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  A4850004  sh a1, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator call: 0 with: 16rE0 with: 16r2B2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rE2 with: 16r2D2C with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rF0 with: -16r2A2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rF2 with: -16r2C2C with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0] raise: Error.
+ 			self assert: (simulator memory at: 16rE4 + 1) equals: 42.
+ 			self assert: (simulator memory at: 16rE5 + 1) equals: 43.
+ 			self assert: (simulator memory at: 16rE6 + 1) equals: 44.
+ 			self assert: (simulator memory at: 16rE7 + 1) equals: 45.
+ 			self assert: (simulator memory at: 16rF4 + 1) equals: 16r100 - 42.
+ 			self assert: (simulator memory at: 16rF5 + 1) equals: 16r100 - 43.
+ 			self assert: (simulator memory at: 16rF6 + 1) equals: 16r100 - 44.
+ 			self assert: (simulator memory at: 16rF7 + 1) equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testShNegativeOffset (in category 'tests - memory') -----
+ testShNegativeOffset
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler shR: A1 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  A485FFFC  sh a1, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator call: 0 with: 16rE8 with: 16r2B2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rEA with: 16r2D2C with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rEB with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rF8 with: -16r2A2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rFA with: -16r2C2C with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rFB with: 0 with: 0 with: 0] raise: Error.
+ 			self assert: (simulator memory at: 16rE4 + 1) equals: 42.
+ 			self assert: (simulator memory at: 16rE5 + 1) equals: 43.
+ 			self assert: (simulator memory at: 16rE6 + 1) equals: 44.
+ 			self assert: (simulator memory at: 16rE7 + 1) equals: 45.
+ 			self assert: (simulator memory at: 16rF4 + 1) equals: 16r100 - 42.
+ 			self assert: (simulator memory at: 16rF5 + 1) equals: 16r100 - 43.
+ 			self assert: (simulator memory at: 16rF6 + 1) equals: 16r100 - 44.
+ 			self assert: (simulator memory at: 16rF7 + 1) equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSll (in category 'tests - arithmetic') -----
+ testSll
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sllR: V0 R: A0 C: 2).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00041080  sll v0, a0, 2
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 42 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42 << 2.
+ 			result := simulator call: 0 with: -42 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -42 << 2].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSllv (in category 'tests - arithmetic') -----
+ testSllv
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sllvR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00A41004  sllv v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 42 with: 2 with: 0 with: 0.
+ 			self assert: result equals: 42 << 2.
+ 			result := simulator call: 0 with: -42 with: 2 with: 0 with: 0.
+ 			self assert: result equals: -42 << 2].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSlt (in category 'tests - arithmetic') -----
+ testSlt
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sltR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  0085102A  slt v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 4 with: 3 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 4 with: -3 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: 5 with: 5 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -5 with: -5 with: 0 with: 0.
+ 			self assert: result equals: 0].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSlti (in category 'tests - arithmetic') -----
+ testSlti
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sltiR: V0 R: A0 C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  28820003  slti v0, a0, 3
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: 4 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSltiNegative (in category 'tests - arithmetic') -----
+ testSltiNegative
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sltiR: V0 R: A0 C: -3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  2882FFFD  slti v0, a0, -3
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: 4 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -4 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSltiu (in category 'tests - arithmetic') -----
+ testSltiu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sltiuR: V0 R: A0 C: 3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  2C820003  sltiu v0, a0, 3
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: 4 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSltiuNegative (in category 'tests - arithmetic') -----
+ testSltiuNegative
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sltiuR: V0 R: A0 C: -3).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  2C82FFFD  sltiu v0, a0, -3
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 4 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: -2 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -3 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -4 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSltu (in category 'tests - arithmetic') -----
+ testSltu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sltuR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  0085102B  sltu v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 4 with: 3 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: 4 with: -3 with: 0 with: 0.
+ 			self assert: result equals: 1.
+ 			result := simulator call: 0 with: 5 with: 5 with: 0 with: 0.
+ 			self assert: result equals: 0.
+ 			result := simulator call: 0 with: -5 with: -5 with: 0 with: 0.
+ 			self assert: result equals: 0].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSra (in category 'tests - arithmetic') -----
+ testSra
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sraR: V0 R: A0 C: 2).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00041083  sra v0, a0, 2
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 42 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42 >> 2.
+ 			result := simulator call: 0 with: -42 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -42 >> 2].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSrav (in category 'tests - arithmetic') -----
+ testSrav
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler sravR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00A41007  srav v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 42 with: 2 with: 0 with: 0.
+ 			self assert: result equals: 42 >> 2.
+ 			result := simulator call: 0 with: -42 with: 2 with: 0 with: 0.
+ 			self assert: result equals: -42 >> 2].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSrl (in category 'tests - arithmetic') -----
+ testSrl
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler srlR: V0 R: A0 C: 2).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00041082  srl v0, a0, 2
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 42 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 42 >> 2.
+ 			result := simulator call: 0 with: -42 with: 0 with: 0 with: 0.
+ 			self assert: result equals: (16r100000000 - 42) >> 2].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSrlv (in category 'tests - arithmetic') -----
+ testSrlv
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler srlvR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00A41006  srlv v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 42 with: 2 with: 0 with: 0.
+ 			self assert: result equals: 42 >> 2.
+ 			result := simulator call: 0 with: -42 with: 2 with: 0 with: 0.
+ 			self assert: result equals: (16r100000000 - 42) >> 2].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSubu (in category 'tests - arithmetic') -----
+ testSubu
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler subuR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00851023  subu v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: -1.
+ 			result := simulator call: 0 with: 3 with: -4 with: 0 with: 0.
+ 			self assert: result equals: 7.
+ 			result := simulator call: 0 with: -3 with: 4 with: 0 with: 0.
+ 			self assert: result equals: -7.
+ 			result := simulator call: 0 with: 16r7FFFFFFF with: -1 with: 0 with: 0.
+ 			self assert: result equals: (-1 << 31).
+ 			result := simulator call: 0 with: (-1 << 31) with: 1 with: 0 with: 0.
+ 			self assert: result equals: (1 << 31) - 1].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSw (in category 'tests - memory') -----
+ testSw
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler swR: A1 base: A0 offset: 4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  AC850004  sw a1, 4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator call: 0 with: 16rE0 with: 16r2D2C2B2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rE1 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rE2 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rE3 with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rF0 with: -16r2C2B2A2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rF1 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rF2 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rF3 with: 0 with: 0 with: 0] raise: Error.
+ 			self assert: (simulator memory at: 16rE4 + 1) equals: 42.
+ 			self assert: (simulator memory at: 16rE5 + 1) equals: 43.
+ 			self assert: (simulator memory at: 16rE6 + 1) equals: 44.
+ 			self assert: (simulator memory at: 16rE7 + 1) equals: 45.
+ 			self assert: (simulator memory at: 16rF4 + 1) equals: 16r100 - 42.
+ 			self assert: (simulator memory at: 16rF5 + 1) equals: 16r100 - 43.
+ 			self assert: (simulator memory at: 16rF6 + 1) equals: 16r100 - 44.
+ 			self assert: (simulator memory at: 16rF7 + 1) equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testSwNegativeOffset (in category 'tests - memory') -----
+ testSwNegativeOffset
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler swR: A1 base: A0 offset: -4).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  AC85FFFC  sw a1, -4(a0)
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			simulator call: 0 with: 16rE8 with: 16r2D2C2B2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rE9 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rEA with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rEB with: 0 with: 0 with: 0] raise: Error.
+ 			simulator call: 0 with: 16rF8 with: -16r2C2B2A2A with: 0 with: 0.
+ 			self should: [simulator call: 0 with: 16rF9 with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rFA with: 0 with: 0 with: 0] raise: Error.
+ 			self should: [simulator call: 0 with: 16rFB with: 0 with: 0 with: 0] raise: Error.
+ 			self assert: (simulator memory at: 16rE4 + 1) equals: 42.
+ 			self assert: (simulator memory at: 16rE5 + 1) equals: 43.
+ 			self assert: (simulator memory at: 16rE6 + 1) equals: 44.
+ 			self assert: (simulator memory at: 16rE7 + 1) equals: 45.
+ 			self assert: (simulator memory at: 16rF4 + 1) equals: 16r100 - 42.
+ 			self assert: (simulator memory at: 16rF5 + 1) equals: 16r100 - 43.
+ 			self assert: (simulator memory at: 16rF6 + 1) equals: 16r100 - 44.
+ 			self assert: (simulator memory at: 16rF7 + 1) equals: 16r100 - 45].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testXor (in category 'tests - arithmetic') -----
+ testXor
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler xorR: V0 R: A0 R: A1).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  00851026  xor v0, a0, a1
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 2r101 with: 2r011 with: 0 with: 0.
+ 			self assert: result equals: 2r110.
+ 			result := simulator call: 0 with: -1 with: 42 with: 0 with: 0.
+ 			self assert: result equals: 42 bitInvert].!

Item was added:
+ ----- Method: MIPSELSimulatorTests>>testXori (in category 'tests - arithmetic') -----
+ testXori
+ 	| result |
+ 	self 
+ 		testGenerateInto: 
+ 			[:stream :compiler | 
+ 			stream nextPut: (compiler xoriR: V0 R: A0 C: 16rABCD).
+ 			stream nextPut: (compiler jR: RA).
+ 			stream nextPut: (compiler nop). "Delay slot"]
+ 		disassembly:
+ '00000000  3882ABCD  xori v0, a0, 43981
+ 00000004  03E00008  jr ra
+ 00000008  00000000  nop
+ '		run: 
+ 			[:simulator | 
+ 			result := simulator call: 0 with: 0 with: 0 with: 0 with: 0.
+ 			self assert: result equals: 16rABCD.
+ 			result := simulator call: 0 with: -1 with: 0 with: 0 with: 0.
+ 			self assert: result equals: -16rABCE].!

Item was added:
+ Object subclass: #MIPSInstruction
+ 	instanceVariableNames: 'value'
+ 	classVariableNames: ''
+ 	poolDictionaries: 'MIPSConstants'
+ 	category: 'Cog-Processors'!
+ 
+ !MIPSInstruction commentStamp: 'rmacnak 11/11/2015 20:31:24' prior: 0!
+ Wrapper for decoding MIPS instructions.!

Item was added:
+ ----- Method: MIPSInstruction>>decodeFor: (in category 'as yet unclassified') -----
+ decodeFor: visitor
+ 	| opcode |
+ 	opcode := self opcode.
+ 	opcode = SPECIAL ifTrue: [^self decodeSpecialFor: visitor].
+ 	opcode = REGIMM ifTrue: [^self decodeRegImmFor: visitor].
+ 
+ 	opcode = J ifTrue: [^visitor jump: self].
+ 	opcode = JAL ifTrue: [^visitor jumpAndLink: self].
+ 	opcode = BEQ ifTrue: [^visitor branchEqual: self].
+ 	opcode = BNE ifTrue: [^visitor branchNotEqual: self].
+ 	opcode = BLEZ ifTrue: [^visitor branchLessEqualZero: self].
+ 	opcode = BGTZ ifTrue: [^visitor branchGreaterThanZero: self].
+ 	opcode = ADDIU ifTrue: [^visitor addImmediateUnsigned: self].
+ 	opcode = SLTI ifTrue: [^visitor setOnLessThanImmediate: self].
+ 	opcode = SLTIU ifTrue: [^visitor setOnLessThanImmediateUnsigned: self].
+ 	opcode = ANDI ifTrue: [^visitor andImmediate: self].
+ 	opcode = ORI ifTrue: [^visitor orImmediate: self].
+ 	opcode = XORI ifTrue: [^visitor xorImmediate: self].
+ 	opcode = LUI ifTrue: [^visitor loadUpperImmediate: self].
+ 	opcode = LB ifTrue: [^visitor loadByte: self].
+ 	opcode = LH ifTrue: [^visitor loadHalfword: self].
+ 	opcode = LW ifTrue: [^visitor loadWord: self].
+ 	opcode = LBU ifTrue: [^visitor loadByteUnsigned: self].
+ 	opcode = LHU ifTrue: [^visitor loadHalfwordUnsigned: self].
+ 	opcode = SB ifTrue: [^visitor storeByte: self].
+ 	opcode = SH ifTrue: [^visitor storeHalfword: self].
+ 	opcode = SW ifTrue: [^visitor storeWord: self].
+ 	
+ 	self error: 'Unknown instruction'.!

Item was added:
+ ----- Method: MIPSInstruction>>decodeRegImmFor: (in category 'as yet unclassified') -----
+ decodeRegImmFor: visitor
+ 	| fn |
+ 	fn := self rt.
+ 	fn = BLTZ ifTrue: [^visitor branchLessThanZero: self].
+ 	fn = BGEZ ifTrue: [^visitor branchGreaterEqualZero: self].
+ 	
+ 	self error: 'Unknown instruction'.!

Item was added:
+ ----- Method: MIPSInstruction>>decodeSpecialFor: (in category 'as yet unclassified') -----
+ decodeSpecialFor: visitor
+ 	| function |
+ 	function := self function.
+ 	function = SLL ifTrue: [^visitor shiftLeftLogical: self].
+ 	function = SRL ifTrue: [^visitor shiftRightLogical: self].
+ 	function = SRA ifTrue: [^visitor shiftRightArithmetic: self].
+ 	function = SLLV ifTrue: [^visitor shiftLeftLogicalVariable: self].
+ 	function = SRLV ifTrue: [^visitor shiftRightLogicalVariable: self].
+ 	function = SRAV ifTrue: [^visitor shiftRightArithmeticVariable: self].
+ 	function = JR ifTrue: [^visitor jumpRegister: self].
+ 	function = JALR ifTrue: [^visitor jumpAndLinkRegister: self].
+ 	function = BREAK ifTrue: [^visitor break: self].
+ 	function = ADDU ifTrue: [^visitor addUnsigned: self].
+ 	function = SUBU ifTrue: [^visitor subtractUnsigned: self].
+ 	function = AND ifTrue: [^visitor bitwiseAnd: self].
+ 	function = OR ifTrue: [^visitor bitwiseOr: self].
+ 	function = XOR ifTrue: [^visitor bitwiseXor: self].
+ 	function = SLT ifTrue: [^visitor setOnLessThan: self].
+ 	function = SLTU ifTrue: [^visitor setOnLessThanUnsigned: self].
+ 	
+ 	self error: 'Unknown instruction'.!

Item was added:
+ ----- Method: MIPSInstruction>>function (in category 'fields') -----
+ function
+ 	^value bitAnd: 63!

Item was added:
+ ----- Method: MIPSInstruction>>opcode (in category 'fields') -----
+ opcode
+ 	^value >> 26!

Item was added:
+ ----- Method: MIPSInstruction>>rd (in category 'fields') -----
+ rd
+ 	^(value >> 11) bitAnd: 31!

Item was added:
+ ----- Method: MIPSInstruction>>rs (in category 'fields') -----
+ rs
+ 	^(value >> 21) bitAnd: 31!

Item was added:
+ ----- Method: MIPSInstruction>>rt (in category 'fields') -----
+ rt
+ 	^(value >> 16) bitAnd: 31!

Item was added:
+ ----- Method: MIPSInstruction>>sa (in category 'fields') -----
+ sa
+ 	^(value >> 6) bitAnd: 15!

Item was added:
+ ----- Method: MIPSInstruction>>signedImmediate (in category 'fields') -----
+ signedImmediate
+ 	^self unsigned16ToSigned16: (self unsignedImmediate)!

Item was added:
+ ----- Method: MIPSInstruction>>target (in category 'fields') -----
+ target
+ 	^value bitAnd: 16r3FFFFFF!

Item was added:
+ ----- Method: MIPSInstruction>>unsigned16ToSigned16: (in category 'fields') -----
+ unsigned16ToSigned16: unsignedValue
+ 	self assert: (unsignedValue between: 0 and: 16rFFFF).
+ 	unsignedValue >= 16r8000 ifTrue: [^unsignedValue - 16r10000].
+ 	^unsignedValue!

Item was added:
+ ----- Method: MIPSInstruction>>unsignedImmediate (in category 'fields') -----
+ unsignedImmediate
+ 	^value bitAnd: 16rFFFF!

Item was added:
+ ----- Method: MIPSInstruction>>value (in category 'as yet unclassified') -----
+ value
+ 	^value!

Item was added:
+ ----- Method: MIPSInstruction>>value: (in category 'as yet unclassified') -----
+ value: anInteger
+ 	self assert: (anInteger between: 0 and: 16rFFFFFFFF).
+ 	value := anInteger!

Item was added:
+ Object subclass: #MIPSSimulator
+ 	instanceVariableNames: 'memory registers pc instructionCount inDelaySlot'
+ 	classVariableNames: 'EndSimulationPC'
+ 	poolDictionaries: 'MIPSConstants'
+ 	category: 'Cog-Processors'!
+ 
+ !MIPSSimulator commentStamp: 'rmacnak 11/11/2015 20:33:00' prior: 0!
+ Simulator for 32-bit MIPS, without implementation of memory access.!

Item was added:
+ ----- Method: MIPSSimulator class>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	super initialize.
+ 	EndSimulationPC := 16rABABABAB.
+ 	OneInstruction := 4.
+ 	TwoInstructions := 8.!

Item was added:
+ ----- Method: MIPSSimulator>>addImmediateUnsigned: (in category 'instructions - arithmetic') -----
+ addImmediateUnsigned: instruction
+ 	"Unsigned here means the instruction doesn't generate exceptions,
+ 	 not that the immediate is unsigned."
+ 	| rsValue immediate result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	immediate := instruction signedImmediate.
+ 	result := rsValue + immediate bitAnd: 16rFFFFFFFF. "No exception on overflow"
+ 	self unsignedRegister: instruction rt put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>addUnsigned: (in category 'instructions - arithmetic') -----
+ addUnsigned: instruction
+ 	"Unsigned here means the instruction doesn't generate exceptions."
+ 	| rsValue rtValue result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	result := rsValue + rtValue bitAnd: 16rFFFFFFFF. "No exception on overflow"
+ 	self unsignedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>andImmediate: (in category 'instructions - arithmetic') -----
+ andImmediate: instruction
+ 	| rsValue immediate result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	immediate := instruction unsignedImmediate.
+ 	result := rsValue bitAnd: immediate.
+ 	self unsignedRegister: instruction rt put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>bitwiseAnd: (in category 'instructions - arithmetic') -----
+ bitwiseAnd: instruction
+ 	| rsValue rtValue result |
+ 	rsValue := self signedRegister: instruction rs.
+ 	rtValue := self signedRegister: instruction rt.
+ 	result := rsValue bitAnd: rtValue.
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>bitwiseOr: (in category 'instructions - arithmetic') -----
+ bitwiseOr: instruction
+ 	| rsValue rtValue result |
+ 	rsValue := self signedRegister: instruction rs.
+ 	rtValue := self signedRegister: instruction rt.
+ 	result := rsValue bitOr: rtValue.
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>bitwiseXor: (in category 'instructions - arithmetic') -----
+ bitwiseXor: instruction
+ 	| rsValue rtValue result |
+ 	rsValue := self signedRegister: instruction rs.
+ 	rtValue := self signedRegister: instruction rt.
+ 	result := rsValue bitXor: rtValue.
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>branchEqual: (in category 'instructions - control') -----
+ branchEqual: instruction
+ 	| rsValue rtValue |
+ 	self assert: inDelaySlot not.
+ 	rsValue := self signedRegister: instruction rs.
+ 	rtValue := self signedRegister: instruction rt.
+ 	self doBranch: rsValue = rtValue offset: instruction signedImmediate << 2.!

Item was added:
+ ----- Method: MIPSSimulator>>branchGreaterEqualZero: (in category 'instructions - control') -----
+ branchGreaterEqualZero: instruction
+ 	| rsValue |
+ 	self assert: inDelaySlot not.
+ 	rsValue := self signedRegister: instruction rs.
+ 	self doBranch: rsValue >= 0 offset: instruction signedImmediate << 2.!

Item was added:
+ ----- Method: MIPSSimulator>>branchGreaterThanZero: (in category 'instructions - control') -----
+ branchGreaterThanZero: instruction
+ 	| rsValue |
+ 	self assert: inDelaySlot not.
+ 	rsValue := self signedRegister: instruction rs.
+ 	self doBranch: rsValue > 0 offset: instruction signedImmediate << 2.!

Item was added:
+ ----- Method: MIPSSimulator>>branchLessEqualZero: (in category 'instructions - control') -----
+ branchLessEqualZero: instruction
+ 	| rsValue |
+ 	self assert: inDelaySlot not.
+ 	rsValue := self signedRegister: instruction rs.
+ 	self doBranch: rsValue <= 0 offset: instruction signedImmediate << 2.!

Item was added:
+ ----- Method: MIPSSimulator>>branchLessThanZero: (in category 'instructions - control') -----
+ branchLessThanZero: instruction
+ 	| rsValue |
+ 	self assert: inDelaySlot not.
+ 	rsValue := self signedRegister: instruction rs.
+ 	self doBranch: rsValue < 0 offset: instruction signedImmediate << 2.!

Item was added:
+ ----- Method: MIPSSimulator>>branchNotEqual: (in category 'instructions - control') -----
+ branchNotEqual: instruction
+ 	| rsValue rtValue |
+ 	self assert: inDelaySlot not.
+ 	rsValue := self signedRegister: instruction rs.
+ 	rtValue := self signedRegister: instruction rt.
+ 	self doBranch: rsValue ~= rtValue offset: instruction signedImmediate << 2.!

Item was added:
+ ----- Method: MIPSSimulator>>break: (in category 'instructions - control') -----
+ break: instruction
+ 	self error: 'Break!!'!

Item was added:
+ ----- Method: MIPSSimulator>>call: (in category 'as yet unclassified') -----
+ call: entryPC
+ 	| zapValue |
+ 	zapValue := self unsigned32ToSigned32: 16rBABABABA.
+ 	^self call: entryPC with: zapValue with: zapValue with: zapValue with: zapValue!

Item was added:
+ ----- Method: MIPSSimulator>>call:with:with:with:with: (in category 'as yet unclassified') -----
+ call: entryPC with: arg0 with: arg1 with: arg2 with: arg3.
+ 	
+ 	pc := entryPC.
+ 	self unsignedRegister: RA put: EndSimulationPC.
+ 	self signedRegister: A0 put: arg0.
+ 	self signedRegister: A1 put: arg1.
+ 	self signedRegister: A2 put: arg2.
+ 	self signedRegister: A3 put: arg3.
+ 	
+ 	self execute.
+ 	
+ 	^self signedRegister: V0.!

Item was added:
+ ----- Method: MIPSSimulator>>disassembleFrom:to:in:for:labels:on: (in category 'processor api') -----
+ disassembleFrom: startAddress to: endAddress in: memory for: aSymbolManager "<Cogit>" labels: labelDictionary on: aStream
+ 	MIPSDisassembler new 
+ 		disassemble: memory
+ 		from: startAddress
+ 		to: endAddress
+ 		for: aSymbolManager
+ 		labels: labelDictionary
+ 		on: aStream.!

Item was added:
+ ----- Method: MIPSSimulator>>doBranch:offset: (in category 'as yet unclassified') -----
+ doBranch: taken offset: offset
+ 	| nextPC |
+ 	pc := pc + OneInstruction.
+ 	nextPC := pc + offset. "Branch target is relative to the delay slot."
+ 	self executeDelaySlot.
+ 	taken ifTrue: [pc := nextPC - OneInstruction "Account for general increment"].!

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

Item was added:
+ ----- Method: MIPSSimulator>>execute (in category 'as yet unclassified') -----
+ execute
+ 	| instruction |
+ 	[pc ~= EndSimulationPC] whileTrue: 
+ 		[instruction := MIPSInstruction new value: (self unsignedWord: pc).
+ 		 instruction decodeFor: self.
+ 		 pc := pc + OneInstruction].!

Item was added:
+ ----- Method: MIPSSimulator>>executeDelaySlot (in category 'as yet unclassified') -----
+ executeDelaySlot
+ 	| instruction |
+ 	self assert: inDelaySlot not.
+ 	inDelaySlot := true.
+ 	instruction := MIPSInstruction new value: (self unsignedWord: pc).
+ 	instruction decodeFor: self.
+ 	inDelaySlot := false.!

Item was added:
+ ----- Method: MIPSSimulator>>flushICacheFrom:to: (in category 'processor api') -----
+ flushICacheFrom: startAddress "<Integer>" to: endAddress "<Integer>"!

Item was added:
+ ----- Method: MIPSSimulator>>fp (in category 'processor api') -----
+ fp
+ 	^self signedRegister: FP!

Item was added:
+ ----- Method: MIPSSimulator>>initializeStackFor: (in category 'processor api') -----
+ initializeStackFor: aCogit
+ 	self flag: #OABI.
+ 	aCogit setStackAlignment: 8 expectedSPOffset: 0 expectedFPOffset: 0.
+ 	self initializeWithMemory: ByteArray new.
+ 	!

Item was added:
+ ----- Method: MIPSSimulator>>initializeWithMemory: (in category 'as yet unclassified') -----
+ initializeWithMemory: aByteArray
+ 	memory := aByteArray.
+ 	registers := Array new: 32 withAll: 0.
+ 	pc := 0.
+ 	inDelaySlot := false.
+ 	instructionCount := 0.!

Item was added:
+ ----- Method: MIPSSimulator>>jump: (in category 'instructions - control') -----
+ jump: instruction
+ 	| nextPC |
+ 	self assert: inDelaySlot not.
+ 	pc := pc + OneInstruction.
+ 	nextPC := (pc bitAnd: 16rF0000000) + (instruction target << 2). "Region is that of the delay slot."	
+ 	self executeDelaySlot.
+ 	pc := nextPC - OneInstruction. "Account for general increment"!

Item was added:
+ ----- Method: MIPSSimulator>>jumpAndLink: (in category 'instructions - control') -----
+ jumpAndLink: instruction
+ 	| nextPC |
+ 	self assert: inDelaySlot not.
+ 	self unsignedRegister: RA put: pc + TwoInstructions. "Return past delay slot."
+ 	pc := pc + OneInstruction.
+ 	nextPC := (pc bitAnd: 16rF0000000) + (instruction target << 2). "Region is that of the delay slot."	
+ 	self executeDelaySlot.
+ 	pc := nextPC - OneInstruction. "Account for general increment"!

Item was added:
+ ----- Method: MIPSSimulator>>jumpAndLinkRegister: (in category 'instructions - control') -----
+ jumpAndLinkRegister: instruction
+ 	| nextPC |
+ 	self assert: inDelaySlot not.
+ 	self unsignedRegister: instruction rd put: pc + TwoInstructions. "Return past delay slot."
+ 	nextPC := self unsignedRegister: instruction rs.
+ 	pc := pc + OneInstruction.
+ 	self executeDelaySlot.
+ 	pc := nextPC.
+ 	pc := pc - 4. "Account for general increment"!

Item was added:
+ ----- Method: MIPSSimulator>>jumpRegister: (in category 'instructions - control') -----
+ jumpRegister: instruction
+ 	| nextPC |
+ 	self assert: inDelaySlot not.
+ 	nextPC := self unsignedRegister: instruction rs.
+ 	pc := pc + OneInstruction.
+ 	self executeDelaySlot.
+ 	pc := nextPC.
+ 	pc := pc - 4. "Account for general increment"!

Item was added:
+ ----- Method: MIPSSimulator>>loadByte: (in category 'instructions - memory') -----
+ loadByte: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := self signedByte: address.
+ 	self signedRegister: instruction rt put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>loadByteUnsigned: (in category 'instructions - memory') -----
+ loadByteUnsigned: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := self unsignedByte: address.
+ 	self unsignedRegister: instruction rt put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>loadHalfword: (in category 'instructions - memory') -----
+ loadHalfword: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := self signedHalfword: address.
+ 	self signedRegister: instruction rt put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>loadHalfwordUnsigned: (in category 'instructions - memory') -----
+ loadHalfwordUnsigned: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := self unsignedHalfword: address.
+ 	self unsignedRegister: instruction rt put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>loadUpperImmediate: (in category 'instructions - arithmetic') -----
+ loadUpperImmediate: instruction
+ 	| result |
+ 	self assert: instruction rs = 0.
+ 	result := instruction signedImmediate << 16.
+ 	self signedRegister: instruction rt put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>loadWord: (in category 'instructions - memory') -----
+ loadWord: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := self signedWord: address.
+ 	self signedRegister: instruction rt put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>memory (in category 'as yet unclassified') -----
+ memory
+ 	^memory!

Item was added:
+ ----- Method: MIPSSimulator>>orImmediate: (in category 'instructions - arithmetic') -----
+ orImmediate: instruction
+ 	| rsValue immediate result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	immediate := instruction unsignedImmediate.
+ 	result := rsValue bitOr: immediate.
+ 	self unsignedRegister: instruction rt put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>printOn: (in category 'as yet unclassified') -----
+ printOn: stream
+ 	stream nextPutAll: self class name; nextPut: $:; cr.
+ 	0 to: 31 do:
+ 		[:reg | | hex |
+ 		stream space.
+ 		stream nextPutAll: (MIPSConstants nameForRegister: reg).
+ 		stream space.
+ 		hex := (self unsignedRegister: reg) printStringBase: 16.
+ 		8 - hex size timesRepeat: [stream nextPut: $0].
+ 		stream nextPutAll: hex.
+ 		stream space.
+ 		(self signedRegister: reg) printOn: stream.
+ 		stream cr].
+ 	!

Item was added:
+ ----- Method: MIPSSimulator>>setFramePointer:stackPointer: (in category 'processor api') -----
+ setFramePointer: fp stackPointer: sp
+ 	self signedRegister: SP put: sp.
+ 	self signedRegister: FP put: fp.!

Item was added:
+ ----- Method: MIPSSimulator>>setOnLessThan: (in category 'instructions - arithmetic') -----
+ setOnLessThan: instruction
+ 	| rsValue rtValue result |
+ 	rsValue := self signedRegister: instruction rs.
+ 	rtValue := self signedRegister: instruction rt.
+ 	result := rsValue < rtValue ifTrue: [1] ifFalse: [0].
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>setOnLessThanImmediate: (in category 'instructions - arithmetic') -----
+ setOnLessThanImmediate: instruction
+ 	| rsValue immediate result |
+ 	rsValue := self signedRegister: instruction rs.
+ 	immediate := instruction signedImmediate.
+ 	result := rsValue < immediate ifTrue: [1] ifFalse: [0].
+ 	self signedRegister: instruction rt put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>setOnLessThanImmediateUnsigned: (in category 'instructions - arithmetic') -----
+ setOnLessThanImmediateUnsigned: instruction
+ 	"The immediate is still sign-extended; it is the comparison that is unsigned."
+ 	| rsValue immediate result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	immediate := self signed32ToUnsigned32: instruction signedImmediate.
+ 	result := rsValue < immediate ifTrue: [1] ifFalse: [0].
+ 	self signedRegister: instruction rt put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>setOnLessThanUnsigned: (in category 'instructions - arithmetic') -----
+ setOnLessThanUnsigned: instruction
+ 	| rsValue rtValue result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	result := rsValue < rtValue ifTrue: [1] ifFalse: [0].
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>shiftLeftLogical: (in category 'instructions - arithmetic') -----
+ shiftLeftLogical: instruction
+ 	| result rtValue shiftAmount |
+ 	self assert: instruction rs = 0.
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	shiftAmount := instruction sa.
+ 	result := (rtValue << shiftAmount) bitAnd: 16rFFFFFFFF.
+ 	self unsignedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>shiftLeftLogicalVariable: (in category 'instructions - arithmetic') -----
+ shiftLeftLogicalVariable: instruction
+ 	| result rtValue shiftAmount |
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	shiftAmount := self unsignedRegister: instruction rs.
+ 	(31 allMask: shiftAmount) ifFalse: 
+ 		["MIPS will use only the low 5 bits for this shift, but we probably
+ 		  don't want to generate any code that hits this behavior."
+ 		self error].
+ 	result := (rtValue << shiftAmount) bitAnd: 16rFFFFFFFF.
+ 	self unsignedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>shiftRightArithmetic: (in category 'instructions - arithmetic') -----
+ shiftRightArithmetic: instruction
+ 	| result rtValue shiftAmount |
+ 	self assert: instruction rs = 0.
+ 	rtValue := self signedRegister: instruction rt.
+ 	shiftAmount := instruction sa.
+ 	result := rtValue >> shiftAmount.
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>shiftRightArithmeticVariable: (in category 'instructions - arithmetic') -----
+ shiftRightArithmeticVariable: instruction
+ 	| result rtValue shiftAmount |
+ 	rtValue := self signedRegister: instruction rt.
+ 	shiftAmount := self unsignedRegister: instruction rs.
+ 	(31 allMask: shiftAmount) ifFalse:
+ 		["MIPS will use only the low 5 bits for this shift, but we probably
+ 		  don't want to generate any code that hits this behavior."
+ 		self error].
+ 	result := rtValue >> shiftAmount.
+ 	self signedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>shiftRightLogical: (in category 'instructions - arithmetic') -----
+ shiftRightLogical: instruction
+ 	| result rtValue shiftAmount |
+ 	self assert: instruction rs = 0.
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	shiftAmount := instruction sa.
+ 	result := rtValue >> shiftAmount.
+ 	self unsignedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>shiftRightLogicalVariable: (in category 'instructions - arithmetic') -----
+ shiftRightLogicalVariable: instruction
+ 	| result rtValue shiftAmount |
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	shiftAmount := self unsignedRegister: instruction rs.
+ 	(31 allMask: shiftAmount) ifFalse:
+ 		["MIPS will use only the low 5 bits for this shift, but we probably
+ 		  don't want to generate any code that hits this behavior."
+ 		self error].
+ 	result := rtValue >> shiftAmount.
+ 	self unsignedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>signed32ToUnsigned32: (in category 'converting') -----
+ signed32ToUnsigned32: signedValue
+ 	self assert: (signedValue between: -16r80000000 and: 16r7FFFFFFF).
+ 	signedValue < 0 ifTrue: [^signedValue + 16r100000000].
+ 	^signedValue!

Item was added:
+ ----- Method: MIPSSimulator>>signedRegister: (in category 'registers') -----
+ signedRegister: registerNumber 
+ 	registerNumber == ZR ifTrue: [^0] ifFalse: [^registers at: registerNumber + 1].!

Item was added:
+ ----- Method: MIPSSimulator>>signedRegister:put: (in category 'registers') -----
+ signedRegister: registerNumber put: signedValue
+ 	self assert: (signedValue between: -16r80000000 and: 16r7FFFFFFF).
+ 	registerNumber == ZR ifFalse: [registers at: registerNumber + 1 put: signedValue].!

Item was added:
+ ----- Method: MIPSSimulator>>sp (in category 'processor api') -----
+ sp
+ 	^self signedRegister: SP!

Item was added:
+ ----- Method: MIPSSimulator>>storeByte: (in category 'instructions - memory') -----
+ storeByte: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := (self signedRegister: instruction rt) bitAnd: 16rFF.
+ 	self unsignedByte: address put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>storeHalfword: (in category 'instructions - memory') -----
+ storeHalfword: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := (self signedRegister: instruction rt) bitAnd: 16rFFFF.
+ 	self unsignedHalfword: address put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>storeWord: (in category 'instructions - memory') -----
+ storeWord: instruction
+ 	| base address value |
+ 	base := self unsignedRegister: instruction rs.
+ 	address := base + instruction signedImmediate.
+ 	value := self signedRegister: instruction rt.
+ 	self signedWord: address put: value.!

Item was added:
+ ----- Method: MIPSSimulator>>subtractUnsigned: (in category 'instructions - arithmetic') -----
+ subtractUnsigned: instruction
+ 	"Unsigned here means the instruction doesn't generate exceptions."
+ 	| rsValue rtValue result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	rtValue := self unsignedRegister: instruction rt.
+ 	result := rsValue - rtValue bitAnd: 16rFFFFFFFF. "No exception on overflow"
+ 	self unsignedRegister: instruction rd put: result.!

Item was added:
+ ----- Method: MIPSSimulator>>unsigned32ToSigned32: (in category 'converting') -----
+ unsigned32ToSigned32: unsignedValue
+ 	self assert: (unsignedValue between: 0 and: 16rFFFFFFFF).
+ 	unsignedValue >= 16r80000000 ifTrue: [^unsignedValue - 16r100000000].
+ 	^unsignedValue!

Item was added:
+ ----- Method: MIPSSimulator>>unsignedRegister: (in category 'registers') -----
+ unsignedRegister: registerNumber
+ 	registerNumber == ZR 
+ 		ifTrue: [^0]
+ 		ifFalse: [^self signed32ToUnsigned32: (registers at: registerNumber + 1)].!

Item was added:
+ ----- Method: MIPSSimulator>>unsignedRegister:put: (in category 'registers') -----
+ unsignedRegister: registerNumber put: unsignedValue
+ 	registerNumber == ZR ifFalse:
+ 		[registers at: registerNumber + 1 put: (self unsigned32ToSigned32: unsignedValue)].!

Item was added:
+ ----- Method: MIPSSimulator>>xorImmediate: (in category 'instructions - arithmetic') -----
+ xorImmediate: instruction
+ 	| rsValue immediate result |
+ 	rsValue := self unsignedRegister: instruction rs.
+ 	immediate := instruction unsignedImmediate.
+ 	result := rsValue bitXor: immediate.
+ 	self unsignedRegister: instruction rt put: result.!



More information about the Vm-dev mailing list