Grafoscopio/src/Grafoscopio/GrafoscopioNode.class.st

715 lines
19 KiB
Smalltalk

"
An UbakyeNode is and administrator of all node operations in a tree.
Instance Variables
node: <Object>
node
- xxxxx
"
Class {
#name : #GrafoscopioNode,
#superclass : #Object,
#instVars : [
'header',
'headers',
'key',
'icon',
'body',
'tags',
'children',
'parent',
'node',
'level',
'nodesInPreorder',
'metadata',
'links'
],
#classInstVars : [
'clipboard'
],
#category : #'Grafoscopio-Model'
}
{ #category : #utility }
GrafoscopioNode class >> cleanTreeRootReferences [
| ref |
clipboard ifNil: [ ^ self ].
clipboard children ifNil: [ ^ self ].
clipboard preorderTraversal allButFirstDo: [ :n |
ref := n.
n level - 1 timesRepeat: [ ref := ref parent ].
ref ifNotNil: [ ref parent: nil ]
]
]
{ #category : #accessing }
GrafoscopioNode class >> clipboard [
^ clipboard
]
{ #category : #accessing }
GrafoscopioNode class >> clipboard: anObject [
clipboard := anObject
]
{ #category : #'instance creation' }
GrafoscopioNode class >> header: aHeader body: aText [
"Create a new instance with given header and body"
^(self new)
header: aHeader;
body: aText;
yourself.
]
{ #category : #'instance creation' }
GrafoscopioNode class >> header: aHeader icon: anIcon body: aText [
"Create a new instances with given header, icon and body"
^(self new)
header: aHeader;
icon: anIcon;
body: aText;
yourself.
]
{ #category : #'instance creation' }
GrafoscopioNode class >> named: aString [
"Create a new instance with a given header and empty body"
^(self new)
header: aString;
yourself
]
{ #category : #utility }
GrafoscopioNode class >> specialWords [
"I return a list of word that were used in the first versions of grafoscopio to mark node
headers to indicate special ways to handle them and their node contents.
Previous versions of first notebooks stored in grafoscopio using this convention should be
migrated to newer versions where tags are used for the same function with simpler code"
^ #('%config' '%abstract' '%invisible' '%idea' '%footnote' 'nuevoNodo' '%embed').
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> addNode: aNode [
"Adds the given node to the receivers collection of children, and sets this object as the parent
of the node"
self children add: aNode.
aNode level: (self level) + 1.
aNode parent: self.
^aNode
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> addNodeAfterMe [
"Adds a generic node after the given node so they become slibings of the same parent"
| genericNode |
genericNode := self class new header: 'newNode'; body: ''.
self parent children add: genericNode after: self.
genericNode parent: self parent.
genericNode level: self level.
^ genericNode
]
{ #category : #accessing }
GrafoscopioNode >> ancestors [
"I return a collection of all the nodes wich are ancestors of the receiver node"
| currentNode ancestors |
currentNode := self.
ancestors := OrderedCollection new.
[currentNode level > 0]
whileTrue: [
ancestors add: currentNode parent.
currentNode := currentNode parent.].
ancestors := ancestors reversed.
^ ancestors
]
{ #category : #accessing }
GrafoscopioNode >> ancestorsHeaders [
"Returns the headers of all the ancestors of the node.
Maybe this and 'headers' should be integrated, so both act on a collection of children instead of
having two separate methods"
| currentNode ancestors |
currentNode := self.
ancestors := OrderedCollection new.
(self level - 1)
timesRepeat: [
ancestors add: currentNode parent.
currentNode := currentNode parent.].
ancestors := ancestors reversed.
^ ancestors collect: [:ancestor | ancestor header ]
]
{ #category : #exporting }
GrafoscopioNode >> asMarkdown [
"I export children of the current node as pandoc markdown, using special nodes accoding to tags.
Early version... tags processing should be vastly improved"
| markdownOutput |
markdownOutput := '' writeStream.
self exportPreambleTo: markdownOutput.
(self preorderTraversal) do: [ :eachNode |
(eachNode level > 0)
ifTrue: [(eachNode hasAncestorTaggedAs: 'invisible') | (eachNode tags = 'invisible')
ifFalse: [ markdownOutput nextPutAll: (eachNode markdownContent) ]]].
^markdownOutput contents
]
{ #category : #exporting }
GrafoscopioNode >> asSton [
"Exports current tree as STON format"
| stonOutput |
stonOutput := '' writeStream.
self flatten.
stonOutput nextPutAll: (STON toStringPretty: self children).
^stonOutput contents
]
{ #category : #accessing }
GrafoscopioNode >> asText [
^ self body
]
{ #category : #initialization }
GrafoscopioNode >> becomeDefaultTestTree [
| node1 node2 node3 node4 |
self level: 0.
self header: 'Arbol principal'.
node1 := self class new
header: 'Markup';
body: 'I am just a node with markup';
level: 1.
node2 := self class new
header: 'Code';
body: 'ProfStef openPharoZenWorkspace';
tagAs: 'código'.
node3 := self class new
header: 'Child';
body: 'Just testing'.
node1 addNode: node3.
node4 := self class new
header: 'Something';
body: 'else'.
node1 addNode: node4.
self
addNode: node1;
addNode: node2.
]
{ #category : #initialization }
GrafoscopioNode >> becomeDefaultTree [
"I create a starting tree for all grafoscopio notebooks with just one textual node"
| node1 |
self level: 0.
self header: 'Arbol principal'.
node1 := GrafoscopioNode
header: 'Node 1'
body: ''.
self addNode: node1.
]
{ #category : #accessing }
GrafoscopioNode >> body [
"Returns the receivers body"
^ body
]
{ #category : #accessing }
GrafoscopioNode >> body: anObject [
"Sets the receivers body to the given object"
body := anObject
]
{ #category : #accessing }
GrafoscopioNode >> children [
"Returns the receivers list of children"
^ children ifNil: [children := OrderedCollection new]
]
{ #category : #accessing }
GrafoscopioNode >> children: aCollection [
"Sets the receivers children"
aCollection do: [:currentNode | currentNode parent: self ].
children := aCollection.
]
{ #category : #accessing }
GrafoscopioNode >> content [
"Returns the receivers body"
^ body
]
{ #category : #accessing }
GrafoscopioNode >> content: anObject [
"Sets the receivers body to the given object"
body := anObject
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> copyToClipboard [
self class clipboard: self copy.
self class cleanTreeRootReferences
]
{ #category : #utility }
GrafoscopioNode >> deleteReferencesToRoot: aRootNode [
| sparseTree |
sparseTree := self preorderTraversal.
]
{ #category : #movement }
GrafoscopioNode >> demote [
"Moves the current node down in the hierachy, making a children of its current previous slibing"
| collection index predecessor |
collection := self parent children.
index := collection indexOf: self.
(index between: 2 and: collection size)
ifTrue: [ predecessor := collection before: self.
collection remove: self.
predecessor addNode: self]
]
{ #category : #exporting }
GrafoscopioNode >> exportCodeBlockTo: aStream [
"I convert the content of a node taged as 'código' (code) as pandoc markdown and put it Into aStream.
The code block is decorated with LaTeX commands for proper syntax highlighting using pygments.
Pdf exportation requires the installation of pygments and minted package for latex"
aStream nextPutAll: ('\begin{minted}{smalltalk}'); lf.
aStream nextPutAll: (self body contents withInternetLineEndings); lf.
aStream nextPutAll: '\end{minted}';lf;lf.
^aStream contents
]
{ #category : #exporting }
GrafoscopioNode >> exportPreambleTo: aStream [
"comment stating purpose of message"
| configDict |
aStream nextPutAll: '---'; lf.
aStream nextPutAll: 'header-includes:'; lf.
aStream nextPutAll: ' - \documentclass{article}'; lf.
aStream nextPutAll: ' - \usepackage{minted}'; lf.
aStream nextPutAll: ' - \usemintedstyle{friendly}'; lf.
(self header = '%config')
ifTrue: [
configDict := STON fromString: (self body).
aStream nextPutAll: 'title: ', (configDict at: 'title'); lf.
aStream nextPutAll: 'author: ', ((configDict at: 'author') at: 'given'), ' ', ((configDict at: 'author') at: 'family'); lf.
aStream nextPutAll: 'bibliography: ', (configDict at: 'bibliography'); lf.
aStream nextPutAll: 'abstract: ', '|'; lf; nextPutAll: (configDict at: 'abstract'); lf.
].
aStream nextPutAll: '---'; lf.
]
{ #category : #exporting }
GrafoscopioNode >> flatten [
"I traverse the tree looking for node bodies containing 'Text' objects and transform them to
their string content, so space is saved and storage format is DVCS friendly while serializing them to STON"
(self preorderTraversal) do: [ :eachNode |
(eachNode body class = Text)
ifTrue: [eachNode body: (eachNode body asString)]
]
]
{ #category : #exporting }
GrafoscopioNode >> hasAncestorHeaderWith: aSpecialWord [
"Looks if the receptor node has an ancestor with a header with 'aSpecialWord' as the only or the first word"
^ (self ancestorsHeaders includes: aSpecialWord) | ((self ancestorsHeaders collect: [:eachHeader | (eachHeader findTokens: $ ) at: 1 ]) includes: aSpecialWord)
]
{ #category : #exporting }
GrafoscopioNode >> hasAncestorTaggedAs: aSpecialWord [
"Looks if the receptor node has an ancestor with a header with 'aSpecialWord' in its tags"
self ancestors detect: [:eachAncestor | eachAncestor tags = aSpecialWord ] ifFound: [^true ] ifNone: [^false ].
]
{ #category : #accessing }
GrafoscopioNode >> hasChildren [
(self children size > 0)
ifTrue: [ ^true ]
ifFalse: [ ^false ]
]
{ #category : #accessing }
GrafoscopioNode >> header [
"Returns the receiver header"
^ header
]
{ #category : #accessing }
GrafoscopioNode >> header: anObject [
"Sets the receivers header"
header := anObject
]
{ #category : #accessing }
GrafoscopioNode >> headers [
"I returns the headers of the receiver children"
^ headers := self children collect: [:currentNode | currentNode header ]
]
{ #category : #accessing }
GrafoscopioNode >> icon [
"Returns the receivers icon"
^icon
]
{ #category : #accessing }
GrafoscopioNode >> icon: aSymbol [
"Sets the receivers icon"
icon := aSymbol
]
{ #category : #initialization }
GrafoscopioNode >> initialize [
"Creates a empty new node"
super initialize.
self
header: 'newHeader';
body: '';
level: 0
]
{ #category : #accessing }
GrafoscopioNode >> isEmpty [
body ifNil: [ ^ true ] ifNotNil: [ ^ false ]
]
{ #category : #accessing }
GrafoscopioNode >> key [
"Returns a unique key identifying the receiver in the help system"
^key
]
{ #category : #accessing }
GrafoscopioNode >> key: aUniqueKey [
"Sets a unique key identifying the receiver in the help system"
key := aUniqueKey
]
{ #category : #accessing }
GrafoscopioNode >> lastLink [
links ifNil: [ ^ '' ].
^ links last
]
{ #category : #accessing }
GrafoscopioNode >> level [
"Returns the level of the node. See the setter message for details"
^level
]
{ #category : #accessing }
GrafoscopioNode >> level: anInteger [
"Sets the node level in a hierarchy. The only node with level 0 is the root node and from there levels increase
in 1 for its direct children, 2 for its grand children and so on. Silibings nodes has the same level"
level := anInteger
]
{ #category : #accessing }
GrafoscopioNode >> links [
"I model local or remote links that are associated to a particular node."
^ links ifNil: [ ^ links := OrderedCollection new ]
]
{ #category : #accessing }
GrafoscopioNode >> links: anObject [
links add: anObject
]
{ #category : #exporting }
GrafoscopioNode >> margin [
"I define the same margin of the page used for PDF exportations"
^'2 cm'
]
{ #category : #exporting }
GrafoscopioNode >> margins [
"I define each individual margin of the page used for PDF exportations"
| margins |
margins := Dictionary new
add: 'top' -> '3 cm';
add: 'bottom' -> '3 cm';
add: 'left' -> '2 cm';
add: 'right' -> '2 cm';
yourself.
^ margins
]
{ #category : #exporting }
GrafoscopioNode >> markdownContent [
"Extracts the markdown of a node using body as content, header as title and level as hierarchical level of the title.
If special nodes types are present, converts them into proper markup to be embedded inside markdown"
| markdown embedNodes temporalBody invisibleChildren |
markdown := '' writeStream.
(self class specialWords includes: self header) not & (self class specialWords includes: ((self header findTokens: $ ) at: 1)) not & (self tags = 'código') not
ifTrue: [
self level timesRepeat: [ markdown nextPutAll: '#' ].
markdown nextPutAll: ' '.
markdown nextPutAll: (self header copyReplaceTokens: #cr with: #lf); crlf; crlf.
embedNodes := self children select: [:each | ((each header findTokens: $ ) at: 1) = '%embed'].
temporalBody := self body asString.
embedNodes ifNotNil: [
(temporalBody includesSubstring: '%embed-all')
ifFalse: [embedNodes do: [ :each | temporalBody := temporalBody copyReplaceAll: (each header) with: each body]]
ifTrue: [
embedNodes do:
[ :each | temporalBody := temporalBody copyReplaceAll: '%embed-all' with: (each body,
(String with: Character cr),
'%embed-all')].
temporalBody := temporalBody copyReplaceAll: '%embed-all' with: ''
]
].
markdown nextPutAll: (temporalBody contents withInternetLineEndings ); crlf; crlf].
((self header findString: '%idea') = 1)
ifTrue: [
embedNodes := self children select: [:each | ((each header findTokens: $ ) at: 1) = '%embed'].
temporalBody := self body.
embedNodes ifNotNil: [ embedNodes do: [ :each | temporalBody := temporalBody copyReplaceAll: (each header) with: each body]].
markdown nextPutAll: (temporalBody contents withUnixLineEndings); lf; lf.
].
((self header findString: '%footnote') = 1)
ifTrue: [
markdown nextPutAll: ('[^',(self header copyReplaceAll: '%footnote ' with: ''),']: ' ); lf.
markdown nextPutAll: (self body contents withInternetLineEndings); lf; lf. ].
((self header findString: '%embed') = 1)
ifTrue: [ ].
(self tags = 'invisible')
ifTrue: [
invisibleChildren := self children.
invisibleChildren ifNotNil: [ ] ].
(self tags = 'código') ifTrue: [ self exportCodeBlockTo: markdown ].
^markdown contents
]
{ #category : #accessing }
GrafoscopioNode >> metadata [
^ metadata
]
{ #category : #accessing }
GrafoscopioNode >> metadata: anObject [
metadata := anObject
]
{ #category : #movement }
GrafoscopioNode >> moveAfter [
"Moves the current node a place before in the children collection where is located"
| collection index successor |
collection := self parent children.
index := collection indexOf: self.
(index between: 1 and: collection size - 1)
ifTrue: [
successor := collection after: self.
collection at: index + 1 put: self.
collection at: index put: successor]
]
{ #category : #movement }
GrafoscopioNode >> moveBefore [
"Moves the current node a place before in the children collection where is located"
| collection index predecessor |
collection := self parent children.
index := collection indexOf: self.
(index between: 2 and: collection size)
ifTrue: [
predecessor := collection before: self.
collection at: index -1 put: self.
collection at: index put: predecessor]
]
{ #category : #'instance creation' }
GrafoscopioNode >> newNode [
node := Dictionary newFrom: {
#header -> 'newHeadline'.
#body -> ''.
#children -> #()}.
^ node.
]
{ #category : #accessing }
GrafoscopioNode >> parent [
"Returns the parent of the current node"
^ parent
]
{ #category : #accessing }
GrafoscopioNode >> parent: aNode [
"A parent is a node that has the current node in its children"
parent := aNode
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> pasteFromClipboard [
self class clipboard
ifNotNil: [ self addNode: self class clipboard ]
ifNil: [ self inform: 'Cache is emtpy. Pleas cut/copy a node before pasting' ]
]
{ #category : #exporting }
GrafoscopioNode >> preorderTraversal [
nodesInPreorder := OrderedCollection new.
self visitedGoTo: nodesInPreorder.
^ nodesInPreorder.
]
{ #category : #movement }
GrafoscopioNode >> promote [
"Moves the current node up in the hierachy, making it a slibing of its current parent"
| collection grandparent |
collection := self parent children.
grandparent := self parent parent.
collection isNotNil & grandparent isNotNil
ifTrue: [
(grandparent children) add: self after: (self parent).
self level: (self parent) level.
self parent: grandparent.
collection remove: self.]
]
{ #category : #exporting }
GrafoscopioNode >> publish [
| publishedUrl |
(self confirm: 'Publish playground content to the cloud?')
ifFalse: [ ^ self ].
self content ifEmpty: [
self inform: 'Nothing was published because the playground is empty'.
^ self ].
Clipboard clipboardText: (publishedUrl := (GTUrlProvider new post: self content) asString).
self inform: publishedUrl , ' was published and the url was copied to clipboard'
]
{ #category : #accessing }
GrafoscopioNode >> remoteRepository [
^ remoteRepository
]
{ #category : #accessing }
GrafoscopioNode >> remoteRepository: anObject [
remoteRepository := anObject
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> removeLastNode [
"Adds the given node to the receivers collection of children, and sets this object as the parent
of the node"
self children removeLast.
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> removeNode: aNode [
self children remove: aNode.
]
{ #category : #accessing }
GrafoscopioNode >> saveContent: anObject [
"Sets the receivers body to the given object"
body := anObject
]
{ #category : #accessing }
GrafoscopioNode >> specModelClass [
self tags = 'código' ifTrue: [^GrafoscopioCodeModel].
self tags = 'johan' ifTrue:[^GrafoscopioButtonModel].
"por defecto"
^ GrafoscopioTextModel
]
{ #category : #accessing }
GrafoscopioNode >> tagAs: aTag [
"Tags the recipient node with aTag. For the moment we will have only one tag.
In the future we will have several and there will be rules to know how tags interact with
each other"
tags := aTag.
]
{ #category : #accessing }
GrafoscopioNode >> tags [
"Returns the receiver tags. For the moment is just one... yes silly, but will be extenden properly"
^ tags
]
{ #category : #accessing }
GrafoscopioNode >> title [
"Returns the receiver header"
^ header
]
{ #category : #operation }
GrafoscopioNode >> visitLastLink [
links ifNil: [ self inform: 'This node has no associated links to visit'. ^ self ].
[WebBrowser openOn: self lastLink] fork.
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> visitedGoTo: aCollection [
"Stores the current node in a collection and recursively stores its children"
aCollection add: self.
(self children isNotEmpty) & ((self header findString: '#invisible')=1) not
ifTrue: [ (self children) do: [ :eachNode | eachNode visitedGoTo: aCollection]].
]