The Trunk: Graphics-tpr.206.mcz

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

The Trunk: Graphics-tpr.206.mcz

commits-2
tim Rowledge uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-tpr.206.mcz

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

Name: Graphics-tpr.206
Author: tpr
Time: 25 March 2013, 3:39:44.074 pm
UUID: 3475831d-5338-41ce-ab44-41981bd4daeb
Ancestors: Graphics-tpr.204

Change Form>pixelValueAt: to make use of the new primitivePixelValueAt
Change the users of bitPeekerFromForm: to take advantage of that.
Leave bitPeekerFromForm: to support any externally stored code we can't see right now.
Passes the tests in BitBltTest as of 20130325

=============== Diff against Graphics-tpr.204 ===============

Item was removed:
- ----- Method: ColorForm>>pixelValueAt: (in category 'pixel accessing') -----
- pixelValueAt: aPoint
- "Return the raw pixel value at the given point. Typical clients use colorAt: to get a Color."
- "Details: To get the raw pixel value, be sure the peeker's colorMap is nil."
-
- ^ (BitBlt bitPeekerFromForm: self) colorMap: nil; pixelAt: aPoint
- !

Item was changed:
  ----- Method: Form>>floodFill2:at: (in category 'filling') -----
  floodFill2: aColor at: interiorPoint
  "Fill the shape (4-connected) at interiorPoint.  The algorithm is based on Paul Heckbert's 'A Seed Fill Algorithm', Graphic Gems I, Academic Press, 1990.
  NOTE: This is a less optimized variant for flood filling which is precisely along the lines of Heckbert's algorithm. For almost all cases #floodFill:at: will be faster (see the comment there) but this method is left in both as reference and as a fallback if such a strange case is encountered in reality."
+ | poker stack old new x y top x1 x2 dy left goRight |
- | peeker poker stack old new x y top x1 x2 dy left goRight |
- peeker := BitBlt bitPeekerFromForm: self.
  poker := BitBlt bitPokerToForm: self.
  stack := OrderedCollection new: 50.
  "read old pixel value"
