Running after a bugg

This commit is contained in:
SantiagoBragagnolo 2020-04-03 11:08:47 +00:00
parent 57cc92df10
commit c07b6f70b3
15 changed files with 1055 additions and 4 deletions

View File

@ -0,0 +1,13 @@
Extension { #name : #FormCanvas }
{ #category : #'*Grafoscopio' }
FormCanvas >> gfcParagraph: para bounds: bounds color: c [
| scanner |
self setPaintColor: c.
scanner := (port clippedBy: (bounds translateBy: origin)) gfcDisplayScannerFor: para
foreground: c background: Color transparent
ignoreColorChanges: false.
para drawOn: (self copyClipRect: bounds) using: scanner at: origin + bounds topLeft.
]

View File

@ -0,0 +1,9 @@
Extension { #name : #GrafPort }
{ #category : #'*Grafoscopio' }
GrafPort >> gfcDisplayScannerFor: para foreground: foreColor background: backColor ignoreColorChanges: shadowMode [
^ (GrafoscopioDisplayScanner new text: para text textStyle: para textStyle
foreground: foreColor background: backColor fillBlt: self
ignoreColorChanges: shadowMode)
setPort: self shallowCopy
]

View File

@ -1,5 +1,114 @@
Class {
#name : #GrafoscopioComposer,
#superclass : #Object,
#instVars : [
'text',
'styler',
'container',
'lines'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> actualWidth [
^ 50
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> calculateMaximumAmountOfCharactersToComposeStartingAt: anInteger [
self shouldBeImplemented.
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> calculateMaximumAmountOfCharactersToComposeStartingAt: startingY contemplating: delta [
| deltaX deltaY |
" This method is mean to restrict the amount of text to be processed. For knowing how much of the text is going to be processed, we calculate the size of a minimal character with the default font.
This strategy is not really the best, since we should check with the smallest font used in the text instead of using the default.
But by the time being this code should beenough, knowning that for a text drawn in a scrolled area we have almost infinite space. We should mind this bug first then come back .
"
deltaX := delta + (((styler fontAt: styler defaultFontIndex) linearWidthOf: $.) roundDownTo: 1).
deltaY := (styler fontAt: styler defaultFontIndex) height.
^ (container width / deltaX) * ((container height - startingY ) / deltaY ).
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> composeLinesFrom: start to: stop delta: delta into: lineColl priorLines: priorLines atY: startingY [
| maxChars |
stop > 0
ifTrue: [ self haltOnce ].
" we set the lines collection "
lines := lineColl.
" we do calculate the size of an average "
maxChars := self
calculateMaximumAmountOfCharactersToComposeStartingAt: startingY
contemplating: delta.
" we should care about really fragmenting the composittion once we have this assert failling
should be enough to stop the inspection of the tree nodes once the from > maxChars.
something like:
text allSegmentsOfLinesUpTo: [: from : to | from > maxChars] collect: [ :from :to | GrafoscopioLine new from: from to: to].
for this we should implement #allSegmentsOfLinesUpTo:collect:
"
self assert: stop - start < maxChars.
lines
addAll:
(text
allSegmentsOfLinesCollect: [ :from :to | GrafoscopioLine new from: from to: to ])
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> container: aRectangle [
container := aRectangle
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> cursorWidth: anInteger [
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> emphasisHere: anObject [
self assert: (anObject isNil or: [ anObject isArray ])
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> lineIndexForPoint: aPoint [
^ 1
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> lineIndexOfCharacterIndex: anInteger [
^ 1
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> lines [
^ lines ifNil: [ lines := { GrafoscopioLine new }]
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> replaceFrom: anInteger to: anInteger2 with: aCollection [
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> text [
^ text
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> text: aCollection [
text := aCollection
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> textStyle: aTextStyle [
styler := aTextStyle
]

View File

@ -0,0 +1,417 @@
Class {
#name : #GrafoscopioDisplayScanner,
#superclass : #Object,
#instVars : [
'destX',
'lastIndex',
'stopConditions',
'text',
'textStyle',
'alignment',
'leftMargin',
'rightMargin',
'font',
'line',
'runStopIndex',
'spaceCount',
'spaceWidth',
'emphasisCode',
'kern',
'pendingKernX',
'bitBlt',
'lineY',
'runX',
'foregroundColor',
'fillBlt',
'morphicOffset',
'ignoreColorChanges',
'destY'
],
#classVars : [
'DefaultStopConditions',
'PaddedSpaceCondition'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #queries }
GrafoscopioDisplayScanner class >> defaultFont [
^ TextStyle defaultFont
]
{ #category : #'class initialization' }
GrafoscopioDisplayScanner class >> initialize [
"
RubCharacterScanner initialize
"
| a |
a := RubTextStopConditions new.
a at: 1 + 1 put: #embeddedObject.
a at: Character tab asciiValue + 1 put: #tab.
a at: Character cr asciiValue + 1 put: #cr.
a at: Character lf asciiValue + 1 put: #cr.
DefaultStopConditions := a .
PaddedSpaceCondition := a copy.
PaddedSpaceCondition at: Character space asciiValue + 1 put: #paddedSpace.
]
{ #category : #private }
GrafoscopioDisplayScanner >> addEmphasis: code [
"Set the bold-ital-under-strike emphasis."
emphasisCode := emphasisCode bitOr: code
]
{ #category : #private }
GrafoscopioDisplayScanner >> addKern: kernDelta [
"Set the current kern amount."
kern := kern + kernDelta
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> cr [
"When a carriage return is encountered, simply increment the pointer
into the paragraph."
pendingKernX := 0.
(lastIndex < text size and: [(text at: lastIndex) = Character cr and: [(text at: lastIndex+1) = Character lf]])
ifTrue: [lastIndex := lastIndex + 2]
ifFalse: [lastIndex := lastIndex + 1].
^false
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> crossedX [
"This condition will sometimes be reached 'legally' during display, when,
for instance the space that caused the line to wrap actually extends over
the right boundary. This character is allowed to display, even though it
is technically outside or straddling the clipping ectangle since it is in
the normal case not visible and is in any case appropriately clipped by
the scanner."
^ true
]
{ #category : #displaying }
GrafoscopioDisplayScanner >> displayEmbeddedForm: aForm [
aForm
displayOn: bitBlt destForm
at: destX @ (lineY + line baseline - aForm height)
clippingBox: bitBlt clipRect
rule: Form blend
fillColor: Color white
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> 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 baselineY lastPos bundle |
line := textLine.
morphicOffset := offset.
lineY := textLine top + offset y.
rightMargin := textLine rightMargin + offset x.
lastIndex := textLine first.
leftInRun <= 0 ifTrue: [self setStopConditions].
leftMargin := (textLine leftMarginForAlignment: alignment) + offset x.
destX := runX := leftMargin.
self fillTextBackgroundAt: lineY .
lastIndex := textLine first.
leftInRun <= 0
ifTrue: [nowLeftInRun := text runLengthFor: lastIndex]
ifFalse: [nowLeftInRun := leftInRun].
baselineY := lineY + textLine baseline.
destY := baselineY - font ascent.
runStopIndex := lastIndex + (nowLeftInRun - 1) min: textLine last.
spaceCount := 0.
[
startIndex := lastIndex.
lastPos := destX@destY.
bundle := textLine scanAndDrawCharactersFrom: lastIndex to: runStopIndex
in: text rightX: rightMargin stopConditions: stopConditions
kern: kern firstDestX:destX style: textStyle on: bitBlt at: lastPos withBaseline: baselineY.
lastIndex := bundle first.
stopCondition := bundle second.
pendingKernX := bundle third.
destX := bundle fourth.
"textLine display: text textStyle: textStyle on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: (stopCondition == #endOfRun ifTrue:[lastIndex] ifFalse:[lastIndex-1]) ."
" textLine display: text with: font with: kern on: bitBlt at: lastPos destX: destX baseline: baselineY startIndex: startIndex lastIndex:(stopCondition == #endOfRun ifTrue:[lastIndex] ifFalse:[lastIndex-1]) emphasisCode: emphasisCode."
self perform: stopCondition.
] whileFalse.
^ runStopIndex - lastIndex "Number of characters remaining in the current run"
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> embeddedObject [
| savedIndex |
savedIndex := lastIndex.
text
attributesAt: lastIndex
do: [ :attr |
attr anchoredMorph
ifNotNil: [
"Following may look strange but logic gets reversed.
If the morph fits on this line we're not done (return false for true)
and if the morph won't fit we're done (return true for false)"
(self placeEmbeddedObject: attr anchoredMorph)
ifFalse: [ ^ true ] ] ].
lastIndex := savedIndex + 1. "for multiple(!) embedded morphs"
^ false
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> endOfRun [
"The end of a run in the display case either means that there is actually
a change in the style (run code) to be associated with the string or the
end of this line has been reached."
| runLength |
lastIndex = line last ifTrue: [^true].
runX := destX.
runLength := text runLengthFor: (lastIndex := lastIndex + 1).
runStopIndex := lastIndex + (runLength - 1) min: line last.
self setStopConditions.
^ false
]
{ #category : #displaying }
GrafoscopioDisplayScanner >> fillTextBackgroundAt: aPosition [
fillBlt == nil ifFalse:
["Not right"
fillBlt destX: line left destY: aPosition
width: line width left height: line lineHeight; copyBits].
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> initialize [
super initialize.
destX := destY := leftMargin := 0
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> isBreakableAt: index in: sourceString in: encodingClass [
^ false.
]
{ #category : #'text constants' }
GrafoscopioDisplayScanner >> justified [
^ 3
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> leadingTab [
"return true if only tabs lie to the left"
line first to: lastIndex do:
[:i | (text at: i) == Character tab ifFalse: [^ false]].
^ true
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> nextTabXFrom: anX [
"Tab stops are distances from the left margin. Set the distance into the
argument, anX, normalized for the paragraph's left margin."
| normalizedX tabX mx |
mx := 9999.
normalizedX := anX - leftMargin.
tabX := self tabWidth.
[ tabX <= normalizedX and: [ tabX < mx ] ] whileTrue: [ tabX := tabX + self tabWidth ].
^ tabX < mx
ifTrue: [ leftMargin + tabX min: rightMargin ]
ifFalse: [ rightMargin ]
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> paddedSpace [
"Each space is a stop condition when the alignment is right justified.
Padding must be added to the base width of the space according to
which space in the line this space is and according to the amount of
space that remained at the end of the line when it was composed."
spaceCount := spaceCount + 1.
destX := destX + spaceWidth + (line justifiedPadFor: spaceCount font: font).
lastIndex := lastIndex + 1.
pendingKernX := 0.
^ false
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> placeEmbeddedObject: anchoredMorph [
anchoredMorph relativeTextAnchorPosition ifNotNil:[
anchoredMorph position:
anchoredMorph relativeTextAnchorPosition +
(anchoredMorph owner bounds origin x @ 0)
- (0@morphicOffset y) + (0@lineY).
^true
].
(self superPlaceEmbeddedObject: anchoredMorph) ifFalse: [^ false].
anchoredMorph isMorph ifTrue: [
anchoredMorph position: ((destX - anchoredMorph width)@lineY) - morphicOffset
] ifFalse: [
destY := lineY.
runX := destX.
anchoredMorph
displayOn: bitBlt destForm
at: destX - anchoredMorph width @ destY
clippingBox: bitBlt clipRect
rule: Form blend
fillColor: Color white
].
^ true
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> registerBreakableIndex [
"Record left x and character index of the line-wrappable point.
The default implementation here does nothing."
^ false.
]
{ #category : #private }
GrafoscopioDisplayScanner >> setActualFont: aFont [
"Set the basal font to an isolated font reference."
font := aFont
]
{ #category : #private }
GrafoscopioDisplayScanner >> setAlignment: style [
alignment := style.
]
{ #category : #private }
GrafoscopioDisplayScanner >> setConditionArray: aSymbol [
aSymbol == #paddedSpace ifTrue: [^stopConditions := PaddedSpaceCondition "copy"].
aSymbol == nil ifTrue: [^stopConditions := DefaultStopConditions "copy"].
self error: 'undefined stopcondition for space character'.
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setFont [
| priorFont baselineY |
foregroundColor := Smalltalk ui theme textColor.
text ifNil:[ ^ self setActualFont: textStyle defaultFont ].
"Set the font and other emphasis."
priorFont := font.
text == nil
ifFalse: [
emphasisCode := 0.
kern := 0.
alignment := textStyle alignment.
font := nil.
(text attributesAt: lastIndex forStyle: textStyle) do: [ :att | att emphasizeScanner: self ] ].
font == nil
ifTrue: [ self setActualFont: textStyle defaultFont ].
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: Character space. " map := font characterToGlyphMap."
stopConditions := DefaultStopConditions.
font installOn: bitBlt foregroundColor: foregroundColor backgroundColor: Color transparent.
text ifNotNil:[
destY := lineY + line baseline - font ascent].
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setFont: aNumber [
self setActualFont: (textStyle fontAt: aNumber)
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setPort: aBitBlt [
"Install the BitBlt to use"
bitBlt := aBitBlt.
bitBlt sourceX: 0; width: 0. "Init BitBlt so that the first call to a primitive will not fail"
bitBlt sourceForm: nil. "Make sure font installation won't be confused"
]
{ #category : #'stop conditions' }
GrafoscopioDisplayScanner >> setStopConditions [
"Set the font and the stop conditions for the current run."
self setFont.
self setConditionArray: (alignment = self justified ifTrue: [#paddedSpace]).
"
alignment = self justified ifTrue: [
stopConditions == DefaultStopConditions
ifTrue:[stopConditions := stopConditions copy].
stopConditions at: Character space asciiValue + 1 put: #paddedSpace]
"
]
{ #category : #scanning }
GrafoscopioDisplayScanner >> superPlaceEmbeddedObject: anchoredMorph [
"Place the anchoredMorph or return false if it cannot be placed.
In any event, advance destX by its width."
| w |
"Workaround: The following should really use #textAnchorType"
anchoredMorph relativeTextAnchorPosition ifNotNil:[^true].
destX := destX + (w := anchoredMorph width).
(destX > rightMargin and: [(leftMargin + w) <= rightMargin])
ifTrue: ["Won't fit, but would on next line"
^ false].
lastIndex := lastIndex + 1.
^ true
]
{ #category : #private }
GrafoscopioDisplayScanner >> text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode [
text := t.
textStyle := ts.
foregroundColor := foreColor.
backColor isTransparent
ifFalse: [ fillBlt := blt.
fillBlt fillColor: backColor ].
ignoreColorChanges := shadowMode
]
{ #category : #private }
GrafoscopioDisplayScanner >> textColor: textColor [
ignoreColorChanges ifTrue: [^ self].
foregroundColor := textColor
]
{ #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> widthOf: char inFont: aFont [
(char isMemberOf: CombinedChar) ifTrue: [
^ aFont widthOf: char base.
] ifFalse: [
^ aFont widthOf: char.
].
]

View File

@ -0,0 +1,74 @@
Class {
#name : #GrafoscopioDisplayScanner2,
#superclass : #Object,
#instVars : [
'text',
'textStyle',
'foregroundColor',
'backgroundColor',
'fillBlt',
'ignoreColorChanges',
'bitBlt'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #private }
GrafoscopioDisplayScanner2 >> displayLine: line offset: offset leftInRun2: leftInRun [
fillBlt == nil
ifFalse: [ "Not right"
fillBlt
destX: line left
destY: 100
width: 300
height: 30;
copyBits ].
^ line
display: text
on: bitBlt
with: offset
using: textStyle
]
{ #category : #private }
GrafoscopioDisplayScanner2 >> displayLine: line offset: offset leftInRun: leftInRun [
fillBlt == nil
ifFalse: [ "Not right"
fillBlt
destX: line left
destY: 100
width: 300
height: 30;
copyBits ].
^ line
display: text
on: bitBlt
with: offset
using: textStyle
]
{ #category : #'reflective operations' }
GrafoscopioDisplayScanner2 >> doesNotUnderstand: something [
self halt.
]
{ #category : #'as yet unclassified' }
GrafoscopioDisplayScanner2 >> setPort: aBitBlt [
"Install the BitBlt to use"
bitBlt := aBitBlt.
bitBlt sourceX: 0; width: 0. "Init BitBlt so that the first call to a primitive will not fail"
bitBlt sourceForm: nil. "Make sure font installation won't be confused"
]
{ #category : #private }
GrafoscopioDisplayScanner2 >> text: t textStyle: ts foreground: foreColor background: backColor fillBlt: blt ignoreColorChanges: shadowMode [
text := t.
textStyle := ts.
foregroundColor := foreColor.
fillBlt := blt.
(backgroundColor := backColor) isTransparent
ifFalse: [ fillBlt fillColor: backgroundColor ].
ignoreColorChanges := shadowMode
]

View File

@ -4,6 +4,24 @@ Class {
#category : #'Grafoscopio-Rub'
}
{ #category : #private }
GrafoscopioEditingArea >> drawSubmorphsOn: aCanvas [
"Display submorphs back to front"
| drawBlock |
submorphs isEmpty ifTrue: [^self].
drawBlock := [:canvas | submorphs reverseDo: [:m | canvas fullDrawMorph: m]].
self clipSubmorphs
ifTrue: [aCanvas clipBy: (aCanvas clipRect intersect: self clippingBounds ifNone: [ ^ self ]) during: drawBlock]
ifFalse: [drawBlock value: aCanvas].
"Draw the focus here since we are using inset bounds
for the focus rectangle."
aCanvas gfcParagraph: self paragraph bounds: self drawingBounds color: self textColor.
(scrollPane isNil and: [ self readOnly not and: [ self hasKeyboardFocus or: [ self hasFindReplaceFocus ] ] ])
ifTrue: [self drawKeyboardFocusOn: aCanvas ]
]
{ #category : #private }
GrafoscopioEditingArea >> newParagraph [
| newParagraph |

View File

@ -0,0 +1,227 @@
Class {
#name : #GrafoscopioLine,
#superclass : #Object,
#instVars : [
'from',
'to',
'fontCode',
'lastUsedConfiguration'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #'as yet unclassified' }
GrafoscopioLine >> baseline [
^ 10
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> bottom [
^ 10
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> bottomRight [
^ self right@ self bottom
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> configurationFor: text with: style at: lastIndex [
| attributes |
attributes := text attributesAt: lastIndex forStyle: style.
(lastUsedConfiguration isNotNil and: [lastUsedConfiguration attributes = attributes ]) ifFalse: [
lastUsedConfiguration := GrafoscopioLineConfiguration new.
lastUsedConfiguration loadDefaultsFromStyle: style and: attributes.
.
].
^ lastUsedConfiguration .
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> display: text textStyle: style on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: lastIndex [
| configuration kern font emphasisCode |
configuration := self configurationFor: text with: style at: lastIndex .
kern := configuration kern.
font := configuration font.
emphasisCode := configuration emphasisCode.
lastIndex >= startIndex
ifTrue: [ bitBlt
displayString: text string
from: startIndex
to: lastIndex
at: lastPos
kern: kern
baselineY: baselineY
font: font ].
(emphasisCode allMask: 4)
ifTrue: [ font
displayUnderlineOn: bitBlt
from: lastPos x @ baselineY
to: destX @ baselineY ].
(emphasisCode allMask: 16)
ifTrue: [ font
displayStrikeoutOn: bitBlt
from: lastPos x @ baselineY
to: destX @ baselineY ]
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> first [
^ from
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> fontCodeFor: aGrafoscopioPillarASText [
fontCode
ifNil: [ (aGrafoscopioPillarASText runs at: self first)
do: [ :d | d emphasizeScanner: self ] ].
^ fontCode
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> from: anInteger to: anInteger2 [
from := anInteger.
to := anInteger2
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> height [
^ 30
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> last [
^ to
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> left [
^ 1
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> leftMargin [
^ self left
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> leftMarginForAlignment: anInteger [
^ 1
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> lineHeight [
^ 30
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> right [
^ 10000
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> rightMargin [
^ self right
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> scanAndDrawCharactersFrom: startIndex to: stopIndex in: text rightX: rightX stopConditions: stopConditions kern: kernDelta firstDestX:d style: textStyle on: bitBlt at: lastPos withBaseline: baselineY [
|bundle lastIndex stopCondition destX |
bundle := self scanCharactersFrom: startIndex to: stopIndex
in: text rightX: rightX stopConditions: stopConditions
kern: kernDelta firstDestX:d.
lastIndex := bundle first.
stopCondition := bundle second.
destX := bundle fourth.
self display: text textStyle: textStyle on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: (stopCondition == #endOfRun ifTrue:[lastIndex] ifFalse:[lastIndex-1]) .
^ bundle
]
{ #category : #scanning }
GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: text rightX: rightX stopConditions: stops kern: kernDelta firstDestX:d [
| ascii encoding f nextDestX maxAscii startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun font lastIndex pendingKernX destX spaceWidth source |
source := text string.
startIndex > stopIndex
ifTrue: [ lastIndex := stopIndex.
^ {lastIndex . stops endOfRun . 0 . d } ].
lastIndex := startIndex.
startEncoding := (source at: startIndex) leadingChar.
" font := self fontFor: text at: startIndex."
destX := d .
font ifNil: [font := TextStyle defaultFont fontArray at: 1].
font isFontSet ifTrue: [
f := [font fontArray at: startEncoding + 1]
on: Exception do: [:ex | nil].
f ifNil: [ f := font fontArray at: 1].
maxAscii := f maxAscii.
spaceWidth := f widthOf: Character space.
] ifFalse: [
maxAscii := font maxAscii.
].
floatDestX := destX.
widthAndKernedWidth := Array new: 2.
atEndOfRun := false.
[lastIndex <= stopIndex] whileTrue: [
encoding := (source at: lastIndex) leadingChar.
encoding ~= startEncoding ifTrue: [lastIndex := lastIndex - 1. ^ stops endOfRun].
ascii := (source at: lastIndex) charCode.
ascii > maxAscii ifTrue: [ascii := maxAscii].
(encoding = 0 and: [ascii < stops size and: [(stops at: ascii + 1) ~~ nil]]) ifTrue: [
self haltOnce.
^ {lastIndex .(stops at: ascii + 1) . pendingKernX . destX }].
nextChar := (lastIndex + 1 <= stopIndex)
ifTrue:[source at: lastIndex + 1]
ifFalse:[
atEndOfRun := true.
"if there is a next char in sourceString, then get the kern
and store it in pendingKernX"
lastIndex + 1 <= source size
ifTrue:[source at: lastIndex + 1]
ifFalse:[ nil]].
font
widthAndKernedWidthOfLeft: (source at: lastIndex)
right: nextChar
into: widthAndKernedWidth.
nextDestX := floatDestX + (widthAndKernedWidth at: 1).
nextDestX > rightX ifTrue: [^ {lastIndex . stops crossedX . pendingKernX . destX }].
floatDestX := floatDestX + kernDelta + (widthAndKernedWidth at: 2).
atEndOfRun
ifTrue:[
pendingKernX := (widthAndKernedWidth at: 2) - (widthAndKernedWidth at: 1).
floatDestX := floatDestX - pendingKernX].
destX := floatDestX .
lastIndex := lastIndex + 1.
].
lastIndex := stopIndex.
^ {lastIndex . stops endOfRun . pendingKernX . destX }
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> setFont: anInteger [
fontCode := anInteger
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> size [
^ (self last - self first ) + 1
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> top [
^ 1
]
{ #category : #'as yet unclassified' }
GrafoscopioLine >> topLeft [
^ self left @ self top
]

View File

@ -0,0 +1,59 @@
Class {
#name : #GrafoscopioLineConfiguration,
#superclass : #Object,
#instVars : [
'emphasisCode',
'kern',
'alignment',
'font',
'attributes',
'style'
],
#category : #'Grafoscopio-Rub'
}
{ #category : #'as yet unclassified' }
GrafoscopioLineConfiguration >> attributes [
^ attributes
]
{ #category : #'as yet unclassified' }
GrafoscopioLineConfiguration >> emphasisCode [
^ emphasisCode
]
{ #category : #'as yet unclassified' }
GrafoscopioLineConfiguration >> font [
^ font
]
{ #category : #initialization }
GrafoscopioLineConfiguration >> initialize [
super initialize.
emphasisCode := 0.
kern := 0.
]
{ #category : #'as yet unclassified' }
GrafoscopioLineConfiguration >> kern [
^ kern
]
{ #category : #initialization }
GrafoscopioLineConfiguration >> loadDefaultsFromStyle: aStyle [
alignment := aStyle alignment.
]
{ #category : #'as yet unclassified' }
GrafoscopioLineConfiguration >> loadDefaultsFromStyle: aTextStyle and: aCollection [
attributes := aCollection.
style := aTextStyle.
self loadDefaultsFromStyle: aTextStyle.
attributes do: [ : att | att emphasizeScanner: self ].
]
{ #category : #'as yet unclassified' }
GrafoscopioLineConfiguration >> setFont: aNumber [
font := style fontAt: aNumber
]

View File

@ -4,6 +4,22 @@ Class {
#category : #'Grafoscopio-Rub'
}
{ #category : #'accessing composer' }
GrafoscopioParagraph >> drawOn: aCanvas using: aDisplayScanner at: aPosition [
"Send all visible lines to the displayScanner for display"
| offset leftInRun line visibleRectangle |
self drawingEnabled
ifFalse: [ ^ self ].
visibleRectangle := aCanvas clipRect.
offset := (aPosition - self position) truncated.
leftInRun := 0.
(self lineIndexForPoint: visibleRectangle topLeft) to: (self lineIndexForPoint: visibleRectangle bottomRight) do: [ :i |
line := self lines at: i.
line first <= line last
ifTrue: [ leftInRun := aDisplayScanner displayLine: line offset: offset leftInRun: leftInRun ] ]
]
{ #category : #'accessing composer' }
GrafoscopioParagraph >> newComposer [
^ GrafoscopioComposer new

View File

@ -23,7 +23,8 @@ GrafoscopioPillarASText class >> openExample [
GrafoscopioPillarASText class >> pillarExample [
^ PRPillarParser
parse:
'!! About Pillar
'!!
About Pillar
!!
Pillar is a system to manage documents (books, presentations, and web sites). From a common format, it is able to generate documents in multiple formats (html, markdown, latex, AsciiDoc).
It is composed of several modules such as importers, transformers, document model and outputers.
@ -81,6 +82,50 @@ GrafoscopioPillarASText >> allRangesOfSubstring: aString [
^ { }
]
{ #category : #removing }
GrafoscopioPillarASText >> allSegmentsOfLinesCollect: aBlock [
| return |
return := OrderedCollection new.
self
allTextNodesDo:
[ :node | return add: (aBlock value: node textStart value: node textStop) ].
^ return
]
{ #category : #removing }
GrafoscopioPillarASText >> allSegmentsOfLinesDo: aBlock [
^ self
allTextNodesDo: [ :node | aBlock value: node textStart value: node textStop ]
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> allTextNodes [
^ self allTextNodesFrom: ast
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> allTextNodesDo: aBlock [
^ self allTextNodesFrom: ast do: aBlock
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> allTextNodesFrom: aNode [
^ aNode hasChildren
ifFalse: [ aNode isTextOrLineBreak
ifTrue: [ {aNode} ]
ifFalse: [ {} ] ]
ifTrue:
[ aNode children flatCollect: [ :n | self allTextNodesFrom: n ] ]
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> allTextNodesFrom: aNode do: aBlock [
^ aNode hasChildren
ifFalse: [ aNode isTextOrLineBreak
ifTrue: [ aBlock value: aNode ] ]
ifTrue: [ aNode children do: [ :n | self allTextNodesFrom: n do: aBlock ] ]
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> ast: aPRDocument [
ast := aPRDocument.
@ -96,10 +141,8 @@ GrafoscopioPillarASText >> ast: aPRDocument [
GrafoscopioPillarASText >> at: anInteger [
| node |
(anInteger > self size or: [ anInteger < 1 ])
ifTrue: [ ^ self errorSubscriptBounds: anInteger ].
ifTrue: [ ^ self errorSubscriptBounds: anInteger ].
node := self detectAstNodeFor: anInteger in: ast.
^ node text at: anInteger - node textStart +1
@ -132,6 +175,30 @@ GrafoscopioPillarASText >> detectAstNodeFor: anInteger in: aNode [
ifFalse: [ lastNode := aNode ]
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> detectAstNodesBetween: from and: to in: aNode [
| children childrenStream currentNode |
aNode hasChildren ifFalse: [ ^ {aNode} ].
childrenStream := aNode children readStream.
children := OrderedCollection new.
[ childrenStream atEnd not and: [ (currentNode :=childrenStream next) textStart < to ] ] whileTrue:[
currentNode textStart >= from ifTrue: [
children addAll: (self detectAstNodesBetween: from and: to in: currentNode ) .
].
].
^ children.
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> extractStringFrom: aPoisition to: anOtherPosition [
^ String
streamContents: [ :str |
(self detectAstNodesBetween: aPoisition and: anOtherPosition in: ast)
inject: str
into: [ :stream :each | stream nextPutAll: each text . stream ] ]
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASText >> removeAttribute: att from: start to: stop [

View File

@ -24,6 +24,16 @@ GrafoscopioPillarASTextStringDecorator >> copyFrom: one to: two [
{ #category : #'as yet unclassified' }
GrafoscopioPillarASTextStringDecorator >> isByteString [
^ false
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASTextStringDecorator >> isEmpty [
^ text isEmpty
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASTextStringDecorator >> isWideString [
^ true
]

View File

@ -33,6 +33,11 @@ GrafoscopioPillarASTextStringProjectionDecorator >> from: anInteger [
from := anInteger
]
{ #category : #'as yet unclassified' }
GrafoscopioPillarASTextStringProjectionDecorator >> isEmpty [
^ from <= to
]
{ #category : #accessing }
GrafoscopioPillarASTextStringProjectionDecorator >> size [
^ to - from

View File

@ -1,5 +1,15 @@
Extension { #name : #PRDocumentItem }
{ #category : #'*Grafoscopio' }
PRDocumentItem >> isLineBreak [
^ false
]
{ #category : #'*Grafoscopio' }
PRDocumentItem >> isTextOrLineBreak [
^ false
]
{ #category : #'*Grafoscopio' }
PRDocumentItem >> textSize [
^ self textStop - self textStart

View File

@ -0,0 +1,11 @@
Extension { #name : #PRLineBreak }
{ #category : #'*Grafoscopio' }
PRLineBreak >> isLineBreak [
^ true
]
{ #category : #'*Grafoscopio' }
PRLineBreak >> isTextOrLineBreak [
^ true
]

View File

@ -0,0 +1,6 @@
Extension { #name : #PRText }
{ #category : #'*Grafoscopio' }
PRText >> isTextOrLineBreak [
^ true
]