Commit before going to previous experiment. fed up of the scanner by the time being

This commit is contained in:
SantiagoBragagnolo 2020-04-07 12:38:44 +00:00
parent c07b6f70b3
commit 447665261c
10 changed files with 382 additions and 124 deletions

View File

@ -12,12 +12,7 @@ Class {
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioComposer >> actualWidth [ GrafoscopioComposer >> actualWidth [
^ 50 ^ (lines collect: [ :l | l approximateWidth ]) max
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> calculateMaximumAmountOfCharactersToComposeStartingAt: anInteger [
self shouldBeImplemented.
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
@ -38,11 +33,47 @@ GrafoscopioComposer >> calculateMaximumAmountOfCharactersToComposeStartingAt: st
^ (container width / deltaX) * ((container height - startingY ) / deltaY ). ^ (container width / deltaX) * ((container height - startingY ) / deltaY ).
] ]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> charWidthForCharIndex: idx [
| font |
text ifNil: [ ^ 1 ].
font := styler
fontAt:
((text runs at: idx) detect: [ :a | a isKindOf: TextFontChange ])
fontNumber.
^ font widthOf: (text at: idx)
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> composeLinesFrom: from to: to [
| genLines width charWidth lastAdded maxWidth |
genLines := OrderedCollection new.
width := 0.
lastAdded := from.
maxWidth := container width.
from to: to do: [ :i |
charWidth := self charWidthForCharIndex: i.
width + charWidth > maxWidth
ifTrue: [ genLines
add:
(GrafoscopioLine new
from: lastAdded
to: i - 1
text: text
styler: styler;
yourself).
lastAdded := i.
width := 0
].
width := width + charWidth
].
^ genLines
]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioComposer >> composeLinesFrom: start to: stop delta: delta into: lineColl priorLines: priorLines atY: startingY [ GrafoscopioComposer >> composeLinesFrom: start to: stop delta: delta into: lineColl priorLines: priorLines atY: startingY [
| maxChars | | maxChars stackedY bounding |
stop > 0
ifTrue: [ self haltOnce ].
" we set the lines collection " " we set the lines collection "
lines := lineColl. lines := lineColl.
" we do calculate the size of an average " " we do calculate the size of an average "
@ -56,11 +87,28 @@ GrafoscopioComposer >> composeLinesFrom: start to: stop delta: delta into: lineC
text allSegmentsOfLinesUpTo: [: from : to | from > maxChars] collect: [ :from :to | GrafoscopioLine new from: from to: to]. text allSegmentsOfLinesUpTo: [: from : to | from > maxChars] collect: [ :from :to | GrafoscopioLine new from: from to: to].
for this we should implement #allSegmentsOfLinesUpTo:collect: for this we should implement #allSegmentsOfLinesUpTo:collect:
" "
stackedY := startingY.
self assert: stop - start < maxChars. self assert: stop - start < maxChars.
bounding := container.
text
allSegmentsOfLinesDo: [ :from :to |
| h |
(self composeLinesFrom: from to: to)
do: [ :line |
lines add: line.
h := line height.
line
bounds:
(bounding origin x @ stackedY
corner: bounding corner x @ (stackedY + h)).
stackedY := stackedY + h ] ].
lines lines
addAll: ifEmpty: [ lines
(text add:
allSegmentsOfLinesCollect: [ :from :to | GrafoscopioLine new from: from to: to ]) (GrafoscopioLine new
from: 1 to: 1;
bounds: (0 @ 0 corner: 0 @ 0);
yourself) ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
@ -79,13 +127,45 @@ GrafoscopioComposer >> emphasisHere: anObject [
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioComposer >> lineIndexForPoint: aPoint [ GrafoscopioComposer >> fastFindFirstLineIndexSuchThat: lineBlock [
^ 1 "Perform a binary search of the lines array and return the index
of the first element for which lineBlock evaluates as true.
This assumes the condition is one that goes from false to true for
increasing line numbers (as, eg, yval > somey or start char > somex).
If lineBlock is not true for any element, return size+1."
| index low high |
low := 1.
high := lines size.
[index := high + low // 2.
low > high]
whileFalse:
[(lineBlock value: (lines at: index))
ifTrue: [high := index - 1]
ifFalse: [low := index + 1]].
^ low
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioComposer >> lineIndexOfCharacterIndex: anInteger [ GrafoscopioComposer >> lineIndexForPoint: aPoint [
^ 1 "Answer the index of the line in which to select the character nearest to aPoint."
| i py |
py := aPoint y truncated.
"Find the first line at this y-value"
i := (self fastFindFirstLineIndexSuchThat: [:line | line bottom > py]) min: self lines size.
"Now find the first line at this x-value"
[i < self lines size and: [(self lines at: i+1) top = (self lines at: i) top
and: [aPoint x >= (self lines at: i+1) left]]]
whileTrue: [i := i + 1].
^ i
]
{ #category : #'as yet unclassified' }
GrafoscopioComposer >> lineIndexOfCharacterIndex: characterIndex [
^ (self
fastFindFirstLineIndexSuchThat:
[ :line | line first >= characterIndex and: [ line last <= characterIndex ] ])
- 1 max: 1
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }

View File

@ -72,7 +72,7 @@ GrafoscopioDisplayScanner >> addKern: kernDelta [
{ #category : #'stop conditions' } { #category : #'stop conditions' }
GrafoscopioDisplayScanner >> cr [ GrafoscopioDisplayScanner >> cr [
"When a carriage return is encountered, simply increment the pointer "When a carriage return is encountered, simply increment the pointer
into the paragraph." into the paragraph."
pendingKernX := 0. pendingKernX := 0.
(lastIndex < text size and: [(text at: lastIndex) = Character cr and: [(text at: lastIndex+1) = Character lf]]) (lastIndex < text size and: [(text at: lastIndex) = Character cr and: [(text at: lastIndex+1) = Character lf]])
@ -105,33 +105,32 @@ GrafoscopioDisplayScanner >> displayEmbeddedForm: aForm [
] ]
{ #category : #scanning } { #category : #scanning }
GrafoscopioDisplayScanner >> displayLine: textLine offset: offset leftInRun: leftInRun [ GrafoscopioDisplayScanner >> displayLine: textLine offset: offset [
"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." "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 | | stopCondition baselineY lastPos bundle |
offset traceCr.
line := textLine. line := textLine.
morphicOffset := offset. morphicOffset := offset.
lineY := textLine top + offset y. lineY := textLine top + offset y.
rightMargin := textLine rightMargin + offset x. rightMargin := (textLine rightMargin + offset x).
lastIndex := textLine first. lastIndex := textLine first.
leftInRun <= 0 ifTrue: [self setStopConditions]. self setStopConditions.
leftMargin := (textLine leftMarginForAlignment: alignment) + offset x. leftMargin := (textLine leftMarginForAlignment: alignment) + offset x.
destX := runX := leftMargin. destX := runX := leftMargin.
self fillTextBackgroundAt: lineY . self fillTextBackgroundAt: lineY .
lastIndex := textLine first. lastIndex := textLine first.
leftInRun <= 0
ifTrue: [nowLeftInRun := text runLengthFor: lastIndex]
ifFalse: [nowLeftInRun := leftInRun].
baselineY := lineY + textLine baseline. baselineY := lineY + textLine baseline.
destY := baselineY - font ascent. destY := baselineY - font ascent.
runStopIndex := lastIndex + (nowLeftInRun - 1) min: textLine last. runStopIndex := textLine last.
spaceCount := 0. spaceCount := 0.
[ [
startIndex := lastIndex.
lastPos := destX@destY. lastPos := destX@destY.
destY = 388 ifTrue: [ self haltOnce ].
lastPos traceCr.
bundle := textLine scanAndDrawCharactersFrom: lastIndex to: runStopIndex bundle := textLine scanAndDrawCharactersFrom: lastIndex to: runStopIndex
in: text rightX: rightMargin stopConditions: stopConditions in: text rightX: rightMargin stopConditions: stopConditions
kern: kern firstDestX:destX style: textStyle on: bitBlt at: lastPos withBaseline: baselineY. kern: kern firstDestX:destX style: textStyle on: bitBlt at: lastPos withBaseline: baselineY.
@ -139,13 +138,15 @@ GrafoscopioDisplayScanner >> displayLine: textLine offset: offset leftInRun: lef
stopCondition := bundle second. stopCondition := bundle second.
pendingKernX := bundle third. pendingKernX := bundle third.
destX := bundle fourth. 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 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." " 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. self perform: stopCondition.
] whileFalse. ] whileFalse.
^ runStopIndex - lastIndex "Number of characters remaining in the current run"
^ {stopCondition . runStopIndex - lastIndex} "Number of characters remaining in the current run"
] ]
{ #category : #scanning } { #category : #scanning }
@ -172,7 +173,7 @@ GrafoscopioDisplayScanner >> endOfRun [
a change in the style (run code) to be associated with the string or the a change in the style (run code) to be associated with the string or the
end of this line has been reached." end of this line has been reached."
| runLength | | runLength |
lastIndex = line last ifTrue: [^true]. lastIndex >=( line last - 1) ifTrue: [^true].
runX := destX. runX := destX.
runLength := text runLengthFor: (lastIndex := lastIndex + 1). runLength := text runLengthFor: (lastIndex := lastIndex + 1).
runStopIndex := lastIndex + (runLength - 1) min: line last. runStopIndex := lastIndex + (runLength - 1) min: line last.
@ -197,7 +198,7 @@ GrafoscopioDisplayScanner >> initialize [
{ #category : #'multilingual scanning' } { #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> isBreakableAt: index in: sourceString in: encodingClass [ GrafoscopioDisplayScanner >> isBreakableAt: index in: sourceString in: encodingClass [
^ false. ^ encodingClass isBreakableAt: index in: sourceString.
] ]
@ -403,6 +404,11 @@ GrafoscopioDisplayScanner >> textColor: textColor [
foregroundColor := textColor foregroundColor := textColor
] ]
{ #category : #'as yet unclassified' }
GrafoscopioDisplayScanner >> textStyle [
^ textStyle
]
{ #category : #'multilingual scanning' } { #category : #'multilingual scanning' }
GrafoscopioDisplayScanner >> widthOf: char inFont: aFont [ GrafoscopioDisplayScanner >> widthOf: char inFont: aFont [

View File

@ -13,7 +13,7 @@ GrafoscopioEditingArea >> drawSubmorphsOn: aCanvas [
submorphs isEmpty ifTrue: [^self]. submorphs isEmpty ifTrue: [^self].
drawBlock := [:canvas | submorphs reverseDo: [:m | canvas fullDrawMorph: m]]. drawBlock := [:canvas | submorphs reverseDo: [:m | canvas fullDrawMorph: m]].
self clipSubmorphs self clipSubmorphs
ifTrue: [aCanvas clipBy: (aCanvas clipRect intersect: self clippingBounds ifNone: [ ^ self ]) during: drawBlock] ifTrue: [aCanvas clipBy: (aCanvas clipRect intersect: self clippingBounds ifNone: [ ^ self ]) during: drawBlock]
ifFalse: [drawBlock value: aCanvas]. ifFalse: [drawBlock value: aCanvas].
"Draw the focus here since we are using inset bounds "Draw the focus here since we are using inset bounds
for the focus rectangle." for the focus rectangle."
@ -36,3 +36,8 @@ GrafoscopioEditingArea >> privateInstantiateParagraphObject [
^ RubOpeningClosingDelimiterDecorator next: GrafoscopioParagraph new. ^ RubOpeningClosingDelimiterDecorator next: GrafoscopioParagraph new.
] ]
{ #category : #private }
GrafoscopioEditingArea >> wrapped [
^ true.
]

View File

@ -4,6 +4,9 @@ Class {
#instVars : [ #instVars : [
'from', 'from',
'to', 'to',
'bounds',
'text',
'styler',
'fontCode', 'fontCode',
'lastUsedConfiguration' 'lastUsedConfiguration'
], ],
@ -11,54 +14,78 @@ Class {
} }
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> baseline [ GrafoscopioLine >> approximateWidth [
^ 10 | runs |
text ifNil: [ ^ 1 ].
runs := text runs.
^ ((self first to: self last)
collect: [ :r |
(styler
fontAt: ((runs at: r) detect: [ :a | a isKindOf: TextFontChange ]) fontNumber)
widthOf: $A ]) max * self size * 1.2
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> baseline [
| runs |
text ifNil:[^0] .
runs := text runs.
^ ((self first to: self last)
collect: [ :r |
(styler
fontAt: ((runs at: r) detect: [ :a | a isKindOf: TextFontChange ]) fontNumber)
ascent ]) max
]
{ #category : #accessing }
GrafoscopioLine >> bottom [ GrafoscopioLine >> bottom [
^ 10 ^ bounds bottom
]
{ #category : #accessing }
GrafoscopioLine >> bottomRight [
^ bounds bottomRight
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> bottomRight [ GrafoscopioLine >> bounds: aRectangle [
^ self right@ self bottom bounds := aRectangle
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> configurationFor: text with: style at: lastIndex [ GrafoscopioLine >> configurationFor: aText with: style at: lastIndex [
| attributes | | attributes |
attributes := text attributesAt: lastIndex forStyle: style. attributes := aText attributesAt: lastIndex forStyle: style.
(lastUsedConfiguration isNotNil and: [lastUsedConfiguration attributes = attributes ]) ifFalse: [ (lastUsedConfiguration isNotNil and: [lastUsedConfiguration attributes = attributes ]) ifFalse: [
lastUsedConfiguration := GrafoscopioLineConfiguration new. lastUsedConfiguration := GrafoscopioLineConfiguration new.
lastUsedConfiguration loadDefaultsFromStyle: style and: attributes. lastUsedConfiguration loadDefaultsFromStyle: style and: attributes.
.
]. ].
^ lastUsedConfiguration . ^ lastUsedConfiguration .
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> display: text textStyle: style on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: lastIndex [ GrafoscopioLine >> display: aText textStyle: style on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: lastIndex [
| configuration kern font emphasisCode | | configuration kern font emphasisCode |
configuration := self
configuration := self configurationFor: text with: style at: lastIndex . configurationFor: aText
with: style
kern := configuration kern. at: lastIndex.
kern := configuration kern.
font := configuration font. font := configuration font.
emphasisCode := configuration emphasisCode. emphasisCode := configuration emphasisCode.
lastIndex >= startIndex lastIndex >= startIndex
ifTrue: [ bitBlt ifTrue: [ [ bitBlt
displayString: text string displayString: (aText extractStringFrom: startIndex to: lastIndex)
from: startIndex from: 1
to: lastIndex to: lastIndex - startIndex + 1
at: lastPos at: lastPos
kern: kern kern: kern
baselineY: baselineY baselineY: baselineY
font: font ]. font: font ]
on: Error
do: [ :e | self halt ] ].
(emphasisCode allMask: 4) (emphasisCode allMask: 4)
ifTrue: [ font ifTrue: [ font
displayUnderlineOn: bitBlt displayUnderlineOn: bitBlt
@ -71,7 +98,7 @@ GrafoscopioLine >> display: text textStyle: style on: bitBlt at: lastPos startDr
to: destX @ baselineY ] to: destX @ baselineY ]
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> first [ GrafoscopioLine >> first [
^ from ^ from
] ]
@ -84,70 +111,112 @@ GrafoscopioLine >> fontCodeFor: aGrafoscopioPillarASText [
^ fontCode ^ fontCode
] ]
{ #category : #'as yet unclassified' } { #category : #'instance creation' }
GrafoscopioLine >> from: anInteger to: anInteger2 [ GrafoscopioLine >> from: anInteger to: anInteger2 [
from := anInteger. from := anInteger.
to := anInteger2 to := anInteger2.
bounds := 0@0 corner: 0@0
]
{ #category : #'instance creation' }
GrafoscopioLine >> from: anInteger to: anInteger2 text: aText styler: aStyler [
aText ifNil: [ self halt ].
self from: anInteger to: anInteger2.
text := aText.
styler := aStyler
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> height [ GrafoscopioLine >> height [
^ 30 | runs |
text ifNil:[^0] .
runs := text runs.
^ ((self first to: self last)
collect: [ :r |
(styler
fontAt: ((runs at: r) detect: [ :a | a isKindOf: TextFontChange ]) fontNumber)
height ]) max
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> heightForWidth: aWidth [
| onelineWidth onlineHeight|
onelineWidth := self width.
onlineHeight := self height.
aWidth > onelineWidth ifTrue: [ ^ onlineHeight ].
^((onelineWidth /aWidth )roundUpTo: 1)* onlineHeight
]
{ #category : #accessing }
GrafoscopioLine >> last [ GrafoscopioLine >> last [
^ to ^ to
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> left [ GrafoscopioLine >> left [
^ 1 ^ 1
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> leftMargin [ GrafoscopioLine >> leftMargin [
^ self left ^ self left
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> leftMarginForAlignment: anInteger [ GrafoscopioLine >> leftMarginForAlignment: anInteger [
^ 1 ^ self left
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> lineHeight [ GrafoscopioLine >> lineHeight [
^ 30 ^ self height
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> right [ GrafoscopioLine >> right [
^ 10000 ^ self width
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> rightMargin [ GrafoscopioLine >> rightMargin [
^ self right ^ self right
] ]
{ #category : #'as yet unclassified' } { #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 [ GrafoscopioLine >> scanAndDrawCharactersFrom: startIndex to: stopIndex in: aText rightX: rightX stopConditions: stopConditions kern: kernDelta firstDestX: d style: textStyle on: bitBlt at: lastPos withBaseline: baselineY [
|bundle lastIndex stopCondition destX | | bundle lastIndex stopCondition destX |
[ bundle := self
bundle := self scanCharactersFrom: startIndex to: stopIndex scanCharactersFrom: startIndex
in: text rightX: rightX stopConditions: stopConditions to: stopIndex
kern: kernDelta firstDestX:d. in: aText
rightX: rightX
lastIndex := bundle first. stopConditions: stopConditions
stopCondition := bundle second. kern: kernDelta
destX := bundle fourth. firstDestX: d.
self display: text textStyle: textStyle on: bitBlt at: lastPos startDrawingAt: destX withBaseline: baselineY from: startIndex upTo: (stopCondition == #endOfRun ifTrue:[lastIndex] ifFalse:[lastIndex-1]) . lastIndex := bundle first.
^ bundle stopCondition := bundle second.
destX := bundle fourth.
self
display: aText
textStyle: textStyle
on: bitBlt
at: lastPos
startDrawingAt: destX
withBaseline: baselineY
from: startIndex
upTo:
(stopCondition == #endOfRun
ifTrue: [ lastIndex ]
ifFalse: [ lastIndex - 1 ]).
^ bundle ]
on: SubscriptOutOfBounds
do: [ :e | self halt ]
] ]
{ #category : #scanning } { #category : #scanning }
GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: text rightX: rightX stopConditions: stops kern: kernDelta firstDestX:d [ GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: aText rightX: rightX stopConditions: stops kern: kernDelta firstDestX:d [
| ascii encoding f nextDestX maxAscii startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun font lastIndex pendingKernX destX spaceWidth source | | ascii encoding f nextDestX maxAscii startEncoding floatDestX widthAndKernedWidth nextChar atEndOfRun font lastIndex pendingKernX destX source |
source := text string. source := text string.
startIndex > stopIndex startIndex > stopIndex
@ -163,7 +232,6 @@ GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: text rightX:
on: Exception do: [:ex | nil]. on: Exception do: [:ex | nil].
f ifNil: [ f := font fontArray at: 1]. f ifNil: [ f := font fontArray at: 1].
maxAscii := f maxAscii. maxAscii := f maxAscii.
spaceWidth := f widthOf: Character space.
] ifFalse: [ ] ifFalse: [
maxAscii := font maxAscii. maxAscii := font maxAscii.
]. ].
@ -176,7 +244,6 @@ GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: text rightX:
ascii := (source at: lastIndex) charCode. ascii := (source at: lastIndex) charCode.
ascii > maxAscii ifTrue: [ascii := maxAscii]. ascii > maxAscii ifTrue: [ascii := maxAscii].
(encoding = 0 and: [ascii < stops size and: [(stops at: ascii + 1) ~~ nil]]) ifTrue: [ (encoding = 0 and: [ascii < stops size and: [(stops at: ascii + 1) ~~ nil]]) ifTrue: [
self haltOnce.
^ {lastIndex .(stops at: ascii + 1) . pendingKernX . destX }]. ^ {lastIndex .(stops at: ascii + 1) . pendingKernX . destX }].
nextChar := (lastIndex + 1 <= stopIndex) nextChar := (lastIndex + 1 <= stopIndex)
@ -206,22 +273,55 @@ GrafoscopioLine >> scanCharactersFrom: startIndex to: stopIndex in: text rightX:
^ {lastIndex . stops endOfRun . pendingKernX . destX } ^ {lastIndex . stops endOfRun . pendingKernX . destX }
] ]
{ #category : #'as yet unclassified' } { #category : #initialization }
GrafoscopioLine >> setFont: anInteger [ GrafoscopioLine >> setFont: anInteger [
fontCode := anInteger fontCode := anInteger
] ]
{ #category : #'as yet unclassified' } { #category : #accessing }
GrafoscopioLine >> size [ GrafoscopioLine >> size [
^ (self last - self first ) + 1 ^ (self last - self first ) + 1
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> string [
^ text extractStringFrom: from to: to
]
{ #category : #accessing }
GrafoscopioLine >> top [ GrafoscopioLine >> top [
^ 1 ^ bounds top
]
{ #category : #accessing }
GrafoscopioLine >> topLeft [
^ bounds topLeft
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioLine >> topLeft [ GrafoscopioLine >> width [
^ self left @ self top | string runs font |
text ifNil: [ ^1 ].
string := self string.
runs := text runs.
^ (1 to: self size)
inject: 0
into: [ :acc :idx |
font := styler
fontAt:
((runs at: idx) detect: [ :a | a isKindOf: TextFontChange ])
fontNumber.
acc + (font widthOf: (string at: idx)) ]
]
{ #category : #accessing }
GrafoscopioLine >> withThePrevious: anAmountOfCharacters [
^ anAmountOfCharacters = 0
ifTrue: [ self ]
ifFalse: [ self class new
from: from - anAmountOfCharacters - 1
to: to
text: text
styler: styler;
yourself ]
] ]

View File

@ -4,23 +4,47 @@ Class {
#category : #'Grafoscopio-Rub' #category : #'Grafoscopio-Rub'
} }
{ #category : #'accessing composer' }
GrafoscopioParagraph >> defaultEmptyText [
^ super defaultEmptyText
]
{ #category : #'accessing composer' } { #category : #'accessing composer' }
GrafoscopioParagraph >> drawOn: aCanvas using: aDisplayScanner at: aPosition [ GrafoscopioParagraph >> drawOn: aCanvas using: aDisplayScanner at: aPosition [
"Send all visible lines to the displayScanner for display" "Send all visible lines to the displayScanner for display"
| offset leftInRun line visibleRectangle | | offset charactersLeft line visibleRectangle return |
self drawingEnabled self drawingEnabled
ifFalse: [ ^ self ]. ifFalse: [ ^ self ].
visibleRectangle := aCanvas clipRect. visibleRectangle := aCanvas clipRect.
visibleRectangle setPoint: visibleRectangle origin point: visibleRectangle corner x @ 350.
offset := (aPosition - self position) truncated. offset := (aPosition - self position) truncated.
leftInRun := 0. charactersLeft := 0.
(self lineIndexForPoint: visibleRectangle topLeft) to: (self lineIndexForPoint: visibleRectangle bottomRight) do: [ :i | (self lineIndexForPoint: visibleRectangle topLeft) to: (self lineIndexForPoint: visibleRectangle bottomRight) do: [ :i |
line := self lines at: i. line := self lines at: i.
line first <= line last return := aDisplayScanner displayLine: line offset: offset.
ifTrue: [ leftInRun := aDisplayScanner displayLine: line offset: offset leftInRun: leftInRun ] ] charactersLeft := return second.
]
]
{ #category : #'accessing composer' }
GrafoscopioParagraph >> move: anEvent for: model controller: editor [
self traceCr: 'handle event'
"super move: anEvent for: model controller: editor."
] ]
{ #category : #'accessing composer' } { #category : #'accessing composer' }
GrafoscopioParagraph >> newComposer [ GrafoscopioParagraph >> newComposer [
^ GrafoscopioComposer new ^ GrafoscopioComposer new
] ]
{ #category : #'accessing composer' }
GrafoscopioParagraph >> uptodateComposer [
^ self composer
text: self text;
textStyle: self textStyle;
container: self compositionRectangle;
emphasisHere: textArea emphasisHere;
cursorWidth: textArea cursorWidth;
yourself
]

View File

@ -84,23 +84,36 @@ GrafoscopioPillarASText >> allRangesOfSubstring: aString [
{ #category : #removing } { #category : #removing }
GrafoscopioPillarASText >> allSegmentsOfLinesCollect: aBlock [ GrafoscopioPillarASText >> allSegmentsOfLinesCollect: aBlock [
| return | | return chunk |
return := OrderedCollection new. return := OrderedCollection new.
chunk := OrderedCollection new.
" This method puts together many different nodes togehter into one line. Each line finishes with a breakline. The last one maybe not ."
self self
allTextNodesDo: allTextNodesDo: [ :node |
[ :node | return add: (aBlock value: node textStart value: node textStop) ]. chunk add: node.
node isLineBreak
ifTrue: [ return
add: (aBlock value: chunk first textStart value: chunk last textStop).
chunk removeAll ] ].
chunk
ifNotEmpty: [ return
add: (aBlock value: chunk first textStart value: chunk last textStop) ].
^ return ^ return
] ]
{ #category : #removing } { #category : #removing }
GrafoscopioPillarASText >> allSegmentsOfLinesDo: aBlock [ GrafoscopioPillarASText >> allSegmentsOfLinesDo: aBlock [
^ self | chunk |
allTextNodesDo: [ :node | aBlock value: node textStart value: node textStop ] chunk := OrderedCollection new.
] " This method puts together many different nodes togehter into one line. Each line finishes with a breakline. The last one maybe not ."
self
{ #category : #'as yet unclassified' } allTextNodesDo: [ :node |
GrafoscopioPillarASText >> allTextNodes [ chunk add: node.
^ self allTextNodesFrom: ast node isLineBreak
ifTrue: [ aBlock value: chunk first textStart value: chunk last textStop.
chunk removeAll ] ].
chunk
ifNotEmpty: [ aBlock value: chunk first textStart value: chunk last textStop ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
@ -108,16 +121,6 @@ GrafoscopioPillarASText >> allTextNodesDo: aBlock [
^ self allTextNodesFrom: ast do: 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' } { #category : #'as yet unclassified' }
GrafoscopioPillarASText >> allTextNodesFrom: aNode do: aBlock [ GrafoscopioPillarASText >> allTextNodesFrom: aNode do: aBlock [
^ aNode hasChildren ^ aNode hasChildren
@ -141,7 +144,7 @@ GrafoscopioPillarASText >> ast: aPRDocument [
GrafoscopioPillarASText >> at: anInteger [ GrafoscopioPillarASText >> at: anInteger [
| node | | node |
(anInteger > self size or: [ anInteger < 1 ]) (anInteger > (self size +1 ) or: [ anInteger < 1 ])
ifTrue: [ ^ self errorSubscriptBounds: anInteger ]. ifTrue: [ ^ self errorSubscriptBounds: anInteger ].
node := self detectAstNodeFor: anInteger in: ast. node := self detectAstNodeFor: anInteger in: ast.
@ -182,8 +185,8 @@ GrafoscopioPillarASText >> detectAstNodesBetween: from and: to in: aNode [
childrenStream := aNode children readStream. childrenStream := aNode children readStream.
children := OrderedCollection new. children := OrderedCollection new.
[ childrenStream atEnd not and: [ (currentNode :=childrenStream next) textStart < to ] ] whileTrue:[ [ childrenStream atEnd not and: [ (currentNode :=childrenStream next) textStart <= to ] ] whileTrue:[
currentNode textStart >= from ifTrue: [ ((currentNode textStart >= from) or: [ currentNode textStop >= from ]) ifTrue: [
children addAll: (self detectAstNodesBetween: from and: to in: currentNode ) . children addAll: (self detectAstNodesBetween: from and: to in: currentNode ) .
]. ].
]. ].
@ -191,12 +194,26 @@ GrafoscopioPillarASText >> detectAstNodesBetween: from and: to in: aNode [
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioPillarASText >> extractStringFrom: aPoisition to: anOtherPosition [ GrafoscopioPillarASText >> extractStringFrom: aPosition to: anOtherPosition [
| from to nodes preffix suffix |
nodes := self detectAstNodesBetween: aPosition and: anOtherPosition in: ast.
from := (aPosition - nodes first textStart +1 ) .
nodes size = 1 ifTrue: [
^ nodes first text copyFrom: from to: from + anOtherPosition - aPosition .
].
to := nodes last textStop - anOtherPosition + 1.
preffix := nodes first text copyFrom: from to: nodes first textSize.
suffix := nodes last text copyFrom: 1 to: to.
^ String ^ String
streamContents: [ :str | streamContents: [ :str |
(self detectAstNodesBetween: aPoisition and: anOtherPosition in: ast) str nextPutAll: preffix.
(nodes copyFrom: 2 to: nodes size)
inject: str inject: str
into: [ :stream :each | stream nextPutAll: each text . stream ] ] into: [ :stream :each |
stream nextPutAll: each text.
stream ].
str nextPutAll: suffix ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }

View File

@ -3,7 +3,8 @@ Class {
#superclass : #GrafoscopioPillarASTextStringDecorator, #superclass : #GrafoscopioPillarASTextStringDecorator,
#instVars : [ #instVars : [
'from', 'from',
'to' 'to',
'cached'
], ],
#category : #'Grafoscopio-Pillar' #category : #'Grafoscopio-Pillar'
} }
@ -14,9 +15,13 @@ GrafoscopioPillarASTextStringProjectionDecorator >> allRangesOfSubstring: aStrin
] ]
{ #category : #accessing } { #category : #accessing }
GrafoscopioPillarASTextStringProjectionDecorator >> at: anInteger [ GrafoscopioPillarASTextStringProjectionDecorator >> at: anInteger [
from + anInteger > to ifTrue: [ ^ self error: ' out of bounds ' ]. ^ self cached at: anInteger
^ super at: from + anInteger ]
{ #category : #accessing }
GrafoscopioPillarASTextStringProjectionDecorator >> cached [
^ cached ifNil: [ cached := text extractStringFrom: from to: to ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }

View File

@ -71,6 +71,11 @@ GrafoscopioPillarTextAnnotator >> visitLineBreak: anObject [
^ self visitText: anObject ^ self visitText: anObject
] ]
{ #category : #'visiting-document' }
GrafoscopioPillarTextAnnotator >> visitLink: aLink [
super visitLink: aLink
]
{ #category : #'visiting-document' } { #category : #'visiting-document' }
GrafoscopioPillarTextAnnotator >> visitRaw: aTextObject [ GrafoscopioPillarTextAnnotator >> visitRaw: aTextObject [
self visitText: aTextObject self visitText: aTextObject

View File

@ -9,3 +9,13 @@ PRLineBreak >> isLineBreak [
PRLineBreak >> isTextOrLineBreak [ PRLineBreak >> isTextOrLineBreak [
^ true ^ true
] ]
{ #category : #'*Grafoscopio' }
PRLineBreak >> text [
^ OSPlatform current lineEnding
]
{ #category : #'*Grafoscopio' }
PRLineBreak >> textSize [
^ self text size
]

View File

@ -0,0 +1,6 @@
Extension { #name : #Text }
{ #category : #'*Grafoscopio' }
Text >> allSegmentsOfLinesDo: aBlockClosure [
]