[Vm-dev] VM Maker: VMMaker-dtl.384.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jul 9 16:13:18 UTC 2016


David T. Lewis uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker-dtl.384.mcz

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

Name: VMMaker-dtl.384
Author: dtl
Time: 9 July 2016, 12:03:18.999 pm
UUID: 53635f21-7aaa-454b-bbfc-9fc2b67fb70b
Ancestors: VMMaker-dtl.383

VMMaker 4.15.7
Updates from oscog, Laura's JPEGReadWriter2 plus a missing fsync primitive:

Name: VMMaker.oscog-eem.1489

Integrate Monty's fsync primitive.

Name: VMMaker.oscog-eem.1887

Integrate Laura's greyscale JPEG support code, eliminating one cCode:inSmalltalk.  Too lazy to eliminate the other. Requires http://squeakvm.org/svn/squeak/trunk/platforms/Cross/plugins r3742.

Name: VMMaker.oscog-eem.1888

Integrate changes proposed by Laura Perez Cerrato

"Working on JPEGReadWriter2 I noticed that both reading and writing primitives include a sanity check that ensures that the source/destination Smalltalk bitmap has the exact size in bytes needed, instead of checking that its size is at least that needed. Some BitBlt primitives perform the same check, thus not allowing operations with forms with associated bitmaps with a size greater than needed. 

When performing operations with images, and specially when such images are large in size, actually processing the images takes a small fraction of the time it takes to perform the whole operation, while allocating and deallocating correctly sized bitmaps takes much longer. If one would wish to process a series of similarly sized images (with a definite maximum size), it would be desirable to allocate a bitmap big enough to hold any of them only once and then reuse it, thus avoiding the aforementioned cost. Checking that source and destination bitmaps are big enough instead of checking that their size is exactly that which is expected would allow that optimization.

A brief exploration of BitBlt and JPEGReadWriter2's code, accompanied with some experimenting of what would happen if such sanity checks were modified as proposed, has lead me to thinking that these changes would be benefitial. I haven't observed any undesirable side effects (meaning, nothing seems to have blown up :))....."

=============== Diff against VMMaker-dtl.383 ===============

Item was changed:
  ----- Method: BitBltSimulation>>loadBitBltDestForm (in category 'interpreter interface') -----
  loadBitBltDestForm
  	"Load the dest form for BitBlt. Return false if anything is wrong, true otherwise."
  
  	| destBitsSize |
  	<inline: true>
  	destBits := interpreterProxy fetchPointer: FormBitsIndex ofObject: destForm.
  	destWidth := interpreterProxy fetchInteger: FormWidthIndex ofObject: destForm.
  	destHeight := interpreterProxy fetchInteger: FormHeightIndex ofObject: destForm.
  	(destWidth >= 0 and: [destHeight >= 0])
  		ifFalse: [^ false].
  	destDepth := interpreterProxy fetchInteger: FormDepthIndex ofObject: destForm.
  	destMSB := destDepth > 0.
  	destDepth < 0 ifTrue:[destDepth := 0 - destDepth].
  	"Ignore an integer bits handle for Display in which case 
  	the appropriate values will be obtained by calling ioLockSurfaceBits()."
  	(interpreterProxy isIntegerObject: destBits) ifTrue:[
  		"Query for actual surface dimensions"
  		(self queryDestSurface: (interpreterProxy integerValueOf: destBits))
  			ifFalse:[^false].
  		destPPW := 32 // destDepth.
  		destBits := destPitch := 0.
  	] ifFalse:[
  		destPPW := 32 // destDepth.
  		destPitch := destWidth + (destPPW-1) // destPPW * 4.
  		destBitsSize := interpreterProxy byteSizeOf: destBits.
  		((interpreterProxy isWordsOrBytes: destBits)
+ 			and: [destBitsSize >= (destPitch * destHeight)])
- 			and: [destBitsSize = (destPitch * destHeight)])
  			ifFalse: [^ false].
  		"Skip header since external bits don't have one"
  		destBits := self oopForPointer: (interpreterProxy firstIndexableField: destBits).
  	].
  	^true!

