Transforms the level into a calculated number.

Implements 'see html' / 'see pdf'. 
Changes parts of the process usage to taskit shell. 
Starts implementation of wrapBody in image.
This commit is contained in:
SantiagoBragagnolo 2020-02-19 15:34:13 +00:00
parent 65849aad20
commit 55fe04c3a8
6 changed files with 439 additions and 113 deletions

View File

@ -44,7 +44,6 @@ GfWorldMenu class >> helpMenuOn: aBuilder [
{ #category : #'world menu' }
GfWorldMenu class >> launchMenuOn: aBuilder [
<worldMenu>
(aBuilder item: #'New notebook')
label: 'New notebook';
order: 1;
@ -55,6 +54,10 @@ GfWorldMenu class >> launchMenuOn: aBuilder [
order: 2;
parent: #GfLaunch;
action: [ GrafoscopioNotebook new openFromFileSelector ].
(aBuilder item: #GfLaunchOpenRecent)
label: 'Open recent...';
order: 2;
parent: #GfLaunch.
(aBuilder item: #'Notebook from the Internet...')
label: 'Notebook from the Internet...';
order: 3;
@ -64,7 +67,7 @@ GfWorldMenu class >> launchMenuOn: aBuilder [
label: 'Recent notebooks...';
order: 4;
parent: #GfLaunch;
action: [ GfUIHelpers openFromRecentlyUsed ].
action: [ GfUIHelpers openFromRecentlyUsed ]
]
{ #category : #'world menu' }
@ -81,6 +84,19 @@ GfWorldMenu class >> mainMenuItemsOn: aBuilder [
(aBuilder item: #GfHelpAndDocs; label: 'Help & Docs') target: self. ]
]
{ #category : #'world menu' }
GfWorldMenu class >> openRecentMenu: aBuilder [
<worldMenu>
GrafoscopioNotebook recents
do: [ :f |
(aBuilder item: #'Open', f basename )
label: 'Open ', f basename;
order: 1;
parent: #GfLaunchOpenRecent;
action: [ GrafoscopioNotebook open: f ] ]
]
{ #category : #'world menu' }
GfWorldMenu class >> updateMenuOn: aBuilder [
<worldMenu>

View File

@ -24,7 +24,6 @@ Class {
'children',
'parent',
'node',
'level',
'nodesInPreorder',
'links',
'output'
@ -96,7 +95,6 @@ GrafoscopioNode >> addNode: aNode [
of the node"
"aNode parent = self ifTrue: [ ^ self ]."
self children add: aNode.
aNode level: (self level) + 1.
aNode parent: self.
^aNode
]
@ -105,10 +103,12 @@ 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 header: 'newNode'; body: ''.
genericNode := self class new
created: DateAndTime now printString;
header: 'newNode';
body: ''.
self parent children add: genericNode after: self.
genericNode parent: self parent.
genericNode level: self level.
^ genericNode
]
@ -185,6 +185,17 @@ 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).
@ -192,33 +203,31 @@ GrafoscopioNode >> asSton [
]
{ #category : #accessing }
GrafoscopioNode >> asText [
^ self body
]
{ #category : #initialization }
GrafoscopioNode >> becomeDefaultTestTree [
| node1 node2 node3 node4 |
self
level: 0;
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';
level: 1.
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>'.
@ -234,10 +243,11 @@ GrafoscopioNode >> becomeDefaultTree [
| node1 |
self class new.
self
level: 0;
created: DateAndTime now printString;
header: 'Arbol principal';
tagAs: 'código'.
node1 := self class new
created: DateAndTime now printString;
header: 'Node 1';
body: '';
tagAs: 'text'.
@ -255,8 +265,6 @@ GrafoscopioNode >> body [
{ #category : #accessing }
GrafoscopioNode >> body: anObject [
"Sets the receivers body to the given object"
body := anObject
]
@ -279,11 +287,33 @@ GrafoscopioNode >> bodyAsMarkdownInto: aStream [
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: self root flatten asSton) hex
^ (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 }
@ -305,7 +335,7 @@ GrafoscopioNode >> children: aCollection [
GrafoscopioNode >> content [
"Returns the receivers body"
^ body
^ self body
]
@ -323,6 +353,19 @@ 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
@ -353,6 +396,34 @@ 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.
@ -387,6 +458,13 @@ 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
@ -465,7 +543,7 @@ GrafoscopioNode >> footnoteAsMarkdownInto: aStream [
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 withInternetLineEndings
self body contents asString withInternetLineEndings
linesDo: [ :line | aStream nextPutAll: ' ', line; lf ].
aStream nextPutAll: String lf.
@ -567,6 +645,18 @@ 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. "
@ -596,13 +686,12 @@ GrafoscopioNode >> importPlaygroundLink [
{ #category : #initialization }
GrafoscopioNode >> initialize [
"I create a empty new node"
super initialize.
self
self
header: 'newHeader';
tagAs: 'text';
body: '';
level: 0
body: ''
]
{ #category : #accessing }
@ -610,6 +699,21 @@ 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' ].
@ -668,15 +772,7 @@ GrafoscopioNode >> lastNetLink [
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
^ self calculateLevel
]
{ #category : #accessing }
@ -691,12 +787,12 @@ GrafoscopioNode >> links: anObject [
]
{ #category : #operation }
GrafoscopioNode >> linksToMarkdownFile [
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 endsWith: '.md') or: [ l endsWith: '.markdown']]
detect: [:l | (l endsWithAnyOf: #('.md' '.markdown' '.md.html'))]
ifFound: [ ^ true ]
ifNone: [^ false]].
^ false
@ -831,9 +927,12 @@ GrafoscopioNode >> newNode [
{ #category : #accessing }
GrafoscopioNode >> output [
(self isTaggedAs: 'código') ifFalse: [ ^ self ].
(self isTaggedAs: 'código')
ifFalse: [ ^ self ].
self body ifNil: [ ^ nil ].
^ (Compiler evaluate: self body)
^ OpalCompiler new
source: self body;
evaluate
]
{ #category : #accessing }
@ -904,6 +1003,21 @@ 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"
@ -913,7 +1027,6 @@ GrafoscopioNode >> promote [
collection isNotNil & grandparent isNotNil
ifTrue: [
(grandparent children) add: self after: (self parent).
self level: (self parent) level.
self parent: grandparent.
collection remove: self.]
@ -996,8 +1109,20 @@ GrafoscopioNode >> saveContent: anObject [
]
{ #category : #operation }
GrafoscopioNode >> selectMarkdownSubtreesToExport [
^ (self root preorderTraversal) select: [ :each | each linksToMarkdownFile ].
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 }
@ -1029,10 +1154,12 @@ 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.
self links ifNotEmpty: [ newNode links addAll: self links ].
^ newNode.
]
@ -1088,6 +1215,36 @@ 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)
@ -1126,23 +1283,3 @@ GrafoscopioNode >> wrapBodyLines [
ifTrue: [ self shouldBeImplemented ].
bodyFile ensureDelete.
]
{ #category : #'as yet unclassified' }
GrafoscopioNode >> wrapBodyLinesFor: inputFile [
| outputFile |
outputFile := FileLocator temp / 'body.tmp.txt'.
outputFile ensureDelete.
outputFile ensureCreateFile.
OSSUnixSubprocess new
command: 'fold';
arguments: {'-sw'. '80'. inputFile fullName. outputFile fullName};
redirectStdout;
redirectStderr;
runAndWaitOnExitDo: [ :process :outString :errString |
process isSuccess
ifTrue: [ ^ outString ]
ifFalse: [
self inform: errString.
^inputFile contents ]
]
]

View File

@ -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 selectMarkdownSubtreesToExport isNotEmpty equals: true.
self assert: tree selectMarkupSubtreesToExport isNotEmpty equals: true.
]
@ -69,6 +69,17 @@ 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 |
@ -135,3 +146,16 @@ 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
]

View File

@ -20,7 +20,11 @@ Class {
'workingFile',
'notebook',
'debugMessage',
'imagesList'
'imagesList',
'exporting'
],
#classInstVars : [
'recents'
],
#category : #'Grafoscopio-UI'
}
@ -48,6 +52,11 @@ GrafoscopioNotebook class >> defaultSpec [
bc add: #body; add: #links height: self toolbarHeight ]]]
]
{ #category : #'instance creation' }
GrafoscopioNotebook class >> initialize [
recents := Set new.
]
{ #category : #'instance creation' }
GrafoscopioNotebook class >> newDefault [
^ self new.
@ -58,6 +67,16 @@ GrafoscopioNotebook class >> open: aFileReference [
self newDefault openFromFile: aFileReference
]
{ #category : #'instance creation' }
GrafoscopioNotebook class >> recents [
^ recents
]
{ #category : #'instance creation' }
GrafoscopioNotebook class >> registerRecent: aFileReference [
recents add: aFileReference
]
{ #category : #utilities }
GrafoscopioNotebook >> addCommandFrom: dictionary into: stream [
dictionary keysAndValuesDo: [ :k :v |
@ -72,17 +91,41 @@ 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 |
self body class = GrafoscopioTextModel
ifTrue: [ body body whenTextChanged: [ :arg | aNode body: arg ] ].
body body class = GlamourPresentationModel
| 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
ifFalse: [ ^ self ].
playground := body body glmPres.
playground := self body body glmPres.
playground
onChangeOfPort: #text
act: [ :x | aNode body: (x pane port: #entity) value content ]
act: [ :x |
aNode body: (x pane port: #entity) value content.
"aNode updateEditionTimestamp."
"self inform: aNode edited" ]
]
{ #category : #accessing }
@ -96,7 +139,7 @@ GrafoscopioNotebook >> body: anObject [
]
{ #category : #utilities }
GrafoscopioNotebook >> checksum [
GrafoscopioNotebook >> checksumForRootSubtree [
"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."
@ -187,9 +230,15 @@ GrafoscopioNotebook >> downloadImages [
]
{ #category : #persistence }
GrafoscopioNotebook >> exportAllSubtreesAsMarkdow [
GrafoscopioNotebook >> ensureNotExporting [
self isAlreadyExporting
ifTrue: [ ^ self error: ' Already exporting! Please wait ' ]
]
{ #category : #persistence }
GrafoscopioNotebook >> exportAllSubtreesAsMarkup [
| toBeExported |
toBeExported := self notebook selectMarkdownSubtreesToExport.
toBeExported := self notebook selectMarkupSubtreesToExport.
toBeExported ifEmpty: [ ^ self ].
toBeExported do: [ :each | self subtreeAsMarkdownFileFor: each ].
self inform: toBeExported size asString , ' exported markdown subtrees.'
@ -199,24 +248,26 @@ GrafoscopioNotebook >> exportAllSubtreesAsMarkdow [
GrafoscopioNotebook >> exportAsHTML [
"I export the current tree/document to a HTML file, using pandoc external app.
I suppose pandoc is already installed and available in the system."
| htmlFile |
self markdownFile exists ifTrue: [ self markdownFile delete ].
self markdownFile exists
ifTrue: [ self markdownFile delete ].
self exportAsMarkdown.
htmlFile := self markdownFile parent fullName,'/', self markdownFile basenameWithoutExtension, '.html'.
htmlFile asFileReference exists ifTrue: [ htmlFile asFileReference delete ].
Smalltalk platformName = 'unix'
ifTrue: [
OSSUnixSubprocess new
command: 'pandoc';
arguments: {'--standalone'. self markdownFile fullName. '--output' . htmlFile};
redirectStdout;
runAndWaitOnExitDo: [ :process :outString :errString |
process isSuccess
ifTrue: [ self inform: ('File exported as: ', String cr, htmlFile) ]
ifFalse: [ self inform: 'Exportation unsuccesful. Please review that you have
installed Pandoc and have used the exportation options properly.' ]]].
htmlFile := self htmlFile.
htmlFile exists
ifTrue: [ htmlFile delete ].
self
exportUsing:
{'--standalone'.
self markdownFile fullName.
'--output'.
htmlFile fullName}
output: htmlFile fullName
"
Smalltalk platformName = 'Win32'
ifTrue: ["WinProcess createProcess: 'pandoc --standalone ', self markdownFile fullName, ' -o ', htmlFile"].
ifTrue: [WinProcess createProcess: 'pandoc --standalone ', self markdownFile fullName, ' -o ', htmlFile]."
]
{ #category : #persistence }
@ -225,12 +276,14 @@ GrafoscopioNotebook >> exportAsLaTeX [
I suppose pandoc is already installed and available in the system."
| texFile |
self markdownFile exists ifTrue: [ self markdownFile delete ].
self halt.
"self exportAsMarkdown.""<- This violates the separation of concenrs. Markdown exportation should
be explicit. There is still the issue of how to deal with desynchronization between a notebook
which has unsaved changes as markdown.... TO BE REVIWED!"
texFile := self markdownFile parent fullName,'/', self markdownFile basenameWithoutExtension, '.tex'.
texFile asFileReference exists ifTrue: [ texFile asFileReference delete ].
OSProcess command: 'pandoc --standalone ', self markdownFile fullName, ' -o ', texFile.
"OSProcess command: 'pandoc --standalone ', self markdownFile fullName, ' -o ', texFile."
self inform: ('File exported as: ', String cr, texFile).
]
@ -247,26 +300,28 @@ GrafoscopioNotebook >> exportAsPDF [
"I export the current tree/document to a PDF file, using pandoc and LaTeX external apps.
The latex engine used is xelatex, to minimize errors and warnings related with UTF8 support.
I suppose all them are already installed and defined in the system."
| pandocCommonCommand |
self markdownFile exists ifFalse: [ self exportAsMarkdown ].
| pandocCommonCommand |
self ensureNotExporting.
self exportAsMarkdown.
self pdfFile ensureDelete.
pandocCommonCommand := 'pandoc ', self pandocOptionsComputed, ' ', self markdownFile fullName,
' --output ', self pdfFile fullName.
Smalltalk platformName = 'unix'
ifTrue: [ ExternalOSProcess command: 'cd ', self markdownFile parent fullName,'; ', pandocCommonCommand ].
Smalltalk platformName = 'Win32'
ifTrue: [ WinProcess createProcess: pandocCommonCommand ].
self inform: ('File exported as: ', String cr, self pdfFile fullName)
pandocCommonCommand := self pandocOptionsComputed , ' '
, self markdownFile fullName , ' --output ' , self pdfFile fullName.
^ self
exportUsing: ((' ' split: pandocCommonCommand) reject: #isEmpty)
output: self pdfFile fullName
]
{ #category : #persistence }
GrafoscopioNotebook >> exportAsSton: aNotebook on: aFileStream [
aNotebook flatten.
(STON writer on: aFileStream)
self notebook root updateEditionTimestamp.
(STON writer on: aFileStream)
newLine: String crlf;
prettyPrint: true;
keepNewLines: true;
nextPut: aNotebook children
nextPut: aNotebook children.
]
{ #category : #utility }
@ -284,7 +339,7 @@ GrafoscopioNotebook >> exportNode: aGrafoscopioNode asMarkdownIn: aFile [
stream
nextPutAll:
('---', String cr,
'exportedFrom: ', self checksum, String cr) withInternetLineEndings.
'exportedFrom: ', self checksumForRootSubtree, String cr) withInternetLineEndings.
aGrafoscopioNode metadataAsYamlIn: stream.
stream
nextPutAll:
@ -293,6 +348,37 @@ GrafoscopioNotebook >> exportNode: aGrafoscopioNode asMarkdownIn: aFile [
self inform: 'Exported as: ', String cr, aFile fullName
]
{ #category : #persistence }
GrafoscopioNotebook >> exportUsing: arguments [
self ensureNotExporting.
exporting := (#pandoc command arguments: arguments) future.
exporting
onSuccessDo: [ :val |
exporting := nil.
self
inform: 'File exported as: ' , String cr , self pdfFile fullName ].
exporting
onFailureDo: [ :e |
exporting := nil.
self
inform: 'Error exporting, ' , self pdfFile fullName , ': ' , e messageText ]
]
{ #category : #persistence }
GrafoscopioNotebook >> exportUsing: arguments output: aName [
self ensureNotExporting.
exporting := (#pandoc command arguments: arguments) future.
exporting
onSuccessDo: [ :val |
exporting := nil.
self inform: 'File exported as: ' , String cr , aName ].
exporting
onFailureDo: [ :e |
exporting := nil.
self inform: 'Error exporting, ' , aName , ': ' , e messageText ].
^ exporting
]
{ #category : #api }
GrafoscopioNotebook >> extent [
^900@500
@ -313,6 +399,11 @@ GrafoscopioNotebook >> findAndReplace [
]
{ #category : #testing }
GrafoscopioNotebook >> hasAWorkingFileDefined [
self workingFile ifNil: [ ^ false ] ifNotNil: [ ^ true ]
]
{ #category : #accessing }
GrafoscopioNotebook >> header [
^ header
@ -323,6 +414,13 @@ GrafoscopioNotebook >> header: anObject [
header := anObject
]
{ #category : #persistence }
GrafoscopioNotebook >> htmlFile [
^ (self markdownFile parent fullName , '/'
, self markdownFile basenameWithoutExtension , '.html')
asFileReference
]
{ #category : #operation }
GrafoscopioNotebook >> htmlToMarkdown [
self currentNodeContent htmlToMarkdown.
@ -343,6 +441,7 @@ GrafoscopioNotebook >> imagesList [
{ #category : #accessing }
GrafoscopioNotebook >> imagesList: anObject [
self halt.
imagesList := anObject
]
@ -394,8 +493,12 @@ 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 ]
links whenTextChanged: [ :arg |
tree highlightedItem content addLink: arg.
tree highlightedItem content updateEditionTimestamp.
]
]
{ #category : #initialization }
@ -404,6 +507,7 @@ GrafoscopioNotebook >> initializeWidgets [
header := self newTextInput.
header autoAccept: true.
body := self newText.
body class logCr.
body disable.
body text: '<- Select a node'.
body autoAccept: true.
@ -420,6 +524,22 @@ GrafoscopioNotebook >> initializeWidgets [
self askOkToClose: true.
]
{ #category : #persistence }
GrafoscopioNotebook >> isAlreadyExporting [
^ exporting isNotNil
]
{ #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
@ -552,7 +672,7 @@ GrafoscopioNotebook >> notebookContent: aTree [
{ #category : #initialization }
GrafoscopioNotebook >> notebookSubMenu [
^ MenuModel new
^ MenuPresenter new
addGroup: [ :group |
group
addItem: [ :item |
@ -613,15 +733,20 @@ GrafoscopioNotebook >> notebookSubMenu [
addItem: [ :item |
item
name: 'See html';
icon:
(self iconNamed: #smallInspectIt);
action: [ self inform: 'To be implemented...' ] ].
icon: (self iconNamed: #smallInspectIt);
action: [ self seeHtml ] ].
group
addItem: [ :item |
item
name: 'See pdf';
icon: (Smalltalk ui icons iconNamed: #smallInspectIt);
action: [ self inform: 'To be implemented...' ] ].
action: [ self seePdf ] ].
group
addItem: [ :item |
item
name: 'Import Article';
icon: (Smalltalk ui icons iconNamed: #smallInspectIt);
action: [ self importArticle ] ].
group
addItem: [ :item |
item
@ -630,9 +755,10 @@ GrafoscopioNotebook >> notebookSubMenu [
action: [ self defineDebugMessageUI ] ] ]
]
{ #category : #private }
{ #category : #'event handling' }
GrafoscopioNotebook >> okToChange [
^ true
self isSaved ifTrue: [ ^ true ] ifFalse: [ ^ self askToSaveBeforeClosing ]
]
{ #category : #persistence }
@ -644,7 +770,7 @@ GrafoscopioNotebook >> openDefault [
{ #category : #persistence }
GrafoscopioNotebook >> openFromFile: aFileReference [
self class registerRecent: aFileReference.
self loadFromFile: aFileReference.
^ self openWithSpec.
]
@ -799,7 +925,7 @@ GrafoscopioNotebook >> removeNode [
{ #category : #persistence }
GrafoscopioNotebook >> saveToFile: aFileReference [
"I save the current tree/document to a file."
"I save the current tree/document to a file and update storage timestamp."
aFileReference ifNil: [ self inform: 'No file selected for saving. Save NOT done.'. ^ self ].
workingFile := aFileReference.
@ -831,11 +957,24 @@ GrafoscopioNotebook >> saveWorkingNotebook [
self workingFile
ifNil: [ self saveToFileUI ]
ifNotNil: [ self saveToFile: workingFile ].
self notebook root updateEditionTimestamp.
GfUIHelpers updateRecentNotebooksWith: workingFile
]
{ #category : #inspecting }
GrafoscopioNotebook >> seeHtml [
self pdfFile exists
ifTrue: [ (#open command argument: self htmlFile fullName) schedule ]
]
{ #category : #persistence }
GrafoscopioNotebook >> seePdf [
self exportAsPDF
onSuccessDo: [ :v | (#open command argument: self pdfFile fullName) schedule ]
]
{ #category : #persistence }
GrafoscopioNotebook >> subtreeAsMarkdown [
| currentNode |
@ -891,7 +1030,7 @@ GrafoscopioNotebook >> topBar [
name: nil;
description: 'Export all Markdown subtrees';
icon: (self iconNamed: #glamorousMore);
action: [ self exportAllSubtreesAsMarkdow ] ].
action: [ self exportAllSubtreesAsMarkup ] ].
group
addItem: [ :item |
item
@ -1062,6 +1201,7 @@ 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.

View File

@ -4,7 +4,7 @@ Usually my content is markdown text.
"
Class {
#name : #GrafoscopioTextModel,
#superclass : #ComposableModel,
#superclass : #ComposablePresenter,
#instVars : [
'body'
],
@ -36,6 +36,6 @@ GrafoscopioTextModel >> content: aGrafoscopioNodeContent [
GrafoscopioTextModel >> initializeWidgets [
body := self newText.
body beForText.
body beForGrafoscopio.
body autoAccept: true.
]

View File

@ -0,0 +1,9 @@
Extension { #name : #TextPresenter }
{ #category : #'*Grafoscopio' }
TextPresenter >> beForGrafoscopio [
self
isCodeCompletionAllowed: true;
menuHolder: [ self getMenu ];
isForSmalltalkCode: true
]