Changing to a new image because of System Browser bug.
This commit is contained in:
parent
0e8846a161
commit
c83cb4d5ba
@ -13,13 +13,11 @@ Class {
|
||||
#superclass : #Object,
|
||||
#instVars : [
|
||||
'header',
|
||||
'headers',
|
||||
'created',
|
||||
'edited',
|
||||
'headers',
|
||||
'key',
|
||||
'id',
|
||||
'selected',
|
||||
'expanded',
|
||||
'key',
|
||||
'icon',
|
||||
'body',
|
||||
'tags',
|
||||
@ -107,10 +105,7 @@ GrafoscopioNode >> addNode: aNode [
|
||||
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: ''.
|
||||
genericNode := self class new header: 'newNode'; body: ''.
|
||||
self parent children add: genericNode after: self.
|
||||
genericNode parent: self parent.
|
||||
genericNode level: self level.
|
||||
@ -190,17 +185,6 @@ 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).
|
||||
@ -217,29 +201,24 @@ GrafoscopioNode >> asText [
|
||||
GrafoscopioNode >> becomeDefaultTestTree [
|
||||
| node1 node2 node3 node4 |
|
||||
self
|
||||
created: DateAndTime now printString;
|
||||
level: 0;
|
||||
level: 0;
|
||||
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';
|
||||
level: 1.
|
||||
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>'.
|
||||
@ -255,12 +234,10 @@ GrafoscopioNode >> becomeDefaultTree [
|
||||
| node1 |
|
||||
self class new.
|
||||
self
|
||||
created: DateAndTime now printString;
|
||||
level: 0;
|
||||
header: 'Arbol principal';
|
||||
tagAs: 'código'.
|
||||
node1 := self class new
|
||||
created: DateAndTime now printString;
|
||||
header: 'Node 1';
|
||||
body: '';
|
||||
tagAs: 'text'.
|
||||
@ -278,6 +255,8 @@ GrafoscopioNode >> body [
|
||||
|
||||
{ #category : #accessing }
|
||||
GrafoscopioNode >> body: anObject [
|
||||
"Sets the receivers body to the given object"
|
||||
|
||||
body := anObject
|
||||
]
|
||||
|
||||
@ -302,26 +281,9 @@ GrafoscopioNode >> bodyAsMarkdownInto: aStream [
|
||||
|
||||
{ #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"
|
||||
^ (SHA1 new hashMessage: self root flatten asSton) hex
|
||||
]
|
||||
|
||||
{ #category : #accessing }
|
||||
@ -343,7 +305,7 @@ GrafoscopioNode >> children: aCollection [
|
||||
GrafoscopioNode >> content [
|
||||
"Returns the receivers body"
|
||||
|
||||
^ self body
|
||||
^ body
|
||||
|
||||
]
|
||||
|
||||
@ -361,19 +323,6 @@ GrafoscopioNode >> copyToClipboard [
|
||||
|
||||
]
|
||||
|
||||
{ #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
|
||||
@ -404,34 +353,6 @@ GrafoscopioNode >> demote [
|
||||
|
||||
]
|
||||
|
||||
{ #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.
|
||||
@ -466,13 +387,6 @@ 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
|
||||
@ -653,18 +567,6 @@ GrafoscopioNode >> icon: aSymbol [
|
||||
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. "
|
||||
@ -708,21 +610,6 @@ 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' ].
|
||||
@ -804,12 +691,12 @@ GrafoscopioNode >> links: anObject [
|
||||
]
|
||||
|
||||
{ #category : #operation }
|
||||
GrafoscopioNode >> linksToMarkupFile [
|
||||
GrafoscopioNode >> linksToMarkdownFile [
|
||||
"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'))]
|
||||
detect: [:l | (l endsWith: '.md') or: [ l endsWith: '.markdown']]
|
||||
ifFound: [ ^ true ]
|
||||
ifNone: [^ false]].
|
||||
^ false
|
||||
@ -1017,21 +904,6 @@ GrafoscopioNode >> preorderTraversal [
|
||||
^ 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"
|
||||
@ -1122,20 +994,8 @@ GrafoscopioNode >> saveContent: 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
|
||||
GrafoscopioNode >> selectMarkdownSubtreesToExport [
|
||||
^ (self root preorderTraversal) select: [ :each | each linksToMarkdownFile ].
|
||||
]
|
||||
|
||||
{ #category : #accessing }
|
||||
@ -1167,13 +1027,10 @@ GrafoscopioNode >> surfaceCopy [
|
||||
to the rest of the container tree, which could end in copying the whole tree."
|
||||
| newNode |
|
||||
newNode := self class new.
|
||||
newNode
|
||||
^ newNode
|
||||
header: self header;
|
||||
body: self body;
|
||||
tags: self tags;
|
||||
level: self level.
|
||||
self links ifNotEmpty: [ newNode links addAll: self links ].
|
||||
^ newNode.
|
||||
tags: self tags.
|
||||
|
||||
|
||||
]
|
||||
@ -1229,36 +1086,6 @@ GrafoscopioNode >> toggleCodeText [
|
||||
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)
|
||||
|
@ -60,7 +60,7 @@ GrafoscopioNodeTest >> testHasMarkdownSubtreesToExport [
|
||||
Please see look #becomeDefaultTestTree message to see the details that makes this test true."
|
||||
| tree |
|
||||
tree := GrafoscopioNode new becomeDefaultTestTree.
|
||||
self assert: tree selectMarkupSubtreesToExport isNotEmpty equals: true.
|
||||
self assert: tree selectMarkdownSubtreesToExport isNotEmpty equals: true.
|
||||
|
||||
]
|
||||
|
||||
@ -69,17 +69,6 @@ GrafoscopioNodeTest >> testInitializeIsOk [
|
||||
self shouldnt: [ GrafoscopioNode new ] raise: Error
|
||||
]
|
||||
|
||||
{ #category : #tests }
|
||||
GrafoscopioNodeTest >> testNodeSelection [
|
||||
| tree child1 |
|
||||
tree := GrafoscopioNode new becomeDefaultTestTree.
|
||||
child1 := tree preorderTraversalRootChildren at: 1.
|
||||
child1 selected: true.
|
||||
self assert: tree detectSelectionIndex equals: 1
|
||||
|
||||
|
||||
]
|
||||
|
||||
{ #category : #tests }
|
||||
GrafoscopioNodeTest >> testPromoteNode [
|
||||
| tree child1 child2 |
|
||||
@ -146,16 +135,3 @@ GrafoscopioNodeTest >> testSanitizedLink [
|
||||
self assert: (node sanitizeDefaultLink = 'https://docutopia.tupale.co/hackbo:hackbot') equals: true
|
||||
|
||||
]
|
||||
|
||||
{ #category : #tests }
|
||||
GrafoscopioNodeTest >> testToggleNodeSelection [
|
||||
"I verify that a selected node can be unchosen once a new selection has been done."
|
||||
|
||||
| tree testNode1 testNode2 |
|
||||
tree := GrafoscopioNode new becomeDefaultTestTree.
|
||||
testNode1 := (tree preorderTraversalRootChildren at: 1) selected: true.
|
||||
self assert: tree detectSelectionIndex equals: testNode1 preorderTraversalIndex.
|
||||
testNode2 := (tree preorderTraversalRootChildren at: 2).
|
||||
testNode2 toggleSelected.
|
||||
self assert: tree detectSelectionIndex equals: testNode2 preorderTraversalIndex
|
||||
]
|
||||
|
@ -72,41 +72,17 @@ GrafoscopioNotebook >> addNode [
|
||||
self notebookContent: notebook.
|
||||
]
|
||||
|
||||
{ #category : #persistence }
|
||||
GrafoscopioNotebook >> askToSaveBeforeClosing [
|
||||
|
||||
| saveChanges |
|
||||
|
||||
saveChanges := UIManager default
|
||||
question: 'Do you want to save changes in the notebook before closing?'
|
||||
title: 'Save changes before closing?'.
|
||||
saveChanges ifNil: [ ^ self notebook unsavedNodes inspect ].
|
||||
^ saveChanges
|
||||
]
|
||||
|
||||
{ #category : #operation }
|
||||
GrafoscopioNotebook >> autoSaveBodyOf: aNode [
|
||||
| playground bodyContents |
|
||||
bodyContents := aNode body.
|
||||
self body class = GrafoscopioTextModel
|
||||
ifTrue: [ self body body whenTextChanged: [ :arg |
|
||||
aNode body: arg.
|
||||
"self body body whenTextIsAccepted: [:bodyText |
|
||||
self inform: bodyText.
|
||||
aNode updateEditionTimestamp ]."
|
||||
bodyContents = arg ifFalse: [
|
||||
"self inform: arg."
|
||||
"aNode updateEditionTimestamp" ]]].
|
||||
self body body class = GlamourPresentationModel
|
||||
| playground |
|
||||
self body class = GrafoscopioTextModel
|
||||
ifTrue: [ body body whenTextChanged: [ :arg | aNode body: arg ] ].
|
||||
body body class = GlamourPresentationModel
|
||||
ifFalse: [ ^ self ].
|
||||
playground := self body body glmPres.
|
||||
playground := body body glmPres.
|
||||
playground
|
||||
onChangeOfPort: #text
|
||||
act: [ :x |
|
||||
aNode body: (x pane port: #entity) value content.
|
||||
"aNode updateEditionTimestamp."
|
||||
"self inform: aNode edited" ]
|
||||
|
||||
act: [ :x | aNode body: (x pane port: #entity) value content ]
|
||||
]
|
||||
|
||||
{ #category : #accessing }
|
||||
@ -120,7 +96,7 @@ GrafoscopioNotebook >> body: anObject [
|
||||
]
|
||||
|
||||
{ #category : #utilities }
|
||||
GrafoscopioNotebook >> checksumForRootSubtree [
|
||||
GrafoscopioNotebook >> checksum [
|
||||
"I return the checksum (crypto hash) of the workingFile where this notebook is being stored.
|
||||
I'm useful for data provenance and traceability of derivated files coming from this source
|
||||
notebook."
|
||||
@ -211,9 +187,9 @@ GrafoscopioNotebook >> downloadImages [
|
||||
]
|
||||
|
||||
{ #category : #persistence }
|
||||
GrafoscopioNotebook >> exportAllSubtreesAsMarkup [
|
||||
GrafoscopioNotebook >> exportAllSubtreesAsMarkdow [
|
||||
| toBeExported |
|
||||
toBeExported := self notebook selectMarkupSubtreesToExport.
|
||||
toBeExported := self notebook selectMarkdownSubtreesToExport.
|
||||
toBeExported ifEmpty: [ ^ self ].
|
||||
toBeExported do: [ :each | self subtreeAsMarkdownFileFor: each ].
|
||||
self inform: toBeExported size asString , ' exported markdown subtrees.'
|
||||
@ -286,13 +262,11 @@ GrafoscopioNotebook >> exportAsPDF [
|
||||
{ #category : #persistence }
|
||||
GrafoscopioNotebook >> exportAsSton: aNotebook on: aFileStream [
|
||||
aNotebook flatten.
|
||||
self notebook root updateEditionTimestamp.
|
||||
(STON writer on: aFileStream)
|
||||
(STON writer on: aFileStream)
|
||||
newLine: String crlf;
|
||||
prettyPrint: true;
|
||||
keepNewLines: true;
|
||||
nextPut: aNotebook children.
|
||||
|
||||
nextPut: aNotebook children
|
||||
]
|
||||
|
||||
{ #category : #utility }
|
||||
@ -310,7 +284,7 @@ GrafoscopioNotebook >> exportNode: aGrafoscopioNode asMarkdownIn: aFile [
|
||||
stream
|
||||
nextPutAll:
|
||||
('---', String cr,
|
||||
'exportedFrom: ', self checksumForRootSubtree, String cr) withInternetLineEndings.
|
||||
'exportedFrom: ', self checksum, String cr) withInternetLineEndings.
|
||||
aGrafoscopioNode metadataAsYamlIn: stream.
|
||||
stream
|
||||
nextPutAll:
|
||||
@ -339,11 +313,6 @@ GrafoscopioNotebook >> findAndReplace [
|
||||
|
||||
]
|
||||
|
||||
{ #category : #testing }
|
||||
GrafoscopioNotebook >> hasAWorkingFileDefined [
|
||||
self workingFile ifNil: [ ^ false ] ifNotNil: [ ^ true ]
|
||||
]
|
||||
|
||||
{ #category : #accessing }
|
||||
GrafoscopioNotebook >> header [
|
||||
^ header
|
||||
@ -425,12 +394,8 @@ GrafoscopioNotebook >> initializePresenter [
|
||||
(tree highlightedItem content header) = arg
|
||||
ifFalse: [
|
||||
tree highlightedItem content header: arg.
|
||||
tree highlightedItem content updateEditionTimestamp.
|
||||
tree roots: tree roots]].
|
||||
links whenTextChanged: [ :arg |
|
||||
tree highlightedItem content addLink: arg.
|
||||
tree highlightedItem content updateEditionTimestamp.
|
||||
]
|
||||
links whenTextChanged: [ :arg | tree highlightedItem content addLink: arg ]
|
||||
]
|
||||
|
||||
{ #category : #initialization }
|
||||
@ -439,7 +404,6 @@ GrafoscopioNotebook >> initializeWidgets [
|
||||
header := self newTextInput.
|
||||
header autoAccept: true.
|
||||
body := self newText.
|
||||
body class logCr.
|
||||
body disable.
|
||||
body text: '<- Select a node'.
|
||||
body autoAccept: true.
|
||||
@ -456,17 +420,6 @@ GrafoscopioNotebook >> initializeWidgets [
|
||||
self askOkToClose: true.
|
||||
]
|
||||
|
||||
{ #category : #persistence }
|
||||
GrafoscopioNotebook >> isSaved [
|
||||
"I tell if a notebook has been saved in a persistence storage, including last editions."
|
||||
^ self hasAWorkingFileDefined and: [self isSavedAfterLastEdition ].
|
||||
]
|
||||
|
||||
{ #category : #testing }
|
||||
GrafoscopioNotebook >> isSavedAfterLastEdition [
|
||||
^ self notebook isSavedAfterLastEdition
|
||||
]
|
||||
|
||||
{ #category : #accessing }
|
||||
GrafoscopioNotebook >> links [
|
||||
^ links
|
||||
@ -677,10 +630,9 @@ GrafoscopioNotebook >> notebookSubMenu [
|
||||
action: [ self defineDebugMessageUI ] ] ]
|
||||
]
|
||||
|
||||
{ #category : #'event handling' }
|
||||
{ #category : #private }
|
||||
GrafoscopioNotebook >> okToChange [
|
||||
|
||||
self isSaved ifTrue: [ ^ true ] ifFalse: [ ^ self askToSaveBeforeClosing ]
|
||||
^ true
|
||||
]
|
||||
|
||||
{ #category : #persistence }
|
||||
@ -847,7 +799,7 @@ GrafoscopioNotebook >> removeNode [
|
||||
|
||||
{ #category : #persistence }
|
||||
GrafoscopioNotebook >> saveToFile: aFileReference [
|
||||
"I save the current tree/document to a file and update storage timestamp."
|
||||
"I save the current tree/document to a file."
|
||||
|
||||
aFileReference ifNil: [ self inform: 'No file selected for saving. Save NOT done.'. ^ self ].
|
||||
workingFile := aFileReference.
|
||||
@ -879,7 +831,6 @@ GrafoscopioNotebook >> saveWorkingNotebook [
|
||||
self workingFile
|
||||
ifNil: [ self saveToFileUI ]
|
||||
ifNotNil: [ self saveToFile: workingFile ].
|
||||
self notebook root updateEditionTimestamp.
|
||||
GfUIHelpers updateRecentNotebooksWith: workingFile
|
||||
|
||||
|
||||
@ -940,7 +891,7 @@ GrafoscopioNotebook >> topBar [
|
||||
name: nil;
|
||||
description: 'Export all Markdown subtrees';
|
||||
icon: (self iconNamed: #glamorousMore);
|
||||
action: [ self exportAllSubtreesAsMarkup ] ].
|
||||
action: [ self exportAllSubtreesAsMarkdow ] ].
|
||||
group
|
||||
addItem: [ :item |
|
||||
item
|
||||
@ -1111,7 +1062,6 @@ GrafoscopioNotebook >> updateBodyFor: aNodeContainer [
|
||||
tree needRebuild: false.
|
||||
body needRebuild: true.
|
||||
aNode := aNodeContainer content.
|
||||
aNode toggleSelected.
|
||||
header text: aNode header.
|
||||
body := self instantiate: aNode specModelClass new.
|
||||
body content: aNode body.
|
||||
|
@ -4,7 +4,7 @@ Usually my content is markdown text.
|
||||
"
|
||||
Class {
|
||||
#name : #GrafoscopioTextModel,
|
||||
#superclass : #ComposablePresenter,
|
||||
#superclass : #ComposableModel,
|
||||
#instVars : [
|
||||
'body'
|
||||
],
|
||||
|
Loading…
Reference in New Issue
Block a user