The Trunk: Graphics-nice.274.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-nice.274.mcz

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

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

Name: Graphics-nice.274
Author: nice
Time: 22 October 2013, 9:00:55.08 pm
UUID: 6b3c3622-fbce-410a-a7ea-6f69ea48428f
Ancestors: Graphics-nice.273

Restore primitive 103 for fast Character scanning.
Note: the difference will be hardly noticeable with a COG VM, but more sensible with an interpreter VM on a slow machine.
Note2: I did not use EndOfRun and CrossedX pool variables (TextConstant), because it's obscuring the fact that these hacks occupy slots above 256, and because there are only two references now, one in CharacterScanner class>>initialize, the other hidden in primitive 103...
Avoid passing the stopConditions and kern inst. var. down the message chain (but for primitive 103).

=============== Diff against Graphics-nice.273 ===============

Item was changed:
  ----- Method: CharacterBlockScanner>>characterBlockAtPoint:index:in: (in category 'scanning') -----
  characterBlockAtPoint: aPoint index: index in: textLine
  "This method is the Morphic characterBlock finder.  It combines
  MVC's characterBlockAtPoint:, -ForIndex:, and buildCharacterBlockIn:"
  | runLength lineStop stopCondition |
  line := textLine.
  rightMargin := line rightMargin.
  lastIndex := line first.
  self setStopConditions. "also sets font"
  characterIndex := index.  " == nil means scanning for point"
  characterPoint := aPoint.
  (characterPoint isNil or: [characterPoint y > line bottom])
  ifTrue: [characterPoint := line bottomRight].
  destX := leftMargin := line leftMarginForAlignment: alignment.
  destY := line top.
  (text isEmpty or: [(characterPoint y < destY or: [characterPoint x < destX])
  or: [characterIndex notNil and: [characterIndex < line first]]])
  ifTrue: [^ (CharacterBlock new stringIndex: line first text: text
  topLeft: destX@destY extent: 0 @ textStyle lineGrid)
  textLine: line].
  runLength := text runLengthFor: line first.
  lineStop := characterIndex "scanning for index"
  ifNil: [ line last ]. "scanning for point"
  runStopIndex := lastIndex + (runLength - 1) min: lineStop.
  lastCharacterWidth := 0.
  spaceCount := 0.
 
  [
  stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
+ in: text string rightX: characterPoint x.
- in: text string rightX: characterPoint x
- stopConditions: stopConditions kern: kern.
  "see setStopConditions for stopping conditions for character block operations."
  self perform: stopCondition
  ] whileFalse.
  characterIndex
  ifNil: ["Result for characterBlockAtPoint: "
  ^ (CharacterBlock new
  stringIndex: lastIndex
  text: text topLeft: characterPoint + (font descentKern @ 0)
  extent: lastCharacterWidth @ line lineHeight - (font baseKern @ 0))
  textLine: line]
  ifNotNil: ["Result for characterBlockForIndex: "
  ^ (CharacterBlock new
  stringIndex: characterIndex
  text: text topLeft: characterPoint + ((font descentKern) - kern @ 0)
  extent: lastCharacterWidth @ line lineHeight)
  textLine: line]!

Item was changed:
  Object subclass: #CharacterScanner
+ instanceVariableNames: 'destX lastIndex xTable map destY stopConditions text textStyle alignment leftMargin rightMargin font line runStopIndex spaceCount spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks pendingKernX'
- instanceVariableNames: 'destX lastIndex destY stopConditions text textStyle alignment leftMargin rightMargin font line runStopIndex spaceCount spaceWidth emphasisCode kern indentationLevel wantsColumnBreaks pendingKernX'
  classVariableNames: 'ColumnBreakStopConditions CompositionStopConditions DefaultStopConditions MeasuringStopConditions PaddedSpaceCondition'
  poolDictionaries: 'TextConstants'
  category: 'Graphics-Text'!
 
