The Trunk: Graphics-nice.135.mcz

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

The Trunk: Graphics-nice.135.mcz

commits-2
Nicolas Cellier uploaded a new version of Graphics to project The Trunk:
http://source.squeak.org/trunk/Graphics-nice.135.mcz

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

Name: Graphics-nice.135
Author: nice
Time: 11 June 2010, 10:08:12.299 pm
UUID: 8f262453-aaa3-3240-b062-5a54c8d95b3a
Ancestors: Graphics-mtf.134

Use a few nextLine instead of to upTo: Character cr to make things work even if a LF has leaked in.

=============== Diff against Graphics-mtf.134 ===============

Item was changed:
  ----- Method: BitBlt class>>benchDiffsFrom:to: (in category 'benchmarks') -----
  benchDiffsFrom: before to: afterwards
  "Given two outputs of BitBlt>>benchmark show the relative improvements."
  | old new log oldLine newLine oldVal newVal improvement |
  log := WriteStream on: String new.
  old := ReadStream on: before.
  new := ReadStream on: afterwards.
  [old atEnd or:[new atEnd]] whileFalse:[
+ oldLine := old nextLine.
+ newLine := new nextLine.
- oldLine := old upTo: Character cr.
- newLine := new upTo: Character cr.
  (oldLine includes: Character tab) ifTrue:[
  oldLine := ReadStream on: oldLine.
  newLine := ReadStream on: newLine.
  Transcript cr; show: (oldLine upTo: Character tab); tab.
  log cr; nextPutAll: (newLine upTo: Character tab); tab.
 
  [oldLine skipSeparators. newLine skipSeparators.
  oldLine atEnd] whileFalse:[
  oldVal := Integer readFrom: oldLine.
  newVal := Integer readFrom: newLine.
  improvement := oldVal asFloat / newVal asFloat roundTo: 0.01.
  Transcript show: improvement printString; tab; tab.
  log print: improvement; tab; tab].
  ] ifFalse:[
  Transcript cr; show: oldLine.
  log cr; nextPutAll: oldLine.
  ].
  ].
  ^log contents!

Item was changed:
  ----- Method: BDFFontReader>>getLine (in category 'reading') -----
  getLine
+ ^file nextLine!
- ^file upTo: Character cr.!

Item was changed:
  ----- Method: StrikeFont>>readFromBitFont: (in category 'file in/out') -----
  readFromBitFont: fileName
  "This builds a StrikeFont instance by reading the data file format
  produced by BitFont, a widely available font conversion utility
  written by Peter DiCamillo at Brown University"
  "StrikeFont new readFromBitFont: 'Palatino10.BF' "
  | f lastAscii charLine width ascii charForm line missingForm tempGlyphs iRect p rectLine left tokens right |
  f := FileStream readOnlyFileNamed: fileName.
  self readBFHeaderFrom: f.
 
  "NOTE: if font has been scaled (and in any case),
  the REAL bitmap dimensions come after the header."
  self restOfLine: 'Extent information for entire font' from: f.
  "Parse the following line (including mispelling!!)"
  "Image rectange: left = -2, right = 8, bottom = -2, top = 7"
+ tokens := f nextLine  findTokens: ' '.
- tokens := (f upTo: Character cr)  findTokens: ' '.
  iRect := Rectangle left: (tokens at: 5) asNumber right: (tokens at: 8) asNumber
  top: (tokens at: 14) asNumber bottom: (tokens at: 11) asNumber.
  ascent := iRect top.
  descent := iRect bottom negated.
 
  tempGlyphs := Form extent: (maxWidth*257) @ self height.
  xTable := (Array new: 258) atAllPut: 0.
  xTable at: 1 put: 0.
 
  "Read character forms and blt into tempGlyphs"
  lastAscii := -1.
  [charLine := self restOfLine: 'Character: ' from: f.
  charLine == nil ifFalse:
  [p := f position.
+ rectLine := f nextLine.
- rectLine := f upTo: Character cr.
  (rectLine beginsWith: 'Image rectange: left = ')
  ifTrue: [tokens := rectLine findTokens: ' '.
  left := (tokens at: 5) asNumber. right := (tokens at: 8) asNumber]
  ifFalse: [left := right := 0. f position: p].
  width:= (self restOfLine: 'Width (final pen position) = ' from: f) asNumber - left
  max: (right-left+1).
  (charLine beginsWith: 'Missing character') ifTrue: [ascii := 256].
  ('x''*' match: charLine) ifTrue:
  [ascii := Number readFrom: (charLine copyFrom: 3 to: 4) asUppercase base: 16].
  charForm := Form extent: width@self height.
  ('*[all blank]' match: charLine) ifFalse:
  [self restOfLine: '  +' from: f.
  1 to: self height do:
+ [:y | line := f nextLine.
- [:y | line := f upTo: Character cr.
  4 to: (width + 3 min: line size + iRect left - left) do:
  [:x | (line at: x - iRect left + left) = $*
  ifTrue: [charForm pixelValueAt: (x-4)@(y-1) put: 1]]]]].
  charLine == nil]
  whileFalse:
  [self displayChar: ascii form: charForm.
  ascii = 256
  ifTrue: [missingForm := charForm deepCopy]
  ifFalse:
  [minAscii := minAscii min: ascii.
  maxAscii := maxAscii max: ascii.
  lastAscii+1 to: ascii-1 do: [:a | xTable at: a+2 put: (xTable at: a+1)].
  tempGlyphs copy: ((xTable at: ascii+1)@0
  extent: charForm extent)
  from: 0@0 in: charForm rule: Form over.
  xTable at: ascii+2 put: (xTable at: ascii+1) + width.
  lastAscii := ascii]].
  f close.
  lastAscii+1 to: maxAscii+1 do: [:a | xTable at: a+2 put: (xTable at: a+1)].
  missingForm == nil ifFalse:
  [tempGlyphs copy: missingForm boundingBox from: missingForm
  to: (xTable at: maxAscii+2)@0 rule: Form over.
  xTable at: maxAscii+3 put: (xTable at: maxAscii+2) + missingForm width].
  glyphs := Form extent: (xTable at: maxAscii+3) @ self height.
  glyphs copy: glyphs boundingBox from: 0@0 in: tempGlyphs rule: Form over.
  xTable := xTable copyFrom: 1 to: maxAscii+3.
  characterToGlyphMap := nil.!

Item was changed:
  ----- Method: StrikeFont>>restOfLine:from: (in category 'file in/out') -----
  restOfLine: leadString from: file
  "Utility method to assist reading of BitFont data files"
  | line |
+ [line := file nextLine.
- [line := file upTo: Character cr.
  line size < leadString size or: [leadString ~= (line copyFrom: 1 to: leadString size)]]
  whileTrue: [file atEnd ifTrue: [^ nil]].
  ^ line copyFrom: leadString size+1 to: line size!