Item was changed:
  ----- Method: BitBltSimulation>>loadBitBltSourceForm (in category 'interpreter interface') -----
  loadBitBltSourceForm
  	"Load the source form for BitBlt. Return false if anything is wrong, true otherwise."
  	| sourceBitsSize |
  	<inline: true>
  	sourceBits := interpreterProxy fetchPointer: FormBitsIndex ofObject: sourceForm.
  	sourceWidth := self fetchIntOrFloat: FormWidthIndex ofObject: sourceForm.
  	sourceHeight := self fetchIntOrFloat: FormHeightIndex ofObject: sourceForm.
  	(sourceWidth >= 0 and: [sourceHeight >= 0])
  		ifFalse: [^ false].
  	sourceDepth := interpreterProxy fetchInteger: FormDepthIndex ofObject: sourceForm.
  	sourceMSB := sourceDepth > 0.
  	sourceDepth < 0 ifTrue:[sourceDepth := 0 - sourceDepth].
  	"Ignore an integer bits handle for Display in which case 
  	the appropriate values will be obtained by calling ioLockSurfaceBits()."
  	(interpreterProxy isIntegerObject: sourceBits) ifTrue:[
  		"Query for actual surface dimensions"
  		(self querySourceSurface: (interpreterProxy integerValueOf: sourceBits))
  			ifFalse:[^false].
  		sourcePPW := 32 // sourceDepth.
  		sourceBits := sourcePitch := 0.
  	] ifFalse:[
  		sourcePPW := 32 // sourceDepth.
  		sourcePitch := sourceWidth + (sourcePPW-1) // sourcePPW * 4.
  		sourceBitsSize := interpreterProxy byteSizeOf: sourceBits.
  		((interpreterProxy isWordsOrBytes: sourceBits)
+ 			and: [sourceBitsSize >= (sourcePitch * sourceHeight)])
- 			and: [sourceBitsSize = (sourcePitch * sourceHeight)])
  			ifFalse: [^ false].
  		"Skip header since external bits don't have one"
  		sourceBits := self oopForPointer: (interpreterProxy firstIndexableField: sourceBits).
  	].
  	^true!

Item was added:
+ ----- Method: FilePlugin>>primitiveFileSync (in category 'file primitives') -----
+ primitiveFileSync
+ 	| file |
+ 	<var: 'file' type: 'SQFile *'>
+ 	<export: true>
+ 	file := self fileValueOf: (interpreterProxy stackValue: 0).
+ 	interpreterProxy failed ifFalse:[self sqFileSync: file].
+ 	interpreterProxy failed ifFalse: [interpreterProxy pop: 1].!

Item was added:
+ ----- Method: FilePluginSimulator>>sqFileSync: (in category 'simulation') -----
+ sqFileSync: file
+ 	^file sync!

Item was added:
+ ----- Method: JPEGReadWriter2Plugin>>primImageNumComponents: (in category 'primitives') -----
+ primImageNumComponents: aJPEGDecompressStruct
+ 
+ 	<export: true>
+ 
+ 	self
+ 		primitive: 'primImageNumComponents'
+ 		parameters: #(ByteArray).
+ 
+ 	"Various parameter checks"
+ 	self cCode: '
+ 		interpreterProxy->success
+ 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(0))) >= (sizeof(struct jpeg_decompress_struct))); 
+ 		if (interpreterProxy->failed()) return null;
+ 	' inSmalltalk: [].
+ 
+ 	^(self cCode: '((j_decompress_ptr)aJPEGDecompressStruct)->num_components' inSmalltalk: [0])
+ 		 asOop: SmallInteger!

Item was changed:
  ----- Method: JPEGReadWriter2Plugin>>primJPEGReadHeader:fromByteArray:errorMgr: (in category 'primitives') -----
  primJPEGReadHeader: aJPEGDecompressStruct fromByteArray: source errorMgr: aJPEGErrorMgr2Struct
+ 	
+ 	| sourceSize |
+ 	
- 
- 	| pcinfo pjerr sourceSize |
  	<export: true>
