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

commits at source.squeak.org commits at source.squeak.org
Fri May 19 19:08:59 UTC 2017


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

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

Name: VMMaker.oscog-eem.2217
Author: eem
Time: 19 May 2017, 12:08:08.01384 pm
UUID: 1b21a9ae-6dc4-40cb-9bb5-3da7e6b7c468
Ancestors: VMMaker.oscog-nice.2216

Add the Terf SoundPlugin extensions (to deal with multiple devices, their names, volumes, etc).

=============== Diff against VMMaker.oscog-nice.2216 ===============

Item was added:
+ ----- Method: SoundPlugin>>primitiveGetDefaultSoundPlayer (in category 'primitives') -----
+ primitiveGetDefaultSoundPlayer
+ 	"Answer a String with the operating system name of the default output device, or nil"
+ 	"no arguments"
+ 	| cDeviceName sz newString newStringPtr |
+ 	<export: true>
+ 	<var: #cDeviceName type: 'char*'>
+ 	<var: #newStringPtr type: 'char*'>
+ 
+ 	"Parse arguments"
+ 	interpreterProxy methodArgumentCount = 0 
+ 		ifFalse:[^interpreterProxy primitiveFail].
+ 	
+ 	"Get the answer."
+ 	cDeviceName := self cCode: 'getDefaultSoundPlayer()'.
+ 	cDeviceName == 0 ifTrue: [
+ 		^interpreterProxy pop: 1 thenPush: interpreterProxy nilObject
+ 		].
+ 
+ 	"Copy the answer to a Squeak String."
+ 	sz :=  self cCode: 'strlen(cDeviceName)'.
+ 	newString := interpreterProxy 
+ 								instantiateClass: interpreterProxy classString
+ 								indexableSize: sz.
+ 	newStringPtr := interpreterProxy firstIndexableField: newString.
+ 	self cCode: 'strncpy(newStringPtr, cDeviceName, sz)'.
+ 
+ 	self touch: newStringPtr.
+ 	self touch: cDeviceName.
+ 	"Pop the receiver, and answer the new string."
+ 	^interpreterProxy pop: 1 thenPush: newString!

Item was added:
+ ----- Method: SoundPlugin>>primitiveGetDefaultSoundRecorder (in category 'primitives') -----
+ primitiveGetDefaultSoundRecorder
+ 	"Answer a String with the operating system name of the default input device, or nil"
+ 	"no arguments"
+ 	| cDeviceName sz newString newStringPtr |
+ 	<export: true>
+ 	<var: #cDeviceName type: 'char*'>
+ 	<var: #newStringPtr type: 'char*'>
+ 
+ 	"Parse arguments"
+ 	interpreterProxy methodArgumentCount = 0 
+ 		ifFalse:[^interpreterProxy primitiveFail].
+ 
+ 	"Get the answer."
+ 	cDeviceName := self cCode: 'getDefaultSoundRecorder()'.
+ 	cDeviceName == 0 ifTrue: [
+ 		^interpreterProxy pop: 1 thenPush: interpreterProxy nilObject
+ 		].
+ 
+ 	"Copy the answer to a Squeak String."
+ 	sz :=  self cCode: 'strlen(cDeviceName)'.
+ 	newString := interpreterProxy 
+ 								instantiateClass: interpreterProxy classString
+ 								indexableSize: sz.
+ 	newStringPtr := interpreterProxy firstIndexableField: newString.
+ 	self cCode: 'strncpy(newStringPtr, cDeviceName, sz)'.
+ 
+ 	self touch: newStringPtr.
+ 	self touch: cDeviceName.
+ 	"Pop the receiver, and answer the new string."
+ 	^interpreterProxy pop: 1 thenPush: newString!

Item was added:
+ ----- Method: SoundPlugin>>primitiveGetNumberOfSoundPlayerDevices (in category 'primitives') -----
+ primitiveGetNumberOfSoundPlayerDevices
+ 	"arguments: name(type, stack offset)
+ 		dialString(String, 0)"
+ 	"answers an Integer"
+ 	| result |
+ 	<export: true>
+ 
+ 	"Parse arguments"
+ 	interpreterProxy methodArgumentCount = 0 
+ 		ifFalse:[^interpreterProxy primitiveFail].
+ 	
+ 	"get result"
+ 	result := self cCode: 'getNumberOfSoundPlayerDevices()'.
+ 
+ 	"answer it"
+ 	result := interpreterProxy signed32BitIntegerFor: result.
+ 	^interpreterProxy pop: 1 thenPush: result. "pop receiver, return result"!

