[Vm-dev] VM Maker: VMMaker.oscog-eem.3168.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Feb 23 19:27:00 UTC 2022


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

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

Name: VMMaker.oscog-eem.3168
Author: eem
Time: 23 February 2022, 11:26:52.582045 am
UUID: a0f1436f-0a54-429c-a61e-271ce020741a
Ancestors: VMMaker.oscog-eem.3167

CogARMv8Compiler: add logging of which lines set or clear executability via pthread_jit_write_protect_np.  Hence find that Cogit>>freeUnmarkedMachineCode was not enabling executability.

We'll leave the logging in for now; it can be made conditional at some future date.

=============== Diff against VMMaker.oscog-eem.3167 ===============

Item was changed:
  CogAbstractInstruction subclass: #CogARMv8Compiler
  	instanceVariableNames: ''
+ 	classVariableNames: 'AL ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS CASAL CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg CBNZ CBZ CC CCMPNE CLREX CS CSET D0 D1 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D2 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D3 D30 D31 D4 D5 D6 D7 D8 D9 DC DC_CISW DC_CIVAC DC_CSW DC_CVAC DC_CVAU DC_ISW DC_IVAC DC_ZVA DMB DSB DSB_ALL DSB_ALLSY DSB_ISH DSB_NSH DSB_OSH DSB_READS DSB_SY DSB_WRITES DataCacheFlushRequired DataCacheLineLength DivRRR EQ FP GE GT HI HasAtomicInstructions IC IC_IALLU IC_IALLUIS IC_IVAU ISB InstructionCacheFlushRequired InstructionCacheLineLength LDAXR LE LR LS LT LogicalAnd LogicalAndS LogicalOr LogicalXor MI MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1 MSubRRR MoveAwRR MoveRRAw MulOverflowRRR MulRRR NE NativePopRR NativePushRR PJWPNChange PJWPNClear PJWPNSet PJWPNState PL 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 SMULHRRR SP STLR STLXR SXTB SXTH 
 SXTW SXTX UXTB UXTH UXTW UXTX VC VS XZR'
- 	classVariableNames: 'AL ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS CASAL CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg CBNZ CBZ CC CCMPNE CLREX CS CSET D0 D1 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D2 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D3 D30 D31 D4 D5 D6 D7 D8 D9 DC DC_CISW DC_CIVAC DC_CSW DC_CVAC DC_CVAU DC_ISW DC_IVAC DC_ZVA DMB DSB DSB_ALL DSB_ALLSY DSB_ISH DSB_NSH DSB_OSH DSB_READS DSB_SY DSB_WRITES DataCacheFlushRequired DataCacheLineLength DivRRR EQ FP GE GT HI HasAtomicInstructions IC IC_IALLU IC_IALLUIS IC_IVAU ISB InstructionCacheFlushRequired InstructionCacheLineLength LDAXR LE LR LS LT LogicalAnd LogicalAndS LogicalOr LogicalXor MI MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1 MSubRRR MoveAwRR MoveRRAw MulOverflowRRR MulRRR NE NativePopRR NativePushRR PL 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 SMULHRRR SP STLR STLXR SXTB SXTH SXTW SXTX UXTB UXTH UXTW UXTX VC VS XZR'
  	poolDictionaries: 'ARMv8A64Opcodes'
  	category: 'VMMaker-JIT'!
  
  !CogARMv8Compiler commentStamp: 'eem 1/7/2021 23:01' prior: 0!
  I generate ARMv8 machine code instructions from CogAbstractInstructions with CogRTLOpcodes.
  Here in "Arm ARM" refers to
  	Arm® Architecture Reference Manual
  	Armv8, for Armv8-A architecture profile
  https://developer.arm.com/docs/ddi0487/latest/arm-architecture-reference-manual-armv8-for-armv8-a-architecture-profile
  
  Some things to know about ARMv8 instructions:
  Whether 31 in a register field implies the zero register or the SP register(s) depends on the specific instruction.
  
  C3.2.1 Load/Store register
  If a Load instruction specifies writeback and the register being loaded is also the base register,
  then behavior is CONSTRAINED UNPREDICTABLE and one of the following behaviors must occur:
  - The instruction is treated as UNDEFINED.
  - The instruction is treated as a NOP.
  - The instruction performs the load using the specified addressing mode and the base register
    becomes UNKNOWN.  In addition, if an exception occurs during the execution of such an
    instruction, the base address might be corrupted so that the instruction cannot be repeated.
  If a Store instruction performs a writeback and the register that is stored is also the base register,
  then behavior is CONSTRAINED UNPREDICTABLE and one of the following behaviors must occur:
  - The instruction is treated as UNDEFINED.
  - The instruction is treated as a NOP.
  - The instruction performs the store to the designated register using the specified addressing
    mode, but the value stored is UNKNOWN.!