+ 	
- 	<var: #pcinfo type: 'j_decompress_ptr '>
- 	<var: #pjerr type: 'error_ptr2 '>
  	self
  		primitive: 'primJPEGReadHeaderfromByteArrayerrorMgr'
  		parameters: #(ByteArray ByteArray ByteArray).
-  
  
- 		pcinfo := nil. pjerr := nil. sourceSize := nil.
- 		pcinfo. pjerr. sourceSize.
- 
  	"Various parameter checks"
+ 	interpreterProxy success: 
+ 		(self cCode: 'interpreterProxy->stSizeOf(interpreterProxy->stackValue(2)) >= (sizeof(struct jpeg_decompress_struct))' inSmalltalk: []).
+ 	interpreterProxy success:
+ 		(self cCode: 'interpreterProxy->stSizeOf(interpreterProxy->stackValue(0)) >= (sizeof(struct error_mgr2))' inSmalltalk: []).
+ 	interpreterProxy failed ifTrue: [ ^ nil ].
+ 	
+ 	sourceSize := interpreterProxy stSizeOf: (interpreterProxy stackValue: 1).
+ 	sourceSize > 0 ifTrue:
+ 		[self primJPEGReadHeader: aJPEGDecompressStruct
+ 			fromByteArray: source
+ 			size: sourceSize
+ 			errorMgrReadHeader: aJPEGErrorMgr2Struct]!
- 	self cCode: '
- 		interpreterProxy->success
- 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(2))) >= (sizeof(struct jpeg_decompress_struct)));
- 		interpreterProxy->success
- 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(0))) >= (sizeof(struct error_mgr2))); 
- 		if (interpreterProxy->failed()) return null;
- 	' inSmalltalk: [].
- 
- 	self cCode: '
- 		sourceSize = interpreterProxy->stSizeOf(interpreterProxy->stackValue(1));
- 		pcinfo = (j_decompress_ptr)aJPEGDecompressStruct;
- 		pjerr = (error_ptr2)aJPEGErrorMgr2Struct;
- 		if (sourceSize) {
- 			pcinfo->err = jpeg_std_error(&pjerr->pub);
- 			pjerr->pub.error_exit = error_exit;
- 			if (setjmp(pjerr->setjmp_buffer)) {
- 				jpeg_destroy_decompress(pcinfo);
- 				sourceSize = 0;
- 			}
- 			if (sourceSize) {
- 				jpeg_create_decompress(pcinfo);
- 				jpeg_mem_src(pcinfo, source, sourceSize);
- 				jpeg_read_header(pcinfo, TRUE);
- 			}
- 		}
- 	' inSmalltalk: [].!

Item was changed:
  ----- Method: JPEGReadWriter2Plugin>>primJPEGReadImage:fromByteArray:onForm:doDithering:errorMgr: (in category 'primitives') -----
  primJPEGReadImage: aJPEGDecompressStruct fromByteArray: source onForm: form doDithering: ditherFlag errorMgr: aJPEGErrorMgr2Struct
  
+ 	| formBitmap formNativeDepth formDepth formWidth formHeight pixelsPerWord formPitch formBitmapSizeInBytes sourceSize formBitmapOOP formComponentBitSize formComponents wordsPerRow |
- 	| pcinfo pjerr buffer rowStride formBits formDepth i j formPix ok rOff gOff bOff rOff2 gOff2 bOff2 formWidth formHeight pixPerWord formPitch formBitsSize sourceSize r1 r2 g1 g2 b1 b2 formBitsOops dmv1 dmv2 di dmi dmo |
  	<export: true>
+ 	<var: #formBitmap type: 'unsigned int*'>
- 	<var: #pcinfo type: 'j_decompress_ptr '>
- 	<var: #pjerr type: 'error_ptr2 '>
- 	<var: #buffer type: 'JSAMPARRAY '>
- 	<var: #formBits type: 'unsigned * '>
  
  	self
  		primitive: 'primJPEGReadImagefromByteArrayonFormdoDitheringerrorMgr'
  		parameters: #(ByteArray ByteArray Form Boolean ByteArray).
  
