[ENH] SmartSyntaxInterpreterPlugin

Martin Kuball MartinKuball at web.de
Sun May 8 09:42:56 UTC 2005


Hi!

While working on a plugin for the xvidcore library I made some 
additions to the SmartSyntaxInterpreterPlugin and ExternalAddress. I 
don't now If the changes were necessary in the first place. Maybe 
there are already solutions to the problems I had. But if not, It 
would be nice the have my changes includes in VMMaker.

So here is what I did.
-- I added a class ByteArrayOrNil. The value will be translated into a 
char* pointer if I pass a ByteArray or a C null value if I pass the 
nil Object.
-- I added translation code to class ExternalAddress to automatically 
extract the pointer contained in the ByteArray.

For an example see the XvidPlugin code.

Martin
-------------- next part --------------
A non-text attachment was scrubbed...
Name: plattform.tar
Type: application/x-tar
Size: 10240 bytes
Desc: not available
Url : http://lists.squeakfoundation.org/pipermail/squeak-dev/attachments/20050508/6f0450b3/plattform.tar
-------------- next part --------------
'From Squeak3.8gamma of ''24 November 2004'' [latest update: #6548] on 8 May 2005 at 11:26:25 am'!
Behavior subclass: #ByteArrayOrNil
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMaker-SmartSyntaxPlugins'!
SmartSyntaxInterpreterPlugin subclass: #XvidPlugin
	instanceVariableNames: 'yTable buTable guTable gvTable rvTable'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'VMMaker-Plugins'!

!XvidPlugin commentStamp: '<historical>' prior: 0!
This plugin implements an interface to the xvidcore library Version 1.x

xvidcore is the video encoding/decoding library from the XVID project.

The interface is just a thin layer to pass the buffers from and to squeak. This was not possible using FFI.

Some more effort was necessary to implement the colorspace conversion. Although xvid supports a 32bit argb colorspace, the alpha component has a 0 value which means fully transparent in squeak. Therefore the conversion from the internal representation is done by the plugin itself.

To compile the plugin you need a plattform specific makefile that links the plugin against the xvid library.
!


!ByteArrayOrNil class methodsFor: 'as yet unclassified' stamp: 'maku 4/18/2005 21:12'!
ccg: cg emitLoadFor: aString from: anInteger on: aStream

	cg emitLoad: aString asCharPtrFrom: anInteger on: aStream! !

!ByteArrayOrNil class methodsFor: 'as yet unclassified' stamp: 'maku 4/18/2005 21:51'!
ccg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		ccgLoad: aBlock 
		expr: aString 
		asNullableCharPtrFrom: anInteger! !

!ByteArrayOrNil class methodsFor: 'as yet unclassified' stamp: 'maku 4/18/2005 21:12'!
ccgDeclareCForVar: aSymbolOrString

	^'char *', aSymbolOrString! !


!ExternalAddress class methodsFor: 'class initialization' stamp: 'maku 4/18/2005 22:48'!
ccg: cg prolog: aBlock expr: aString index: anInteger

	^cg 
		ccgLoad: aBlock 
		expr: aString 
		asExternalAddressFrom: anInteger! !

!ExternalAddress class methodsFor: 'class initialization' stamp: 'maku 5/3/2005 20:30'!
ccgDeclareCForVar: aSymbolOrString

	^'void *', aSymbolOrString! !


!SmartSyntaxInterpreterPlugin methodsFor: 'debugging' stamp: 'maku 5/3/2005 20:29'!
addressOf: rcvr

	| rcvrClass |
	self returnTypeC: 'void *'.
	(interpreterProxy isBytes: rcvr) ifFalse: [^ nil].
	rcvrClass _ interpreterProxy fetchClassOf: rcvr.
	rcvrClass == interpreterProxy classExternalAddress
	ifTrue:
	[
		^ self cCoerce: (interpreterProxy fetchPointer: 0 ofObject: rcvr) to: 'void *'.
	] ifFalse: [^ nil].
! !