+ !CharacterScanner commentStamp: 'nice 10/22/2013 20:04' prior: 0!
- !CharacterScanner commentStamp: 'nice 10/10/2013 02:32' prior: 0!
  A CharacterScanner holds the state associated with scanning text. Subclasses scan characters for specified purposes, such as computing a CharacterBlock or placing characters into Forms.
 
  Instance Variables
  alignment: <Integer>
  destX: <Number>
  destY: <Number>
  emphasisCode: <Object>
  font: <AbstractFont>
  indentationLevel: <Integer>
  kern: <Number>
  lastIndex: <Integer>
  leftMargin: <Number>
  line: <TextLine>
+ map: <Array>
  pendingKernX: <Number>
  rightMargin: <Number>
  runStopIndex: <Integer>
  spaceCount: <Integer>
  spaceWidth: <Number>
  stopConditions: <Array>
  text: <Text>
  textStyle: <TextStyle>
  wantsColumnBreaks: <Boolean>
+ xTable: <Array>
 
  alignment
  - an Integer encoding the alignment of text
 
  destX
  - horizontal position for next character (distance from left of composition area)
 
  destY
  - vertical position for next character (distance from top of composition area)
 
  emphasisCode
  - an Integer encoding the current text emphasis to use (bold, italic, ...)
 
  font
  - the current font used for measuring/composing/displaying characters
 
  indentationLevel
  - an Integer specifying a number of leading tabs to be inserted at beginning of new lines
 
  kern
  - a Number specifying additional horizontal spacing to place between characters (spacing is reduced when kern is negative)
 
  lastIndex
  - the Integer index of next character to be processed in the text
 
  leftMargin
  - a Number specifying the distance between left of composition zone and left of first character in the line.
 
  line
  - an object holding information about the line currently being displayed (like first and last index in text).
  Note: this is either a TextLine in Morphic, or TextLineInterval for ST80 compatibility
 
+ map
+ - an array mapping character code to glyph position.
+ This is used by primitive 103 only, in case of ByteString.
+
  pendingKernX
  - a Number to be added to horizontal spacing of next char if ever it is in the same font than previous one.
  The inner scan loop is interrupted by a change of text run.
  But some changes won't change the font, so the kerning must be remembered and applied later.
 
  rightMargin
  - a Number specifying the distance between right of composition zone and right of last character in the line.
 
  runStopIndex
  - the Integer index of last character in current text run.
 
  spaceCount
  - the number of spaces encoutered so far in current line. This is useful for adjusting the spacing in cas of Justified alignment.
 
  spaceWidth
  - the width of space character in current font.
 
  stopConditions
  - an Array mapping a table of characters codes for which special actions are to be taken.
  These are typically control characters like carriage return or horizontal tab.
 
  text
  - the text to be measured/composed/displayed
 
  textStyle
  - an object holding a context for the text style (which set of font to use, which margins, etc...)
 
  wantsColumnBreaks
  - a Boolean indicating whether some special handling for multiple columns is requested.
  THIS ONLY MAKES SENSE IN CompositionScanner AND SHOULD BE MOVED TO THE SUBCLASS
 
+ xTable
+ - an array mapping character code to glyph x coordinate in form.
+ This is used by primitive 103 only, in case of ByteString.
+
+ Implementation note: accelerated Character scanning with primitive 103 requires following order for 5 first instance variables, please don't alter:
+ destX lastIndex xTable map destY
-
  !

Item was changed:
  ----- Method: CharacterScanner class>>initialize (in category 'class initialization') -----
  initialize
  "
  CharacterScanner initialize
  "
  | a |
+ a := Array new: 258.
- a := Array new: 256.
  a at: 1 + 1 put: #embeddedObject.
  a at: Tab asciiValue + 1 put: #tab.
  a at: CR asciiValue + 1 put: #cr.
  a at: Character lf asciiValue + 1 put: #cr.
+ "Note: following two codes are used only by primitive 103 for accelerated Character scanning"
+ a at: 257 put: #endOfRun.
+ a at: 258 put: #crossedX.
 
  DefaultStopConditions := a copy.
 
  CompositionStopConditions := a copy.
  CompositionStopConditions at: Space asciiValue + 1 put: #space.
  ColumnBreakStopConditions := CompositionStopConditions copy.
  ColumnBreakStopConditions at: Character characterForColumnBreak asciiValue + 1 put: #columnBreak.
 
  PaddedSpaceCondition := a copy.
  PaddedSpaceCondition at: Space asciiValue + 1 put: #paddedSpace.
 