+ 	formBitmapOOP := interpreterProxy fetchPointer: 0 ofObject: form. 
+ 	formNativeDepth := interpreterProxy fetchInteger: 3 ofObject: form.
+ 	formWidth := interpreterProxy fetchInteger: 1 ofObject: form.
+ 	formHeight := interpreterProxy fetchInteger: 2 ofObject: form.
+ 	formDepth := formNativeDepth abs.
+ 	
- 	"Avoid warnings when saving method"
- 	 pcinfo := nil. pjerr := nil. buffer := nil. rowStride := nil.
- 		formDepth := nil. formBits := nil. i := nil. j := nil. formPix := nil.
- 		ok := nil. rOff := nil. gOff := nil. bOff := nil. rOff2 := nil. gOff2 := nil. bOff2 := nil. sourceSize := nil.
- 		r1 := nil. r2 := nil. g1 := nil. g2 := nil. b1 := nil. b2 := nil.
- 		dmv1 := nil. dmv2 := nil. di := nil. dmi := nil. dmo := nil.
- 		pcinfo. pjerr. buffer. rowStride. formBits. formDepth. i. j. formPix. ok.
- 		rOff. gOff. bOff. rOff2. gOff2. bOff2. sourceSize.
- 		r1. r2. g1.g2. b1. b2. dmv1. dmv2. di. dmi. dmo.
- 
- 	formBitsOops := interpreterProxy fetchPointer: 0 ofObject: form.
- 	formDepth := interpreterProxy fetchInteger: 3 ofObject: form.
- 
  	"Various parameter checks"
+ 	interpreterProxy success:
+ 		(self cCode: 'interpreterProxy->stSizeOf(interpreterProxy->stackValue(4)) >= (sizeof(struct jpeg_decompress_struct))' inSmalltalk: []).
+ 	interpreterProxy success:
+ 		(self cCode: 'interpreterProxy->stSizeOf(interpreterProxy->stackValue(0)) >= (sizeof(struct error_mgr2))' inSmalltalk: []).
+ 	interpreterProxy failed ifTrue: [ ^ nil ].
+ 	
+ 	formComponents := formDepth ~= 8 ifTrue: [4] ifFalse: [1].
+ 	formComponentBitSize := formDepth ~= 16 ifTrue: [8] ifFalse: [4].
+ 	pixelsPerWord := 32 // (formComponents * formComponentBitSize).
+ 	wordsPerRow := (formWidth + pixelsPerWord - 1) // pixelsPerWord.
+ 	formPitch := formWidth + (pixelsPerWord-1) // pixelsPerWord * 4.
+ 	formBitmapSizeInBytes := interpreterProxy byteSizeOf: formBitmapOOP.
+ 	
- 	self cCode: '
- 		interpreterProxy->success
- 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(4))) >= (sizeof(struct jpeg_decompress_struct)));
- 		interpreterProxy->success
- 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(0))) >= (sizeof(struct error_mgr2))); 
- 		if (interpreterProxy->failed()) return null;
- 	' inSmalltalk: [].
- 	formWidth := (self cCode: '((j_decompress_ptr)aJPEGDecompressStruct)->image_width' inSmalltalk: [0]).
- 	formHeight := (self cCode: '((j_decompress_ptr)aJPEGDecompressStruct)->image_height' inSmalltalk: [0]).
- 	pixPerWord := 32 // formDepth.
- 	formPitch := formWidth + (pixPerWord-1) // pixPerWord * 4.
- 	formBitsSize := interpreterProxy byteSizeOf: formBitsOops.
  	interpreterProxy success: 
+ 		((interpreterProxy isWordsOrBytes: formBitmapOOP) and: 
+ 		[formBitmapSizeInBytes >= (formPitch * formHeight)]).
- 		((interpreterProxy isWordsOrBytes: formBitsOops)
- 			and: [formBitsSize = (formPitch * formHeight)]).
  	interpreterProxy failed ifTrue: [^ nil].