!SmartSyntaxPluginCodeGenerator methodsFor: 'coercing' stamp: 'maku 5/3/2005 19:57'!
ccgLoad: aBlock expr: aString asExternalAddressFrom: anInteger
	"Answer codestring for character pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"

	^ String streamContents: [:aStream | aStream
		nextPutAll: (aBlock value: 'self addressOf: (interpreterProxy stackValue: ' , anInteger asString , ').' );
		nextPutAll: aString;
		nextPutAll: ' isNil ifTrue: [interpreterProxy primitiveFail]']
! !

!SmartSyntaxPluginCodeGenerator methodsFor: 'coercing' stamp: 'maku 4/19/2005 19:31'!
ccgLoad: aBlock expr: aString asNullableCharPtrFrom: anInteger
	"Answer codestring for character pointer to first indexable field of object (without validating side-effect unless specified in valBlock), as described in comment to ccgLoad:expr:asRawOopFrom:"

	^ String streamContents: [:aStream | aStream
		nextPutAll: '((interpreterProxy stackValue: ';
		nextPutAll: anInteger asString;
		nextPutAll: ') = interpreterProxy nilObject) ifTrue: [';
		nextPutAll: (aBlock value: 'null');
		nextPutAll: ']';
		crtab: 4;
		nextPutAll: 'ifFalse: [';
		nextPutAll: (self ccgLoad: aBlock expr: aString asCharPtrFrom: anInteger andThen: (self ccgValBlock: 'isBytes'));
		nextPutAll: ']'
	]
! !


!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/8/2005 11:11'!
convertImage: planes into: output height: height width: width
	"Convert the xvid internal image planes to a single plane bgra image." 

	| ey er eb yStride uvStride width2 inY inU inV eg outBuffer |
	self inline: false.
	self var: #planes type: 'xvid_dec_frame_t*'.
	self var: #output type: 'char*'.

	self var: #yStride declareC: 'int yStride'.
	self var: #uvStride declareC: 'int uvStride'.
	self var: #inY declareC: 'unsigned char* inY'.
	self var: #inU declareC: 'unsigned char* inU'.
	self var: #inV declareC: 'unsigned char* inV'.
	self var: #outBuffer declareC: 'unsigned char* outBuffer'.
	self var: #ey declareC: 'float ey'.
	self var: #er declareC: 'float er'.
	self var: #eg declareC: 'float eg'.
	self var: #eb declareC: 'float eb'.

	self cCode: 'inY = planes->output.plane[0]' inSmalltalk: [inY _ 0].
	self cCode: 'inU = planes->output.plane[1]' inSmalltalk: [inU _ 0].
	self cCode: 'inV = planes->output.plane[2]' inSmalltalk: [inV _ 0].
	self cCode: 'yStride = planes->output.stride[0]' inSmalltalk: [yStride _ 0].
	self cCode: 'uvStride = planes->output.stride[1]' inSmalltalk: [uvStride _ 0].
	width2 _ width / 2.
	outBuffer _ output.

	1 to: height do:
	[ :y |
		1 to: width2 do:
		[ :x |
			self cCode: 'eb = buTable[*inU]' inSmalltalk: [eb _ eb + 1].
			self cCode: 'eg = guTable[*inU] + gvTable[*inV]' inSmalltalk: [eg _ eg + 1].
			self cCode: 'er = rvTable[*inV]' inSmalltalk: [er _ er + 1].
			inU _ inU + 1.
			inV _ inV + 1.

			self cCode: 'ey = yTable[*inY]' inSmalltalk: [ey _ ey + 1].
			self insert: ey + eb into: outBuffer at: 0.
			self insert: ey - eg into: outBuffer at: 1.
			self insert: ey + er into: outBuffer at: 2.
			outBuffer at: 3 put: 255.
			outBuffer _ outBuffer + 4.
			inY _ inY + 1.

			self cCode: 'ey = yTable[*inY]'.
			self insert: ey + eb into: outBuffer at: 0.
			self insert: ey - eg into: outBuffer at: 1.
			self insert: ey + er into: outBuffer at: 2.
			outBuffer at: 3 put: 255.
			outBuffer _ outBuffer + 4.
			inY _ inY + 1
		].
		inU _ inU - width2.
		inV _ inV - width2.
		inY _ (inY - width) + yStride.
		y odd ifFalse:
		[
			inU _ inU + uvStride.
		 	inV _ inV + uvStride
		]
	]
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/1/2005 16:49'!
initialiseModule

	self export: true.

	0 to: 255 do: [:i | yTable at: i  put: ((i - 16) * 1.164)].
	0 to: 255 do: [:i | buTable at: i put: ((i - 128) * 2.018)].
	0 to: 255 do: [:i | guTable at: i put: ((i - 128) * 0.391)].
	0 to: 255 do: [:i | gvTable at: i put: ((i - 128) * 0.813)].
	0 to: 255 do: [:i | rvTable at: i put: ((i - 128) * 1.596)].
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/8/2005 11:20'!
insert: color into: output at: offset

	| intColor |
	self var: #output type: 'unsigned char*'.
	intColor _ self cCoerce: color to: 'int'.
	intColor _ 255 min: intColor.
	intColor _ 0 max: intColor.
	output at: offset put: intColor
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 4/24/2005 15:06'!
odd: aNumber

	^ (aNumber bitAnd: 1) > 0
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/1/2005 13:26'!
primitiveXvidCloseDecoder: handle

	| ret |
	self primitive: 'primitiveXvidCloseDecoder'
		parameters: #(ExternalAddress).

	ret _ self cCode: 'xvid_decore(handle, 1, null, null)'.
	^ ret asSmallIntegerObj
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/1/2005 13:26'!
primitiveXvidCreateDecoder: data

	| ret |
	self primitive: 'primitiveXvidCreateDecoder'
		parameters: #(ByteArray).
	ret _ self cCode: 'xvid_decore(null, 0, data, null)'.

	^ ret asSmallIntegerObj
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/1/2005 13:26'!
primitiveXvidDecode: handle frame: frame status: status input: input

	| ret |
	self primitive: 'primitiveXvidDecode'
		parameters: #(ExternalAddress ByteArray ByteArrayOrNil ByteArray).
	self cCode: '((xvid_dec_frame_t*)frame)->bitstream = input'.
	self cCode: '((xvid_dec_frame_t*)frame)->output.plane[0] = 0'.
	ret _ self cCode: 'xvid_decore(handle, 2, frame, status)'.
	^ ret asSmallIntegerObj
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 4/19/2005 19:26'!
primitiveXvidGlobal: mode param: aXvidInitStructure

	| ret |
	self primitive: 'primitiveXvidGlobal'
		parameters: #(SmallInteger ByteArray).

	ret _ self cCode: 'xvid_global(null, mode, aXvidInitStructure, null)'.
	^ ret asSmallIntegerObj
