New experiment on writitnig

This commit is contained in:
SantiagoBragagnolo 2020-04-13 11:41:09 +00:00
parent e1df08eae6
commit c7766f92b9
7 changed files with 125 additions and 63 deletions

View File

@ -14,13 +14,12 @@ Class {
{ #category : #accessing } { #category : #accessing }
GrafoscopioAttributeBranchVisitor >> analyzeBranch: aBranch at: anIndex [ GrafoscopioAttributeBranchVisitor >> analyzeBranch: aBranch at: anIndex [
index := anIndex. index := anIndex.
self halt.
^ [ aBranch ^ [ aBranch
inject: OrderedCollection new inject: OrderedCollection new
into: [ :attrs :node | into: [ :attrs :node |
node accept: self. node accept: self.
attrs addAll: (attributes at: node). attrs addAll: (self attributesAt: node).
attrs ] ] attrs ] ]
ensure: [ index := 0 ] ensure: [ index := 0 ]
] ]
@ -30,6 +29,25 @@ GrafoscopioAttributeBranchVisitor >> attributes [
^ attributes ^ attributes
] ]
{ #category : #accessing }
GrafoscopioAttributeBranchVisitor >> attributesAt: aNode [
^ (attributes detect: [ :a | a first = aNode ]) second
]
{ #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> attributesAt: aNode ifAbsentPut: aBlock [
^ attributes
detect: [ :a | a first = aNode ]
ifFound: [ :a | a second ]
ifNone: [ | val |
val := aBlock value.
attributes
add:
{aNode.
val}.
val ]
]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> index: anIndex [ GrafoscopioAttributeBranchVisitor >> index: anIndex [
index := anIndex index := anIndex
@ -37,7 +55,7 @@ GrafoscopioAttributeBranchVisitor >> index: anIndex [
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> initialize [ GrafoscopioAttributeBranchVisitor >> initialize [
attributes := Dictionary new. attributes := OrderedCollection new.
styler := GrafoscopioPillarStyler defaultStyler. styler := GrafoscopioPillarStyler defaultStyler.
] ]
@ -47,89 +65,82 @@ GrafoscopioAttributeBranchVisitor >> text: aGrafoscopioPillarASText [
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitCodeblock: aPRCodeblock [ GrafoscopioAttributeBranchVisitor >> visitCodeblock: aPRCodeblock [
attributes self
at: aPRCodeblock attributesAt: aPRCodeblock
ifAbsentPut: [ styler attributesForCodeBlock: aPRCodeblock ]. ifAbsentPut: [ styler attributesForCodeBlock: aPRCodeblock at: index ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitCommentedLine: aPRCommentedLine [ GrafoscopioAttributeBranchVisitor >> visitCommentedLine: aPRCommentedLine [
self attributesAt: aPRCommentedLine ifAbsentPut: [ styler default ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitDocument: aPRDocument [ GrafoscopioAttributeBranchVisitor >> visitDocument: aPRDocument [
attributes at: aPRDocument ifAbsentPut: [ styler attributesForDocument: aPRDocument ] self attributesAt: aPRDocument ifAbsentPut: [ styler attributesForDocument: aPRDocument ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitExternalLink: aPRExternalLink [ GrafoscopioAttributeBranchVisitor >> visitExternalLink: aPRExternalLink [
attributes self
at: aPRExternalLink attributesAt: aPRExternalLink
ifAbsentPut: [ styler attributesForExternalLink: aPRExternalLink ] ifAbsentPut: [ styler attributesForExternalLink: aPRExternalLink ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitFigure: aPRFigure [ GrafoscopioAttributeBranchVisitor >> visitFigure: aPRFigure [
attributes at: aPRFigure ifAbsentPut: [ styler attributesForFigure: aPRFigure ] self attributesAt: aPRFigure ifAbsentPut: [ styler attributesForFigure: aPRFigure ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitFormatText: aGrafoscopioFormatTextNode [ GrafoscopioAttributeBranchVisitor >> visitFormatText: aGrafoscopioFormatTextNode [
attributes self attributesAt: aGrafoscopioFormatTextNode
at: aGrafoscopioFormatTextNode
ifAbsentPut: [ styler attributesForFormatText: aGrafoscopioFormatTextNode ] ifAbsentPut: [ styler attributesForFormatText: aGrafoscopioFormatTextNode ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitHeader: aPRHeader [ GrafoscopioAttributeBranchVisitor >> visitHeader: aPRHeader [
attributes self
at: aPRHeader attributesAt: aPRHeader
ifAbsentPut: [ styler attributesForHeader: aPRHeader ]. ifAbsentPut: [ styler attributesForHeader: aPRHeader ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitInternalLink: aPRInternalLink [ GrafoscopioAttributeBranchVisitor >> visitInternalLink: aPRInternalLink [
attributes self
at: aPRInternalLink attributesAt: aPRInternalLink
ifAbsentPut: [ styler attributesForInternalLink: aPRInternalLink ] ifAbsentPut: [ styler attributesForInternalLink: aPRInternalLink ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitLineBreak: aPRLineBreak [ GrafoscopioAttributeBranchVisitor >> visitLineBreak: aPRLineBreak [
attributes self attributesAt: aPRLineBreak
at: aPRLineBreak
ifAbsentPut: [ styler attributesForLineBreak: aPRLineBreak ] ifAbsentPut: [ styler attributesForLineBreak: aPRLineBreak ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitListItem: aPRListItem [ GrafoscopioAttributeBranchVisitor >> visitListItem: aPRListItem [
attributes self
at: aPRListItem attributesAt: aPRListItem
ifAbsentPut: [ styler attributesForListItem: aPRListItem at: index ] ifAbsentPut: [ styler attributesForListItem: aPRListItem at: index ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitParagraph: aPRParagraph [ GrafoscopioAttributeBranchVisitor >> visitParagraph: aPRParagraph [
attributes self
at: aPRParagraph attributesAt: aPRParagraph
ifAbsentPut: [ styler attributesForParagraph: aPRParagraph ] ifAbsentPut: [ styler attributesForParagraph: aPRParagraph ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitText: aPRText [ GrafoscopioAttributeBranchVisitor >> visitText: aPRText [
attributes self attributesAt: aPRText
at: aPRText
ifAbsentPut: [ styler attributesForText: aPRText ] ifAbsentPut: [ styler attributesForText: aPRText ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioAttributeBranchVisitor >> visitUnorderedList: aPRUnorderedList [ GrafoscopioAttributeBranchVisitor >> visitUnorderedList: aPRUnorderedList [
attributes self attributesAt: aPRUnorderedList
at: aPRUnorderedList
ifAbsentPut: [ styler attributesForUnorderedList: aPRUnorderedList ] ifAbsentPut: [ styler attributesForUnorderedList: aPRUnorderedList ]
] ]

View File

@ -27,11 +27,9 @@ GrafoscopioFormat >> installTextNodeAtLeftWithValue: aString in: aNode [
{ #category : #'target resize' } { #category : #'target resize' }
GrafoscopioFormat >> installTextNodeAtRightWithValue: aString in: aNode [ GrafoscopioFormat >> installTextNodeAtRightWithValue: aString in: aNode [
aNode | newTextChild |
children: newTextChild := self newTextChildFor: aString in: aNode.
aNode children, {(GrafoscopioFormatTextNode new aNode children: aNode children , {newTextChild}
text: aString;
yourself)}
] ]
{ #category : #'target resize' } { #category : #'target resize' }

View File

@ -338,11 +338,22 @@ GrafoscopioPillarASText >> detectAstNodeFor: anInteger [
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioPillarASText >> detectAstNodeFor: anInteger in: aNode [ GrafoscopioPillarASText >> detectAstNodeFor: anInteger in: aNode [
(lastNode isNotNil " The size should match "
and: [ anInteger between: lastNode textStart and: lastNode textStop -1 ])
ifTrue: [ ^ lastNode ].
(anInteger between: aNode textStart and: aNode textStop) (anInteger between: aNode textStart and: aNode textStop)
ifFalse: [ self error: 'Cannot find a node for ' , anInteger asString ]. ifFalse: [ self error: 'Cannot find a node for ' , anInteger asString ].
" if the node is the same as the last, or if it is further (probably we are just iterating the thing) we try to reuse the last result or to go throug as a list. "
lastNode ifNotNil: [
(anInteger between: lastNode textStart and: lastNode textStop -1 ) ifTrue: [
^ lastNode.
].
anInteger >= lastNode textStop ifTrue: [
[(lastNode := lastNode next) notNil ] whileTrue: [
(anInteger between: lastNode textStart and: lastNode textStop -1) ifTrue:[ ^ lastNode ]
]
]
].
^ aNode hasChildren ^ aNode hasChildren
ifTrue: [ aNode children ifTrue: [ aNode children
detect: [ :c | anInteger between: c textStart and: c textStop -1 ] detect: [ :c | anInteger between: c textStart and: c textStop -1 ]
@ -385,14 +396,11 @@ GrafoscopioPillarASText >> detectFullBranchFor: anId [
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioPillarASText >> detectFullBranchFor: anInteger in: aNode [ GrafoscopioPillarASText >> detectFullBranchFor: anInteger in: aNode [
(anInteger between: aNode textStart and: aNode textStop -1 ) | branch basenode |
ifFalse: [ self error: 'Cannot find a node for ' , anInteger asString ]. basenode := (self detectAstNodeFor: anInteger) .
^ aNode hasChildren branch := OrderedCollection new.
ifTrue: [ | sub | [basenode notNil ] whileTrue:[ branch add: basenode. basenode := basenode parent ].
sub := aNode children ^ branch reverse.
detect: [ :c | anInteger between: c textStart and: c textStop -1 ].
{aNode} , (self detectFullBranchFor: anInteger in: sub) ]
ifFalse: [ {aNode} ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
@ -445,6 +453,7 @@ GrafoscopioPillarASText >> reannotate: aPRText [
| current previous parents | | current previous parents |
aPRText textStop: aPRText textStart + aPRText text size. aPRText textStop: aPRText textStart + aPRText text size.
aPRText markAsDirty.
parents := Set new. parents := Set new.
parents add: aPRText parent. parents add: aPRText parent.
current := aPRText next. current := aPRText next.
@ -453,6 +462,7 @@ GrafoscopioPillarASText >> reannotate: aPRText [
[ current isNotNil ] [ current isNotNil ]
whileTrue: [ whileTrue: [
current markAsDirty.
current textStart: previous textStop. current textStart: previous textStop.
current textStop: current textStart + current text size. current textStop: current textStart + current text size.
previous := current. previous := current.
@ -485,6 +495,7 @@ GrafoscopioPillarASText >> replaceFrom: start to: stop with: aCollection [
node text: node text, aCollection. node text: node text, aCollection.
nodes := { node }. nodes := { node }.
]. ].
nodes first markAsDirty.
self reannotate: nodes first. self reannotate: nodes first.
] ]

View File

@ -12,14 +12,9 @@ GrafoscopioPillarStyler class >> defaultStyler [
^ self new ^ self new
] ]
{ #category : #'as yet unclassified' }
GrafoscopioPillarStyler >> attributesForCodeBlock: aDocument [
^ self default
]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
GrafoscopioPillarStyler >> attributesForCodeBlock: aPRCodeblock at: index [ GrafoscopioPillarStyler >> attributesForCodeBlock: aPRCodeblock at: index [
self halt.
aPRCodeblock language originalName = 'pharo-image' aPRCodeblock language originalName = 'pharo-image'
ifTrue: [ ^ {(TextAnchor new ifTrue: [ ^ {(TextAnchor new
anchoredMorph: (self class compiler evaluate: (aPRCodeblock propertyAt: #text)))} ]. anchoredMorph: (self class compiler evaluate: (aPRCodeblock propertyAt: #text)))} ].
@ -27,7 +22,8 @@ self halt.
ifTrue: [ | runs | ifTrue: [ | runs |
runs := (self pharoStyler runs := (self pharoStyler
privateStyle: aPRCodeblock text asText , '.') runs. privateStyle: aPRCodeblock text asText , '.') runs.
^ runs at: index - aPRCodeblock textStart ] ^ runs at: index - aPRCodeblock textStart ].
^{}
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
@ -59,7 +55,7 @@ GrafoscopioPillarStyler >> attributesForHeader: aPRHeader [
toFont: toFont:
(LogicalFont (LogicalFont
familyName: 'Source Code Pro' familyName: 'Source Code Pro'
pointSize: (20 - (aPRHeader level * 5) max: 10)))} pointSize: (20 - (aPRHeader level * 5) max: 10))) . TextEmphasis bold}
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }
@ -78,7 +74,7 @@ GrafoscopioPillarStyler >> attributesForListItem: aPRListItem at: index [
ifTrue: [ {(TextIndent tabs: aPRListItem level). ifTrue: [ {(TextIndent tabs: aPRListItem level).
(TextAnchor new (TextAnchor new
anchoredMorph: (self iconNamed: #menuPin); anchoredMorph: (self iconNamed: #menuPin);
yourself)} ] yourself)} ] ifFalse: [ { } ]
] ]
{ #category : #'as yet unclassified' } { #category : #'as yet unclassified' }

View File

@ -22,6 +22,13 @@ PRDocumentItem >> isTextOrLineBreak [
^ false ^ false
] ]
{ #category : #'*Grafoscopio' }
PRDocumentItem >> markAsDirty [
self parent ifNotNil: [ :p | p markAsDirty ].
properties removeKey: #textStart ifAbsent: [ ].
properties removeKey: #textStop ifAbsent: [ ]
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRDocumentItem >> parent [ PRDocumentItem >> parent [
^ self propertyAt: #parent ifAbsent: [ nil ] ^ self propertyAt: #parent ifAbsent: [ nil ]
@ -37,11 +44,20 @@ PRDocumentItem >> textSize [
^ self textStop - self textStart ^ self textStop - self textStart
] ]
{ #category : #'*Grafoscopio' }
PRDocumentItem >> textStart [
^ self
propertyAt: #textStart
ifAbsentPut: [ self hasChildren
ifTrue: [ self children first textStart ]
ifFalse: [ 0 ] ]
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRDocumentItem >> textStop [ PRDocumentItem >> textStop [
^ self ^ self
propertyAt: #textStop propertyAt: #textStop
ifAbsent: [ self hasChildren ifAbsentPut: [ self hasChildren
ifTrue: [ self children last textStop ] ifTrue: [ self children last textStop ]
ifFalse: [ 0 ] ] ifFalse: [ 0 ] ]
] ]

View File

@ -15,6 +15,11 @@ PRLineBreak >> isTextOrLineBreak [
^ true ^ true
] ]
{ #category : #'*Grafoscopio' }
PRLineBreak >> markAsDirty [
self parent ifNotNil: [ :p | p markAsDirty ]
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRLineBreak >> next [ PRLineBreak >> next [
^ self propertyAt: #next ifAbsent: [ nil ] ^ self propertyAt: #next ifAbsent: [ nil ]
@ -40,6 +45,11 @@ PRLineBreak >> textSize [
^ self text size ^ self text size
] ]
{ #category : #'*Grafoscopio' }
PRLineBreak >> textStart [
^ self propertyAt: #textStart
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRLineBreak >> textStart: aValue [ PRLineBreak >> textStart: aValue [
^ self ^ self
@ -47,6 +57,11 @@ PRLineBreak >> textStart: aValue [
put: aValue put: aValue
] ]
{ #category : #'*Grafoscopio' }
PRLineBreak >> textStop [
^ self propertyAt: #textStop
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRLineBreak >> textStop: aValue [ PRLineBreak >> textStop: aValue [
^ self ^ self

View File

@ -5,6 +5,11 @@ PRText >> isTextOrLineBreak [
^ true ^ true
] ]
{ #category : #'*Grafoscopio' }
PRText >> markAsDirty [
self parent ifNotNil: [ :p | p markAsDirty ]
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRText >> next [ PRText >> next [
^ self propertyAt: #next ifAbsent: [ nil ] ^ self propertyAt: #next ifAbsent: [ nil ]
@ -15,6 +20,11 @@ PRText >> next: aText [
self propertyAt: #next put: aText. self propertyAt: #next put: aText.
] ]
{ #category : #'*Grafoscopio' }
PRText >> textStart [
^ self propertyAt: #textStart
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRText >> textStart: aValue [ PRText >> textStart: aValue [
^ self ^ self
@ -22,6 +32,11 @@ PRText >> textStart: aValue [
put: aValue put: aValue
] ]
{ #category : #'*Grafoscopio' }
PRText >> textStop [
^ self propertyAt: #textStop
]
{ #category : #'*Grafoscopio' } { #category : #'*Grafoscopio' }
PRText >> textStop: aValue [ PRText >> textStop: aValue [
^ self ^ self