Item was added:
+ ----- Method: SoundPlugin>>primitiveGetNumberOfSoundRecorderDevices (in category 'primitives') -----
+ primitiveGetNumberOfSoundRecorderDevices
+ 	"arguments: name(type, stack offset)
+ 		dialString(String, 0)"
+ 	"answers an Integer"
+ 	| result |
+ 	<export: true>
+ 
+ 	"Parse arguments"
+ 	interpreterProxy methodArgumentCount = 0 
+ 		ifFalse:[^interpreterProxy primitiveFail].
+ 	
+ 	"get result"
+ 	result := self cCode: 'getNumberOfSoundRecorderDevices()'.
+ 
+ 	"answer it"
+ 	result := interpreterProxy signed32BitIntegerFor: result.
+ 	^interpreterProxy pop: 1 thenPush: result. "pop receiver, return result"!

Item was added:
+ ----- Method: SoundPlugin>>primitiveGetSoundPlayerDeviceName (in category 'primitives') -----
+ primitiveGetSoundPlayerDeviceName
+ 	"arguments: name(type, stack offset)
+ 		deviceNumber(Integer, 0)"
+ 	"answers a string or nil"
+ 	| deviceNumber sz cDeviceName newString newStringPtr |
+ 	<export: true>
+ 	<var: #cDeviceName type: 'char*'>
+ 	<var: #newStringPtr type: 'char*'>
+ 
+ 	"Parse arguments" 
+ 	interpreterProxy methodArgumentCount = 1 
+ 		ifFalse:[^interpreterProxy primitiveFail].
+ 
+ 	deviceNumber := interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0).
+ 	interpreterProxy failed ifTrue: [^nil].
+ 	
+ 	"Get the answer."
+ 	cDeviceName := self cCode: 'getSoundPlayerDeviceName(deviceNumber - 1)'.
+ 	cDeviceName == 0 ifTrue: [
+ 		^interpreterProxy pop: 2 thenPush: interpreterProxy nilObject
+ 		].
+ 
+ 	"Copy the answer to a Squeak String."
+ 	sz :=  self cCode: 'strlen(cDeviceName)'.
+ 	newString := interpreterProxy 
+ 								instantiateClass: interpreterProxy classString
+ 								indexableSize: sz.
+ 	newStringPtr := interpreterProxy firstIndexableField: newString.
+ 	self cCode: 'strncpy(newStringPtr, cDeviceName, sz)'.
+ 
+ 	self touch: deviceNumber.
+ 	self touch: newStringPtr.
+ 	self touch: cDeviceName.
+ 	"Pop the receiver and arg, and answer the new string."
+ 	^interpreterProxy pop: 2 thenPush: newString!

Item was added:
+ ----- Method: SoundPlugin>>primitiveGetSoundRecorderDeviceName (in category 'primitives') -----
+ primitiveGetSoundRecorderDeviceName
+ 	"arguments: name(type, stack offset)
+ 		deviceNumber(Integer, 0)"
+ 	"answers a string or nil"
+ 	| deviceNumber sz cDeviceName newString newStringPtr |
+ 	<export: true>
+ 	<var: #cDeviceName type: 'char*'>
+ 	<var: #newStringPtr type: 'char*'>
+ 
+ 	"Parse arguments" 
+ 	interpreterProxy methodArgumentCount = 1 
+ 		ifFalse:[^interpreterProxy primitiveFail].
+ 
+ 
+ 	deviceNumber := interpreterProxy positive32BitValueOf: (interpreterProxy stackValue: 0).
+ 	interpreterProxy failed ifTrue: [^nil].
+ 	
+ 	"Get the answer."
+ 	cDeviceName := self cCode: 'getSoundRecorderDeviceName(deviceNumber - 1)'.
+ 	cDeviceName == 0 ifTrue: [
+ 		^interpreterProxy pop: 2 thenPush: interpreterProxy nilObject
+ 		].
+ 
+ 	"Copy the answer to a Squeak String."
+ 	sz :=  self cCode: 'strlen(cDeviceName)'.
+ 	newString := interpreterProxy 
+ 								instantiateClass: interpreterProxy classString
+ 								indexableSize: sz.
+ 	newStringPtr := interpreterProxy firstIndexableField: newString.
+ 	self cCode: 'strncpy(newStringPtr, cDeviceName, sz)'.
+ 
+ 	self touch: deviceNumber.
+ 	self touch: newStringPtr.
+ 	self touch: cDeviceName.
+ 	"Pop the receiver and arg, and answer the new string."
+ 	^interpreterProxy pop: 2 thenPush: newString!

Item was added:
+ ----- Method: SoundPlugin>>primitiveSetDefaultSoundPlayer (in category 'primitives') -----
+ primitiveSetDefaultSoundPlayer
+ 	"Tell the operating system to use the specified device name as the output device for sound."
+ 	"arg at top of stack is the String"
+ 	| deviceName obj srcPtr sz |
+ 	<export: true>
+ 	<var: 'deviceName' declareC: 'char deviceName[257]'>
+ 	<var: 'srcPtr' type: #'char *'>
+ 
+ 	"Parse arguments"
+ 	interpreterProxy methodArgumentCount = 1 ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	obj := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isBytes: obj) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	(sz := interpreterProxy byteSizeOf: obj) <= 256 ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	srcPtr := interpreterProxy firstIndexableField: obj.
+ 	self touch: srcPtr.
+ 	self touch: deviceName.
+ 	self touch: sz.
+ 	self cCode: 'strncpy(deviceName, srcPtr, sz)'.
+ 	self cCode: 'deviceName[sz] = NULL'.
+ 	
+ 	"do the work"
+ 	self cCode: 'setDefaultSoundPlayer(deviceName)'.
+ 	self success ifTrue: "pop arg, leave receiver"
+ 		[interpreterProxy pop: 1]!