! !

!XvidPlugin methodsFor: 'initialize-release' stamp: 'maku 5/1/2005 17:37'!
primitveReadImage: frame into: buffer height: height width: width

	self primitive: 'primitiveReadImage'
		parameters: #(ByteArray WordArray SmallInteger SmallInteger).

	self convertImage: (self cCoerce: frame to: 'xvid_dec_frame_t*')
				  into: (self cCoerce: buffer to: 'char*')
                   height: height width: width.
	^ 1
! !


!XvidPlugin class methodsFor: 'initialize-release' stamp: 'maku 5/1/2005 18:44'!
declareCVarsIn: cg 

	super declareCVarsIn: cg.

	cg addHeaderFile: '<xvid.h>'.
	cg var: 'yTable'  declareC: 'float yTable[256]'.
	cg var: 'buTable' declareC: 'float buTable[256]'.
	cg var: 'guTable' declareC: 'float guTable[256]'.
	cg var: 'gvTable' declareC: 'float gvTable[256]'.
	cg var: 'rvTable' declareC: 'float rvTable[256]'.
! !

!XvidPlugin class methodsFor: 'initialize-release' stamp: 'maku 4/17/2005 19:07'!
requiresPlatformFiles
	"default is ok for most, any plugin needing platform specific files must say so"

	^ true
! !

XvidPlugin class removeSelector: #hasHeaderFile!
XvidPlugin class removeSelector: #requiresCrossPlatformFiles!

!XvidPlugin class reorganize!
('initialize-release' declareCVarsIn: requiresPlatformFiles)
!

