New experiment on writitnig
This commit is contained in:
parent
0ee9e63e47
commit
14c8668f50
@ -14,13 +14,12 @@ Class {
|
||||
|
||||
{ #category : #accessing }
|
||||
GrafoscopioAttributeBranchVisitor >> analyzeBranch: aBranch at: anIndex [
|
||||
index := anIndex.
|
||||
self halt.
|
||||
index := anIndex.
|
||||
^ [ aBranch
|
||||
inject: OrderedCollection new
|
||||
into: [ :attrs :node |
|
||||
node accept: self.
|
||||
attrs addAll: (attributes at: node).
|
||||
attrs addAll: (self attributesAt: node).
|
||||
attrs ] ]
|
||||
ensure: [ index := 0 ]
|
||||
]
|
||||
@ -30,6 +29,25 @@ GrafoscopioAttributeBranchVisitor >> 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' }
|
||||
GrafoscopioAttributeBranchVisitor >> index: anIndex [
|
||||
index := anIndex
|
||||
@ -37,7 +55,7 @@ GrafoscopioAttributeBranchVisitor >> index: anIndex [
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> initialize [
|
||||
attributes := Dictionary new.
|
||||
attributes := OrderedCollection new.
|
||||
styler := GrafoscopioPillarStyler defaultStyler.
|
||||
]
|
||||
|
||||
@ -47,89 +65,82 @@ GrafoscopioAttributeBranchVisitor >> text: aGrafoscopioPillarASText [
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitCodeblock: aPRCodeblock [
|
||||
attributes
|
||||
at: aPRCodeblock
|
||||
ifAbsentPut: [ styler attributesForCodeBlock: aPRCodeblock ].
|
||||
|
||||
GrafoscopioAttributeBranchVisitor >> visitCodeblock: aPRCodeblock [
|
||||
self
|
||||
attributesAt: aPRCodeblock
|
||||
ifAbsentPut: [ styler attributesForCodeBlock: aPRCodeblock at: index ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitCommentedLine: aPRCommentedLine [
|
||||
|
||||
GrafoscopioAttributeBranchVisitor >> visitCommentedLine: aPRCommentedLine [
|
||||
self attributesAt: aPRCommentedLine ifAbsentPut: [ styler default ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitDocument: aPRDocument [
|
||||
attributes at: aPRDocument ifAbsentPut: [ styler attributesForDocument: aPRDocument ]
|
||||
self attributesAt: aPRDocument ifAbsentPut: [ styler attributesForDocument: aPRDocument ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitExternalLink: aPRExternalLink [
|
||||
attributes
|
||||
at: aPRExternalLink
|
||||
self
|
||||
attributesAt: aPRExternalLink
|
||||
ifAbsentPut: [ styler attributesForExternalLink: aPRExternalLink ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitFigure: aPRFigure [
|
||||
attributes at: aPRFigure ifAbsentPut: [ styler attributesForFigure: aPRFigure ]
|
||||
self attributesAt: aPRFigure ifAbsentPut: [ styler attributesForFigure: aPRFigure ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitFormatText: aGrafoscopioFormatTextNode [
|
||||
attributes
|
||||
at: aGrafoscopioFormatTextNode
|
||||
self attributesAt: aGrafoscopioFormatTextNode
|
||||
ifAbsentPut: [ styler attributesForFormatText: aGrafoscopioFormatTextNode ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitHeader: aPRHeader [
|
||||
attributes
|
||||
at: aPRHeader
|
||||
ifAbsentPut: [ styler attributesForHeader: aPRHeader ].
|
||||
|
||||
self
|
||||
attributesAt: aPRHeader
|
||||
ifAbsentPut: [ styler attributesForHeader: aPRHeader ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitInternalLink: aPRInternalLink [
|
||||
attributes
|
||||
at: aPRInternalLink
|
||||
GrafoscopioAttributeBranchVisitor >> visitInternalLink: aPRInternalLink [
|
||||
self
|
||||
attributesAt: aPRInternalLink
|
||||
ifAbsentPut: [ styler attributesForInternalLink: aPRInternalLink ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitLineBreak: aPRLineBreak [
|
||||
attributes
|
||||
at: aPRLineBreak
|
||||
self attributesAt: aPRLineBreak
|
||||
ifAbsentPut: [ styler attributesForLineBreak: aPRLineBreak ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitListItem: aPRListItem [
|
||||
attributes
|
||||
at: aPRListItem
|
||||
GrafoscopioAttributeBranchVisitor >> visitListItem: aPRListItem [
|
||||
self
|
||||
attributesAt: aPRListItem
|
||||
ifAbsentPut: [ styler attributesForListItem: aPRListItem at: index ]
|
||||
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitParagraph: aPRParagraph [
|
||||
attributes
|
||||
at: aPRParagraph
|
||||
GrafoscopioAttributeBranchVisitor >> visitParagraph: aPRParagraph [
|
||||
self
|
||||
attributesAt: aPRParagraph
|
||||
ifAbsentPut: [ styler attributesForParagraph: aPRParagraph ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitText: aPRText [
|
||||
attributes
|
||||
at: aPRText
|
||||
self attributesAt: aPRText
|
||||
ifAbsentPut: [ styler attributesForText: aPRText ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioAttributeBranchVisitor >> visitUnorderedList: aPRUnorderedList [
|
||||
attributes
|
||||
at: aPRUnorderedList
|
||||
self attributesAt: aPRUnorderedList
|
||||
ifAbsentPut: [ styler attributesForUnorderedList: aPRUnorderedList ]
|
||||
]
|
||||
|
@ -27,11 +27,9 @@ GrafoscopioFormat >> installTextNodeAtLeftWithValue: aString in: aNode [
|
||||
|
||||
{ #category : #'target resize' }
|
||||
GrafoscopioFormat >> installTextNodeAtRightWithValue: aString in: aNode [
|
||||
aNode
|
||||
children:
|
||||
aNode children, {(GrafoscopioFormatTextNode new
|
||||
text: aString;
|
||||
yourself)}
|
||||
| newTextChild |
|
||||
newTextChild := self newTextChildFor: aString in: aNode.
|
||||
aNode children: aNode children , {newTextChild}
|
||||
]
|
||||
|
||||
{ #category : #'target resize' }
|
||||
|
@ -338,11 +338,22 @@ GrafoscopioPillarASText >> detectAstNodeFor: anInteger [
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioPillarASText >> detectAstNodeFor: anInteger in: aNode [
|
||||
(lastNode isNotNil
|
||||
and: [ anInteger between: lastNode textStart and: lastNode textStop -1 ])
|
||||
ifTrue: [ ^ lastNode ].
|
||||
" The size should match "
|
||||
(anInteger between: aNode textStart and: aNode textStop)
|
||||
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
|
||||
ifTrue: [ aNode children
|
||||
detect: [ :c | anInteger between: c textStart and: c textStop -1 ]
|
||||
@ -385,14 +396,11 @@ GrafoscopioPillarASText >> detectFullBranchFor: anId [
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioPillarASText >> detectFullBranchFor: anInteger in: aNode [
|
||||
(anInteger between: aNode textStart and: aNode textStop -1 )
|
||||
ifFalse: [ self error: 'Cannot find a node for ' , anInteger asString ].
|
||||
^ aNode hasChildren
|
||||
ifTrue: [ | sub |
|
||||
sub := aNode children
|
||||
detect: [ :c | anInteger between: c textStart and: c textStop -1 ].
|
||||
{aNode} , (self detectFullBranchFor: anInteger in: sub) ]
|
||||
ifFalse: [ {aNode} ]
|
||||
| branch basenode |
|
||||
basenode := (self detectAstNodeFor: anInteger) .
|
||||
branch := OrderedCollection new.
|
||||
[basenode notNil ] whileTrue:[ branch add: basenode. basenode := basenode parent ].
|
||||
^ branch reverse.
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
@ -445,6 +453,7 @@ GrafoscopioPillarASText >> reannotate: aPRText [
|
||||
| current previous parents |
|
||||
|
||||
aPRText textStop: aPRText textStart + aPRText text size.
|
||||
aPRText markAsDirty.
|
||||
parents := Set new.
|
||||
parents add: aPRText parent.
|
||||
current := aPRText next.
|
||||
@ -453,6 +462,7 @@ GrafoscopioPillarASText >> reannotate: aPRText [
|
||||
|
||||
[ current isNotNil ]
|
||||
whileTrue: [
|
||||
current markAsDirty.
|
||||
current textStart: previous textStop.
|
||||
current textStop: current textStart + current text size.
|
||||
previous := current.
|
||||
@ -485,6 +495,7 @@ GrafoscopioPillarASText >> replaceFrom: start to: stop with: aCollection [
|
||||
node text: node text, aCollection.
|
||||
nodes := { node }.
|
||||
].
|
||||
nodes first markAsDirty.
|
||||
self reannotate: nodes first.
|
||||
|
||||
]
|
||||
|
@ -12,14 +12,9 @@ GrafoscopioPillarStyler class >> defaultStyler [
|
||||
^ self new
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioPillarStyler >> attributesForCodeBlock: aDocument [
|
||||
^ self default
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
GrafoscopioPillarStyler >> attributesForCodeBlock: aPRCodeblock at: index [
|
||||
self halt.
|
||||
|
||||
aPRCodeblock language originalName = 'pharo-image'
|
||||
ifTrue: [ ^ {(TextAnchor new
|
||||
anchoredMorph: (self class compiler evaluate: (aPRCodeblock propertyAt: #text)))} ].
|
||||
@ -27,7 +22,8 @@ self halt.
|
||||
ifTrue: [ | runs |
|
||||
runs := (self pharoStyler
|
||||
privateStyle: aPRCodeblock text asText , '.') runs.
|
||||
^ runs at: index - aPRCodeblock textStart ]
|
||||
^ runs at: index - aPRCodeblock textStart ].
|
||||
^{}
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
@ -59,7 +55,7 @@ GrafoscopioPillarStyler >> attributesForHeader: aPRHeader [
|
||||
toFont:
|
||||
(LogicalFont
|
||||
familyName: 'Source Code Pro'
|
||||
pointSize: (20 - (aPRHeader level * 5) max: 10)))}
|
||||
pointSize: (20 - (aPRHeader level * 5) max: 10))) . TextEmphasis bold}
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
@ -78,7 +74,7 @@ GrafoscopioPillarStyler >> attributesForListItem: aPRListItem at: index [
|
||||
ifTrue: [ {(TextIndent tabs: aPRListItem level).
|
||||
(TextAnchor new
|
||||
anchoredMorph: (self iconNamed: #menuPin);
|
||||
yourself)} ]
|
||||
yourself)} ] ifFalse: [ { } ]
|
||||
]
|
||||
|
||||
{ #category : #'as yet unclassified' }
|
||||
|
@ -22,6 +22,13 @@ PRDocumentItem >> isTextOrLineBreak [
|
||||
^ false
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRDocumentItem >> markAsDirty [
|
||||
self parent ifNotNil: [ :p | p markAsDirty ].
|
||||
properties removeKey: #textStart ifAbsent: [ ].
|
||||
properties removeKey: #textStop ifAbsent: [ ]
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRDocumentItem >> parent [
|
||||
^ self propertyAt: #parent ifAbsent: [ nil ]
|
||||
@ -37,11 +44,20 @@ PRDocumentItem >> textSize [
|
||||
^ self textStop - self textStart
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRDocumentItem >> textStart [
|
||||
^ self
|
||||
propertyAt: #textStart
|
||||
ifAbsentPut: [ self hasChildren
|
||||
ifTrue: [ self children first textStart ]
|
||||
ifFalse: [ 0 ] ]
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRDocumentItem >> textStop [
|
||||
^ self
|
||||
propertyAt: #textStop
|
||||
ifAbsent: [ self hasChildren
|
||||
ifAbsentPut: [ self hasChildren
|
||||
ifTrue: [ self children last textStop ]
|
||||
ifFalse: [ 0 ] ]
|
||||
]
|
||||
|
@ -15,6 +15,11 @@ PRLineBreak >> isTextOrLineBreak [
|
||||
^ true
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRLineBreak >> markAsDirty [
|
||||
self parent ifNotNil: [ :p | p markAsDirty ]
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRLineBreak >> next [
|
||||
^ self propertyAt: #next ifAbsent: [ nil ]
|
||||
@ -40,6 +45,11 @@ PRLineBreak >> textSize [
|
||||
^ self text size
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRLineBreak >> textStart [
|
||||
^ self propertyAt: #textStart
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRLineBreak >> textStart: aValue [
|
||||
^ self
|
||||
@ -47,6 +57,11 @@ PRLineBreak >> textStart: aValue [
|
||||
put: aValue
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRLineBreak >> textStop [
|
||||
^ self propertyAt: #textStop
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRLineBreak >> textStop: aValue [
|
||||
^ self
|
||||
|
@ -5,6 +5,11 @@ PRText >> isTextOrLineBreak [
|
||||
^ true
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRText >> markAsDirty [
|
||||
self parent ifNotNil: [ :p | p markAsDirty ]
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRText >> next [
|
||||
^ self propertyAt: #next ifAbsent: [ nil ]
|
||||
@ -15,6 +20,11 @@ PRText >> next: aText [
|
||||
self propertyAt: #next put: aText.
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRText >> textStart [
|
||||
^ self propertyAt: #textStart
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRText >> textStart: aValue [
|
||||
^ self
|
||||
@ -22,6 +32,11 @@ PRText >> textStart: aValue [
|
||||
put: aValue
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRText >> textStop [
|
||||
^ self propertyAt: #textStop
|
||||
]
|
||||
|
||||
{ #category : #'*Grafoscopio' }
|
||||
PRText >> textStop: aValue [
|
||||
^ self
|
||||
|
Loading…
Reference in New Issue
Block a user