The Trunk: Graphics-lpc.350.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
4 messages Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Graphics-lpc.350.mcz

commits-2
Laura Perez Cerrato uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-lpc.350.mcz

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

Name: Graphics-lpc.350
Author: lpc
Time: 15 June 2016, 2:00:37.274582 pm
UUID: 5d02a1bd-65f6-469c-b8b5-456e1dfef5eb
Ancestors: Graphics-mt.349

Support for both the current version and the new version of JPEGReadWriter2Plugin

=============== Diff against Graphics-mt.349 ===============

Item was changed:
  Form subclass: #ColorForm
  instanceVariableNames: 'colors cachedDepth cachedColormap'
  classVariableNames: ''
  poolDictionaries: ''
  category: 'Graphics-Display Objects'!
+ ColorForm class
+ instanceVariableNames: 'grayScalePalette'!
 
  !ColorForm commentStamp: '<historical>' prior: 0!
  ColorForm is a normal Form plus a color map of up to 2^depth Colors. Typically, one reserves one entry in the color map for transparent. This allows 1, 3, 15, or 255 non-transparent colors in ColorForms of depths 1, 2, 4, and 8 bits per pixel. ColorForms don't support depths greater than 8 bits because that would require excessively large color maps with little real benefit, since 16-bit and 32-bit depths already support thousands and millions of colors.
 
  ColorForms have several uses:
    1) Precise colors. You can have up to 256 true colors, instead being limited to the 8-bit color palette.
    2) Easy transparency. Just store (Color transparent) at the desired position in the color map.
    3) Cheap color remapping by changing the color map.
 
  A color map is an Array of up to 2^depth Color objects. A Bitmap colorMap is automatically computed and cached for rapid display. Note that if you change the color map, you must resubmit it via the colors: method to flush this cache.
 
  ColorForms can be a bit tricky. Note that:
    a) When you BitBlt from one ColorForm to another, you must remember to copy the color map of the source ColorForm to the destination ColorForm.
    b) A ColorForm's color map is an array of depth-independent Color objects. BitBlt requires a BitMap of actual pixel values, adjusted to the destination depth. These are different things!! ColorForms automatically maintain a cache of the BitBlt-style color map corresponding to the colors array for the last depth on which the ColorForm was displayed, so there should be little need for clients to work with BitBlt-style color maps.
    c) The default map for 8 bit depth has black in the first entry, not transparent.  Say (cform colors at: 1 put: Color transparent).
  !
+ ColorForm class
+ instanceVariableNames: 'grayScalePalette'!

Item was added:
+ ----- Method: ColorForm class>>grayScalePalette (in category 'constants') -----
+ grayScalePalette
+ grayScalePalette ifNil: [
+ grayScalePalette := (0 to: 255) collect: [:brightness | Color gray: brightness asFloat / 255.0].
+ grayScalePalette at: 1 put: Color transparent].
+ ^ grayScalePalette!

Item was added:
+ ----- Method: ColorForm>>isGrayScale (in category 'testing') -----
+ isGrayScale
+ ^ self colors = ColorForm grayScalePalette.!

Item was changed:
  ----- Method: Form>>asGrayScale (in category 'converting') -----
  asGrayScale
  "Assume the receiver is a grayscale image. Return a grayscale ColorForm computed by extracting the brightness levels of one color component. This technique allows a 32-bit Form to be converted to an 8-bit ColorForm to save space while retaining a full 255 levels of gray. (The usual colormapping technique quantizes to 8, 16, or 32 levels, which loses information.)"
+ | f32 srcForm result map bb |
- | f32 srcForm result map bb grays |
  self depth = 32 ifFalse: [
  f32 := Form extent: width@height depth: 32.
  self displayOn: f32.
  ^ f32 asGrayScale].
  self unhibernate.
  srcForm := Form extent: (width * 4)@height depth: 8.
  srcForm bits: bits.
  result := ColorForm extent: width@height depth: 8.
  map := Bitmap new: 256.
  2 to: 256 do: [:i | map at: i put: i - 1].
  map at: 1 put: 1.  "map zero pixel values to near-black"
  bb := (BitBlt toForm: result)
  sourceForm: srcForm;
  combinationRule: Form over;
  colorMap: map.
  0 to: width - 1 do: [:dstX |
  bb  sourceRect: (((dstX * 4) + 2)@0 extent: 1@height);
  destOrigin: dstX@0;
  copyBits].
 
  "final BitBlt to zero-out pixels that were truely transparent in the original"
  map := Bitmap new: 512.
  map at: 1 put: 16rFF.
  (BitBlt toForm: result)
  sourceForm: self;
  sourceRect: self boundingBox;
  destOrigin: 0@0;
  combinationRule: Form erase;
  colorMap: map;
  copyBits.
 