+ 	
+ 	sourceSize := interpreterProxy stSizeOf: (interpreterProxy stackValue: 3).
+ 	
+ 	interpreterProxy success: (sourceSize ~= 0).
+ 	interpreterProxy failed ifTrue: [  ^ nil ].
+ 	
+ 	formBitmap := interpreterProxy firstIndexableField: formBitmapOOP.
+ 	
+ 	self 
+ 		cCode: 'primJPEGReadImagefromByteArrayonFormdoDitheringerrorMgrReadScanlines(
+ 			aJPEGDecompressStruct,
+     			aJPEGErrorMgr2Struct,
+ 			source,
+     			sourceSize,
+     			ditherFlag,
+     			formBitmap,
+    			pixelsPerWord,
+    			wordsPerRow,
+     			formNativeDepth);'
+ 		inSmalltalk: [].!
- 	formBits := interpreterProxy firstIndexableField: formBitsOops.
- 
- 	self cCode: '
- 		sourceSize = interpreterProxy->stSizeOf(interpreterProxy->stackValue(3));
- 		if (sourceSize == 0) {
- 			interpreterProxy->success(false);
- 			return null;
- 		}
- 		pcinfo = (j_decompress_ptr)aJPEGDecompressStruct;
- 		pjerr = (error_ptr2)aJPEGErrorMgr2Struct;
- 		pcinfo->err = jpeg_std_error(&pjerr->pub);
- 		pjerr->pub.error_exit = error_exit;
- 		ok = 1;
- 		if (setjmp(pjerr->setjmp_buffer)) {
- 			jpeg_destroy_decompress(pcinfo);
- 			ok = 0;
- 		}
- 		if (ok) {
- 			ok = jpeg_mem_src_newLocationOfData(pcinfo, source, sourceSize);
- 			if (ok) {
- 				/* Dither Matrix taken from Form>>orderedDither32To16, but rewritten for this method. */
- 				int ditherMatrix1[] = { 2, 0, 14, 12, 1, 3, 13, 15 };
- 				int ditherMatrix2[] = { 10, 8, 6, 4, 9, 11, 5, 7 };
-  				jpeg_start_decompress(pcinfo);
- 				rowStride = pcinfo->output_width * pcinfo->output_components;
- 				if (pcinfo->out_color_components == 3) {
- 					rOff = 0; gOff = 1; bOff = 2;
- 					rOff2 = 3; gOff2 = 4; bOff2 = 5;
- 				} else {
- 					rOff = 0; gOff = 0; bOff = 0;
- 					rOff2 = 1; gOff2 = 1; bOff2 = 1;
- 				}
- 				/* Make a one-row-high sample array that will go away when done with image */
- 				buffer = (*(pcinfo->mem)->alloc_sarray)
- 					((j_common_ptr) pcinfo, JPOOL_IMAGE, rowStride, 1);
- 
- 				/* Step 6: while (scan lines remain to be read) */
- 				/*           jpeg_read_scanlines(...); */
- 
- 				/* Here we use the library state variable cinfo.output_scanline as the
- 				 * loop counter, so that we dont have to keep track ourselves.
- 				 */
- 				while (pcinfo->output_scanline < pcinfo->output_height) {
- 					/* jpeg_read_scanlines expects an array of pointers to scanlines.
- 					 * Here the array is only one element long, but you could ask for
- 					 * more than one scanline at a time if thats more convenient.
- 					 */
- 					(void) jpeg_read_scanlines(pcinfo, buffer, 1);
- 
- 					switch (formDepth) {
- 						case 32:
- 							for(i = 0, j = 0; i < rowStride; i +=(pcinfo->out_color_components), j++) {
- 								formPix = (255 << 24) | (buffer[0][i+rOff] << 16) | (buffer[0][i+gOff] << 8) | buffer[0][i+bOff];
- 								if (formPix == 0) formPix = 1;
- 								formBits [ ((pcinfo->output_scanline - 1) * (pcinfo->image_width)) + j ] = formPix;
- 							}
- 							break;
- 
- 						case 16:
- 							for(i = 0, j = 0; i < rowStride; i +=(pcinfo->out_color_components*2), j++) {
- 								r1 = buffer[0][i+rOff];
- 								r2 = buffer[0][i+rOff2];
- 								g1 = buffer[0][i+gOff];
- 								g2 = buffer[0][i+gOff2];
- 								b1 = buffer[0][i+bOff];
- 								b2 = buffer[0][i+bOff2];
- 
- 								if (!!ditherFlag) {
- 									r1 = r1 >> 3;
- 									r2 = r2 >> 3;
- 									g1 = g1 >> 3;
- 									g2 = g2 >> 3;
- 									b1 = b1 >> 3;
- 									b2 = b2 >> 3;
- 								} else {
- 									/* Do 4x4 ordered dithering. Taken from Form>>orderedDither32To16 */
- 									dmv1 = ditherMatrix1[ ((pcinfo->output_scanline & 3 )<< 1) | (j&1) ];
- 									dmv2 = ditherMatrix2[ ((pcinfo->output_scanline & 3 )<< 1) | (j&1) ];
- 
- 									di = (r1 * 496) >> 8; dmi = di & 15; dmo = di >> 4;
- 									if(dmv1 < dmi) { r1 = dmo+1; } else { r1 = dmo; };
- 									di = (g1 * 496) >> 8; dmi = di & 15; dmo = di >> 4;
- 									if(dmv1 < dmi) { g1 = dmo+1; } else { g1 = dmo; };
- 									di = (b1 * 496) >> 8; dmi = di & 15; dmo = di >> 4;
- 									if(dmv1 < dmi) { b1 = dmo+1; } else { b1 = dmo; };
- 
- 									di = (r2 * 496) >> 8; dmi = di & 15; dmo = di >> 4;
- 									if(dmv2 < dmi) { r2 = dmo+1; } else { r2 = dmo; };
- 									di = (g2 * 496) >> 8; dmi = di & 15; dmo = di >> 4;
- 									if(dmv2 < dmi) { g2 = dmo+1; } else { g2 = dmo; };
- 									di = (b2 * 496) >> 8; dmi = di & 15; dmo = di >> 4;
- 									if(dmv2 < dmi) { b2 = dmo+1; } else { b2 = dmo; };
- 								}
- 
- 								formPix = (r1 << 10) | (g1 << 5) | b1;
- 								if (!!formPix) formPix = 1;
- 								formPix = (formPix << 16) | (r2 << 10) | (g2 << 5) | b2;
- 								if (!!(formPix & 65535)) formPix = formPix | 1;
- 								formBits [ ((pcinfo->output_scanline - 1) * (pcinfo->image_width)) / 2 + j ] = formPix;
- 							}
- 							break;
- 					}
- 				}
- 				jpeg_finish_decompress(pcinfo);
- 			}
- 			jpeg_destroy_decompress(pcinfo);
- 		}
- 	' inSmalltalk: [].!