XvidPlugin removeSelector: #addressOf:!
XvidPlugin removeSelector: #addressOfd:!
XvidPlugin removeSelector: #convertImage:into:!
XvidPlugin removeSelector: #convertImage:into:height:!
XvidPlugin removeSelector: #primitiveXvidDecode:frame:status:input:output:!
XvidPlugin removeSelector: #primitiveXvidDecode:frame:status:input:output:height:!
XvidPlugin removeSelector: #primitiveXvidDecode:frame:status:input:output:height:width:!
XvidPlugin removeSelector: #primitiveXvidDecode:mode:data:status:!
XvidPlugin removeSelector: #primitiveXvidInit:!
XvidPlugin removeSelector: #primitiveXvidInit:param:!

!XvidPlugin reorganize!
('initialize-release' convertImage:into:height:width: initialiseModule insert:into:at: odd: primitiveXvidCloseDecoder: primitiveXvidCreateDecoder: primitiveXvidDecode:frame:status:input: primitiveXvidGlobal:param: primitveReadImage:into:height:width:)
!

-------------- next part --------------
Object subclass: #XvidCore
	instanceVariableNames: 'xvidHandle decodeStructure statusStructure outputBuffer imageSize colorFormat'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AudioVideoLib-Codecs-Xvid'!

!XvidCore methodsFor: 'external calls' stamp: 'maku 4/18/2005 22:19'!
primCloseDecoder: handle

	<primitive: 'primitiveXvidCloseDecoder' module: 'XvidPlugin'>
	^ self primitiveFailed
! !

!XvidCore methodsFor: 'external calls' stamp: 'maku 4/18/2005 22:14'!
primCreateDecoder: aByteArray

	<primitive: 'primitiveXvidCreateDecoder' module: 'XvidPlugin'>
	^ self primitiveFailed
! !

!XvidCore methodsFor: 'external calls' stamp: 'maku 4/24/2005 17:07'!
primDecode: handle frame: frame status: status input: input

	<primitive: 'primitiveXvidDecode' module: 'XvidPlugin'>
	^ self primitiveFailed
! !

!XvidCore methodsFor: 'external calls' stamp: 'maku 4/17/2005 19:14'!
primGlobal: mode param: aByteArray

	<primitive: 'primitiveXvidGlobal' module: 'XvidPlugin'>
	^ self primitiveFailed
! !

!XvidCore methodsFor: 'external calls' stamp: 'maku 4/24/2005 17:07'!
primReadImage: frame into: buffer height: height width: width

	<primitive: 'primitiveReadImage' module: 'XvidPlugin'>
	^ self primitiveFailed
! !


!XvidCore methodsFor: 'initialization' stamp: 'maku 4/19/2005 22:22'!
close
	"Close the decoder to release resources."

	| ret |
	self isOpen ifTrue:
	[
		ret _ self primCloseDecoder: xvidHandle.
		xvidHandle	  _ nil.
		ret = 0 ifFalse: [self error: 'error closing decoder: ', ret printString]
	]
! !

!XvidCore methodsFor: 'initialization' stamp: 'maku 4/19/2005 22:35'!
createDecoderFor: aVideoFormat

	| ret createInfo |
	imageSize _ aVideoFormat extent.

	createInfo _ XvidCreateStructure new.
	createInfo width: aVideoFormat width; height: aVideoFormat height.
	ret _ self primCreateDecoder: createInfo getHandle.
	ret = 0 ifFalse: [self error: 'error creating decoder: ', ret printString].

	xvidHandle _ createInfo handle getHandle.

	decodeStructure _ XvidDecodeStructure new.
	statusStructure _ XvidStatusStructure new.

	self setColorFormat: colorFormat.
! !

!XvidCore methodsFor: 'initialization' stamp: 'maku 4/20/2005 20:53'!
initialize

	| ret |
	super initialize.
	colorFormat _ 4.
	ret _ self primGlobal: 0 param: XvidInitStructure new getHandle.
	ret = 0 ifFalse: [self error: 'error initializing xvid: ', ret printString]! !


!XvidCore methodsFor: 'accessing' stamp: 'maku 4/17/2005 18:43'!
getXvidInfo

	| info ret |
	info _ XvidInfoStructure new.
	ret _ self primGlobal: 1 param: info getHandle.
	ret = 0 ifTrue: [^ info] ifFalse: [self error: 'error getting info: ' , ret printString]