+
+ result colors: ColorForm grayScalePalette.
- grays := (0 to: 255) collect: [:brightness | Color gray: brightness asFloat / 255.0].
- grays at: 1 put: Color transparent.
- result colors: grays.
  ^ result
  !

Item was added:
+ ----- Method: Form>>isGrayScale (in category 'testing') -----
+ isGrayScale
+ ^ false!

Item was changed:
  ----- Method: JPEGReadWriter2>>compress:quality: (in category 'public access') -----
  compress: aForm quality: quality
+ "Encode the given Form and answer the compressed ByteArray. Quality goes from 0 (low) to 100 (high), where -1 means default.
+ We can only compress:
+ * 32-bit deep Forms
+ * -32-bit deep Forms
+ * 16-bit deep Forms
+ * -16-bit deep Forms
+ * GrayScale ColorForms (see #isGrayScale)"
- "Encode the given Form and answer the compressed ByteArray. Quality goes from 0 (low) to 100 (high), where -1 means default."
-
  | sourceForm jpegCompressStruct jpegErrorMgr2Struct buffer byteCount |
+
  aForm unhibernate.
+
+ sourceForm := self supports8BitGrayscaleJPEGs
+ ifTrue: [
+ (aForm depth = 32) | (aForm depth = 16) | (aForm isGrayScale)
+ ifTrue: [aForm]
+ ifFalse: [aForm asFormOfDepth: 32 ]]
+ ifFalse: [
+ (aForm nativeDepth > 0) & ((aForm depth = 32) | ((aForm depth = 16) & (aForm width even)))
+ ifTrue: [aForm]
+ ifFalse: [aForm asFormOfDepth: 32 ]].
+
- "odd width images of depth 16 give problems; avoid them."
- sourceForm := (aForm depth = 32) | (aForm width even & (aForm depth = 16))
- ifTrue: [aForm]
- ifFalse: [aForm asFormOfDepth: 32].
  jpegCompressStruct := ByteArray new: self primJPEGCompressStructSize.
  jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
  buffer := ByteArray new: sourceForm width * sourceForm height + 1024.
  byteCount := self primJPEGWriteImage: jpegCompressStruct
  onByteArray: buffer
  form: sourceForm
  quality: quality
  progressiveJPEG: false
  errorMgr: jpegErrorMgr2Struct.
  byteCount = 0 ifTrue: [self error: 'buffer too small for compressed data'].
  ^ buffer copyFrom: 1 to: byteCount
  !

Item was changed:
  ----- Method: JPEGReadWriter2>>nextImageSuggestedDepth: (in category 'public access') -----
+ nextImageSuggestedDepth: suggestedDepth
+ "Decode and answer a Form of the given depth from my stream. Close the stream if it is a file stream.
+ We can read RGB JPEGs into:
+ * 32-bit Forms
+ * -32-bit Forms
+ * 16-bit Forms (with or without dithering!!)
+ * -16-bit Forms (with or without dithering!!)
+ We can read grayscale JPEGs into:
+ * 32-bit Forms
+ * -32-bit Forms
+ * 16-bit Forms (with or without dithering!!)
+ * -16-bit Forms (with or without dithering!!)
+ * 8-bit grayScale ColorForms (see #isGrayScale)
+ * -8-bit grayScale ColorForms (see #isGrayScale)"
- nextImageSuggestedDepth: depth
- "Decode and answer a Form of the given depth from my stream. Close the stream if it is a file stream. Possible depths are 16-bit and 32-bit."
 
+ | bytes width height components form jpegDecompressStruct jpegErrorMgr2Struct |
- | bytes width height form jpegDecompressStruct jpegErrorMgr2Struct depthToUse |
  bytes := stream upToEnd.
  stream close.
  jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
  jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
  self
  primJPEGReadHeader: jpegDecompressStruct
  fromByteArray: bytes
  errorMgr: jpegErrorMgr2Struct.
  width := self primImageWidth: jpegDecompressStruct.
  height := self primImageHeight: jpegDecompressStruct.
+ components := self primImageNumComponents: jpegDecompressStruct.
+ form :=
+ self supports8BitGrayscaleJPEGs
+ ifTrue: [
+ components = 3
+ ifTrue: [ Form extent: width@height depth: suggestedDepth ]
+ ifFalse: [ (Form extent: width@height depth: suggestedDepth) asGrayScale ]]
+ ifFalse: [
+ Form
+ extent: width@height
+ depth:
+ (suggestedDepth = 32
+ ifTrue: [ 32 ]
+ ifFalse: [
+ ((suggestedDepth = 16) & (width even))
+ ifTrue: [ 16 ]
+ ifFalse: [ 32 ]])].
+
- "Odd width images of depth 16 gave problems. Avoid them (or check carefully!!)"
- depthToUse := ((depth = 32) | width odd) ifTrue: [32] ifFalse: [16].
- form := Form extent: width@height depth: depthToUse.
- (width = 0 or: [height = 0]) ifTrue: [^ form].
  self
  primJPEGReadImage: jpegDecompressStruct
  fromByteArray: bytes
  onForm: form
  doDithering: true
  errorMgr: jpegErrorMgr2Struct.
+ ^ form!
- ^ form
- !

Item was changed:
  ----- Method: JPEGReadWriter2>>nextPutImage:quality:progressiveJPEG: (in category 'public access') -----
  nextPutImage: aForm quality: quality progressiveJPEG: progressiveFlag
+ "Encode the given Form on my stream with the given settings. Quality goes from 0 (low) to 100 (high), where -1 means default. If progressiveFlag is true, encode as a progressive JPEG.
+ We can compress:
+ * 32-bit deep Forms
+ * -32-bit deep Forms
+ * 16-bit deep
+ * -16-bit deep
+ * GrayScale ColorForms (see #isGrayScale)"
- "Encode the given Form on my stream with the given settings. Quality goes from 0 (low) to 100 (high), where -1 means default. If progressiveFlag is true, encode as a progressive JPEG."
 
  | sourceForm jpegCompressStruct jpegErrorMgr2Struct buffer byteCount |
+
  aForm unhibernate.
+
+ sourceForm := self supports8BitGrayscaleJPEGs
+ ifTrue: [
+ (aForm depth = 32) | (aForm depth = 16) | (aForm isGrayScale)
+ ifTrue: [aForm]
+ ifFalse: [aForm asFormOfDepth: 32 ]]
+ ifFalse: [
+ (aForm nativeDepth > 0) & ((aForm depth = 32) | ((aForm depth = 16) & (aForm width even)))
+ ifTrue: [aForm]
+ ifFalse: [aForm asFormOfDepth: 32 ]].
+
- "odd width images of depth 16 give problems; avoid them."
- sourceForm := (aForm depth = 32) | (aForm width even & (aForm depth = 16))
- ifTrue: [aForm]
- ifFalse: [aForm asFormOfDepth: 32].
  jpegCompressStruct := ByteArray new: self primJPEGCompressStructSize.
  jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
  buffer := ByteArray new: sourceForm width * sourceForm height + 1024.
  "Try to write the image. Retry with a larger buffer if needed."
  [
  byteCount := self primJPEGWriteImage: jpegCompressStruct
  onByteArray: buffer
  form: sourceForm
  quality: quality
  progressiveJPEG: progressiveFlag
  errorMgr: jpegErrorMgr2Struct.
  byteCount = 0 and: [ buffer size < (sourceForm width * sourceForm height * 3 + 1024) ] ]
  whileTrue: [ buffer := ByteArray new: buffer size * 2 ].
  byteCount = 0 ifTrue: [ self error: 'buffer too small for compressed data' ].
  stream next: byteCount putAll: buffer startingAt: 1.
  self close.
  !

Item was added:
+ ----- Method: JPEGReadWriter2>>primImageNumComponents: (in category 'primitives') -----
+ primImageNumComponents: aJPEGDecompressStruct
+
+ <primitive: 'primImageNumComponents' module: 'JPEGReadWriter2Plugin'>
+ ^ 3!

Item was added:
+ ----- Method: JPEGReadWriter2>>primSupports8BitGrayscaleJPEGs (in category 'primitives') -----
+ primSupports8BitGrayscaleJPEGs
+ <primitive: 'primSupports8BitGrayscaleJPEGs' module: 'JPEGReadWriter2Plugin'>
+ ^ false!

Item was added:
+ ----- Method: JPEGReadWriter2>>supports8BitGrayscaleJPEGs (in category 'testing') -----
+ supports8BitGrayscaleJPEGs
+ ^ self primSupports8BitGrayscaleJPEGs!

Item was changed:
  ----- Method: JPEGReadWriter2>>uncompress:into: (in category 'public access') -----
  uncompress: aByteArray into: aForm
+ ^ self uncompress: aByteArray into: aForm doDithering: true
- "Uncompress an image from the given ByteArray into the given Form.
- Fails if the given Form has the wrong dimensions or depth.
- If aForm has depth 16, do ordered dithering."
-
- | jpegDecompressStruct jpegErrorMgr2Struct w h |
- aForm unhibernate.
- jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
- jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
- self
- primJPEGReadHeader: jpegDecompressStruct
- fromByteArray: aByteArray
- errorMgr: jpegErrorMgr2Struct.
- w := self primImageWidth: jpegDecompressStruct.
- h := self primImageHeight: jpegDecompressStruct.
- ((aForm width = w) & (aForm height = h)) ifFalse: [
- ^ self error: 'form dimensions do not match'].
-
- "odd width images of depth 16 give problems; avoid them"
- w odd
- ifTrue: [
- aForm depth = 32 ifFalse: [^ self error: 'must use depth 32 with odd width']]
- ifFalse: [
- ((aForm depth = 16) | (aForm depth = 32)) ifFalse: [^ self error: 'must use depth 16 or 32']].
-
- self primJPEGReadImage: jpegDecompressStruct
- fromByteArray: aByteArray
- onForm: aForm
- doDithering: true
- errorMgr: jpegErrorMgr2Struct.
  !

Item was changed:
  ----- Method: JPEGReadWriter2>>uncompress:into:doDithering: (in category 'public access') -----
  uncompress: aByteArray into: aForm doDithering: ditherFlag
  "Uncompress an image from the given ByteArray into the given Form.
  Fails if the given Form has the wrong dimensions or depth.
+ We can read RGB JPEGs into:
+ * 32-bit Forms
+ * -32-bit Forms
+ * 16-bit Forms (with or without dithering!!)
+ * -16-bit Forms (with or without dithering!!)
+ We can read grayscale JPEGs into:
+ * 32-bit Forms
+ * -32-bit Forms
+ * 16-bit Forms (with or without dithering!!)
+ * -16-bit Forms (with or without dithering!!)
+ * 8-bit grayScale ColorForms (see #isGrayScale)
+ * -8-bit grayScale ColorForms (see #isGrayScale)"
- If aForm has depth 16 and ditherFlag = true, do ordered dithering."
 
+ | jpegDecompressStruct jpegErrorMgr2Struct width height components |
+
- | jpegDecompressStruct jpegErrorMgr2Struct w h |
  aForm unhibernate.
+
  jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
  jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
  self
  primJPEGReadHeader: jpegDecompressStruct
  fromByteArray: aByteArray
  errorMgr: jpegErrorMgr2Struct.
+ width := self primImageWidth: jpegDecompressStruct.
+ height := self primImageHeight: jpegDecompressStruct.
+ components := self primImageNumComponents: jpegDecompressStruct.
+
+ ((aForm width = width) & (aForm height = height)) ifFalse: [
+ ^ self error: 'form dimensions do not match' ].
+ self supports8BitGrayscaleJPEGs
- w := self primImageWidth: jpegDecompressStruct.
- h := self primImageHeight: jpegDecompressStruct.
- ((aForm width = w) & (aForm height = h)) ifFalse: [
- ^ self error: 'form dimensions do not match'].
-
- "odd width images of depth 16 give problems; avoid them"
- w odd
  ifTrue: [
+ components = 3
+ ifTrue: [
+ aForm depth = 8
+ ifTrue: [ ^ self error: 'Cannot uncompress multi-channel JPEGs into 8-bit deep forms' ]].
+ components = 1
+ ifTrue: [
+ aForm depth = 8
+ ifTrue: [
+ aForm isGrayScale
+ ifFalse: [ ^ self error: 'Cannot uncompress single-channel JPEGs into 8-bit deep forms that are not grayscale' ]]]]
+
- aForm depth = 32 ifFalse: [^ self error: 'must use depth 32 with odd width']]
  ifFalse: [
+ aForm nativeDepth < 0
+ ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs into little-endian forms' ]
+ ifFalse: [
+ aForm depth = 16
+ ifTrue: [
+ width odd
+ ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs with an odd width into 16-bit deep forms' ]].
+ aForm depth = 8
+ ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs into 8-bit deep forms' ]]].
- ((aForm depth = 16) | (aForm depth = 32)) ifFalse: [^ self error: 'must use depth 16 or 32']].
 
  self primJPEGReadImage: jpegDecompressStruct
  fromByteArray: aByteArray
  onForm: aForm
  doDithering: ditherFlag
  errorMgr: jpegErrorMgr2Struct.
  !


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-lpc.350.mcz

Eliot Miranda-2
Laura,

    great to see this.  Thank you for your energy!! and welcome.

On Wed, Jun 15, 2016 at 10:01 AM, <[hidden email]> wrote:
Laura Perez Cerrato uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-lpc.350.mcz

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

Name: Graphics-lpc.350
Author: lpc
Time: 15 June 2016, 2:00:37.274582 pm
UUID: 5d02a1bd-65f6-469c-b8b5-456e1dfef5eb
Ancestors: Graphics-mt.349

Support for both the current version and the new version of JPEGReadWriter2Plugin

=============== Diff against Graphics-mt.349 ===============

Item was changed:
  Form subclass: #ColorForm
        instanceVariableNames: 'colors cachedDepth cachedColormap'
        classVariableNames: ''
        poolDictionaries: ''
        category: 'Graphics-Display Objects'!
+ ColorForm class
+       instanceVariableNames: 'grayScalePalette'!

  !ColorForm commentStamp: '<historical>' prior: 0!
  ColorForm is a normal Form plus a color map of up to 2^depth Colors. Typically, one reserves one entry in the color map for transparent. This allows 1, 3, 15, or 255 non-transparent colors in ColorForms of depths 1, 2, 4, and 8 bits per pixel. ColorForms don't support depths greater than 8 bits because that would require excessively large color maps with little real benefit, since 16-bit and 32-bit depths already support thousands and millions of colors.

  ColorForms have several uses:
    1) Precise colors. You can have up to 256 true colors, instead being limited to the 8-bit color palette.
    2) Easy transparency. Just store (Color transparent) at the desired position in the color map.
    3) Cheap color remapping by changing the color map.

  A color map is an Array of up to 2^depth Color objects. A Bitmap colorMap is automatically computed and cached for rapid display. Note that if you change the color map, you must resubmit it via the colors: method to flush this cache.

  ColorForms can be a bit tricky. Note that:
    a) When you BitBlt from one ColorForm to another, you must remember to copy the color map of the source ColorForm to the destination ColorForm.
    b) A ColorForm's color map is an array of depth-independent Color objects. BitBlt requires a BitMap of actual pixel values, adjusted to the destination depth. These are different things!! ColorForms automatically maintain a cache of the BitBlt-style color map corresponding to the colors array for the last depth on which the ColorForm was displayed, so there should be little need for clients to work with BitBlt-style color maps.
    c) The default map for 8 bit depth has black in the first entry, not transparent.  Say (cform colors at: 1 put: Color transparent).
  !
+ ColorForm class
+       instanceVariableNames: 'grayScalePalette'!

Item was added:
+ ----- Method: ColorForm class>>grayScalePalette (in category 'constants') -----
+ grayScalePalette
+       grayScalePalette ifNil: [
+               grayScalePalette := (0 to: 255) collect: [:brightness | Color gray: brightness asFloat / 255.0].
+               grayScalePalette at: 1 put: Color transparent].
+       ^ grayScalePalette!

Item was added:
+ ----- Method: ColorForm>>isGrayScale (in category 'testing') -----
+ isGrayScale
+       ^ self colors = ColorForm grayScalePalette.!

Item was changed:
  ----- Method: Form>>asGrayScale (in category 'converting') -----
  asGrayScale
        "Assume the receiver is a grayscale image. Return a grayscale ColorForm computed by extracting the brightness levels of one color component. This technique allows a 32-bit Form to be converted to an 8-bit ColorForm to save space while retaining a full 255 levels of gray. (The usual colormapping technique quantizes to 8, 16, or 32 levels, which loses information.)"
+       | f32 srcForm result map bb |
-       | f32 srcForm result map bb grays |
        self depth = 32 ifFalse: [
                f32 := Form extent: width@height depth: 32.
                self displayOn: f32.
                ^ f32 asGrayScale].
        self unhibernate.
        srcForm := Form extent: (width * 4)@height depth: 8.
        srcForm bits: bits.
        result := ColorForm extent: width@height depth: 8.
        map := Bitmap new: 256.
        2 to: 256 do: [:i | map at: i put: i - 1].
        map at: 1 put: 1.  "map zero pixel values to near-black"
        bb := (BitBlt toForm: result)
                sourceForm: srcForm;
                combinationRule: Form over;
                colorMap: map.
        0 to: width - 1 do: [:dstX |
                bb  sourceRect: (((dstX * 4) + 2)@0 extent: 1@height);
                        destOrigin: dstX@0;
                        copyBits].

        "final BitBlt to zero-out pixels that were truely transparent in the original"
        map := Bitmap new: 512.
        map at: 1 put: 16rFF.
        (BitBlt toForm: result)
                sourceForm: self;
                sourceRect: self boundingBox;
                destOrigin: 0@0;
                combinationRule: Form erase;
                colorMap: map;
                copyBits.

+
+       result colors: ColorForm grayScalePalette.
-       grays := (0 to: 255) collect: [:brightness | Color gray: brightness asFloat / 255.0].
-       grays at: 1 put: Color transparent.
-       result colors: grays.
        ^ result
  !

Item was added:
+ ----- Method: Form>>isGrayScale (in category 'testing') -----
+ isGrayScale
+       ^ false!

Item was changed:
  ----- Method: JPEGReadWriter2>>compress:quality: (in category 'public access') -----
  compress: aForm quality: quality
+       "Encode the given Form and answer the compressed ByteArray. Quality goes from 0 (low) to 100 (high), where -1 means default.
+       We can only compress:
+               * 32-bit deep Forms
+               * -32-bit deep Forms
+               * 16-bit deep Forms
+               * -16-bit deep Forms
+               * GrayScale ColorForms (see #isGrayScale)"
-       "Encode the given Form and answer the compressed ByteArray. Quality goes from 0 (low) to 100 (high), where -1 means default."
-
        | sourceForm jpegCompressStruct jpegErrorMgr2Struct buffer byteCount |
+
        aForm unhibernate.
+
+       sourceForm := self supports8BitGrayscaleJPEGs
+               ifTrue: [
+                       (aForm depth = 32) | (aForm depth = 16) | (aForm isGrayScale)
+                               ifTrue: [aForm]
+                               ifFalse: [aForm asFormOfDepth: 32 ]]
+               ifFalse: [
+                       (aForm nativeDepth > 0) & ((aForm depth = 32) | ((aForm depth = 16) & (aForm width even)))
+                               ifTrue: [aForm]
+                               ifFalse: [aForm asFormOfDepth: 32 ]].
+
-       "odd width images of depth 16 give problems; avoid them."
-       sourceForm := (aForm depth = 32) | (aForm width even & (aForm depth = 16))
-               ifTrue: [aForm]
-               ifFalse: [aForm asFormOfDepth: 32].
        jpegCompressStruct := ByteArray new: self primJPEGCompressStructSize.
        jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
        buffer := ByteArray new: sourceForm width * sourceForm height + 1024.
        byteCount := self primJPEGWriteImage: jpegCompressStruct
                onByteArray: buffer
                form: sourceForm
                quality: quality
                progressiveJPEG: false
                errorMgr: jpegErrorMgr2Struct.
        byteCount = 0 ifTrue: [self error: 'buffer too small for compressed data'].
        ^ buffer copyFrom: 1 to: byteCount
  !

Item was changed:
  ----- Method: JPEGReadWriter2>>nextImageSuggestedDepth: (in category 'public access') -----
+ nextImageSuggestedDepth: suggestedDepth
+       "Decode and answer a Form of the given depth from my stream. Close the stream if it is a file stream.
+       We can read RGB JPEGs into:
+               * 32-bit Forms
+               * -32-bit Forms
+               * 16-bit Forms (with or without dithering!!)
+               * -16-bit Forms (with or without dithering!!)
+       We can read grayscale JPEGs into:
+               * 32-bit Forms
+               * -32-bit Forms
+               * 16-bit Forms (with or without dithering!!)
+               * -16-bit Forms (with or without dithering!!)
+               * 8-bit grayScale ColorForms (see #isGrayScale)
+               * -8-bit grayScale ColorForms (see #isGrayScale)"
- nextImageSuggestedDepth: depth
-       "Decode and answer a Form of the given depth from my stream. Close the stream if it is a file stream. Possible depths are 16-bit and 32-bit."

+       | bytes width height components form jpegDecompressStruct jpegErrorMgr2Struct |
-       | bytes width height form jpegDecompressStruct jpegErrorMgr2Struct depthToUse |
        bytes := stream upToEnd.
        stream close.
        jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
        jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
        self
                primJPEGReadHeader: jpegDecompressStruct
                fromByteArray: bytes
                errorMgr: jpegErrorMgr2Struct.
        width := self primImageWidth: jpegDecompressStruct.
        height := self primImageHeight: jpegDecompressStruct.
+       components := self primImageNumComponents: jpegDecompressStruct.
+       form :=
+               self supports8BitGrayscaleJPEGs
+                       ifTrue: [
+                               components = 3
+                                       ifTrue: [ Form extent: width@height depth: suggestedDepth ]
+                                       ifFalse: [ (Form extent: width@height depth: suggestedDepth) asGrayScale ]]
+                       ifFalse: [
+                               Form
+                                       extent: width@height
+                                       depth:
+                                               (suggestedDepth = 32
+                                                       ifTrue: [ 32 ]
+                                                       ifFalse: [
+                                                               ((suggestedDepth = 16) & (width even))
+                                                                       ifTrue: [ 16 ]
+                                                                       ifFalse: [ 32 ]])].
+
-       "Odd width images of depth 16 gave problems. Avoid them (or check carefully!!)"
-       depthToUse := ((depth = 32) | width odd) ifTrue: [32] ifFalse: [16].
-       form := Form extent: width@height depth: depthToUse.
-       (width = 0 or: [height = 0]) ifTrue: [^ form].
        self
                primJPEGReadImage: jpegDecompressStruct
                fromByteArray: bytes
                onForm: form
                doDithering: true
                errorMgr: jpegErrorMgr2Struct.
+       ^ form!
-       ^ form
- !

Item was changed:
  ----- Method: JPEGReadWriter2>>nextPutImage:quality:progressiveJPEG: (in category 'public access') -----
  nextPutImage: aForm quality: quality progressiveJPEG: progressiveFlag
+       "Encode the given Form on my stream with the given settings. Quality goes from 0 (low) to 100 (high), where -1 means default. If progressiveFlag is true, encode as a progressive JPEG.
+       We can compress:
+               * 32-bit deep Forms
+               * -32-bit deep Forms
+               * 16-bit deep
+               * -16-bit deep
+               * GrayScale ColorForms (see #isGrayScale)"
-       "Encode the given Form on my stream with the given settings. Quality goes from 0 (low) to 100 (high), where -1 means default. If progressiveFlag is true, encode as a progressive JPEG."

        | sourceForm jpegCompressStruct jpegErrorMgr2Struct buffer byteCount |
+
        aForm unhibernate.
+
+       sourceForm := self supports8BitGrayscaleJPEGs
+               ifTrue: [
+                       (aForm depth = 32) | (aForm depth = 16) | (aForm isGrayScale)
+                               ifTrue: [aForm]
+                               ifFalse: [aForm asFormOfDepth: 32 ]]
+               ifFalse: [
+                       (aForm nativeDepth > 0) & ((aForm depth = 32) | ((aForm depth = 16) & (aForm width even)))
+                               ifTrue: [aForm]
+                               ifFalse: [aForm asFormOfDepth: 32 ]].
+
-       "odd width images of depth 16 give problems; avoid them."
-       sourceForm := (aForm depth = 32) | (aForm width even & (aForm depth = 16))
-               ifTrue: [aForm]
-               ifFalse: [aForm asFormOfDepth: 32].
        jpegCompressStruct := ByteArray new: self primJPEGCompressStructSize.
        jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
        buffer := ByteArray new: sourceForm width * sourceForm height + 1024.
        "Try to write the image. Retry with a larger buffer if needed."
        [
                byteCount := self primJPEGWriteImage: jpegCompressStruct
                        onByteArray: buffer
                        form: sourceForm
                        quality: quality
                        progressiveJPEG: progressiveFlag
                        errorMgr: jpegErrorMgr2Struct.
                byteCount = 0 and: [ buffer size < (sourceForm width * sourceForm height * 3 + 1024) ] ]
                        whileTrue: [ buffer := ByteArray new: buffer size * 2 ].
        byteCount = 0 ifTrue: [ self error: 'buffer too small for compressed data' ].
        stream next: byteCount putAll: buffer startingAt: 1.
        self close.
  !

Item was added:
+ ----- Method: JPEGReadWriter2>>primImageNumComponents: (in category 'primitives') -----
+ primImageNumComponents: aJPEGDecompressStruct
+
+       <primitive: 'primImageNumComponents' module: 'JPEGReadWriter2Plugin'>
+       ^ 3!

Item was added:
+ ----- Method: JPEGReadWriter2>>primSupports8BitGrayscaleJPEGs (in category 'primitives') -----
+ primSupports8BitGrayscaleJPEGs
+       <primitive: 'primSupports8BitGrayscaleJPEGs' module: 'JPEGReadWriter2Plugin'>
+       ^ false!

Item was added:
+ ----- Method: JPEGReadWriter2>>supports8BitGrayscaleJPEGs (in category 'testing') -----
+ supports8BitGrayscaleJPEGs
+       ^ self primSupports8BitGrayscaleJPEGs!

Item was changed:
  ----- Method: JPEGReadWriter2>>uncompress:into: (in category 'public access') -----
  uncompress: aByteArray into: aForm
+       ^ self uncompress: aByteArray into: aForm doDithering: true
-       "Uncompress an image from the given ByteArray into the given Form.
-       Fails if the given Form has the wrong dimensions or depth.
-       If aForm has depth 16, do ordered dithering."
-
-       | jpegDecompressStruct jpegErrorMgr2Struct w h |
-       aForm unhibernate.
-       jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
-       jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
-       self
-               primJPEGReadHeader: jpegDecompressStruct
-               fromByteArray: aByteArray
-               errorMgr: jpegErrorMgr2Struct.
-       w := self primImageWidth: jpegDecompressStruct.
-       h := self primImageHeight: jpegDecompressStruct.
-       ((aForm width = w) & (aForm height = h)) ifFalse: [
-               ^ self error: 'form dimensions do not match'].
-
-       "odd width images of depth 16 give problems; avoid them"
-       w odd
-               ifTrue: [
-                       aForm depth = 32 ifFalse: [^ self error: 'must use depth 32 with odd width']]
-               ifFalse: [
-                       ((aForm depth = 16) | (aForm depth = 32)) ifFalse: [^ self error: 'must use depth 16 or 32']].
-
-       self primJPEGReadImage: jpegDecompressStruct
-               fromByteArray: aByteArray
-               onForm: aForm
-               doDithering: true
-               errorMgr: jpegErrorMgr2Struct.
  !

Item was changed:
  ----- Method: JPEGReadWriter2>>uncompress:into:doDithering: (in category 'public access') -----
  uncompress: aByteArray into: aForm doDithering: ditherFlag
        "Uncompress an image from the given ByteArray into the given Form.
        Fails if the given Form has the wrong dimensions or depth.
+       We can read RGB JPEGs into:
+               * 32-bit Forms
+               * -32-bit Forms
+               * 16-bit Forms (with or without dithering!!)
+               * -16-bit Forms (with or without dithering!!)
+       We can read grayscale JPEGs into:
+               * 32-bit Forms
+               * -32-bit Forms
+               * 16-bit Forms (with or without dithering!!)
+               * -16-bit Forms (with or without dithering!!)
+               * 8-bit grayScale ColorForms (see #isGrayScale)
+               * -8-bit grayScale ColorForms (see #isGrayScale)"
-       If aForm has depth 16 and ditherFlag = true, do ordered dithering."

+       | jpegDecompressStruct jpegErrorMgr2Struct width height components |
+
-       | jpegDecompressStruct jpegErrorMgr2Struct w h |
        aForm unhibernate.
+
        jpegDecompressStruct := ByteArray new: self primJPEGDecompressStructSize.
        jpegErrorMgr2Struct := ByteArray new: self primJPEGErrorMgr2StructSize.
        self
                primJPEGReadHeader: jpegDecompressStruct
                fromByteArray: aByteArray
                errorMgr: jpegErrorMgr2Struct.
+       width := self primImageWidth: jpegDecompressStruct.
+       height := self primImageHeight: jpegDecompressStruct.
+       components := self primImageNumComponents: jpegDecompressStruct.
+
+       ((aForm width = width) & (aForm height = height)) ifFalse: [
+               ^ self error: 'form dimensions do not match' ].
+       self supports8BitGrayscaleJPEGs
-       w := self primImageWidth: jpegDecompressStruct.
-       h := self primImageHeight: jpegDecompressStruct.
-       ((aForm width = w) & (aForm height = h)) ifFalse: [
-               ^ self error: 'form dimensions do not match'].
-
-       "odd width images of depth 16 give problems; avoid them"
-       w odd
                ifTrue: [
+                       components = 3
+                               ifTrue: [
+                                       aForm depth = 8
+                                               ifTrue: [ ^ self error: 'Cannot uncompress multi-channel JPEGs into 8-bit deep forms' ]].
+                       components = 1
+                               ifTrue: [
+                                       aForm depth = 8
+                                               ifTrue: [
+                                                       aForm isGrayScale
+                                                               ifFalse: [ ^ self error: 'Cannot uncompress single-channel JPEGs into 8-bit deep forms that are not grayscale' ]]]]
+
-                       aForm depth = 32 ifFalse: [^ self error: 'must use depth 32 with odd width']]
                ifFalse: [
+                       aForm nativeDepth < 0
+                               ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs into little-endian forms' ]
+                               ifFalse: [
+                                       aForm depth = 16
+                                               ifTrue: [
+                                                       width odd
+                                                               ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs with an odd width into 16-bit deep forms' ]].
+                                       aForm depth = 8
+                                               ifTrue: [ ^ self error: 'Current plugin version doesn''t support uncompressing JPEGs into 8-bit deep forms' ]]].
-                       ((aForm depth = 16) | (aForm depth = 32)) ifFalse: [^ self error: 'must use depth 16 or 32']].

        self primJPEGReadImage: jpegDecompressStruct
                fromByteArray: aByteArray
                onForm: aForm
                doDithering: ditherFlag
                errorMgr: jpegErrorMgr2Struct.
  !





--
_,,,^..^,,,_
best, Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-lpc.350.mcz

marcel.taeumel
In reply to this post by commits-2
Welcome in the team! :)

Best,
Marcel
Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-lpc.350.mcz

David T. Lewis
In reply to this post by commits-2
On Wed, Jun 15, 2016 at 05:01:36PM +0000, [hidden email] wrote:
> Laura Perez Cerrato uploaded a new version of Graphics to project The Trunk:
> http://source.squeak.org/trunk/Graphics-lpc.350.mcz
>

Yay! Thank you Laura for your contributions.

Dave