Item was changed:
  ----- Method: JPEGReadWriter2Plugin>>primJPEGWriteImage:onByteArray:form:quality:progressiveJPEG:errorMgr: (in category 'primitives') -----
  primJPEGWriteImage: aJPEGCompressStruct onByteArray: destination form: form quality: quality progressiveJPEG: progressiveFlag errorMgr: aJPEGErrorMgr2Struct
  
+ 	| formBitmap formWidth formHeight formNativeDepth formDepth destinationSize pixelsPerWord wordsPerRow formPitch formBitmapSizeInBytes formBitmapOOP formComponentBitSize formComponents |
- 	| pcinfo pjerr buffer rowStride formBits formWidth formHeight formDepth i j formPix destinationSize pixPerWord formPitch formBitsSize formBitsOops |
  	<export: true>
+ 	<var: #formBitmap type: 'unsigned int *'> 
- 	<var: #pcinfo type: 'j_compress_ptr '>
- 	<var: #pjerr type: 'error_ptr2 '>
- 	<var: #buffer type: 'JSAMPARRAY '>
- 	<var: #formBits type: 'unsigned * '>
  	<var: #destinationSize type: 'unsigned int'>
  
  	self
  		primitive: 'primJPEGWriteImageonByteArrayformqualityprogressiveJPEGerrorMgr'
  		parameters: #(ByteArray ByteArray Form SmallInteger Boolean ByteArray).
  