! !

!XvidCore methodsFor: 'accessing' stamp: 'maku 4/24/2005 17:10'!
imageData

	self primReadImage: decodeStructure getHandle
                        into: outputBuffer
                     height: imageSize y
                      width: imageSize x.
	^ outputBuffer
! !

!XvidCore methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:43'!
status

	^ statusStructure
! !

!XvidCore methodsFor: 'accessing' stamp: 'maku 5/1/2005 14:38'!
storeImageInto: aForm

	"aForm bits fromByteStream: self imageData readStream"
	self primReadImage: decodeStructure getHandle
                        into: aForm bits
                     height: imageSize y
                      width: imageSize x.
! !


!XvidCore methodsFor: 'coding' stamp: 'maku 4/24/2005 17:07'!
decode: aFrameBuffer
	"Decode the given frame. Answer the number of bytes used."

	| ret |
	decodeStructure length: aFrameBuffer size.
	ret _ self primDecode: xvidHandle
                      frame: decodeStructure getHandle
                       status: statusStructure getHandle
				    input: aFrameBuffer.
	ret <= 0 ifTrue: [self error: 'error decoding frame: ', ret printString].
	^ ret
! !


!XvidCore methodsFor: 'testing' stamp: 'maku 4/19/2005 19:18'!
isOpen

	^ xvidHandle isNil not! !


!XvidCore methodsFor: 'format' stamp: 'maku 4/24/2005 16:53'!
setColorFormat: aNumber

	colorFormat   _ aNumber.
	outputBuffer _ WordArray new: (imageSize x) * (imageSize y). " * colorFormat."
		"64 = 32 bit bgra   512 = 24bit BGR  8192 = internal format"
	decodeStructure csp: 8192.
	decodeStructure stride1: imageSize x * colorFormat! !

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

XvidCore class
	instanceVariableNames: ''!

!XvidCore class methodsFor: 'constants' stamp: 'maku 4/8/2005 23:18'!
moduleName

	^ 'xvidcore'
! !


!XvidCore class methodsFor: 'accessing' stamp: 'maku 4/9/2005 15:16'!
getXvidInfo

! !


ExternalStructure subclass: #XvidCreateStructure
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AudioVideoLib-Codecs-Xvid'!

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
handle
	"This method was automatically generated"
	^ExternalData fromHandle: (handle pointerAt: 13) type: ExternalType void asPointerType! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
handle: anObject
	"This method was automatically generated"
	handle pointerAt: 13 put: anObject getHandle.! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
height
	"This method was automatically generated"
	^handle signedLongAt: 9! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
height: anObject
	"This method was automatically generated"
	handle signedLongAt: 9 put: anObject! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
version
	"This method was automatically generated"
	^handle signedLongAt: 1! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
version: anObject
	"This method was automatically generated"
	handle signedLongAt: 1 put: anObject! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
width
	"This method was automatically generated"
	^handle signedLongAt: 5! !

!XvidCreateStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 21:39'!
width: anObject
	"This method was automatically generated"
	handle signedLongAt: 5 put: anObject! !


!XvidCreateStructure methodsFor: 'initialization' stamp: 'maku 4/9/2005 17:05'!
initialize

	super initialize.
	self version: 16r10000
! !

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

XvidCreateStructure class
	instanceVariableNames: ''!

!XvidCreateStructure class methodsFor: 'field definition' stamp: 'maku 4/19/2005 21:39'!
fields
	"XvidCreateStructure defineFields"

	^ #(
		(version	'long')
		(width		'long')
		(height		'long')
		(handle		'void *')
	)

! !


!XvidCreateStructure class methodsFor: 'instance creation' stamp: 'maku 4/9/2005 17:05'!
new

	^ super new initialize
! !


ExternalStructure subclass: #XvidDecodeStructure
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AudioVideoLib-Codecs-Xvid'!

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
csp
	"This method was automatically generated"
	^handle signedLongAt: 17! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
csp: anObject
	"This method was automatically generated"
	handle signedLongAt: 17 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
general
	"This method was automatically generated"
	^handle signedLongAt: 5! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