Item was changed:
  ----- Method: CogARMv8Compiler class>>declareCVarsIn: (in category 'translation') -----
  declareCVarsIn: aCCodeGenerator
  		
  	#('hasAtomicInstructions' 'instructionCacheLineLength' 'instructionCacheFlushRequired' 'dataCacheLineLength' 'dataCacheFlushRequired') do:
  		[:varName|
  		aCCodeGenerator
  			declareVar: varName type: #'unsigned char';
  			removeConstant: varName capitalized].
+ 	(classPool keys select: [:k| k beginsWith: 'PJWPN']) do:
+ 		[:k|
+ 		aCCodeGenerator removeConstant: k; declareVar: k type: #int].
  	aCCodeGenerator
  		var: #ceFlushDCache "sigh; this is here to placate Slang; we don't use this, but Slang doesn't elide the assignment..."
  			declareC: 'static void (*ceFlushDCache)(usqIntptr_t from, usqIntptr_t to)'!

Item was changed:
  ----- Method: CogARMv8Compiler class>>initialize (in category 'class initialization') -----
  initialize
  	"Initialize various ARM64 instruction-related constants."
  	"self initialize"
  
  	"main registers; a minor complication in reading the doc.
  	ARM refer to the 64bit registers as X0...30 and use R0...30 to refer to the 32bit lower halves.
  	They also use a whole suite of names for the floating point/SIMD registers. See ARMARM DDI0487 B1.2.1 etc for the gory details.
  	Note that R30 (yes, yes, X30) is used as the link register and as such is not really a general purpose register. 
  	Also note that 31 in a general register field means R31, and that in most of these instructions R31 is the zero
  	register named XZR in ARM doc.  but in the rest of these instructions R31 the effective SP register.
  	XZR is a pseudo-register that always reads as 0 and writes to /dev/null.
  	And note that unlike the ARM32, there is no general purpose register for the PC; a big difference.
  	See ARMARM DDI0487 C1.2.5. wrt to both the lack of a PC register and the XZR/SP distinction."
  	
  	"and initialize most sets of variables that run from 0 to N - 1..."
  	#(	"General registers, 0 to 31. We stick with R0...30 to refer to the 64 bit general regs and D0...31 (note the extra reg here!!) for the FP/SIMD regs"
  		(R0 R1 R2 R3 R4 R5 R6 R7 R8 R9 R10 R11 R12 R13 R14 R15 R16 R17 R18 R19 R20 R21 R22 R23 R24 R25 R26 R27 R28 R29 R30 R31)
  		"Floating-point registers, 0 to 31"
  		(D0 D1 D2 D3 D4 D5 D6 D7 D8 D9 D10 D11 D12 D13 D14 D15 D16 D17 D18 D19 D20 D21 D22 D23 D24 D25 D26 D27 D28 D29 D30 D31)
  		"C argument registers, 0 to 6"
  		(CArg0Reg CArg1Reg CArg2Reg CArg3Reg CArg4Reg CArg5Reg CArg6Reg)
  		"Condition Codes 0 to 16. Note that cc=16rF is mapped back to AL in AARCH64. Generally it shouldn't be used."
  		(EQ NE CS CC MI PL VS VC HI LS GE LT GT LE AL)
  		"Logical Op Codes"
  		(LogicalAnd LogicalOr LogicalXor LogicalAndS)
  		"Arithmetic Opcodes"
  		"ADD (shifted register) on page C6-763			10001011
  		 ADDS (shifted register) on page C6-771		10101011
  		 CMN (shifted register) on page C6-854			10101011	Rd=XZR
  		 SUB (shifted register) on page C6-1313		11001011
  		 SUBS (shifted register) on page C6-1323		11101011
  		 CMP (shifted register) on page C6-860			11101011	Rd=XZR
  		 NEG (shifted register) on page C6-1114		11001011	Rn=XZR
  		 NEGS					on page C6-1116		11101011	Rn=XZR"
  		(ArithmeticAdd ArithmeticAddS ArithmeticSub ArithmeticSubS)
  		"Extension Methods "
  		(UXTB UXTH UXTW UXTX "a.k.a. LSL" SXTB SXTH SXTW SXTX)) do:
  		[:classVarNames|
  		 classVarNames withIndexDo:
  			[:k :v|
  			CogARMv8Compiler classPool at: k put: v - 1]].
  
  	SP := XZR := R31.
  	LR := R30.
  	FP := R29.
  
  	"DC variant selectors; see concretizeDataCacheControl"
  	DC_CISW := 13.
  	DC_CIVAC := 14.
  	DC_CSW := 15.
  	DC_CVAC := 16.
  	DC_CVAU := 19.
  	DC_ISW := 26.
  	DC_IVAC := 27.
  	DC_ZVA := 28.
  
  	"IC variant selectors; see concretizeInstructionCacheControl"
  	IC_IALLU := 0.
  	IC_IALLUIS := 1.
  	IC_IVAU := 2.
  
  	"DSB domains and types	C6.2.81 DSB	C6-891"
  	DSB_OSH := 0.		"Domain_OuterSharable"
  	DSB_NSH := 1.		"Domain_NonSharable"
  	DSB_ISH := 2.		"Domain_InnerSharable"
  	DSB_SY := 3.		"Domain_FullSystem"
  
  	DSB_ALLSY := 0.	"Types_All; domain = Domain_FullSystem"
  	DSB_READS := 1.	"Types_Reads"
  	DSB_WRITES := 2.	"Types_Writes"
  	DSB_ALL := 3.		"Types_All; domain ~= Domain_FullSystem"
  