+ 	formBitmapOOP := interpreterProxy fetchPointer: 0 ofObject: form.
- 	pcinfo := nil. pjerr := nil. buffer :=nil. rowStride := nil. formBits := nil. 
- 	formWidth := nil. formHeight := nil. formDepth := nil. i := nil. j := nil. formPix := nil. destinationSize := nil.
- 	pcinfo. pjerr. buffer. rowStride. formBits. formWidth. formHeight. formDepth. i. j. formPix. destinationSize.
- 
- 	formBitsOops := interpreterProxy fetchPointer: 0 ofObject: form.
  	formWidth := interpreterProxy fetchInteger: 1 ofObject: form.
  	formHeight := interpreterProxy fetchInteger: 2 ofObject: form.
+ 	formNativeDepth := interpreterProxy fetchInteger: 3 ofObject: form.
+ 	formDepth := formNativeDepth abs.
- 	formDepth := interpreterProxy fetchInteger: 3 ofObject: form.
  
  	"Various parameter checks"
+ 	interpreterProxy success:
+ 		(self cCode: 'interpreterProxy->stSizeOf(interpreterProxy->stackValue(5)) >= (sizeof(struct jpeg_compress_struct))' inSmalltalk: []).
- 	self cCode: '
- 		interpreterProxy->success
- 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(5))) >= (sizeof(struct jpeg_compress_struct)));
- 		interpreterProxy->success
- 			((interpreterProxy->stSizeOf(interpreterProxy->stackValue(0))) >= (sizeof(struct error_mgr2))); 
- 		if (interpreterProxy->failed()) return null;
- 	' inSmalltalk: [].
- 	pixPerWord := 32 // formDepth.
- 	formPitch := formWidth + (pixPerWord-1) // pixPerWord * 4.
- 	formBitsSize := interpreterProxy byteSizeOf: formBitsOops.
  	interpreterProxy success: 
