Grafoscopio/repository/Grafoscopio/GrafoscopioNode.class.st

1286 lines
36 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',
'created',
'edited',
'selected',
'key',
'icon',
'body',
'tags',
'children',
'parent',
'node',
'nodesInPreorder',
'links',
'output'
],
#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 parent = clipboard parent ifTrue: [ ref parent: nil ]].
clipboard parent: nil.
]
{ #category : #accessing }
GrafoscopioNode class >> clipboard [
^ clipboard
]
{ #category : #accessing }
GrafoscopioNode class >> clipboard: anObject [
clipboard := anObject
]
{ #category : #utility }
GrafoscopioNode class >> contentProviders [
"I list the domains of certain providers that are treated specially, because they
store and offer content like Smalltalk playgrounds or source code, that can be used
in particular ways while importing or exporting content in a node."
^ Dictionary new
at: 'playgrounds' put: #('ws.stfx.eu');
at: 'fossil' put: #('mutabit.com/repos.fossil');
at: 'etherpads' put: #('pad.tupale.co' );
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' '%metadata' '%output' '%embed' '%item').
]
{ #category : #operation }
GrafoscopioNode >> addLink: anUrl [
"anUrl is a string"
(self links includes: anUrl)
ifFalse: [ self links add: anUrl ]
]
{ #category : #adding }
GrafoscopioNode >> addNode: aNode [
"Adds the given node to the receivers collection of children, and sets this object as the parent
of the node"
"aNode parent = self ifTrue: [ ^ self ]."
self children add: aNode.
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
created: DateAndTime now printString;
header: 'newNode';
body: ''.
self parent children add: genericNode after: self.
genericNode parent: self parent.
^ 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 parent notNil and: [ currentNode level > 0 ] ]
whileTrue: [
ancestors add: currentNode parent.
currentNode := currentNode parent].
ancestors := ancestors reversed.
^ ancestors
]
{ #category : #accessing }
GrafoscopioNode >> ancestorsAll [
"I return a collection of all the nodes wich are ancestors of the receiver node"
| currentNode ancestors |
currentNode := self.
ancestors := OrderedCollection new.
[ currentNode parent notNil and: [ 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 metadataAsYamlIn: markdownOutput."
(self preorderTraversal) do: [ :eachNode |
(eachNode level > 0)
ifTrue: [(eachNode hasAncestorTaggedAs: 'invisible')
| (eachNode tags includes: 'invisible')
ifFalse: [
markdownOutput nextPutAll: (eachNode markdownContent) ]]].
^ markdownOutput contents
]
{ #category : #exporting }
GrafoscopioNode >> asSton [
"Exports current tree as STON format"
| stonOutput |
stonOutput := '' writeStream.
stonOutput nextPutAll: (STON toStringPretty: self "flatten").
^stonOutput contents
]
{ #category : #exporting }
GrafoscopioNode >> asStonFromRoot [
"Exports current tree as STON format"
| stonOutput |
stonOutput := '' writeStream.
self flatten.
stonOutput nextPutAll: (STON toStringPretty: self children).
^stonOutput contents
]
{ #category : #initialization }
GrafoscopioNode >> becomeDefaultTestTree [
| node1 node2 node3 node4 |
self
created: DateAndTime now printString;
header: 'Arbol principal'.
node1 := self class new
created: DateAndTime now printString;
header: 'Markup';
body: 'I am <b>just a node with markup</b>';
tagAs: 'text';
links: 'temp.md'.
node2 := self class new
created: DateAndTime now printString;
header: '%output Code';
tagAs: 'código';
body: '(ConfigurationOfGrafoscopio>>#version14:) sourceCode'.
node3 := self class new
created: DateAndTime now printString;
header: '%invisible';
tagAs: 'text';
body: '<i>Just testing</i>'.
node1 addNode: node3.
node4 := self class new
created: DateAndTime now printString;
header: 'Something';
tagAs: 'text';
body: '<h1>else</h1>'.
node1 addNode: node4.
node1 addNode: node2.
self
addNode: node1.
]
{ #category : #initialization }
GrafoscopioNode >> becomeDefaultTree [
"I create a starting tree for all Grafoscopio notebooks with just one textual node as child."
| node1 |
self class new.
self
created: DateAndTime now printString;
header: 'Arbol principal';
tagAs: 'código'.
node1 := self class new
created: DateAndTime now printString;
header: 'Node 1';
body: '';
tagAs: 'text'.
self addNode: node1.
^ self
]
{ #category : #accessing }
GrafoscopioNode >> body [
"Returns the receivers body"
^ body
]
{ #category : #accessing }
GrafoscopioNode >> body: anObject [
body := anObject
]
{ #category : #exporting }
GrafoscopioNode >> bodyAsCode [
"I return the node body with proper decorators added to show them as raw code"
| codeBody |
codeBody := '' writeStream.
codeBody
nextPutAll: '~~~{.numberLines}'; lf;
nextPutAll: (self body contents asString withInternetLineEndings); lf;
nextPutAll: '~~~'; lf; lf.
^ codeBody contents
]
{ #category : #exporting }
GrafoscopioNode >> bodyAsMarkdownInto: aStream [
"I export the header as markdown using the level inside the tree to determine hierarchy
and replacing all line endings to make them Internet friendly".
self embeddedNodes ifNotNil: [ aStream nextPutAll: (self embedNodes contents asString withInternetLineEndings); crlf; crlf].
]
{ #category : #exporting }
GrafoscopioNode >> calculateLevel [
^ parent ifNil: [ 0 ] ifNotNil: [ 1 + parent calculateLevel ]
]
{ #category : #operation }
GrafoscopioNode >> checksum [
"I return the SHA1SUM of the current node.
I'm used to test changes on the node contents, without including changes in the children."
| nodeCopy |
nodeCopy := self surfaceCopy.
^ self checksumFor: nodeCopy asSton.
]
{ #category : #utility }
GrafoscopioNode >> checksumFor: aText [
"I return the SHA1SUM of the current tree. I'm used to test changes on the contents
and for traceability of how the document tree is converted to other formats, as markdown."
^ (SHA1 new hashMessage: aText) hex
]
{ #category : #operation }
GrafoscopioNode >> checksumForRootSubtree [
"I return the SHA1SUM of the current tree. I'm used to test changes on the contents
and for traceability of how the document tree is converted to other formats, as markdown."
^ self checksumFor: self root flatten asStonFromRoot.
"^ (SHA1 new hashMessage: self root flatten asStonFromRoot) hex"
]
{ #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"
^ self 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 subtreeCopy.
]
{ #category : #accessing }
GrafoscopioNode >> created [
^ created
]
{ #category : #accessing }
GrafoscopioNode >> created: aTimestamp [
"I tell when this object was created"
created := aTimestamp
]
{ #category : #operation }
GrafoscopioNode >> currentLink [
"TODO: This method should not only select sanitized links, but also provide ways to detect wich link
is selected from the list. For the moment, is only the last one, but probably links needs to be heavily
refactored to support this kind of operations and a better UI."
^ self sanitizeDefaultLink
]
{ #category : #utility }
GrafoscopioNode >> deleteReferencesToRoot: aRootNode [
| sparseTree |
sparseTree := self preorderTraversal.
]
{ #category : #movement }
GrafoscopioNode >> demote [
"I move the current node down in the hierachy, making it 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 : #'as yet unclassified' }
GrafoscopioNode >> detectSelectionIndex [
"I tell which is the index of the current selected node or return the first childre
(indexed at 1) if is not found."
| root |
root := self root.
root preorderTraversal allButFirst doWithIndex: [ :currentNode :index |
currentNode isSelected ifTrue: [ ^ index ] ].
^ 1.
]
{ #category : #accessing }
GrafoscopioNode >> edited [
^ edited
]
{ #category : #accessing }
GrafoscopioNode >> edited: aTimestamp [
"I store the last time when a node was edited.
Because nodes in the notebook have a autosave feature, I'm updated automatically when nodes are
edited from the GUI.
If I'm in the notebook root (i.e. node's level equals 0) I should store the last time the notebook
was saved on the hard drive."
edited := aTimestamp
]
{ #category : #'custom markup' }
GrafoscopioNode >> embedAll [
"This is just a previous part of the messy markDownContent. The %embed-all keyword should be revaluated.
By default a node embeds all its children. Any non-embedable content should be under a %invisible node"
"(temporalBody includesSubstring: '%embed-all')
ifFalse: [ ]
ifTrue: [
self embeddedNodes do: [ :each |
temporalBody := temporalBody copyReplaceAll: '%embed-all' with: (each body, (String with: Character cr),
'%embed-all')].
temporalBody := temporalBody copyReplaceAll: '%embed-all' with: '']"
]
{ #category : #'custom markup' }
GrafoscopioNode >> embedNodes [
"I find any ocurrence of '%embed a node header' in the body of a node and replace it
by the children which have such header.
Using embedded nodes is useful to change the order in which children appear into parents body,
while exporting"
| temporalBody |
temporalBody := self body.
self embeddedNodes ifNotNil: [ self embeddedNodes do: [ :each |
(each isTaggedAs: 'código')
ifFalse: [temporalBody := temporalBody copyReplaceAll: (each header) with: each body]
ifTrue: [temporalBody := temporalBody copyReplaceAll: (each header) with: each bodyAsCode]]].
^ temporalBody
]
{ #category : #'custom markup' }
GrafoscopioNode >> embeddedNodes [
^ self children select: [:each | each headerStartsWith: '%embed']
]
{ #category : #accessing }
GrafoscopioNode >> expanded: aBoolean [
"I tell if the node is expanded from the UI, showing my children.
Several nodes can be expanded in a single document."
selected := aBoolean
]
{ #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."
aStream nextPutAll: ('~~~{.numberLines}'); lf.
aStream nextPutAll: (self body contents asString withInternetLineEndings); lf.
aStream nextPutAll: ('~~~'); lf;lf.
^aStream contents
]
{ #category : #exporting }
GrafoscopioNode >> exportCodeNodeTo: aStream [
"I convert the content of a node taged as 'código' (code) as pandoc markdown
and put it into aStream."
((self headerStartsWith: '%output') or: [ self headerStartsWith: '%metadata' ])
ifTrue: [ self exportCodeOutputTo: aStream ]
ifFalse: [ self exportCodeBlockTo: aStream ]
]
{ #category : #exporting }
GrafoscopioNode >> exportCodeOutputTo: aStream [
"I convert the output of a node taged as 'código' (code) as pandoc markdown and
put it into aStream."
(self headerStartsWith: '%metadata') ifTrue: [ ^ self ].
aStream nextPutAll: ('~~~{.numberLines}'); lf.
aStream nextPutAll: (self output asString withInternetLineEndings); lf.
aStream nextPutAll: ('~~~'); lf;lf.
^aStream contents
]
{ #category : #exporting }
GrafoscopioNode >> exportLaTeXCodeBlockTo: 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 asString withInternetLineEndings); lf.
aStream nextPutAll: '\end{minted}';lf;lf.
^aStream contents
]
{ #category : #exporting }
GrafoscopioNode >> exportPreambleTo: aStream [
"comment stating purpose of message"
| configDict |
(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]
]
{ #category : #utility }
GrafoscopioNode >> find: aString andReplaceWith: anotherString [
anotherString ifNil: [ ^ self ].
self body: ((self body) copyReplaceAll: aString with: anotherString)
]
{ #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 >> footnoteAsMarkdownInto: aStream [
"I export a node with %footnode in its header for valid Pandoc's markdown
and replace all line endings to make them Internet friendly.
Maybe I should include the condition about my own header, instead of leaving it to markdownCotent..."
aStream nextPutAll: ('[^',(self header copyReplaceAll: '%footnote ' with: ''),']: ' ); lf.
self body contents asString withInternetLineEndings
linesDo: [ :line | aStream nextPutAll: ' ', line; lf ].
aStream nextPutAll: String lf.
]
{ #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 includes: 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 : #exporting }
GrafoscopioNode >> headerAsMarkdownInto: aStream [
"I export the header as markdown using the level inside the tree to determine hierarchy
and replacing all line endings to make them Internet friendly"
self level timesRepeat: [ aStream nextPutAll: '#' ].
aStream nextPutAll: ' '.
aStream nextPutAll: (self header copyReplaceTokens: #cr with: #lf); crlf; crlf.
]
{ #category : #'custom markup' }
GrafoscopioNode >> headerStartsWith: aString [
^ (self header findString: aString) = 1
]
{ #category : #accessing }
GrafoscopioNode >> headers [
"I returns the headers of the receiver children"
^ headers := self children collect: [:currentNode | currentNode header ]
]
{ #category : #operation }
GrafoscopioNode >> htmlToMarkdown [
"I convert the node body from HTML format to Pandoc's Markdown."
| htmlFile |
(self isTaggedAs: 'código' ) ifTrue: [ ^self ].
((self headerStartsWith: '%invisible') "or:[self hasAncestorHeaderWith: '%invisible']")
ifTrue: [ ^self ].
htmlFile := FileLocator temp asFileReference / 'body.html'.
htmlFile ensureCreateFile.
htmlFile writeStreamDo: [:out | out nextPutAll: self body ].
Smalltalk platformName = 'unix'
ifTrue: [ self body: (Pandoc htmlToMarkdown: htmlFile) ].
Smalltalk platformName = 'Win32'
ifTrue: [ self shouldBeImplemented ].
htmlFile ensureDelete.
]
{ #category : #operation }
GrafoscopioNode >> htmlToMarkdownSubtree [
"I convert self and childern nodes body from HTML format to Pandoc's Markdown."
self preorderTraversal do: [ :each | each htmlToMarkdown ]
]
{ #category : #accessing }
GrafoscopioNode >> icon [
"Returns the receivers icon"
^icon
]
{ #category : #accessing }
GrafoscopioNode >> icon: aSymbol [
"Sets the receivers icon"
icon := aSymbol
]
{ #category : #accessing }
GrafoscopioNode >> id [
^id
]
{ #category : #accessing }
GrafoscopioNode >> id: aChecksum [
"I'm a unique identifier that changes when node content changes (i.e. header, body, links)."
id := aChecksum
]
{ #category : #importing }
GrafoscopioNode >> importHtmlLink [
"I take the last link and import its contents in node body. "
| selectedLink downloadedContent |
selectedLink := self currentLink.
selectedLink asUrl host = 'ws.stfx.eu' ifTrue: [ ^ self ].
selectedLink asUrl host = 'docutopia.tupale.co'
ifTrue: [ self inform: 'Docutopia importing still not supported.'.
^ self ].
downloadedContent := (GrafoscopioUtils
downloadingFrom: selectedLink
withMessage: 'Downloading node contents...'
into: FileLocator temp).
self uploadBodyFrom: downloadedContent filteredFor: selectedLink.
]
{ #category : #importing }
GrafoscopioNode >> importPlaygroundLink [
"I take the last link and import its contents in node body.
Last links should be hosted in http://zn.stfx.eu/"
self currentLink asUrl host = 'ws.stfx.eu' ifFalse: [ ^ self ].
self
body: (ZnClient new get: self currentLink);
tagAs: 'código'.
]
{ #category : #initialization }
GrafoscopioNode >> initialize [
"I create a empty new node"
super initialize.
self
header: 'newHeader';
tagAs: 'text';
body: ''
]
{ #category : #accessing }
GrafoscopioNode >> isEmpty [
body ifNil: [ ^ true ] ifNotNil: [ ^ false ]
]
{ #category : #operation }
GrafoscopioNode >> isSavedAfterLastEdition [
| root |
root := self root.
root edited ifNil: [ ^ false ].
^ self unsavedNodes isEmpty.
"self unsavedNodes isEmpty ifFalse: [ ^ self unsavedNodes inspect ]"
]
{ #category : #testing }
GrafoscopioNode >> isSelected [
self selected ifNil: [ ^ false ].
^ self selected.
]
{ #category : #operation }
GrafoscopioNode >> isTaggedAs: aString [
self tags ifEmpty: [ self tagAs: 'text' ].
^ self tags includes: aString
]
{ #category : #exporting }
GrafoscopioNode >> itemAsMarkdownInto: aStream [
"I export a node with %item in its header as valid Pandoc's markdown
and replace all line endings to make them Internet friendly.
Maybe I should include the condition about my own header, instead of leaving it to markdownContent..."
| lines |
lines := self body contents asString withInternetLineEndings lines.
lines ifEmpty: [ ^ self ].
aStream
nextPutAll: ' - ';
nextPutAll: lines first;
lf.
lines
allButFirstDo: [ :line |
aStream
nextPutAll: ' ';
nextPutAll: line;
lf ].
aStream nextPutAll: String lf
]
{ #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 [
self links ifNil: [ ^ '' ].
self links ifEmpty: [ ^ '' ].
^ self links last
]
{ #category : #accessing }
GrafoscopioNode >> lastNetLink [
^ self links detect: [ :l | l asZnUrl isURL ]
]
{ #category : #accessing }
GrafoscopioNode >> level [
"Returns the level of the node. See the setter message for details"
^ self calculateLevel
]
{ #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 [
self links add: anObject
]
{ #category : #operation }
GrafoscopioNode >> linksToMarkupFile [
"I detect if the links contains any reference to a file ending in '.md' or '.markdown'"
self links
ifNotNil: [
self links
detect: [:l | (l endsWithAnyOf: #('.md' '.markdown' '.md.html'))]
ifFound: [ ^ true ]
ifNone: [^ false]].
^ false
]
{ #category : #operation }
GrafoscopioNode >> localFilesLinks [
"I collect all the links that point to the local file system. Because is supposed that
links contains only references to remote URL or local files, anything that is not a URL is
treated as a loca file link."
^ self links collect: [ :l | l asZnUrl host isNil ]
]
{ #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 [
"I extract 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, that use %keywords in its header or body I convert them
into proper markup"
| markdownStream |
markdownStream := '' writeStream.
(self class specialWords includes: self header) not
& (self class specialWords includes: ((self header findTokens: $ ) at: 1)) not
& (self isTaggedAs: 'código') not
& (self hasAncestorHeaderWith: '%invisible') not
ifTrue: [
self headerAsMarkdownInto: markdownStream.
self bodyAsMarkdownInto: markdownStream ].
(self headerStartsWith: '%idea')
ifTrue: [ self bodyAsMarkdownInto: markdownStream ].
(self headerStartsWith: '%item')
ifTrue: [ self itemAsMarkdownInto: markdownStream ].
(self headerStartsWith: '%footnote')
ifTrue: [ self footnoteAsMarkdownInto: markdownStream ].
((self isTaggedAs: 'código')
and: [(self hasAncestorHeaderWith: '%invisible') not
& (self headerStartsWith: '%embed') not ])
ifTrue: [ self exportCodeNodeTo: markdownStream ].
^ markdownStream contents
]
{ #category : #operation }
GrafoscopioNode >> metadata [
| mnode |
mnode := self root preorderTraversal
detect: [ :n | n headerStartsWith: '%metadata' ]
ifNone: [ ^ nil ].
^ mnode output.
]
{ #category : #exporting }
GrafoscopioNode >> metadataAsYamlIn: markdownStream [
"I convert the first '%metadata' node into a YAML preamble contents to be used by Pandoc
exportation."
self metadata
ifNil: [ markdownStream nextPutAll: String crlf. ]
ifNotNil: [
self metadata
keysAndValuesDo: [ :k :v |
k = 'pandocOptions'
ifTrue: [
markdownStream
nextPutAll:
(k, ': ', self pandocOptionsPrettyYaml) ]
ifFalse: [
markdownStream
nextPutAll:
(k , ': ' , v asString) withInternetLineEndings;
lf] ]].
markdownStream
nextPutAll: String cr, String cr.
]
{ #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 >> output [
(self isTaggedAs: 'código')
ifFalse: [ ^ self ].
self body ifNil: [ ^ nil ].
^ OpalCompiler new
source: self body;
evaluate
]
{ #category : #accessing }
GrafoscopioNode >> output: anObject [
output := anObject
]
{ #category : #utility }
GrafoscopioNode >> pandocOptions [
self metadata ifNil: [ ^ nil ].
self metadata at: 'pandocOptions' ifAbsent: [ ^ '' ].
^ self metadata at: 'pandocOptions'
]
{ #category : #utility }
GrafoscopioNode >> pandocOptionsPrettyYaml [
"I convert pandoc options, if present into an indented Yaml block."
| yamlOutput pretyOutput |
pretyOutput := STON toStringPretty: self pandocOptions.
yamlOutput := '' writeStream.
yamlOutput
nextPutAll:
'|';
lf.
pretyOutput linesDo: [ :line |
yamlOutput
nextPutAll:
' ', line;
lf ].
^ yamlOutput contents
]
{ #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"
aNode ifNil: [
parent := aNode.
^self ].
aNode parent = self ifTrue: [ ^ self ].
parent := aNode.
(aNode children includes: self)
ifFalse: [ aNode addNode: self ]
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> pasteFromClipboard [
| clipchild |
self class clipboard
ifNotNil: [
clipchild := self class clipboard.
self addNode: clipchild.
clipchild ]
ifNil: [ self inform: 'Cache is emtpy. Pleas cut/copy a node before pasting' ]
]
{ #category : #operation }
GrafoscopioNode >> preorderTraversal [
nodesInPreorder := OrderedCollection new.
self visitedGoTo: nodesInPreorder.
^ nodesInPreorder.
]
{ #category : #'as yet unclassified' }
GrafoscopioNode >> preorderTraversalIndex [
"I tell which place I occupy in the tree children (without counting the root)."
| root |
root := self root.
root preorderTraversalRootChildren doWithIndex: [ :currentNode :index |
currentNode = self ifTrue: [^ index] ].
]
{ #category : #'as yet unclassified' }
GrafoscopioNode >> preorderTraversalRootChildren [
^ self root preorderTraversal allButFirst
]
{ #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 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 : #'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 : #utility }
GrafoscopioNode >> removeLeadingLineNumbersSized: anInteger [
| cleanBody |
cleanBody := ''.
self body lines do: [ :line | | cleanLine |
line size >= anInteger
ifTrue: [ cleanLine := line copyFrom: anInteger to: line size. ]
ifFalse: [ cleanLine := '' ].
cleanBody := cleanBody, cleanLine, String cr ].
self body: cleanBody asString.
]
{ #category : #'add/remove nodes' }
GrafoscopioNode >> removeNode: aNode [
(self children includes: aNode)
ifTrue: [ self children remove: aNode ]
ifFalse: [ self inform: 'The node doesn''t belong to this node children' ]
]
{ #category : #utility }
GrafoscopioNode >> replaceAccentedHTMLChars [
self body: (self body copyReplaceAll: '&iacute;' with: 'í' )
]
{ #category : #accessing }
GrafoscopioNode >> root [
"I return the root node of the Grafoscopio tree, i.e the common ancestor of all other nodes"
self level = 0
ifFalse: [ ^ self ancestors first ].
^ self
]
{ #category : #operation }
GrafoscopioNode >> sanitizeDefaultLink [
| defaultLink sanitized protocol |
defaultLink := self lastLink.
protocol := 'docutopia://'.
sanitized := (defaultLink beginsWith: protocol)
ifTrue: [ defaultLink
copyReplaceAll: protocol
with: 'https://docutopia.tupale.co/' ]
ifFalse: [ defaultLink ].
^ sanitized
]
{ #category : #accessing }
GrafoscopioNode >> saveContent: anObject [
"Sets the receivers body to the given object"
body := anObject
]
{ #category : #operation }
GrafoscopioNode >> selectMarkupSubtreesToExport [
^ (self root preorderTraversal) select: [ :each | each linksToMarkupFile ].
]
{ #category : #accessing }
GrafoscopioNode >> selected [
^ selected
]
{ #category : #accessing }
GrafoscopioNode >> selected: aBoolean [
"I tell if the node is selected from the UI.
Once other node is selected my value becomes false."
selected := aBoolean
]
{ #category : #accessing }
GrafoscopioNode >> specModelClass [
(self isTaggedAs: 'código') ifTrue: [^GrafoscopioCodeModel].
(self isTaggedAs: 'johan') ifTrue:[^GrafoscopioButtonModel].
"por defecto"
^ GrafoscopioTextModel
]
{ #category : #operation }
GrafoscopioNode >> subtreeCopy [
"I return the same node if its subtree only contains the receiver, or a copy of the receivers
subtree, in other cases."
| linearSubtree linearSubtreeCopy |
linearSubtree := self preorderTraversal.
linearSubtreeCopy := OrderedCollection new.
linearSubtree do: [ :cn | linearSubtreeCopy add: cn surfaceCopy ].
linearSubtreeCopy allButFirst doWithIndex: [ :n :i | | parentPos |
parentPos := linearSubtree indexOf: (linearSubtree at: i+1) parent.
n parent: (linearSubtreeCopy at: parentPos) ].
^ linearSubtreeCopy at: 1.
]
{ #category : #operation }
GrafoscopioNode >> surfaceCopy [
"I copy the most relevant values of the receiver. I'm useful to avoid copying references
to the rest of the container tree, which could end in copying the whole tree."
| newNode |
newNode := self class new.
newNode
header: self header;
body: self body;
tags: self tags.
self links ifNotEmpty: [ newNode links addAll: self links ].
^ newNode.
]
{ #category : #accessing }
GrafoscopioNode >> tagAs: aTag [
"Tags the recipient node with aTag (string). 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"
aTag = 'código' ifTrue: [ ^ self toggleCodeText ].
(self tags includes: aTag)
ifFalse: [ self tags add: aTag ].
^ self
]
{ #category : #accessing }
GrafoscopioNode >> tags [
"I returns the receiver tags."
| migration |
tags isString
ifTrue: [
migration := tags.
tags := OrderedCollection new.
self tagAs: migration ].
tags ifNil: [
tags := OrderedCollection new.
self tagAs: 'text' ].
^ tags
]
{ #category : #accessing }
GrafoscopioNode >> tags: aCollection [
tags := aCollection
]
{ #category : #accessing }
GrafoscopioNode >> title [
"Returns the receiver header"
^ header
]
{ #category : #operation }
GrafoscopioNode >> toggleCodeText [
"Some tags are exclusionary.
For example a node can not be tagged as text and as 'code' (código) simultaneosly.
In that case, I replace the ocurrence of one tag by the other to warranty that both are not
in the same node."
(self isTaggedAs: 'text')
ifTrue: [ ^ self tags replaceAll: 'text' with: 'código'].
(self isTaggedAs: 'código')
ifTrue: [ ^ self tags replaceAll: 'código' with: 'text' ].
]
{ #category : #accessing }
GrafoscopioNode >> toggleSelected [
"I made the receiver the current selected node and deselect all other nodes."
| root previousSelection |
self isSelected ifTrue: [ ^ self ].
root := self root.
previousSelection := self preorderTraversalRootChildren at: (self detectSelectionIndex).
previousSelection selected: false.
self selected: true.
^ self.
]
{ #category : #operation }
GrafoscopioNode >> unsavedNodes [
"I collect all nodes that have changed after the last saving"
| lastSavedOn root unsavedNodes |
root := self root.
lastSavedOn := root edited asDateAndTime.
unsavedNodes := root preorderTraversal select: [ :currentNode |
currentNode edited isNotNil and: [currentNode edited asDateAndTime > lastSavedOn] ].
^ unsavedNodes.
]
{ #category : #'as yet unclassified' }
GrafoscopioNode >> updateEditionTimestamp [
self edited: DateAndTime now printString
]
{ #category : #importing }
GrafoscopioNode >> uploadBodyFrom: fileLocator filteredFor: selectedLink [
(self linksFilters contains: selectedLink)
ifFalse: [ self body: fileLocator contents ]
]
{ #category : #operation }
GrafoscopioNode >> visitLastLink [
self lastLink = ''
ifTrue: [ 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]].
]
{ #category : #'as yet unclassified' }
GrafoscopioNode >> wrapBodyLines [
"I convert the node body from HTML format to Pandoc's Markdown."
| bodyFile |
(self isTaggedAs: 'código' ) ifTrue: [ ^self ].
bodyFile := FileLocator temp asFileReference / 'body.txt'.
bodyFile ensureCreateFile.
bodyFile writeStreamDo: [:out | out nextPutAll: self body ].
Smalltalk platformName = 'unix'
ifTrue: [ self body: (self wrapBodyLinesFor: bodyFile) ].
Smalltalk platformName = 'Win32'
ifTrue: [ self shouldBeImplemented ].
bodyFile ensureDelete.
]