[Vm-dev] Vm-dev Digest, Vol 174, Issue 28

ken.dickey at whidbey.com ken.dickey at whidbey.com
Thu Dec 31 14:10:28 UTC 2020


On 2020-12-31 04:19, vm-dev-request at lists.squeakfoundation.org wrote:
> Send Vm-dev mailing list submissions to
> 	vm-dev at lists.squeakfoundation.org
> 
> To subscribe or unsubscribe via the World Wide Web, visit
> 	http://lists.squeakfoundation.org/mailman/listinfo/vm-dev
> or, via email, send a message with subject or body 'help' to
> 	vm-dev-request at lists.squeakfoundation.org
> 
> You can reach the person managing the list at
> 	vm-dev-owner at lists.squeakfoundation.org
> 
> When replying, please edit your Subject line so it is more specific
> than "Re: Contents of Vm-dev digest..."
> 
> 
> Today's Topics:
> 
>    1. Re: [OpenSmalltalk/opensmalltalk-vm] Trouble running OSVM in
>       an Ubuntu 20/aarch64 docker (raspi) (#544) (tim Rowledge)
>    2. Re: [OpenSmalltalk/opensmalltalk-vm] Trouble running OSVM in
>       an Ubuntu 20/aarch64 docker (raspi) (#544) (Christoph Thiede)
>    3. Re: [OpenSmalltalk/opensmalltalk-vm] Trouble running OSVM in
>       an Ubuntu 20/aarch64 docker (raspi) (#544) (tim Rowledge)
>    4. VM Maker: VMMaker.oscog-nice.2914.mcz (commits at source.squeak.org)
>    5. VM Maker: Cog-nice.429.mcz (commits at source.squeak.org)
>    6. Re: [OpenSmalltalk/opensmalltalk-vm] Trouble running OSVM in
>       an Ubuntu 20/aarch64 docker (raspi) (#544) (Christoph Thiede)
> 
> 
> ----------------------------------------------------------------------
> 
> Message: 1
> Date: Wed, 30 Dec 2020 16:52:24 -0800
> From: tim Rowledge <tim at rowledge.org>
> To: OpenSmalltalk/opensmalltalk-vm
> 	<reply+AIJPEW2V4MQ6XPZSKYQEKSF57EAEDEVBNHHC4SDYLA at reply.github.com>,
> 	Squeak Virtual Machine Development Discussion
> 	<vm-dev at lists.squeakfoundation.org>
> Cc: OpenSmalltalk/opensmalltalk-vm
> 	<opensmalltalk-vm at noreply.github.com>
> Subject: Re: [Vm-dev] [OpenSmalltalk/opensmalltalk-vm] Trouble running
> 	OSVM in an Ubuntu 20/aarch64 docker (raspi) (#544)
> Message-ID: <64A3F2D4-3989-4F08-BBAF-B3CAB0998BF9 at rowledge.org>
> Content-Type: text/plain;	charset=us-ascii
> 
> 
> 
>> On 2020-12-30, at 4:45 PM, Christoph Thiede <notifications at github.com> 
>> wrote:
>> 
>> 
>> Thanks for the help, Tim!
>> 
>> Why on earth would you do that?
>> 
>> I didn't want to pollute my raspi with that compilation stuff ... 
>> However, now I did it (also thanks to the help by Bruce) and succeeded 
>> to compile!
> 
> 
> But all the compiler/tools stuff is already there. Remember, this is a
> full development workstation with more power than we fantasised about
> not so long ago.
> 
>> 
>> Next problem:
>> 
>> root at 96fa02af4449:/# /bin/squeak/squeak 
>> /image/Squeak6.0alpha-20135-64bit.image  -headless
>> mprotect(x,y,PROT_READ | PROT_EXEC): Permission denied
>> Segmentation fault (core dumped)
> 
> install libevdev seems to fix it.
> 
> tim
> --
> tim Rowledge; tim at rowledge.org; http://www.rowledge.org/tim
> Useful random insult:- Teflon brain -- nothing sticks.
> 
> 
> 
> 
> ------------------------------
> 
> Message: 2
> Date: Wed, 30 Dec 2020 17:00:00 -0800
> From: Christoph Thiede <notifications at github.com>
> To: OpenSmalltalk/opensmalltalk-vm
> 	<opensmalltalk-vm at noreply.github.com>
> Cc: Comment <comment at noreply.github.com>, OpenSmalltalk-Bot
> 	<vm-dev at lists.squeakfoundation.org>
> Subject: Re: [Vm-dev] [OpenSmalltalk/opensmalltalk-vm] Trouble running
> 	OSVM in an Ubuntu 20/aarch64 docker (raspi) (#544)
> Message-ID:
> 	<OpenSmalltalk/opensmalltalk-vm/issues/544/752805876 at github.com>
> Content-Type: text/plain; charset="utf-8"
> 
>> But all the compiler/tools stuff is already there. Remember, this is a 
>> full development workstation with more power than we fantasised about 
>> not so long ago.
> 
> True :D
> 
>> install libevdev seems to fix it.
> 
> Which one are you referring to?
> 
> ```
> root at 96fa02af4449:/# apt search libevdev
> Sorting... Done
> Full Text Search... Done
> libevdev-dev/focal-updates 1.9.0+dfsg-1ubuntu0.1 arm64
>   wrapper library for evdev devices - development files
> 
> libevdev-doc/focal-updates 1.9.0+dfsg-1ubuntu0.1 all
>   wrapper library for evdev devices - development docs
> 
> libevdev-tools/focal-updates 1.9.0+dfsg-1ubuntu0.1 arm64
>   wrapper library for evdev devices - tools
> 
> libevdev2/focal-updates 1.9.0+dfsg-1ubuntu0.1 arm64
>   wrapper library for evdev devices
> ```
> 
> --
> You are receiving this because you commented.
> Reply to this email directly or view it on GitHub:
> https://github.com/OpenSmalltalk/opensmalltalk-vm/issues/544#issuecomment-752805876
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL:
> <http://lists.squeakfoundation.org/pipermail/vm-dev/attachments/20201230/9c844cf2/attachment-0001.html>
> 
> ------------------------------
> 
> Message: 3
> Date: Wed, 30 Dec 2020 17:12:21 -0800
> From: tim Rowledge <tim at rowledge.org>
> To: OpenSmalltalk/opensmalltalk-vm
> 	<reply+AIJPEW2XHQ37F7FPRTXY7XF57EBZBEVBNHHC4SDYLA at reply.github.com>,
> 	Squeak Virtual Machine Development Discussion
> 	<vm-dev at lists.squeakfoundation.org>
> Subject: Re: [Vm-dev] [OpenSmalltalk/opensmalltalk-vm] Trouble running
> 	OSVM in an Ubuntu 20/aarch64 docker (raspi) (#544)
> Message-ID: <1E8A1D87-B401-4CC7-B0E5-28405F146B65 at rowledge.org>
> Content-Type: text/plain;	charset=us-ascii
> 
> 
> 
>> On 2020-12-30, at 5:00 PM, Christoph Thiede <notifications at github.com> 
>> wrote:
>> 
>> 
>> But all the compiler/tools stuff is already there. Remember, this is a 
>> full development workstation with more power than we fantasised about 
>> not so long ago.
>> 
>> True :D
>> 
>> install libevdev seems to fix it.
>> 
>> Which one are you referring to?
> 
> Sorry - libevdev-dev - which may be the most redundantly redundant
> library name I've redundantly seen repeated.
> 
> 
> tim
> --
> tim Rowledge; tim at rowledge.org; http://www.rowledge.org/tim
> Fractured Idiom:- MERCI RIEN - Thanks for nothin'.
> 
> 
> 
> 
> ------------------------------
> 
> Message: 4
> Date: Thu, 31 Dec 2020 09:06:50 0000
> From: commits at source.squeak.org
> To: vm-dev at lists.squeakfoundation.org
> Subject: [Vm-dev] VM Maker: VMMaker.oscog-nice.2914.mcz
> Message-ID: <E1kutvM-0007xT-8X at andreas>
> 
> Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
> http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2914.mcz
> 
> ==================== Summary ====================
> 
> Name: VMMaker.oscog-nice.2914
> Author: nice
> Time: 31 December 2020, 10:06:40.613299 am
> UUID: 0e1f0f1f-96ba-41ec-8f4f-c0d2fb618a21
> Ancestors: VMMaker.oscog-nice.2913
> 
> A few fixes for the VM tests
> - enable using a WordArray as simulation memory
> - concretizeAt: does not answer the instruction size but the next 
> address
> 
> =============== Diff against VMMaker.oscog-nice.2913 ===============
> 
> Item was changed:
>   ----- Method: AbstractInstructionTests>>generateInstructions (in
> category 'generating machine code') -----
>   generateInstructions
>   	"See Cogit>>computeMaximumSizes, generateInstructionsAt: &
> outputInstructionsAt:.
>   	 This is a pure Smalltalk (non-Slang) version of that trio of 
> methods."
>   	| address pcDependentInstructions instructions |
>   	address := 0.
>   	pcDependentInstructions := OrderedCollection new.
>   	opcodes do:
>   		[:abstractInstruction|
>   		abstractInstruction
>   			address: address;
>   			maxSize: abstractInstruction computeMaximumSize.
>   		address := address + abstractInstruction maxSize].
>   	address := 0.
>   	opcodes do:
>   		[:abstractInstruction|
>   		abstractInstruction isPCDependent
>   			ifTrue:
>   				[abstractInstruction sizePCDependentInstructionAt: address.
>   				 pcDependentInstructions addLast: abstractInstruction.
>   				 address := address + abstractInstruction machineCodeSize]
>   			ifFalse:
>   				[address := abstractInstruction concretizeAt: address]].
>   	pcDependentInstructions do:
>   		[:abstractInstruction|
>   		abstractInstruction concretizeAt: abstractInstruction address].
>   	instructions := ByteArray new: address.
>   	address := 0.
>   	opcodes do:
>   		[:abstractInstruction| | machineCodeBytes |
>   		self assert: abstractInstruction address = address.
>   		machineCodeBytes := self memoryAsBytes: abstractInstruction
> machineCode object.
>   		1 to: abstractInstruction machineCodeSize do:
>   			[:j|
> + 			instructions at: address + 1 put: (machineCodeBytes byteAt: j).
> - 			instructions at: address + 1 put: (machineCodeBytes at: j).
>   			address := address + 1]].
>   	^instructions!
> 
> Item was changed:
>   ----- Method: AbstractInstructionTests>>runAddCwR: (in category
> 'running') -----
>   runAddCwR: assertPrintBar
>   	"self defaultTester runAddCwR: false"
>   	self concreteCompilerClass dataRegistersWithAccessorsDo:
>   		[:reg :rgetter :rsetter|
>   		self pairs: (-2 to: 2)  do:
>   			[:a :b| | inst len bogus memory |
>   			inst := self gen: AddCwR operand: a operand: reg.
>   			len := inst concretizeAt: 0.
>   			memory := self memoryAsBytes: inst machineCode.
>   			self processor
>   				reset;
>   				perform: rsetter with: (self processor convertIntegerToInternal: 
> b).
>   			[[processor pc < len] whileTrue:
> + 				[processor singleStepIn: memory]]
> - 				[self processor singleStepIn: memory]]
>   				on: Error
>   				do: [:ex| ].
>   			"self processor printRegistersOn: Transcript.
>   			 Transcript show: (self processor disassembleInstructionAt: 0 In:
> memory); cr"
>   			assertPrintBar
>   				ifTrue: [self assert: processor pc = inst machineCodeSize.
>   						self assertCheckLongArithOpCodeSize: inst machineCodeSize]
>   				ifFalse: [bogus := processor pc ~= inst machineCodeSize].
>   			self concreteCompilerClass dataRegistersWithAccessorsDo:
>   				[:ireg :getter :setter| | expected |
>   				(self concreteCompilerClass isRISCTempRegister: ireg) ifFalse:
>   					[expected := getter == rgetter ifTrue: [b + a] ifFalse: [0].
>   					assertPrintBar
>   						ifTrue: [self assert: (self processor
> convertInternalToInteger: (self processor perform: getter)) equals:
> expected]
>   						ifFalse:
>   							[(self processor convertInternalToInteger: (self processor
> perform: getter)) ~= expected ifTrue:
>   								[bogus := true]]].
>   					assertPrintBar ifFalse:
>   						[Transcript
>   							nextPutAll: rgetter; nextPut: $(; print: b; nextPutAll: ') +
> '; print: a; nextPutAll: ' = ';
>   							print: (self processor convertInternalToInteger: (self
> processor perform: rgetter)); cr; flush.
>   						 bogus ifTrue:
>   							[self processor printRegistersOn: Transcript.
>   							 Transcript show: (self processor disassembleInstructionAt: 0
> In: memory); cr]]]]]!
> 
> Item was changed:
>   ----- Method: AbstractInstructionTests>>testNegateR (in category
> 'running') -----
>   testNegateR
>   	"self defaultTester testNegateR"
>   	self concreteCompilerClass dataRegistersWithAccessorsDo:
>   		[:reg :rgetter :rsetter|
>   		-2 to: 2 do:
>   			[:a| | inst len memory |
>   			inst := self gen: NegateR operand: reg.
>   			len := inst concretizeAt: 0.
>   			memory := self memoryAsBytes: inst machineCode.
>   			self processor
>   				reset;
>   				perform: rsetter with: (processor convertIntegerToInternal: a).
>   			[[processor pc < len] whileTrue:
> + 				[processor singleStepIn: memory]]
> - 				[self processor singleStepIn: memory]]
>   				on: Error
>   				do: [:ex| ].
>   			"self processor printRegistersOn: Transcript.
>   			 Transcript show: (self processor disassembleInstructionAt: 0 In:
> memory); cr"
>   			self assert: processor pc equals: inst machineCodeSize.
>   			self concreteCompilerClass dataRegistersWithAccessorsDo:
>   				[:ireg :getter :setter| | expected |
>   				expected := getter == rgetter ifTrue: [ a negated ] ifFalse: [0].
>   				self assert: (processor convertInternalToInteger: (processor
> perform: getter)) equals: expected]]]!
> 
> Item was changed:
>   ----- Method: CogARMCompilerForTests>>concretizeAt: (in category
> 'generate machine code') -----
>   concretizeAt: actualAddress
>   	"Override to check maxSize and machineCodeSize"
> 
> + 	| maxAddress nextAddress |
> - 	| size |
>   	maxSize ifNil: [maxSize := self computeMaximumSize].
> + 	maxAddress := actualAddress + maxSize.
> + 	nextAddress := super concretizeAt: actualAddress.
> - 	size := super concretizeAt: actualAddress.
>   	self assert: (maxSize notNil
>   				and: [self isPCDependent
> + 						ifTrue: [maxAddress >= nextAddress]
> + 						ifFalse: [maxAddress = nextAddress]]).
> + 	^nextAddress!
> - 						ifTrue: [maxSize >= size]
> - 						ifFalse: [maxSize = size]]).
> - 	^size!
> 
> Item was changed:
>   ----- Method: CogIA32CompilerForTests>>concretizeAt: (in category
> 'generate machine code') -----
>   concretizeAt: actualAddress
>   	"Override to check maxSize and machineCodeSize"
> 
> + 	| maxAddress nextAddress |
> - 	| size |
>   	maxSize ifNil: [maxSize := self computeMaximumSize].
> + 	maxAddress := actualAddress + maxSize.
> + 	nextAddress := super concretizeAt: actualAddress.
> - 	size := super concretizeAt: actualAddress.
>   	self assert: (maxSize notNil
>   				and: [self isPCDependent
> + 						ifTrue: [maxAddress >= nextAddress]
> + 						ifFalse: [maxAddress = nextAddress]]).
> + 	^nextAddress!
> - 						ifTrue: [maxSize >= size]
> - 						ifFalse: [maxSize = size]]).
> - 	^size!
> 
> Item was changed:
>   ----- Method: CogX64CompilerForTests>>concretizeAt: (in category
> 'generate machine code') -----
>   concretizeAt: actualAddress
>   	"Override to check maxSize and machineCodeSize"
> 
> + 	| maxAddress nextAddress |
> - 	| size |
>   	maxSize ifNil: [maxSize := self computeMaximumSize].
> + 	maxAddress := actualAddress + maxSize.
> + 	nextAddress := super concretizeAt: actualAddress.
> - 	size := super concretizeAt: actualAddress.
>   	self assert: (maxSize notNil
>   				and: [self isPCDependent
> + 						ifTrue: [maxAddress >= nextAddress]
> + 						ifFalse: [maxAddress = nextAddress]]).
> + 	^nextAddress!
> - 						ifTrue: [maxSize >= size]
> - 						ifFalse: [maxSize = size]]).
> - 	^size!
> 
> Item was changed:
>   VMClass subclass: #OutOfLineLiteralsManager
>   	instanceVariableNames: 'cogit objectMemory objectRepresentation
> firstOpcodeIndex nextLiteralIndex lastDumpedLiteralIndex literals
> literalsSize savedFirstOpcodeIndex savedNextLiteralIndex
> savedLastDumpedLiteralIndex'
>   	classVariableNames: ''
>   	poolDictionaries: 'CogAbstractRegisters CogCompilationConstants
> CogRTLOpcodes'
>   	category: 'VMMaker-JIT'!
> 
> + !OutOfLineLiteralsManager commentStamp: 'nice 12/31/2020 09:14' 
> prior: 0!
> + An OutOfLineLiteralsManager manages the dumping of literals for
> backends that want to keep literals out-of-line, accessed by
> pc-relative addressing.
> - !OutOfLineLiteralsManager commentStamp: 'eem 6/7/2015 12:10' prior: 
> 0!
> - An OutOfLineLiteralsManager manages the dumping of literals for
> backends that wat to keep literals out-of-line, accessed by
> pc-relative addressing.
> 
>   Instance Variables
>   	cogit:		<Cogit>!
> 
> Item was added:
> + ----- Method: RawBitsArray>>byteAt: (in category 
> '*VMMaker-simulation') -----
> + byteAt: anInteger
> + 	"emulate an access to raw (unsigned) bytes, as if the receiver was
> a ByteArray"
> +
> + 	| element p |
> + 	p := self bytesPerBasicElement.
> + 	p = 1 ifTrue: [^self basicAt: 1].
> + 	element := self basicAt: anInteger + p - 1 // p.
> + 	^Smalltalk isLittleEndian
> + 		ifTrue: [element digitAt: anInteger - 1 \\ p + 1]
> + 		ifFalse: [element digitAt: p - (anInteger \\ p)]
> + 	!
> 
> Item was added:
> + ----- Method: WordArray>>unsignedLongAt:bigEndian: (in category
> '*VMMaker-JITsimulation') -----
> + unsignedLongAt: byteIndex bigEndian: bigEndian
> + 	"Compatiblity with the ByteArray & Alien methods of the same name."
> + 	| wordIndex lowBits word hiWord |
> + 	wordIndex := byteIndex - 1 // 4 + 1.
> + 	lowBits := byteIndex - 1 bitAnd: 3.
> + 	word := self at: wordIndex.
> + 	lowBits > 0 ifTrue: "access straddles two words"
> + 		[hiWord := self at: wordIndex + 1.
> + 		 word := (word bitShift: lowBits * -8) + (hiWord bitShift: 4 -
> lowBits * 8)].
> + 	word := word bitAnd: 16rFFFFFFFF.
> + 	bigEndian
> + 		ifTrue:
> + 			[word := ((word bitShift: -24) bitAnd: 16rFF)
> + 					 + ((word bitShift: -8) bitAnd: 16rFF00)
> + 	 				 + ((word bitAnd: 16rFF00) bitShift: 8)
> + 					 + ((word bitAnd: 16rFF) bitShift: 24)].
> + 	^word!
> 
> 
> 
> ------------------------------
> 
> Message: 5
> Date: Thu, 31 Dec 2020 09:08:46 0000
> From: commits at source.squeak.org
> To: vm-dev at lists.squeakfoundation.org
> Subject: [Vm-dev] VM Maker: Cog-nice.429.mcz
> Message-ID: <E1kutwu-0007zI-J5 at andreas>
> 
> Nicolas Cellier uploaded a new version of Cog to project VM Maker:
> http://source.squeak.org/VMMaker/Cog-nice.429.mcz
> 
> ==================== Summary ====================
> 
> Name: Cog-nice.429
> Author: nice
> Time: 31 December 2020, 10:08:44.719565 am
> UUID: 3b588f4d-7263-43c7-87b9-e3f1d9a7bd85
> Ancestors: Cog-eem.428
> 
> Enable using a WordArray or other RawBitsArray species  as simulation 
> memory.
> This implies using byteSize at a few places.
> 
> =============== Diff against Cog-eem.428 ===============
> 
> Item was changed:
>   ----- Method: CogProcessorAlien>>singleStepIn: (in category 
> 'execution') -----
>   singleStepIn: aMemory
>   	| result |
> + 	result := self primitiveSingleStepInMemory: aMemory minimumAddress:
> 0 readOnlyBelow: aMemory byteSize.
> - 	result := self primitiveSingleStepInMemory: aMemory minimumAddress:
> 0 readOnlyBelow: aMemory size.
>   	result ~~ self ifTrue:
>   		[self error: 'eek!!']!
> 
> Item was changed:
>   ----- Method: MIPSSimulator>>initializeWithMemory: (in category 'as
> yet unclassified') -----
> + initializeWithMemory: aRawBitsArray
> + 	memory := aRawBitsArray.
> - initializeWithMemory: aByteArray
> - 	memory := aByteArray.
>   	readableBase := 0.
>   	writableBase := 0.
>   	executableBase := 0.
> + 	readableLimit := memory byteSize.
> + 	writableLimit := memory byteSize.
> + 	executableLimit := memory byteSize.!
> - 	readableLimit := memory size.
> - 	writableLimit := memory size.
> - 	executableLimit := memory size.!
> 
> 
> 
> ------------------------------
> 
> Message: 6
> Date: Thu, 31 Dec 2020 04:18:58 -0800
> From: Christoph Thiede <notifications at github.com>
> To: OpenSmalltalk/opensmalltalk-vm
> 	<opensmalltalk-vm at noreply.github.com>
> Cc: Comment <comment at noreply.github.com>, OpenSmalltalk-Bot
> 	<vm-dev at lists.squeakfoundation.org>
> Subject: Re: [Vm-dev] [OpenSmalltalk/opensmalltalk-vm] Trouble running
> 	OSVM in an Ubuntu 20/aarch64 docker (raspi) (#544)
> Message-ID:
> 	<OpenSmalltalk/opensmalltalk-vm/issues/544/752942612 at github.com>
> Content-Type: text/plain; charset="utf-8"
> 
> I have tried that and built the VM again, but I keep getting the same
> mprotect error message :( Any other ideas?

 From: oscogvm/build.linux64ARMv8/HowToBuild:

vvv======vvv

If running the resultant squeak vm gives an error something like
     mprotect(x,y,PROT_READ|PROT_EXEC)
or
     memory_alias_map: shm_open: Permission denied
you need to enable shared memory for the COG JIT.

As root:
    chmod 777 /dev/shm
    echo 'none /dev/shm tmpfs rw,nosuid,nodev 0 0' >> /etc/fstab
    mount /dev/shm

The squeak vm should now work.
^^^======^^^



More information about the Vm-dev mailing list