+ 		(self cCode: 'interpreterProxy->stSizeOf(interpreterProxy->stackValue(0)) >= (sizeof(struct error_mgr2))' inSmalltalk: []).
+ 	interpreterProxy failed ifTrue: [ ^ nil ].
+ 	
+ 	formComponents := formDepth ~= 8 ifTrue: [4] ifFalse: [1].
+ 	formComponentBitSize := formDepth ~= 16 ifTrue: [8] ifFalse: [4].
+ 	pixelsPerWord := 32 // (formComponents * formComponentBitSize).
+ 	wordsPerRow := (formWidth + pixelsPerWord - 1) // pixelsPerWord.
+ 	formPitch := wordsPerRow * 4.
+ 	formBitmapSizeInBytes := interpreterProxy byteSizeOf: formBitmapOOP.
+ 	interpreterProxy success: 
+ 		((interpreterProxy isWordsOrBytes: formBitmapOOP) and: 
+ 		[formBitmapSizeInBytes >= (formPitch * formHeight)]).
+ 	interpreterProxy failed ifTrue: [ ^ nil ].
+ 	
+ 	formBitmap := interpreterProxy firstIndexableField: formBitmapOOP.
+ 	destinationSize := interpreterProxy stSizeOf: (interpreterProxy stackValue: 4).
+ 	(destinationSize = 0) 
+ 		ifFalse: [ self 
+ 			cCode: ' primJPEGWriteImageonByteArrayformqualityprogressiveJPEGerrorMgrWriteScanlines(
+ 				formWidth, 
+ 				formHeight, 
+ 				formNativeDepth, 
+ 				formBitmap, 
+ 				aJPEGCompressStruct,
+ 				aJPEGErrorMgr2Struct,
+ 				quality,
+ 				progressiveFlag,
+ 				pixelsPerWord, 
+ 				wordsPerRow, 
+ 				destination,
+ 				&destinationSize);'
+ 			inSmalltalk: []].
+ 	
- 		((interpreterProxy isWordsOrBytes: formBitsOops)
- 			and: [formBitsSize = (formPitch * formHeight)]).
- 	interpreterProxy failed ifTrue: [^ nil].
- 	formBits := interpreterProxy firstIndexableField: formBitsOops.
- 	self cCode: '
- 		destinationSize = interpreterProxy->stSizeOf(interpreterProxy->stackValue(4));
- 		pcinfo = (j_compress_ptr)aJPEGCompressStruct;
- 		pjerr = (error_ptr2)aJPEGErrorMgr2Struct;
- 		if (destinationSize) {
- 			pcinfo->err = jpeg_std_error(&pjerr->pub);
- 			pjerr->pub.error_exit = error_exit;
- 			if (setjmp(pjerr->setjmp_buffer)) {
- 				jpeg_destroy_compress(pcinfo);
- 				destinationSize = 0;
- 			}
- 			if (destinationSize) {
- 				jpeg_create_compress(pcinfo);
- 				jpeg_mem_dest(pcinfo, destination, &destinationSize);
- 				pcinfo->image_width = formWidth;
- 				pcinfo->image_height = formHeight;
- 				pcinfo->input_components = 3;
- 				pcinfo->in_color_space = JCS_RGB;
- 				jpeg_set_defaults(pcinfo);
- 				if (quality > 0)
- 					jpeg_set_quality (pcinfo, quality, 1);
- 				if (progressiveFlag)
- 					jpeg_simple_progression(pcinfo);
- 				jpeg_start_compress(pcinfo, TRUE);
- 				rowStride = formWidth * 3;
- 
- 				/* Make a one-row-high sample array that will go away 
- 				  when done with image */
- 				buffer = (*(pcinfo->mem)->alloc_sarray)
- 					((j_common_ptr) pcinfo, JPOOL_IMAGE, rowStride, 1);
- 
- 				while (pcinfo->next_scanline < pcinfo->image_height) {
- 					switch (formDepth) {
- 						case 32:
- 							for(i = 0, j = 0; i < rowStride; i +=3, j++) {
- 								formPix = formBits [ ((pcinfo->next_scanline) * formWidth) + j ];
- 								buffer[0][i] = (formPix >> 16) & 255;
- 								buffer[0][i+1] = (formPix >> 8) & 255;
- 								buffer[0][i+2] = formPix & 255;
- 							}
- 							break;
- 						case 16:
- 							for(i = 0, j = 0; i < rowStride; i +=6, j++) {
- 								formPix = formBits [ ((pcinfo->next_scanline) * formWidth) / 2 + j ];
- 								buffer[0][i] = (formPix >> 23) & 248;
- 								buffer[0][i+1] = (formPix >> 18) & 248;
- 								buffer[0][i+2] = (formPix >> 13) & 248;
- 								buffer[0][i+3] = (formPix >> 7) & 248;
- 								buffer[0][i+4] = (formPix >> 2) & 248;
- 								buffer[0][i+5] = (formPix << 3) & 248;
- 							}
- 							break;
- 					}
- 					(void) jpeg_write_scanlines(pcinfo, buffer, 1);
- 
- 				}
- 				jpeg_finish_compress(pcinfo);
- 				jpeg_destroy_compress(pcinfo);
- 			}
- 		}
- 	' inSmalltalk: [].
  	^(self cCode: 'destinationSize' inSmalltalk: [0])
  		asOop: SmallInteger!

Item was added:
+ ----- Method: JPEGReadWriter2Plugin>>primSupports8BitGrayscaleJPEGs (in category 'primitives') -----
+ primSupports8BitGrayscaleJPEGs
+ 	<export: true>
+ 	self
+ 		primitive: 'primSupports8BitGrayscaleJPEGs'
+ 		parameters: #().
+ 	^ true asOop: Boolean!

Item was changed:
  ----- Method: VMMaker class>>versionString (in category 'version testing') -----
  versionString
  
  	"VMMaker versionString"
  
+ 	^'4.15.7'!
- 	^'4.15.6'!



More information about the Vm-dev mailing list