Plan 9 from Bell Labs’s /usr/web/sources/contrib/de0u/root/sys/src/cmd/squeak/Cross/plugins/CroquetPlugin/CroquetPlugin.st

Copyright © 2021 Plan 9 Foundation.
Distributed under the MIT License.
Download the Plan 9 distribution.


'From Croquet1.0beta of 24 March 2006 [latest update: #6665] on 26 March 2006 at 8:26:17 pm'!
InterpreterPlugin subclass: #CroquetPlugin
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMaker-Plugins'!
!CroquetPlugin commentStamp: '<historical>' prior: 0!
An assorted list of useful primitives for Croquet.!


!CroquetPlugin methodsFor: 'primitives' stamp: 'ar 3/26/2006 19:59'!
primitiveARC4Transform
	"Perform an ARC4 transform of input.
	Arguments:
		buffer		<ByteArray> transformed data
		startIndex 	<Integer>	start of transform
		stopIndex	<Integer>	end of transform
		m			<ByteArray>	key stream data
		x			<Integer>	key state value
		y			<Integer>	key state value
	Return value:
		x@y - updated key state value
	"

	| y x mOop stopIndex startIndex bufOop bufSize buffer a m b mask ptOop xOop yOop |
	self export: true.
	self var: 'buffer' type: 'unsigned char *'.
	self var: 'm' type: 'unsigned char *'.

	interpreterProxy methodArgumentCount = 6
		ifFalse:[^interpreterProxy primitiveFail].
	"pick up arguments"
	y := interpreterProxy stackIntegerValue: 0.
	x := interpreterProxy stackIntegerValue: 1.
	mOop := interpreterProxy stackObjectValue: 2.
	stopIndex := interpreterProxy stackIntegerValue: 3.
	startIndex := interpreterProxy stackIntegerValue: 4.
	bufOop := interpreterProxy stackObjectValue: 5.
	interpreterProxy failed ifTrue:[^nil].
	((interpreterProxy isBytes: mOop) and:[interpreterProxy isBytes: bufOop])
		ifFalse:[^interpreterProxy primitiveFail].
	(interpreterProxy byteSizeOf: mOop) = 256
		ifFalse:[^interpreterProxy primitiveFail].
	bufSize := interpreterProxy byteSizeOf: bufOop.
	(startIndex > 0 and:[startIndex <= bufSize])
		ifFalse:[^interpreterProxy primitiveFail].
	(stopIndex > startIndex and:[stopIndex <= bufSize])
		ifFalse:[^interpreterProxy primitiveFail].
	m := interpreterProxy firstIndexableField: mOop.
	buffer := interpreterProxy firstIndexableField: bufOop.
	startIndex-1 to: stopIndex-1 do:[:i|
		x := (x + 1) bitAnd: 255.
		a := m at: x.
		y := (y + a) bitAnd: 255.
		b := m at: y.
		m at: x put: b.
		m at: y put: a.
		mask := m at: ((a + b) bitAnd: 255).
		buffer at: i put: ((buffer at: i) bitXor: mask).
	].
	ptOop := interpreterProxy instantiateClass: interpreterProxy classPoint indexableSize: 0.
	interpreterProxy pushRemappableOop: ptOop.
	xOop := interpreterProxy positive32BitIntegerFor: x.
	interpreterProxy pushRemappableOop: xOop.
	yOop := interpreterProxy positive32BitIntegerFor: x.
	xOop := interpreterProxy popRemappableOop.
	ptOop := interpreterProxy popRemappableOop.
	interpreterProxy storePointer: 0 ofObject: ptOop withValue: xOop.
	interpreterProxy storePointer: 1 ofObject: ptOop withValue: yOop.
	interpreterProxy pop: interpreterProxy methodArgumentCount + 1.
	interpreterProxy push: ptOop.
! !

!CroquetPlugin methodsFor: 'primitives' stamp: 'ar 3/26/2006 19:45'!
primitiveMD5Transform
	"Perform an MD5 transform of input"
	| bufOop hashOop hash buffer |
	self export: true.
	self var: 'hash' type: 'unsigned int *'.
	self var: 'buffer' type: 'unsigned int *'.
	interpreterProxy methodArgumentCount = 2 
		ifFalse:[^interpreterProxy primitiveFail].

	hashOop := interpreterProxy stackObjectValue: 0.
	((interpreterProxy isWords: hashOop) and:[(interpreterProxy slotSizeOf: hashOop) = 4])
		ifFalse:[^interpreterProxy primitiveFail].
	hash := interpreterProxy firstIndexableField: hashOop.

	bufOop := interpreterProxy stackObjectValue: 1.
	((interpreterProxy isWords: bufOop) and:[(interpreterProxy slotSizeOf: bufOop) = 16])
		ifFalse:[^interpreterProxy primitiveFail].
	buffer := interpreterProxy firstIndexableField: bufOop.


	self cCode:'MD5Transform(hash, buffer)' inSmalltalk:[
		hash. buffer. 
		^interpreterProxy primitiveFail].
	"Pop args; return buffer"
	interpreterProxy pop: interpreterProxy methodArgumentCount+1.
	interpreterProxy push: bufOop.! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

CroquetPlugin class
	instanceVariableNames: ''!

!CroquetPlugin class methodsFor: 'as yet unclassified' stamp: 'ar 3/26/2006 19:37'!
hasHeaderFile
	"If there is a single intrinsic header file to be associated with the plugin, here is where you want to flag"
	^true! !

!CroquetPlugin class methodsFor: 'as yet unclassified' stamp: 'ar 3/26/2006 19:37'!
requiresCrossPlatformFiles
	"default is ok for most, any plugin needing platform specific files must say so"
	^true! !

Bell Labs OSI certified Powered by Plan 9

(Return to Plan 9 Home Page)

Copyright © 2021 Plan 9 Foundation. All Rights Reserved.
Comments to webmaster@9p.io.