Item was added:
+ ----- Method: SoundPlugin>>primitiveSetDefaultSoundRecorder (in category 'primitives') -----
+ primitiveSetDefaultSoundRecorder
+ 	"Tell the operating system to use the specified device name as the input device for sound."
+ 	"arg at top of stack is the String"
+ 	| deviceName obj srcPtr sz |
+ 	<export: true>
+ 	<var: 'deviceName' declareC: 'char deviceName[257]'>
+ 	<var: 'srcPtr' type: #'char *'>
+ 
+ 	"Parse arguments"
+ 	interpreterProxy methodArgumentCount = 1 ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	obj := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isBytes: obj) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	(sz := interpreterProxy byteSizeOf: obj) <= 256 ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	srcPtr := interpreterProxy firstIndexableField: obj.
+ 	self touch: srcPtr.
+ 	self touch: deviceName.
+ 	self touch: sz.
+ 	self cCode: 'strncpy(deviceName, srcPtr, sz)'.
+ 	self cCode: 'deviceName[sz] = NULL'.
+ 	
+ 	"do the work"
+ 	self cCode: 'setDefaultSoundRecorder(deviceName)'.
+ 	self success ifTrue: "pop arg, leave receiver"
+ 		[interpreterProxy pop: 1]!

Item was added:
+ ----- Method: SoundPlugin>>primitiveSoundEnableAEC: (in category 'primitives') -----
+ primitiveSoundEnableAEC: trueOrFalse 
+ 	"Enable or disable acoustic echo-cancellation (AEC).  trueOrFalse should be 0 for false, and 1 for true."
+ 	| result |
+ 	self primitive: 'primitiveSoundEnableAEC' parameters: #(SmallInteger ).
+ 	interpreterProxy failed ifFalse: [
+ 		result := self cCode: 'snd_EnableAEC(trueOrFalse)'.
+ 		result == 0 ifFalse: [interpreterProxy primitiveFailFor: result].
+ 	].!

Item was added:
+ ----- Method: SoundPlugin>>primitiveSoundGetRecordLevel (in category 'primitives') -----
+ primitiveSoundGetRecordLevel
+ 	"Get the sound input recording level  in the range 0-1000."
+ 	| level |
+ 	<var: 'level' type: #int>
+ 	self primitive: 'primitiveSoundGetRecordLevel'.
+ 	level := self cCode: 'snd_GetRecordLevel()'.
+ 	^level asPositiveIntegerObj
+ !

Item was changed:
  ----- Method: SoundPlugin>>primitiveSoundGetVolume (in category 'primitives') -----
  primitiveSoundGetVolume
+ 	"Get the sound input recording level."
- 	"Set the sound input recording level."
  	| left right results |
  	<var: #left type: #double>
  	<var: #right type: #double>
  	self primitive: 'primitiveSoundGetVolume'
  		parameters: #( ).
  	left := 0.
  	right := 0.
  	self cCode: 'snd_Volume((double *) &left,(double *) &right)'.
  	interpreterProxy pushRemappableOop: (right asOop: Float).
  	interpreterProxy pushRemappableOop: (left asOop: Float).
+ 	results := interpreterProxy instantiateClass: (interpreterProxy classArray) indexableSize: 2.
- 	interpreterProxy pushRemappableOop: (interpreterProxy instantiateClass: (interpreterProxy classArray) indexableSize: 2).
- 	results := interpreterProxy popRemappableOop.
  	interpreterProxy storePointer: 0 ofObject: results withValue: interpreterProxy popRemappableOop.
  	interpreterProxy storePointer: 1 ofObject: results withValue: interpreterProxy popRemappableOop.
+ 	^results!
- 	^ results!

Item was added:
+ ----- Method: SoundPlugin>>primitiveSoundSupportsAEC (in category 'primitives') -----
+ primitiveSoundSupportsAEC
+ 	"Answer true if the OS/hardware supports echo-cancellation, and false otherwise."
+ 	| result |
+ 	self primitive: 'primitiveSoundSupportsAEC'.
+ 	interpreterProxy failed ifFalse: [
+ 		result := self cCode: 'snd_SupportsAEC()'.
+ 		result == 0 ifTrue: [^interpreterProxy falseObject] ifFalse: [^interpreterProxy trueObject]
+ 	].
+ !



More information about the Vm-dev mailing list