+ old := self pixelAt: interiorPoint.
- old := peeker pixelAt: interiorPoint.
  "compute new value"
  new := self pixelValueFor: aColor.
  old = new ifTrue:[^self]. "no point, is there?!!"
 
  x := interiorPoint x.
  y := interiorPoint y.
  (y >= 0 and:[y < height]) ifTrue:[
  stack addLast: {y. x. x. 1}. "y, left, right, dy"
  stack addLast: {y+1. x. x. -1}].
  [stack isEmpty] whileFalse:[
  top := stack removeLast.
  y := top at: 1. x1 := top at: 2. x2 := top at: 3. dy := top at: 4.
  y := y + dy.
  "Segment of scanline (y-dy) for x1 <= x <= x2 was previously filled.
  Now explore adjacent pixels in scanline y."
  x := x1.
+ [x >= 0 and:[(self pixelAt: x@y) = old]] whileTrue:[
- [x >= 0 and:[(peeker pixelAt: x@y) = old]] whileTrue:[
  poker pixelAt: x@y put: new.
  x := x - 1].
  goRight := x < x1.
  left := x+1.
  (left < x1 and:[y-dy >= 0 and:[y-dy < height]])
  ifTrue:[stack addLast: {y. left. x1-1. 0-dy}].
  goRight ifTrue:[x := x1 + 1].
  [
  goRight ifTrue:[
+ [x < width and:[(self pixelAt: x@y) = old]] whileTrue:[
- [x < width and:[(peeker pixelAt: x@y) = old]] whileTrue:[
  poker pixelAt: x@y put: new.
  x := x + 1].
  (y+dy >= 0 and:[y+dy < height])
  ifTrue:[stack addLast: {y. left. x-1. dy}].
  (x > (x2+1) and:[y-dy >= 0 and:[y-dy >= 0]])
  ifTrue:[stack addLast: {y. x2+1. x-1. 0-dy}]].
+ [(x := x + 1) <= x2 and:[(self pixelAt: x@y) ~= old]] whileTrue.
- [(x := x + 1) <= x2 and:[(peeker pixelAt: x@y) ~= old]] whileTrue.
  left := x.
  goRight := true.
  x <= x2] whileTrue.
  ].
  !

Item was changed:
  ----- Method: Form>>pixelValueAt: (in category 'pixel access') -----
  pixelValueAt: aPoint
  "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color.  "
 
+ ^ self primPixelValueAtX: aPoint x y: aPoint y!
- ^ (BitBlt bitPeekerFromForm: self) pixelAt: aPoint
- !

Item was changed:
  ----- Method: Form>>primPixelValueAtX:y: (in category 'pixel access') -----
  primPixelValueAtX: x y: y
+ "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color. Make sure the colorMap is nil for ColorForms "
- "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color.  "
 
  <primitive: 'primitivePixelValueAt' module:'PixelValuePeekPlugin'>
+ ^(BitBlt bitPeekerFromForm: self) colorMap: nil;  pixelAt: x@y!
- ^(BitBlt bitPeekerFromForm: self) pixelAtX: x y: y!

Item was changed:
  ----- Method: PNMReadWriter>>nextPutGray: (in category 'writing') -----
  nextPutGray: aForm
+ | myType val |
- | myType peeker val |
  cols := aForm width.
  rows := aForm height.
  depth := aForm depth.
  "stream position: 0."
  aForm depth = 1 ifTrue:[myType := $4] ifFalse:[myType := $5].
  self writeHeader: myType.
- peeker := BitBlt bitPeekerFromForm: aForm.
  0 to: rows-1 do: [:y |
  0 to: cols-1 do: [:x |
+ val := aForm pixelAt: x@y.
- val := peeker pixelAt: x@y.
  stream nextPut: val.
  ]
  ].
  !

Item was changed:
  ----- Method: PNMReadWriter>>nextPutRGB: (in category 'writing') -----
  nextPutRGB: aForm
+ | myType f shift mask |
- | myType peeker f shift mask |
  cols := aForm width.
  rows := aForm height.
  depth := aForm depth.
  f := aForm.
  depth < 16 ifTrue:[
  f := aForm asFormOfDepth: 32.
  depth := 32.
  ].
  myType := $6.
  "stream position: 0."
  self writeHeader: myType.
  depth = 32 ifTrue:[shift := 8. mask := 16rFF] ifFalse:[shift := 5. mask := 16r1F].
- peeker := BitBlt bitPeekerFromForm: f.
  0 to: rows-1 do: [:y |
  0 to: cols-1 do: [:x | | p r g b |
+ p := f pixelAt: x@y.
- p := peeker pixelAt: x@y.
  b := p bitAnd: mask. p := p >> shift.
  g := p bitAnd: mask. p := p >> shift.
  r := p bitAnd: mask.
  stream nextPut: r.
  stream nextPut: g.
  stream nextPut: b.
  ]
  ].
  !

Item was changed:
  ----- Method: Pen>>print:withFont: (in category 'operations') -----
  print: str withFont: font
  "Print the given string in the given font at the current heading"
  | lineStart scale wasDown |
  scale := sourceForm width.
  wasDown := penDown.
  lineStart := location.
  str do:
  [:char |
  char = Character cr ifTrue:
  [self place: lineStart; up; turn: 90; go: font height*scale; turn: -90; down]
  ifFalse:
+ [ | charStart pix rowStart form backgroundCode |
- [ | charStart pix rowStart form bb backgroundCode |
  form := font characterFormAt: char.
  backgroundCode := 1<< (form depth // 3 * 3) - 1.
  charStart := location.
  wasDown ifTrue: [
  self up; turn: -90; go: font descent*scale; turn: 90; down.
  0 to: form height-1 do:
  [:y |
  rowStart := location.
- bb := BitBlt bitPeekerFromForm: form.
  pix := RunArray newFrom:
+ ((0 to: form width-1) collect: [:x | form pixelAt: x@y]).
- ((0 to: form width-1) collect: [:x | bb pixelAt: x@y]).
  pix runs with: pix values do:
  [:run :value |
  value = backgroundCode
  ifTrue: [self up; go: run*scale; down]
  ifFalse: [self go: run*scale]].
  self place: rowStart; up; turn: 90; go: scale; turn: -90; down].
  ].
  self place: charStart; up; go: form width*scale; down].
  ].
  wasDown ifFalse: [self up]
  "
  Display restoreAfter:
  [Pen new squareNib: 2; color: Color red; turn: 45;
  print: 'The owl and the pussycat went to sea
  in a beautiful pea green boat.' withFont: TextStyle defaultFont]
  "!

Item was changed:
  ----- Method: WarpBlt>>warpBitsSmoothing:sourceMap: (in category 'primitives') -----
  warpBitsSmoothing: n sourceMap: sourceMap
+ | deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne poker pix nSteps |
- | deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne picker poker pix nSteps |
  <primitive: 'primitiveWarpBits' module: 'BitBltPlugin'>
 
  "Check for compressed source, destination or halftone forms"
  ((sourceForm isForm) and: [sourceForm unhibernate])
  ifTrue: [^ self warpBitsSmoothing: n sourceMap: sourceMap].
  ((destForm isForm) and: [destForm unhibernate])
  ifTrue: [^ self warpBitsSmoothing: n sourceMap: sourceMap].
  ((halftoneForm isForm) and: [halftoneForm unhibernate])
  ifTrue: [^ self warpBitsSmoothing: n sourceMap: sourceMap].
 
  (width < 1) | (height < 1) ifTrue: [^ self].
  fixedPtOne := 16384.  "1.0 in fixed-pt representation"
  n > 1 ifTrue:
  [(destForm depth < 16 and: [colorMap == nil])
  ifTrue: ["color map is required to smooth non-RGB dest"
  ^ self primitiveFail].
  pix := Array new: n*n].
 
  nSteps := height-1 max: 1.
  deltaP12 := (self deltaFrom: p1x to: p2x nSteps: nSteps)
  @ (self deltaFrom: p1y to: p2y nSteps: nSteps).
  pA := (self startFrom: p1x to: p2x offset: nSteps*deltaP12 x)
  @ (self startFrom: p1y to: p2y offset: nSteps*deltaP12 y).
  deltaP43 := (self deltaFrom: p4x to: p3x nSteps: nSteps)
  @ (self deltaFrom: p4y to: p3y nSteps: nSteps).
  pB := (self startFrom: p4x to: p3x offset: nSteps*deltaP43 x)
  @ (self startFrom: p4y to: p3y offset: nSteps*deltaP43 y).
 
- picker := BitBlt bitPeekerFromForm: sourceForm.
  poker := BitBlt bitPokerToForm: destForm.
  poker clipRect: self clipRect.
  nSteps := width-1 max: 1.
  destY to: destY+height-1 do:
  [:y |
  deltaPAB := (self deltaFrom: pA x to: pB x nSteps: nSteps)
  @ (self deltaFrom: pA y to: pB y nSteps: nSteps).
  sp := (self startFrom: pA x to: pB x offset: nSteps*deltaPAB x)
  @ (self startFrom: pA y to: pB y offset: nSteps*deltaPAB x).
  destX to: destX+width-1 do:
  [:x |
  n = 1
  ifTrue:
  [poker pixelAt: x@y
+ put: (sourceForm pixelAt: sp // fixedPtOne asPoint)]
- put: (picker pixelAt: sp // fixedPtOne asPoint)]
  ifFalse:
  [0 to: n-1 do:
  [:dx | 0 to: n-1 do:
  [:dy |
  pix at: dx*n+dy+1 put:
+ (sourceForm pixelAt: sp
- (picker pixelAt: sp
  + (deltaPAB*dx//n)
  + (deltaP12*dy//n)
  // fixedPtOne asPoint)]].
  poker pixelAt: x@y put: (self mixPix: pix
  sourceMap: sourceMap
  destMap: colorMap)].
  sp := sp + deltaPAB].
  pA := pA + deltaP12.
  pB := pB + deltaP43]!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

Bert Freudenberg
Isn't it a bit premature to it this way? This will make these operations slower than before for everyone who does not have the plugin. Which is pretty much everyone.

- Bert -

On 2013-03-25, at 22:40, [hidden email] wrote:

> tim Rowledge uploaded a new version of Graphics to project The Trunk:
> http://source.squeak.org/trunk/Graphics-tpr.206.mcz
>
> ==================== Summary ====================
>
> Name: Graphics-tpr.206
> Author: tpr
> Time: 25 March 2013, 3:39:44.074 pm
> UUID: 3475831d-5338-41ce-ab44-41981bd4daeb
> Ancestors: Graphics-tpr.204
>
> Change Form>pixelValueAt: to make use of the new primitivePixelValueAt
> Change the users of bitPeekerFromForm: to take advantage of that.
> Leave bitPeekerFromForm: to support any externally stored code we can't see right now.
> Passes the tests in BitBltTest as of 20130325
>
> =============== Diff against Graphics-tpr.204 ===============
>
> Item was removed:
> - ----- Method: ColorForm>>pixelValueAt: (in category 'pixel accessing') -----
> - pixelValueAt: aPoint
> - "Return the raw pixel value at the given point. Typical clients use colorAt: to get a Color."
> - "Details: To get the raw pixel value, be sure the peeker's colorMap is nil."
> -
> - ^ (BitBlt bitPeekerFromForm: self) colorMap: nil; pixelAt: aPoint
> - !
>
> Item was changed:
>  ----- Method: Form>>floodFill2:at: (in category 'filling') -----
>  floodFill2: aColor at: interiorPoint
>   "Fill the shape (4-connected) at interiorPoint.  The algorithm is based on Paul Heckbert's 'A Seed Fill Algorithm', Graphic Gems I, Academic Press, 1990.
>   NOTE: This is a less optimized variant for flood filling which is precisely along the lines of Heckbert's algorithm. For almost all cases #floodFill:at: will be faster (see the comment there) but this method is left in both as reference and as a fallback if such a strange case is encountered in reality."
> + | poker stack old new x y top x1 x2 dy left goRight |
> - | peeker poker stack old new x y top x1 x2 dy left goRight |
> - peeker := BitBlt bitPeekerFromForm: self.
>   poker := BitBlt bitPokerToForm: self.
>   stack := OrderedCollection new: 50.
>   "read old pixel value"
> + old := self pixelAt: interiorPoint.
> - old := peeker pixelAt: interiorPoint.
>   "compute new value"
>   new := self pixelValueFor: aColor.
>   old = new ifTrue:[^self]. "no point, is there?!!"
>
>   x := interiorPoint x.
>   y := interiorPoint y.
>   (y >= 0 and:[y < height]) ifTrue:[
>   stack addLast: {y. x. x. 1}. "y, left, right, dy"
>   stack addLast: {y+1. x. x. -1}].
>   [stack isEmpty] whileFalse:[
>   top := stack removeLast.
>   y := top at: 1. x1 := top at: 2. x2 := top at: 3. dy := top at: 4.
>   y := y + dy.
>   "Segment of scanline (y-dy) for x1 <= x <= x2 was previously filled.
>   Now explore adjacent pixels in scanline y."
>   x := x1.
> + [x >= 0 and:[(self pixelAt: x@y) = old]] whileTrue:[
> - [x >= 0 and:[(peeker pixelAt: x@y) = old]] whileTrue:[
>   poker pixelAt: x@y put: new.
>   x := x - 1].
>   goRight := x < x1.
>   left := x+1.
>   (left < x1 and:[y-dy >= 0 and:[y-dy < height]])
>   ifTrue:[stack addLast: {y. left. x1-1. 0-dy}].
>   goRight ifTrue:[x := x1 + 1].
>   [
>   goRight ifTrue:[
> + [x < width and:[(self pixelAt: x@y) = old]] whileTrue:[
> - [x < width and:[(peeker pixelAt: x@y) = old]] whileTrue:[
>   poker pixelAt: x@y put: new.
>   x := x + 1].
>   (y+dy >= 0 and:[y+dy < height])
>   ifTrue:[stack addLast: {y. left. x-1. dy}].
>   (x > (x2+1) and:[y-dy >= 0 and:[y-dy >= 0]])
>   ifTrue:[stack addLast: {y. x2+1. x-1. 0-dy}]].
> + [(x := x + 1) <= x2 and:[(self pixelAt: x@y) ~= old]] whileTrue.
> - [(x := x + 1) <= x2 and:[(peeker pixelAt: x@y) ~= old]] whileTrue.
>   left := x.
>   goRight := true.
>   x <= x2] whileTrue.
>   ].
>  !
>
> Item was changed:
>  ----- Method: Form>>pixelValueAt: (in category 'pixel access') -----
>  pixelValueAt: aPoint
>   "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color.  "
>
> + ^ self primPixelValueAtX: aPoint x y: aPoint y!
> - ^ (BitBlt bitPeekerFromForm: self) pixelAt: aPoint
> - !
>
> Item was changed:
>  ----- Method: Form>>primPixelValueAtX:y: (in category 'pixel access') -----
>  primPixelValueAtX: x y: y
> + "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color. Make sure the colorMap is nil for ColorForms "
> - "Return the raw pixel value at the given point. This pixel value depends on the receiver's depth. Typical clients use colorAt: to get a Color.  "
>
>   <primitive: 'primitivePixelValueAt' module:'PixelValuePeekPlugin'>
> + ^(BitBlt bitPeekerFromForm: self) colorMap: nil;  pixelAt: x@y!
> - ^(BitBlt bitPeekerFromForm: self) pixelAtX: x y: y!
>
> Item was changed:
>  ----- Method: PNMReadWriter>>nextPutGray: (in category 'writing') -----
>  nextPutGray: aForm
> + | myType val |
> - | myType peeker val |
>   cols := aForm width.
>   rows := aForm height.
>   depth := aForm depth.
>   "stream position: 0."
>   aForm depth = 1 ifTrue:[myType := $4] ifFalse:[myType := $5].
>   self writeHeader: myType.
> - peeker := BitBlt bitPeekerFromForm: aForm.
>   0 to: rows-1 do: [:y |
>   0 to: cols-1 do: [:x |
> + val := aForm pixelAt: x@y.
> - val := peeker pixelAt: x@y.
>   stream nextPut: val.
>   ]
>   ].
>  !
>
> Item was changed:
>  ----- Method: PNMReadWriter>>nextPutRGB: (in category 'writing') -----
>  nextPutRGB: aForm
> + | myType f shift mask |
> - | myType peeker f shift mask |
>   cols := aForm width.
>   rows := aForm height.
>   depth := aForm depth.
>   f := aForm.
>   depth < 16 ifTrue:[
>   f := aForm asFormOfDepth: 32.
>   depth := 32.
>   ].
>   myType := $6.
>   "stream position: 0."
>   self writeHeader: myType.
>   depth = 32 ifTrue:[shift := 8. mask := 16rFF] ifFalse:[shift := 5. mask := 16r1F].
> - peeker := BitBlt bitPeekerFromForm: f.
>   0 to: rows-1 do: [:y |
>   0 to: cols-1 do: [:x | | p r g b |
> + p := f pixelAt: x@y.
> - p := peeker pixelAt: x@y.
>   b := p bitAnd: mask. p := p >> shift.
>   g := p bitAnd: mask. p := p >> shift.
>   r := p bitAnd: mask.
>   stream nextPut: r.
>   stream nextPut: g.
>   stream nextPut: b.
>   ]
>   ].
>  !
>
> Item was changed:
>  ----- Method: Pen>>print:withFont: (in category 'operations') -----
>  print: str withFont: font
>   "Print the given string in the given font at the current heading"
>   | lineStart scale wasDown |
>   scale := sourceForm width.
>   wasDown := penDown.
>   lineStart := location.
>   str do:
>   [:char |
>   char = Character cr ifTrue:
>   [self place: lineStart; up; turn: 90; go: font height*scale; turn: -90; down]
>   ifFalse:
> + [ | charStart pix rowStart form backgroundCode |
> - [ | charStart pix rowStart form bb backgroundCode |
>   form := font characterFormAt: char.
>   backgroundCode := 1<< (form depth // 3 * 3) - 1.
>   charStart := location.
>  wasDown ifTrue: [
>   self up; turn: -90; go: font descent*scale; turn: 90; down.
>   0 to: form height-1 do:
>   [:y |
>   rowStart := location.
> - bb := BitBlt bitPeekerFromForm: form.
>   pix := RunArray newFrom:
> + ((0 to: form width-1) collect: [:x | form pixelAt: x@y]).
> - ((0 to: form width-1) collect: [:x | bb pixelAt: x@y]).
>   pix runs with: pix values do:
>   [:run :value |
>   value = backgroundCode
>   ifTrue: [self up; go: run*scale; down]
>   ifFalse: [self go: run*scale]].
>   self place: rowStart; up; turn: 90; go: scale; turn: -90; down].
>  ].
>   self place: charStart; up; go: form width*scale; down].
>   ].
>   wasDown ifFalse: [self up]
>  "
>  Display restoreAfter:
>  [Pen new squareNib: 2; color: Color red; turn: 45;
>   print: 'The owl and the pussycat went to sea
>  in a beautiful pea green boat.' withFont: TextStyle defaultFont]
>  "!
>
> Item was changed:
>  ----- Method: WarpBlt>>warpBitsSmoothing:sourceMap: (in category 'primitives') -----
>  warpBitsSmoothing: n sourceMap: sourceMap
> + | deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne poker pix nSteps |
> - | deltaP12 deltaP43 pA pB deltaPAB sp fixedPtOne picker poker pix nSteps |
>   <primitive: 'primitiveWarpBits' module: 'BitBltPlugin'>
>
>   "Check for compressed source, destination or halftone forms"
>   ((sourceForm isForm) and: [sourceForm unhibernate])
>   ifTrue: [^ self warpBitsSmoothing: n sourceMap: sourceMap].
>   ((destForm isForm) and: [destForm unhibernate])
>   ifTrue: [^ self warpBitsSmoothing: n sourceMap: sourceMap].
>   ((halftoneForm isForm) and: [halftoneForm unhibernate])
>   ifTrue: [^ self warpBitsSmoothing: n sourceMap: sourceMap].
>
>   (width < 1) | (height < 1) ifTrue: [^ self].
>   fixedPtOne := 16384.  "1.0 in fixed-pt representation"
>   n > 1 ifTrue:
>   [(destForm depth < 16 and: [colorMap == nil])
>   ifTrue: ["color map is required to smooth non-RGB dest"
>   ^ self primitiveFail].
>   pix := Array new: n*n].
>
>   nSteps := height-1 max: 1.
>   deltaP12 := (self deltaFrom: p1x to: p2x nSteps: nSteps)
>   @ (self deltaFrom: p1y to: p2y nSteps: nSteps).
>   pA := (self startFrom: p1x to: p2x offset: nSteps*deltaP12 x)
>   @ (self startFrom: p1y to: p2y offset: nSteps*deltaP12 y).
>   deltaP43 := (self deltaFrom: p4x to: p3x nSteps: nSteps)
>   @ (self deltaFrom: p4y to: p3y nSteps: nSteps).
>   pB := (self startFrom: p4x to: p3x offset: nSteps*deltaP43 x)
>   @ (self startFrom: p4y to: p3y offset: nSteps*deltaP43 y).
>
> - picker := BitBlt bitPeekerFromForm: sourceForm.
>   poker := BitBlt bitPokerToForm: destForm.
>   poker clipRect: self clipRect.
>   nSteps := width-1 max: 1.
>   destY to: destY+height-1 do:
>   [:y |
>   deltaPAB := (self deltaFrom: pA x to: pB x nSteps: nSteps)
>   @ (self deltaFrom: pA y to: pB y nSteps: nSteps).
>   sp := (self startFrom: pA x to: pB x offset: nSteps*deltaPAB x)
>   @ (self startFrom: pA y to: pB y offset: nSteps*deltaPAB x).
>   destX to: destX+width-1 do:
>   [:x |
>   n = 1
>   ifTrue:
>   [poker pixelAt: x@y
> + put: (sourceForm pixelAt: sp // fixedPtOne asPoint)]
> - put: (picker pixelAt: sp // fixedPtOne asPoint)]
>   ifFalse:
>   [0 to: n-1 do:
>   [:dx | 0 to: n-1 do:
>   [:dy |
>   pix at: dx*n+dy+1 put:
> + (sourceForm pixelAt: sp
> - (picker pixelAt: sp
>   + (deltaPAB*dx//n)
>   + (deltaP12*dy//n)
>   // fixedPtOne asPoint)]].
>   poker pixelAt: x@y put: (self mixPix: pix
>   sourceMap: sourceMap
>   destMap: colorMap)].
>   sp := sp + deltaPAB].
>   pA := pA + deltaP12.
>   pB := pB + deltaP43]!
>
>


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

timrowledge

On 26-03-2013, at 8:07 AM, Bert Freudenberg <[hidden email]> wrote:

> Isn't it a bit premature to it this way? This will make these operations slower than before for everyone who does not have the plugin. Which is pretty much everyone.


Well, what is an alternative? You have to make a change at some point if you want to use anything new.

What is the likelihood that someone is going to be loading leading edge ST code but not using a leading edge VM? I don't imagine it is very high. There is no platform VM code involved, so adding the primitive is no extra cost.

Performance-wise, there will be a small cost in the cases where a pixelpeeker BitBlt was being created outside the loop and is now effectively inside the loop. However, look at those cases -
Form>floodFill2:at: - no senders in a plain image
PNMWriter>nextPutGray: & nextPutRGB: - used as a small part of  writing out images to files
Pen>print:withFont:- no senders in a plain image
WarpBlt>warpBitSmoothing:sourceMap: - actually implemented as a bitbltplugin prim anyway

Just to make life even more fun that it already has been, I see that the code that ended up in Graphics-tpr.206.mcz is somewhat different to that I which expected.  The damned primitive isn't even being called properly in that code, and places where I replaced the bitbltpeeker have pixelAt: instead of pixelValueAt: (and it's pretty dumb that we ended up with two variants there). My only explanation is there must have been a dumb-thumb exit-no-save at a stupid place.

And to be even more fun, I think I've found out why a previous attempt caused the removal of AbstractFont methods; the latest configuration of VMMaker (update-dtl-12) refers to FreeType-tween.435. Which changes AbstractFont. I can't help thinking that it isn't a package that should be involved in VMMaker. FreeType-Plugin, sure, that makes sense, but isn't the rest of it supposed to be already part of the image? Or subsumed by other changes already in the image?

And *even* more fun comes from the fact that I can't now submit changes to fix the stuff I noticed without having the f%^%^*^&ing AbstractFont stuff sorted out.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Strange OpCodes: START: Cancel preceding jobs in queue



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

Bert Freudenberg
On 2013-03-26, at 18:53, tim Rowledge <[hidden email]> wrote:

> On 26-03-2013, at 8:07 AM, Bert Freudenberg <[hidden email]> wrote:
>
>> Isn't it a bit premature to it this way? This will make these operations slower than before for everyone who does not have the plugin. Which is pretty much everyone.
>
> Well, what is an alternative? You have to make a change at some point if you want to use anything new.

You could have left the peeker code in place and if the plugin is available, return the form itself rather than a peeker - the interface is the same. But since it is not used in critical code anyway, as you show below, I guess it's okay.

> What is the likelihood that someone is going to be loading leading edge ST code but not using a leading edge VM? I don't imagine it is very high. There is no platform VM code involved, so adding the primitive is no extra cost.

Few people build their own VMs, and not everyone upgrades their VM regularly, not even when a new image is released.

> Performance-wise, there will be a small cost in the cases where a pixelpeeker BitBlt was being created outside the loop and is now effectively inside the loop. However, look at those cases -
> Form>floodFill2:at: - no senders in a plain image
> PNMWriter>nextPutGray: & nextPutRGB: - used as a small part of  writing out images to files
> Pen>print:withFont:- no senders in a plain image
> WarpBlt>warpBitSmoothing:sourceMap: - actually implemented as a bitbltplugin prim anyway

Okay.

> And *even* more fun comes from the fact that I can't now submit changes to fix the stuff I noticed without having the f%^%^*^&ing AbstractFont stuff sorted out.


Just rename "*FreeType-addition" to "*FreeType-override" and the methods should magically re-appear in the graphics package.

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

timrowledge

On 26-03-2013, at 5:07 PM, Bert Freudenberg <[hidden email]> wrote:
>
>
>> And *even* more fun comes from the fact that I can't now submit changes to fix the stuff I noticed without having the f%^%^*^&ing AbstractFont stuff sorted out.
>
>
> Just rename "*FreeType-addition" to "*FreeType-override" and the methods should magically re-appear in the graphics package.


Can't help thinking that making sure the problem isn't caused in the first place would be nicer. My best guess is that the FreeType code was needed at some point in the past before it was incorporated into the main image, and people just forgot to remove it from the VMMaker configuration.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Useful random insult:- Has an inferiority complex, but not a very good one.



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

David T. Lewis
On Tue, Mar 26, 2013 at 05:15:00PM -0700, tim Rowledge wrote:

>
> On 26-03-2013, at 5:07 PM, Bert Freudenberg <[hidden email]> wrote:
> >
> >
> >> And *even* more fun comes from the fact that I can't now submit changes to fix the stuff I noticed without having the f%^%^*^&ing AbstractFont stuff sorted out.
> >
> >
> > Just rename "*FreeType-addition" to "*FreeType-override" and the methods should magically re-appear in the graphics package.
>
>
> Can't help thinking that making sure the problem isn't caused in the first place would be nicer. My best guess is that the FreeType code was needed at some point in the past before it was incorporated into the main image, and people just forgot to remove it from the VMMaker configuration.
>

The FT2Plugin in the SqS/FreetypePlugin repository has a dependency on the
FT2Constants pool, which is part of the FreeType package in the SqS/FreeType
repository. In a perfect world, someone would be maintaining these packages
in such as way as to prevent overrides and other annoyances. In a less than
perfect world, we can at least be thankful that Monticello does a nice job
of detecting the conflicts.

Neither the Freetype plugin nor the shared pool are part of the VMMaker
package on source.squeak.org. I think that's a good thing, and that packages
should be maintained by their rightful owners and kept out of the VMMaker
package unless there is a real need to adopt them.

Right now I don't see it as a problem, just an annoyance. If it's a problem,
the solution is to nag the package maintainers. For myself, I can live with
it so I'm happy to let someone else volunteer to do the nagging ;)

Dave


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

timrowledge
OK, now I'm getting confused. (This seems to be getting more common over the years.)

I *thought* the FreeType stuff was part of the standard 4.4 image, but since I can't find any references to it in a plain image I was clearly confusing it with seeing the little font-cache-updating thingy when starting images with VMMaker stuff installed.


On 26-03-2013, at 6:09 PM, "David T. Lewis" <[hidden email]> wrote:
> The FT2Plugin in the SqS/FreetypePlugin repository has a dependency on the
> FT2Constants pool, which is part of the FreeType package in the SqS/FreeType
> repository. In a perfect world, someone would be maintaining these packages
> in such as way as to prevent overrides and other annoyances. In a less than
> perfect world, we can at least be thankful that Monticello does a nice job
> of detecting the conflicts.

So we would be better off (I postulate) with the FT2Constants separated out so they can be included in the VMMaker configuration without the other stuff.

*If* that is, there is still a reason to do anything with the FT stuff; I don't see any dates in the repository files more recent than early 2008 so I have to wonder if it is in use? It seems unlikely that it could be so perfect that nothing has had to be changed in the meantime. What is the status of this code?




>
> Neither the Freetype plugin nor the shared pool are part of the VMMaker
> package on source.squeak.org. I think that's a good thing, and that packages
> should be maintained by their rightful owners and kept out of the VMMaker
> package unless there is a real need to adopt them.
>
Except it is included in the squeaksource VMMaker->update-dtl.12 configuration. Which makes it a problem by proxy, I guess.

With my very limited and ancient remembrances of MC it seems we can
move FT2Constants to a new category, say 'FreeType-BaseConstants'
create a new package for 'FreeType-BaseConstants'
add the FreeTypePlus repository to it
save a new version the freetype stuff
make a configuration for loading the revised FreeType stuff properly
revise the VMMaker configuration to load only the plugin and constants packages.

Is that about right?


tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Concurrent: an object that looks like a raisin but isn't



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-tpr.206.mcz

David T. Lewis
On Wed, Mar 27, 2013 at 11:04:15AM -0700, tim Rowledge wrote:

> OK, now I'm getting confused. (This seems to be getting more common over the years.)
>
> I *thought* the FreeType stuff was part of the standard 4.4 image, but since I can't find any references to it in a plain image I was clearly confusing it with seeing the little font-cache-updating thingy when starting images with VMMaker stuff installed.
>
>
> On 26-03-2013, at 6:09 PM, "David T. Lewis" <[hidden email]> wrote:
> > The FT2Plugin in the SqS/FreetypePlugin repository has a dependency on the
> > FT2Constants pool, which is part of the FreeType package in the SqS/FreeType
> > repository. In a perfect world, someone would be maintaining these packages
> > in such as way as to prevent overrides and other annoyances. In a less than
> > perfect world, we can at least be thankful that Monticello does a nice job
> > of detecting the conflicts.
>
> So we would be better off (I postulate) with the FT2Constants separated out so they can be included in the VMMaker configuration without the other stuff.
>

Yes.

> *If* that is, there is still a reason to do anything with the FT stuff; I don't see any dates in the repository files more recent than early 2008 so I have to wonder if it is in use? It seems unlikely that it could be so perfect that nothing has had to be changed in the meantime. What is the status of this code?
>

I don't know. The Pharo folks depend on Freetype, so it's possible someone has
forked the development. I have not checked.

>
>
>
> >
> > Neither the Freetype plugin nor the shared pool are part of the VMMaker
> > package on source.squeak.org. I think that's a good thing, and that packages
> > should be maintained by their rightful owners and kept out of the VMMaker
> > package unless there is a real need to adopt them.
> >
> Except it is included in the squeaksource VMMaker->update-dtl.12 configuration. Which makes it a problem by proxy, I guess.
>
> With my very limited and ancient remembrances of MC it seems we can
> move FT2Constants to a new category, say 'FreeType-BaseConstants'
> create a new package for 'FreeType-BaseConstants'
> add the FreeTypePlus repository to it
> save a new version the freetype stuff
> make a configuration for loading the revised FreeType stuff properly
> revise the VMMaker configuration to load only the plugin and constants packages.
>
> Is that about right?
>

Yes, that's right. You would want to have the package maintainer do that,
and also update the various Metacello and SqueakMap loaders and so forth,
as well as the VMMaker configuration map.

So that's definitely the right thing to do. All we need now is for someone
to show a deep personal interest in the issue and go make it happen ;-)

Dave