general: anObject
	"This method was automatically generated"
	handle signedLongAt: 5 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
length
	"This method was automatically generated"
	^handle signedLongAt: 13! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
length: anObject
	"This method was automatically generated"
	handle signedLongAt: 13 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride1
	"This method was automatically generated"
	^handle signedLongAt: 37! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride1: anObject
	"This method was automatically generated"
	handle signedLongAt: 37 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride2
	"This method was automatically generated"
	^handle signedLongAt: 41! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride2: anObject
	"This method was automatically generated"
	handle signedLongAt: 41 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride3
	"This method was automatically generated"
	^handle signedLongAt: 45! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride3: anObject
	"This method was automatically generated"
	handle signedLongAt: 45 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride4
	"This method was automatically generated"
	^handle signedLongAt: 49! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
stride4: anObject
	"This method was automatically generated"
	handle signedLongAt: 49 put: anObject! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
version
	"This method was automatically generated"
	^handle signedLongAt: 1! !

!XvidDecodeStructure methodsFor: 'accessing' stamp: 'maku 4/19/2005 20:03'!
version: anObject
	"This method was automatically generated"
	handle signedLongAt: 1 put: anObject! !


!XvidDecodeStructure methodsFor: 'initialization' stamp: 'maku 4/9/2005 22:49'!
initialize

	super initialize.
	self version: 16r10000
! !

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

XvidDecodeStructure class
	instanceVariableNames: ''!