+ MeasuringStopConditions := (Array new: 258)
+ at: 257 put: #endOfRun;
+ at: 258 put: #crossedX;
+ yourself!
- MeasuringStopConditions := Array new: 256!

Item was added:
+ ----- Method: CharacterScanner>>basicScanByteCharactersFrom:to:in:rightX: (in category 'scanning') -----
+ basicScanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX
+ "this is a scanning method for
+ single byte characters in a ByteString
+ a font that does not do character-pair kerning"
+ | ascii nextDestX char |
+ lastIndex := startIndex.
+ [lastIndex <= stopIndex]
+ whileTrue: [
+ "get the character value"
+ char := sourceString at: lastIndex.
+ ascii := char asciiValue + 1.
+ "if there is an entry in 'stops' for this value, return it"
+ (stopConditions at: ascii)
+ ifNotNil: [^ stopConditions at: ascii].
+ "bump nextDestX by the width of the current character"
+ nextDestX := destX + (font widthOf: char).
+ "if the next x is past the right edge, return crossedX"
+ nextDestX > rightX
+ ifTrue: [^#crossedX].
+ "update destX and incorporate thr kernDelta"
+ destX := nextDestX + kern.
+ lastIndex := lastIndex + 1].
+ ^self handleEndOfRunAt: stopIndex
+
+ !

Item was removed:
- ----- Method: CharacterScanner>>historicalScanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
- historicalScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
- "Primitive. This is the inner loop of text display--but see
- scanCharactersFrom: to:rightX: which would get the string,
- stopConditions and displaying from the instance. March through source
- String from startIndex to stopIndex. If any character is flagged with a
- non-nil entry in stops, then return the corresponding value. Determine
- width of each character from xTable, indexed by map.
- If dextX would exceed rightX, then return stops at: 258.
- Advance destX by the width of the character. If stopIndex has been
- reached, then return stops at: 257. Optional.
- See Object documentation whatIsAPrimitive.
- Historical note: this primitive has been unusable since about Squeak 2.8 when the shape of the CharracterScanner class changed. It is left here as a reminder that the actual primitive still needs supporting in the VM to keep old images such as Scratch1.4 alive - tpr"
- | ascii nextDestX char |
- <primitive: 103>
- lastIndex := startIndex.
- [lastIndex <= stopIndex]
- whileTrue:
- [char := (sourceString at: lastIndex).
- ascii := char asciiValue + 1.
- (stops at: ascii) == nil ifFalse: [^stops at: ascii].
- "Note: The following is querying the font about the width
- since the primitive may have failed due to a non-trivial
- mapping of characters to glyphs or a non-existing xTable."
- nextDestX := destX + (font widthOf: char).
- nextDestX > rightX ifTrue: [^stops at: CrossedX].
- destX := nextDestX + kernDelta.
- lastIndex := lastIndex + 1].
- lastIndex := stopIndex.
- ^stops at: EndOfRun
- !

Item was changed:
  ----- Method: CharacterScanner>>measureString:inFont:from:to: (in category 'scanning') -----
  measureString: aString inFont: aFont from: startIndex to: stopIndex
  "Measure aString width in given font aFont.
  The string shall not include line breaking, tab or other control character."
  destX := destY := lastIndex := 0.
  pendingKernX := 0.
  font := aFont.
  kern := 0 - font baseKern.
  spaceWidth := font widthOf: Space.
  stopConditions := MeasuringStopConditions.
+ self scanCharactersFrom: startIndex to: stopIndex in: aString rightX: 999999.
- self scanCharactersFrom: startIndex to: stopIndex in: aString rightX: 999999 stopConditions: stopConditions kern: kern.
  ^destX!

Item was added:
+ ----- Method: CharacterScanner>>primScanCharactersFrom:to:in:rightX:stopConditions:kern: (in category 'scanning') -----
+ primScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stops kern: kernDelta
+ "Primitive. This is the inner loop of text display--but see
+ scanCharactersFrom: to:rightX: which would get the string,
+ stopConditions and displaying from the instance. March through source
+ String from startIndex to stopIndex. If any character is flagged with a
+ non-nil entry in stops, then return the corresponding value. Determine
+ width of each character from xTable, indexed by map.
+ If dextX would exceed rightX, then return stops at: 258.
+ Advance destX by the width of the character. If stopIndex has been
+ reached, then return stops at: 257. Optional.
+ See Object documentation whatIsAPrimitive.
+ Historical note: this primitive has been unusable since about Squeak 2.8 when the shape of the CharracterScanner class changed. It is left here as a reminder that the actual primitive still needs supporting in the VM to keep old images such as Scratch1.4 alive - tpr"
+ <primitive: 103>
+ ^self basicScanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX !

Item was changed:
  ----- Method: CharacterScanner>>scanByteCharactersFrom:to:in:rightX: (in category 'scanning') -----
  scanByteCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX
  "this is a scanning method for
  single byte characters in a ByteString
  a font that does not do character-pair kerning"
+ ^self primScanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX stopConditions: stopConditions kern: kern
- | ascii nextDestX char |
- lastIndex := startIndex.
- [lastIndex <= stopIndex]
- whileTrue: [
- "get the character value"
- char := sourceString at: lastIndex.
- ascii := char asciiValue + 1.
- "if there is an entry in 'stops' for this value, return it"
- (stopConditions at: ascii)
- ifNotNil: [^ stopConditions at: ascii].
- "bump nextDestX by the width of the current character"
- nextDestX := destX + (font widthOf: char).
- "if the next x is past the right edge, return crossedX"
- nextDestX > rightX
- ifTrue: [^#crossedX].
- "update destX and incorporate thr kernDelta"
- destX := nextDestX + kern.
- lastIndex := lastIndex + 1].
- ^self handleEndOfRunAt: stopIndex
-
  !

Item was added:
+ ----- Method: CharacterScanner>>scanCharactersFrom:to:in:rightX: (in category 'scanning') -----
+ scanCharactersFrom: startIndex to: stopIndex in: sourceString rightX: rightX
+ ^sourceString scanCharactersFrom: startIndex to: stopIndex with: self rightX: rightX font: font!

Item was changed:
  ----- Method: CharacterScanner>>setActualFont: (in category 'text attributes') -----
  setActualFont: aFont
  "Set the basal font to an isolated font reference."
 
+ xTable := aFont xTable.
+ map := aFont characterToGlyphMap.
+ font := aFont.!
- font := aFont!

Item was changed:
  ----- Method: CharacterScanner>>setFont (in category 'private') -----
  setFont
  | priorFont |
  "Set the font and other emphasis."
  priorFont := font.
+ text ifNotNil:[
- text == nil ifFalse:[
  emphasisCode := 0.
  kern := 0.
  indentationLevel := 0.
  alignment := textStyle alignment.
  font := nil.
  (text attributesAt: lastIndex forStyle: textStyle)
  do: [:att | att emphasizeScanner: self]].
+ font ifNil: [self setFont: textStyle defaultFontIndex].
+ self setActualFont: (font emphasized: emphasisCode).
- font == nil ifTrue:
- [self setFont: textStyle defaultFontIndex].
- font := font emphasized: emphasisCode.
  priorFont
  ifNotNil: [
  font = priorFont
  ifTrue:[
  "font is the same, perhaps the color has changed?
  We still want kerning between chars of the same
  font, but of different color. So add any pending kern to destX"
  destX := destX + (pendingKernX ifNil:[0])].
  destX := destX + priorFont descentKern].
  pendingKernX := 0. "clear any pending kern so there is no danger of it being added twice"
  destX := destX - font descentKern.
  "NOTE: next statement should be removed when clipping works"
  leftMargin ifNotNil: [destX := destX max: leftMargin].
  kern := kern - font baseKern.
 
  "Install various parameters from the font."
  spaceWidth := font widthOf: Space.!

Item was changed:
  ----- Method: CompositionScanner>>composeFrom:inRectangle:firstLine:leftSide:rightSide: (in category 'scanning') -----
  composeFrom: startIndex inRectangle: lineRectangle
  firstLine: firstLine leftSide: leftSide rightSide: rightSide
  "Answer an instance of TextLineInterval that represents the next line in the paragraph."
  | runLength stopCondition |
  "Set up margins"
  leftMargin := lineRectangle left.
  leftSide ifTrue: [leftMargin := leftMargin +
  (firstLine ifTrue: [textStyle firstIndent]
  ifFalse: [textStyle restIndent])].
  destX := spaceX := leftMargin.
  rightMargin := lineRectangle right.
  rightSide ifTrue: [rightMargin := rightMargin - textStyle rightIndent].
  lastIndex := startIndex. "scanning sets last index"
  destY := lineRectangle top.
  lineHeight := baseline := 0.  "Will be increased by setFont"
  line := (TextLine start: lastIndex stop: 0 internalSpaces: 0 paddingWidth: 0)
  rectangle: lineRectangle.
  self setStopConditions. "also sets font"
  runLength := text runLengthFor: startIndex.
  runStopIndex := (lastIndex := startIndex) + (runLength - 1).
  nextIndexAfterLineBreak := spaceCount := 0.
  lastBreakIsNotASpace := false.
  self handleIndentation.
  leftMargin := destX.
  line leftMargin: leftMargin.
 
  [stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
+ in: text string rightX: rightMargin.
- in: text string rightX: rightMargin stopConditions: stopConditions
- kern: kern.
  "See setStopConditions for stopping conditions for composing."
  self perform: stopCondition] whileFalse.
 
  ^ line
  lineHeight: lineHeight + textStyle leading
  baseline: baseline + textStyle leading!

Item was changed:
  ----- Method: DisplayScanner>>displayLine:offset:leftInRun: (in category 'scanning') -----
  displayLine: textLine offset: offset leftInRun: leftInRun
  "The call on the primitive (scanCharactersFrom:to:in:rightX:) will be interrupted according to an array of stop conditions passed to the scanner at which time the code to handle the stop condition is run and the call on the primitive continued until a stop condition returns true (which means the line has terminated).  leftInRun is the # of characters left to scan in the current run; when 0, it is time to call setStopConditions."
  | stopCondition nowLeftInRun startIndex string lastPos lineHeight stop |
  line := textLine.
  morphicOffset := offset.
  lineY := line top + offset y.
  lineHeight := line lineHeight.
  rightMargin := line rightMargin + offset x.
  lastIndex := line first.
  leftInRun <= 0 ifTrue: [self setStopConditions].
  leftMargin := (line leftMarginForAlignment: alignment) + offset x.
  destX := leftMargin.
  self fillTextBackground.
  lastDisplayableIndex := lastIndex := line first.
  leftInRun <= 0
  ifTrue: [nowLeftInRun := text runLengthFor: lastIndex]
  ifFalse: [nowLeftInRun := leftInRun].
  destY := lineY + line baseline - font ascent.
  runStopIndex := lastIndex + (nowLeftInRun - 1) min: line last.
  spaceCount := 0.
  string := text string.
  [
  "reset the stopping conditions of this displaying loop, and also the font."
  stopConditionsMustBeReset
  ifTrue:[self setStopConditions].
 
  "remember where this portion of the line starts"
  startIndex := lastIndex.
  lastPos := destX@destY.
 
  "find the end of this portion of the line"
  stopCondition := self scanCharactersFrom: lastIndex to: runStopIndex
+ in: string rightX: rightMargin.
- in: string rightX: rightMargin stopConditions: stopConditions
- kern: kern.
  "handle the stop condition - this will also set lastDisplayableIndex"
  stop := self perform: stopCondition.
 
  "display that portion of the line"
  lastDisplayableIndex >= startIndex ifTrue:[
  self displayString: string
  from: startIndex
  to: lastDisplayableIndex
  at: lastPos].
 
  "if the stop condition were true, stop the loop"
  stop
  ] whileFalse.
  ^ runStopIndex - lastIndex   "Number of characters remaining in the current run"!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

timrowledge

On 22-10-2013, at 7:01 PM, [hidden email] wrote:

> + map := aFont characterToGlyphMap.

Do we actually want this still? I know it is needed in terms of the ivar ordering, but that's a pity since it is a waste of time in all the cases I know about.

It's almost certainly an improvement to get the prim running again, but overall I *think* we'd do better by adding a new prim to BitBltPlugin, to sit alongside the primitiveDisplayString (which I see also requires a characterToGlyphMap at the moment. That way the bitbltplugin effectively becomes our StrikeFont renderer in the same fashion as the FreeTypePlugin works for FreeType fonts.

Has there ever been a case where that map was not effectively an identity map? I can see that there might be some appeal to mapping several characters to one glyph (like all non-printables to a null glyph) but has it ever been done that way?

This ties in with the two mantis reports I mentioned last night -
http://bugs.squeak.org/view.php?id=1372 
and
http://bugs.squeak.org/view.php?id=1342
since it would affect how we implement solutions.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Is reading in the bathroom considered Multi-Tasking?



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

Nicolas Cellier
Well, it's probable that all these indirections were too much, but restoring the primitive makes a difference with this mini-benchmark under interpreter VM:

| text |
text := Compiler evaluate: (FileStream fileNamed: 'text.st') contentsOfEntireFile.
MessageTally spyOn: [[100 timesRepeat: [(NewParagraph new)
        compose: text
        style: TextStyle default copy
        from: 1
        in: ( 0@0 corner: 569@9999999)]] timeToRun ].

with text extracted from "Working With Squeak" workspace, goes from 713ms down to 261ms with the primitive.
So it might be worth until you come with something better...

For COG, the same bench goes from 65ms to 49ms, so the primitive is not really necessary.
I'm pretty sure that Spur will change the numbers in favour of image-side code.


2013/10/22 tim Rowledge <[hidden email]>

On 22-10-2013, at 7:01 PM, [hidden email] wrote:

> +     map := aFont characterToGlyphMap.

Do we actually want this still? I know it is needed in terms of the ivar ordering, but that's a pity since it is a waste of time in all the cases I know about.

It's almost certainly an improvement to get the prim running again, but overall I *think* we'd do better by adding a new prim to BitBltPlugin, to sit alongside the primitiveDisplayString (which I see also requires a characterToGlyphMap at the moment. That way the bitbltplugin effectively becomes our StrikeFont renderer in the same fashion as the FreeTypePlugin works for FreeType fonts.

Has there ever been a case where that map was not effectively an identity map? I can see that there might be some appeal to mapping several characters to one glyph (like all non-printables to a null glyph) but has it ever been done that way?

This ties in with the two mantis reports I mentioned last night -
http://bugs.squeak.org/view.php?id=1372
and
http://bugs.squeak.org/view.php?id=1342
since it would affect how we implement solutions.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Is reading in the bathroom considered Multi-Tasking?






Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

timrowledge

On 22-10-2013, at 12:58 PM, Nicolas Cellier <[hidden email]> wrote:
> So it might be worth until you come with something better…

Oh that's certainly worth it for now. Good stuff.

I'm still interested in finding out about this -
> Has there ever been a case where that map was not effectively an identity map? I can see that there might be some appeal to mapping several characters to one glyph (like all non-printables to a null glyph) but has it ever been done that way?
Anyone? Bueller?

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
My computer NEVER cras



Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

J. Vuletich (mail lists)
You can check how it is used in Cuis.

Cheers,
Juan Vuletich

Quoting tim Rowledge <[hidden email]>:

>
> On 22-10-2013, at 12:58 PM, Nicolas Cellier  
> <[hidden email]> wrote:
>> So it might be worth until you come with something better…
>
> Oh that's certainly worth it for now. Good stuff.
>
> I'm still interested in finding out about this -
>> Has there ever been a case where that map was not effectively an  
>> identity map? I can see that there might be some appeal to mapping  
>> several characters to one glyph (like all non-printables to a null  
>> glyph) but has it ever been done that way?
> Anyone? Bueller?
>
> tim
> --
> tim Rowledge; [hidden email]; http://www.rowledge.org/tim
> My computer NEVER cras
>
>
>
>



Cheers,
Juan Vuletich


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

Eliot Miranda-2
In reply to this post by Nicolas Cellier
Hi Nicolas,


On Tue, Oct 22, 2013 at 12:58 PM, Nicolas Cellier <[hidden email]> wrote:
Well, it's probable that all these indirections were too much, but restoring the primitive makes a difference with this mini-benchmark under interpreter VM:

| text |
text := Compiler evaluate: (FileStream fileNamed: 'text.st') contentsOfEntireFile.
MessageTally spyOn: [[100 timesRepeat: [(NewParagraph new)
        compose: text
        style: TextStyle default copy
        from: 1
        in: ( 0@0 corner: 569@9999999)]] timeToRun ].

with text extracted from "Working With Squeak" workspace, goes from 713ms down to 261ms with the primitive.
So it might be worth until you come with something better...

For COG, the same bench goes from 65ms to 49ms, so the primitive is not really necessary.
I'm pretty sure that Spur will change the numbers in favour of image-side code.

Hmm, we need to be careful here.  Spur should speed up allocations, which include blocks, and at:put: on Arrays & Strings, etc, and garbage collection, but it doesn't speed up the basic execution engine.  So I doubt that it'll be any faster in Spur since the loop probably isn;t doing any allocations or at:put:'s, right?

2013/10/22 tim Rowledge <[hidden email]>

On 22-10-2013, at 7:01 PM, [hidden email] wrote:

> +     map := aFont characterToGlyphMap.

Do we actually want this still? I know it is needed in terms of the ivar ordering, but that's a pity since it is a waste of time in all the cases I know about.

It's almost certainly an improvement to get the prim running again, but overall I *think* we'd do better by adding a new prim to BitBltPlugin, to sit alongside the primitiveDisplayString (which I see also requires a characterToGlyphMap at the moment. That way the bitbltplugin effectively becomes our StrikeFont renderer in the same fashion as the FreeTypePlugin works for FreeType fonts.

Has there ever been a case where that map was not effectively an identity map? I can see that there might be some appeal to mapping several characters to one glyph (like all non-printables to a null glyph) but has it ever been done that way?

This ties in with the two mantis reports I mentioned last night -
http://bugs.squeak.org/view.php?id=1372
and
http://bugs.squeak.org/view.php?id=1342
since it would affect how we implement solutions.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Is reading in the bathroom considered Multi-Tasking?










--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

Nicolas Cellier
Ah, no, I was thinking that String>>at: and asciiValue would be accelerated

            char := sourceString at: lastIndex.
            ascii := char asciiValue + 1.


2013/10/23 Eliot Miranda <[hidden email]>
Hi Nicolas,


On Tue, Oct 22, 2013 at 12:58 PM, Nicolas Cellier <[hidden email]> wrote:
Well, it's probable that all these indirections were too much, but restoring the primitive makes a difference with this mini-benchmark under interpreter VM:

| text |
text := Compiler evaluate: (FileStream fileNamed: 'text.st') contentsOfEntireFile.
MessageTally spyOn: [[100 timesRepeat: [(NewParagraph new)
        compose: text
        style: TextStyle default copy
        from: 1
        in: ( 0@0 corner: 569@9999999)]] timeToRun ].

with text extracted from "Working With Squeak" workspace, goes from 713ms down to 261ms with the primitive.
So it might be worth until you come with something better...

For COG, the same bench goes from 65ms to 49ms, so the primitive is not really necessary.
I'm pretty sure that Spur will change the numbers in favour of image-side code.

Hmm, we need to be careful here.  Spur should speed up allocations, which include blocks, and at:put: on Arrays & Strings, etc, and garbage collection, but it doesn't speed up the basic execution engine.  So I doubt that it'll be any faster in Spur since the loop probably isn;t doing any allocations or at:put:'s, right?

2013/10/22 tim Rowledge <[hidden email]>

On 22-10-2013, at 7:01 PM, [hidden email] wrote:

> +     map := aFont characterToGlyphMap.

Do we actually want this still? I know it is needed in terms of the ivar ordering, but that's a pity since it is a waste of time in all the cases I know about.

It's almost certainly an improvement to get the prim running again, but overall I *think* we'd do better by adding a new prim to BitBltPlugin, to sit alongside the primitiveDisplayString (which I see also requires a characterToGlyphMap at the moment. That way the bitbltplugin effectively becomes our StrikeFont renderer in the same fashion as the FreeTypePlugin works for FreeType fonts.

Has there ever been a case where that map was not effectively an identity map? I can see that there might be some appeal to mapping several characters to one glyph (like all non-printables to a null glyph) but has it ever been done that way?

This ties in with the two mantis reports I mentioned last night -
http://bugs.squeak.org/view.php?id=1372
and
http://bugs.squeak.org/view.php?id=1342
since it would affect how we implement solutions.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Is reading in the bathroom considered Multi-Tasking?










--
best,
Eliot






Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Graphics-nice.274.mcz

Eliot Miranda-2



On Wed, Oct 23, 2013 at 5:51 AM, Nicolas Cellier <[hidden email]> wrote:
Ah, no, I was thinking that String>>at: and asciiValue would be accelerated


            char := sourceString at: lastIndex.
            ascii := char asciiValue + 1.

Oops, I'd forgotten that :-),  You're right, that should make some difference.
 


2013/10/23 Eliot Miranda <[hidden email]>
Hi Nicolas,


On Tue, Oct 22, 2013 at 12:58 PM, Nicolas Cellier <[hidden email]> wrote:
Well, it's probable that all these indirections were too much, but restoring the primitive makes a difference with this mini-benchmark under interpreter VM:

| text |
text := Compiler evaluate: (FileStream fileNamed: 'text.st') contentsOfEntireFile.
MessageTally spyOn: [[100 timesRepeat: [(NewParagraph new)
        compose: text
        style: TextStyle default copy
        from: 1
        in: ( 0@0 corner: 569@9999999)]] timeToRun ].

with text extracted from "Working With Squeak" workspace, goes from 713ms down to 261ms with the primitive.
So it might be worth until you come with something better...

For COG, the same bench goes from 65ms to 49ms, so the primitive is not really necessary.
I'm pretty sure that Spur will change the numbers in favour of image-side code.

Hmm, we need to be careful here.  Spur should speed up allocations, which include blocks, and at:put: on Arrays & Strings, etc, and garbage collection, but it doesn't speed up the basic execution engine.  So I doubt that it'll be any faster in Spur since the loop probably isn;t doing any allocations or at:put:'s, right?

2013/10/22 tim Rowledge <[hidden email]>

On 22-10-2013, at 7:01 PM, [hidden email] wrote:

> +     map := aFont characterToGlyphMap.

Do we actually want this still? I know it is needed in terms of the ivar ordering, but that's a pity since it is a waste of time in all the cases I know about.

It's almost certainly an improvement to get the prim running again, but overall I *think* we'd do better by adding a new prim to BitBltPlugin, to sit alongside the primitiveDisplayString (which I see also requires a characterToGlyphMap at the moment. That way the bitbltplugin effectively becomes our StrikeFont renderer in the same fashion as the FreeTypePlugin works for FreeType fonts.

Has there ever been a case where that map was not effectively an identity map? I can see that there might be some appeal to mapping several characters to one glyph (like all non-printables to a null glyph) but has it ever been done that way?

This ties in with the two mantis reports I mentioned last night -
http://bugs.squeak.org/view.php?id=1372
and
http://bugs.squeak.org/view.php?id=1342
since it would affect how we implement solutions.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
Is reading in the bathroom considered Multi-Tasking?










--
best,
Eliot










--
best,
Eliot