+ 	"Debugging of the executable/writable switch on Apple."
+ 	PJWPNState := false. PJWPNClear := PJWPNSet := PJWPNChange = 0.
+ 
  	"Specific instructions"
  	self
  		initializeSpecificOpcodes: #(MulRRR MulOverflowRRR SMULHRRR DivRRR MSubRRR "N.B. ARMv8 has MSUBRRRR but we only support three operands"
  									MoveAwRR MoveRRAw NativePushRR NativePopRR "these map to ldp/stp"
  									"Cache control and memory barrier"
  									"B2.3.7		Memory barriers	B2-124"
  									DC IC DMB DSB ISB MRS_CTR_EL0 MRS_ID_AA64ISAR0_EL1
  									CASAL CBNZ CBZ CCMPNE CSET CLREX LDAXR STLXR STLR)
  		in: thisContext method!

Item was added:
+ ----- Method: CogARMv8Compiler class>>mustBeGlobal: (in category 'translation') -----
+ mustBeGlobal: var
+ 	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code."
+ 
+ 	^var beginsWith: 'PJWPN'!

Item was changed:
  ----- Method: CogARMv8Compiler>>makeCodeZoneExecutable (in category 'memory access') -----
  makeCodeZoneExecutable
  	<inline: #always>
+ 	self cCode:
+ 		[self cppIf: #__APPLE__ & #__MACH__
+ 			ifTrue:
+ 				[cogit pthread_jit_write_protect_np: true.
+ 				 PJWPNSet := #__LINE__.
+ 				 PJWPNState ifFalse:
+ 					[PJWPNChange := #__LINE__.
+ 					 PJWPNState := true]]]!
- 	self cCode: [self cppIf: #__APPLE__ & #__MACH__ ifTrue: [cogit pthread_jit_write_protect_np: true]]!

Item was changed:
  ----- Method: CogARMv8Compiler>>makeCodeZoneWritable (in category 'memory access') -----
  makeCodeZoneWritable
  	<inline: #always>
+ 	self cCode:
+ 		[self cppIf: #__APPLE__ & #__MACH__
+ 			ifTrue:
+ 				[cogit pthread_jit_write_protect_np: false.
+ 				 PJWPNClear := #__LINE__.
+ 				 PJWPNState ifTrue:
+ 					[PJWPNChange := #__LINE__.
+ 					 PJWPNState := false]]]!
- 	self cCode: [self cppIf: #__APPLE__ & #__MACH__ ifTrue: [cogit pthread_jit_write_protect_np: false]]!

Item was added:
+ ----- Method: CogAbstractInstruction class>>mustBeGlobal: (in category 'translation') -----
+ mustBeGlobal: var
+ 	"Answer if a variable must be global and exported.  Used for inst vars that are accessed from VM support code."
+ 
+ 	^false!

Item was changed:
  ----- Method: Cogit class>>mustBeGlobal: (in category 'translation') -----
  mustBeGlobal: var
  	"Answer if a variable must be global and exported.  Used for inst vars that are
  	 accessed from VM support code, or that need visibility at the gdb/lldb level."
+ 	^(#('ceBaseFrameReturnTrampoline' ceCaptureCStackPointers 'ceCheckForInterruptTrampoline'
- 	^#('ceBaseFrameReturnTrampoline' ceCaptureCStackPointers 'ceCheckForInterruptTrampoline'
  		ceEnterCogCodePopReceiverReg realCEEnterCogCodePopReceiverReg
  		ceCallCogCodePopReceiverReg realCECallCogCodePopReceiverReg
  		ceCallCogCodePopReceiverAndClassRegs realCECallCogCodePopReceiverAndClassRegs
  		ceInvokeInterpret 'ceReturnToInterpreterTrampoline' 'ceCannotResumeTrampoline'
  		ceTryLockVMOwner
  		'cmEntryOffset' 'cmNoCheckEntryOffset' 'cmDynSuperEntryOffset' 'cmSelfSendEntryOffset'
  		'missOffset' 'cbEntryOffset' 'cbNoSwitchEntryOffset' 'blockNoContextSwitchOffset' breakPC
  		ceGetFP ceGetSP cFramePointerInUse
  		methodZoneBase
  		traceFlags traceStores)
+ 			includes: var)
+ 			or: [self activeCompilerClass mustBeGlobal: var]!
- 			includes: var!

Item was changed:
  ----- Method: Cogit>>freeUnmarkedMachineCode (in category 'jit - api') -----
  freeUnmarkedMachineCode
  	"Free machine-code methods whose compiled methods are unmarked
  	 and open PICs whose selectors are not marked, and closed PICs that
  	 refer to unmarked objects."
  	<api>
  	<option: #SpurObjectMemory>
  	| cogMethod freedMethod |
  	self moveProfileToMethods. "simulation only..."
  
  	freedMethod := false.
  	cogMethod := self cCoerceSimple: methodZoneBase to: #'CogMethod *'.
  	[cogMethod < methodZone limitZony] whileTrue:
  		[(cogMethod cmType = CMMethod
  		  and: [(objectMemory isMarked: cogMethod methodObject) not]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 (cogMethod cmType = CMOpenPIC
  		  and: [(objectMemory isImmediate: cogMethod selector) not
  		  and: [(objectMemory isMarked: cogMethod selector) not]]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 (cogMethod cmType = CMClosedPIC
  		  and: [self closedPICRefersToUnmarkedObject: cogMethod]) ifTrue:
  			[freedMethod := true.
  			 methodZone freeMethod: cogMethod].
  		 cogMethod := methodZone methodAfter: cogMethod].
  	freedMethod ifTrue:
+ 		[self unlinkSendsToFree].
+ 	backEnd ensureExecutableCodeZone!
- 		[self unlinkSendsToFree]!



More information about the Vm-dev mailing list