!XvidDecodeStructure class methodsFor: 'field definition' stamp: 'maku 4/19/2005 20:03'!
fields
	"XvidDecodeStructure defineFields"

	^ #(
		(version	'long')		"input"
		(general	'long')		"input, optional, general flags"
		(#nil		'byte*')		"input bitstream"
		(length		'long')		"input, size of bitstream"
		(csp			'long')		"input, colorspace"
		(#nil		'byte*')		"input plane1"
		(#nil		'byte*')		"input plane2"
		(#nil		'byte*')		"input plane3"
		(#nil		'byte*')		"input plane4"
		(stride1		'long')		"input"
		(stride2		'long')
		(stride3		'long')
		(stride4		'long')
	)
! !


!XvidDecodeStructure class methodsFor: 'instance creation' stamp: 'maku 4/9/2005 22:49'!
new

	^ super new initialize
! !


ExternalStructure subclass: #XvidInfoStructure
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AudioVideoLib-Codecs-Xvid'!

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
actualVersion
	"This method was automatically generated"
	^handle signedLongAt: 5! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
actualVersion: anObject
	"This method was automatically generated"
	handle signedLongAt: 5 put: anObject! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
build
	"This method was automatically generated"
	^ExternalData fromHandle: (handle pointerAt: 9) type: ExternalType char asPointerType! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
build: anObject
	"This method was automatically generated"
	handle pointerAt: 9 put: anObject getHandle.! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
cpuflag
	"This method was automatically generated"
	^handle unsignedLongAt: 13! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
cpuflag: anObject
	"This method was automatically generated"
	handle unsignedLongAt: 13 put: anObject! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
threads
	"This method was automatically generated"
	^handle signedLongAt: 17! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
threads: anObject
	"This method was automatically generated"
	handle signedLongAt: 17 put: anObject! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
version
	"This method was automatically generated"
	^handle signedLongAt: 1! !

!XvidInfoStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 16:43'!
version: anObject
	"This method was automatically generated"
	handle signedLongAt: 1 put: anObject! !


!XvidInfoStructure methodsFor: 'initialization' stamp: 'maku 4/9/2005 15:18'!
initialize

	self version: 16r10000
! !

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

XvidInfoStructure class
	instanceVariableNames: ''!

!XvidInfoStructure class methodsFor: 'field definition' stamp: 'maku 4/9/2005 16:43'!
fields
	"XvidInfoStructure defineFields"
	^ #(
		(version		'long')
		(actualVersion	'long')
		(build			'char*')
		(cpuflag		'ulong')
		(threads			'long')
	)
! !


!XvidInfoStructure class methodsFor: 'instance creation' stamp: 'maku 4/9/2005 16:36'!
new

	^ super new initialize
! !


ExternalStructure subclass: #XvidInitStructure
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AudioVideoLib-Codecs-Xvid'!

!XvidInitStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 13:20'!
cpuflag
	"This method was automatically generated"
	^handle unsignedLongAt: 5! !

!XvidInitStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 13:20'!
cpuflag: anObject
	"This method was automatically generated"
	handle unsignedLongAt: 5 put: anObject! !

!XvidInitStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 13:20'!
debug
	"This method was automatically generated"
	^handle signedLongAt: 9! !

!XvidInitStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 13:20'!
debug: anObject
	"This method was automatically generated"
	handle signedLongAt: 9 put: anObject! !

!XvidInitStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 13:20'!
version
	"This method was automatically generated"
	^handle signedLongAt: 1! !

!XvidInitStructure methodsFor: 'accessing' stamp: 'maku 4/9/2005 13:20'!
version: anObject
	"This method was automatically generated"
	handle signedLongAt: 1 put: anObject! !


!XvidInitStructure methodsFor: 'initialization' stamp: 'maku 4/9/2005 15:10'!
initialize

	self version: 16r10000
! !

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

XvidInitStructure class
	instanceVariableNames: ''!

!XvidInitStructure class methodsFor: 'field definition' stamp: 'maku 4/9/2005 13:20'!
fields
	"XvidInitStructure defineFields"
	^ #(
		(version	'long')
		(cpuflag	'ulong')
		(debug		'long')
	)
! !


!XvidInitStructure class methodsFor: 'instance creation' stamp: 'maku 4/9/2005 16:53'!
new

	^ super new initialize
! !


ExternalStructure subclass: #XvidStatusStructure
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'AudioVideoLib-Codecs-Xvid'!

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
general
	"This method was automatically generated"
	^handle signedLongAt: 9! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
general: anObject
	"This method was automatically generated"
	handle signedLongAt: 9 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out1
	"This method was automatically generated"
	^handle signedLongAt: 13! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out1: anObject
	"This method was automatically generated"
	handle signedLongAt: 13 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out2
	"This method was automatically generated"
	^handle signedLongAt: 17! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out2: anObject
	"This method was automatically generated"
	handle signedLongAt: 17 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out3
	"This method was automatically generated"
	^handle signedLongAt: 21! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out3: anObject
	"This method was automatically generated"
	handle signedLongAt: 21 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out4
	"This method was automatically generated"
	^handle signedLongAt: 25! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out4: anObject
	"This method was automatically generated"
	handle signedLongAt: 25 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out5
	"This method was automatically generated"
	^handle signedLongAt: 29! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
out5: anObject
	"This method was automatically generated"
	handle signedLongAt: 29 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
type
	"This method was automatically generated"
	^handle signedLongAt: 5! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
type: anObject
	"This method was automatically generated"
	handle signedLongAt: 5 put: anObject! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
version
	"This method was automatically generated"
	^handle signedLongAt: 1! !

!XvidStatusStructure methodsFor: 'accessing' stamp: 'maku 4/10/2005 11:39'!
version: anObject
	"This method was automatically generated"
	handle signedLongAt: 1 put: anObject! !


!XvidStatusStructure methodsFor: 'initialization' stamp: 'maku 4/10/2005 11:40'!
initialize

	super initialize.
	self version: 16r10000
! !

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

XvidStatusStructure class
	instanceVariableNames: ''!

!XvidStatusStructure class methodsFor: 'field definition' stamp: 'maku 4/17/2005 11:40'!
fields
	"XvidStatusStructure defineFields"

	^ #(
		(version	'long')		"input"
		(type		'long')		"output, -1 = VOL, 0 = nothing"
		(general	'long')		"output, general flags"
		(out1		'long')
		(out2		'long')
		(out3		'long')
		(out4		'long')
		(out5		'long')
	)

! !


!XvidStatusStructure class methodsFor: 'instance creation' stamp: 'maku 4/10/2005 11:39'!
new

	^ super new initialize
! !


XvidCreateStructure compileFields!


XvidDecodeStructure compileFields!


XvidInfoStructure compileFields!


XvidInitStructure compileFields!


XvidStatusStructure compileFields!


More information about the Squeak-dev mailing list