Better internalization of the environment: Now Pandoc PDF exportation is controlled by options defined in a %metadata node inside the notebook.

This is the beginning of more options to connect
the notebook, the playgrounds inside it, and the
operative system.
This commit is contained in:
Offray Vladimir Luna Cárdenas 2017-08-18 02:22:52 +00:00
parent da2c24287a
commit 7d4cc79cf2
2 changed files with 154 additions and 97 deletions

View File

@ -55,44 +55,14 @@ GrafoscopioNode class >> clipboard: anObject [
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 } { #category : #utility }
GrafoscopioNode class >> specialWords [ GrafoscopioNode class >> specialWords [
"I return a list of word that were used in the first versions of grafoscopio to mark node "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. 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 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" migrated to newer versions where tags are used for the same function with simpler code"
^ #('%config' '%abstract' '%invisible' '%idea' '%footnote' 'nuevoNodo' '%embed' '%item'). ^ #('%config' '%abstract' '%invisible' '%idea' '%footnote' '%metadata' '%output' '%embed' '%item').
] ]
{ #category : #operation } { #category : #operation }
@ -179,17 +149,20 @@ GrafoscopioNode >> ancestorsHeaders [
{ #category : #exporting } { #category : #exporting }
GrafoscopioNode >> asMarkdown [ GrafoscopioNode >> asMarkdown [
"I export children of the current node as pandoc markdown, using special nodes accoding to tags. "I export children of the current node as pandoc markdown, using special nodes
Early version... tags processing should be vastly improved" accoding to tags.
Early version... tags processing should be vastly improved"
| markdownOutput | | markdownOutput |
markdownOutput := '' writeStream. markdownOutput := '' writeStream.
self metadataAsYamlIn: markdownOutput. "self metadataAsYamlIn: markdownOutput."
(self preorderTraversal) do: [ :eachNode | (self preorderTraversal) do: [ :eachNode |
(eachNode level > 0) (eachNode level > 0)
ifTrue: [(eachNode hasAncestorTaggedAs: 'invisible') | (eachNode tags includes: 'invisible') ifTrue: [(eachNode hasAncestorTaggedAs: 'invisible')
ifFalse: [ markdownOutput nextPutAll: (eachNode markdownContent) ]]]. | (eachNode tags includes: 'invisible')
^markdownOutput contents ifFalse: [
markdownOutput nextPutAll: (eachNode markdownContent) ]]].
^ markdownOutput contents
] ]
{ #category : #exporting } { #category : #exporting }
@ -212,8 +185,9 @@ GrafoscopioNode >> asText [
{ #category : #initialization } { #category : #initialization }
GrafoscopioNode >> becomeDefaultTestTree [ GrafoscopioNode >> becomeDefaultTestTree [
| node1 node2 node3 node4 | | node1 node2 node3 node4 |
self level: 0. self
self header: 'Arbol principal'. level: 0;
header: 'Arbol principal'.
node1 := self class new node1 := self class new
header: 'Markup'; header: 'Markup';
body: 'I am just a node with markup'; body: 'I am just a node with markup';
@ -221,18 +195,18 @@ GrafoscopioNode >> becomeDefaultTestTree [
links: 'temp.md'; links: 'temp.md';
level: 1. level: 1.
node2 := self class new node2 := self class new
header: 'Code'; header: '%output Code';
body: 'ProfStef openPharoZenWorkspace'; tagAs: 'código';
tagAs: 'código'. body: '(ConfigurationOfGrafoscopio>>#version14:) sourceCode'.
node3 := self class new node3 := self class new
header: 'Child'; header: 'Child';
body: 'Just testing'; tagAs: 'text';
tagAs: 'text'. body: 'Just testing'.
node1 addNode: node3. node1 addNode: node3.
node4 := self class new node4 := self class new
header: 'Something'; header: 'Something';
body: 'else'; tagAs: 'text';
tagAs: 'text'. body: 'else'.
node1 addNode: node4. node1 addNode: node4.
self self
addNode: node1; addNode: node1;
@ -243,7 +217,8 @@ GrafoscopioNode >> becomeDefaultTestTree [
GrafoscopioNode >> becomeDefaultTree [ GrafoscopioNode >> becomeDefaultTree [
"I create a starting tree for all Grafoscopio notebooks with just one textual node as child." "I create a starting tree for all Grafoscopio notebooks with just one textual node as child."
| node1 | | node1 |
self self class new.
self
level: 0; level: 0;
header: 'Arbol principal'; header: 'Arbol principal';
tagAs: 'código'. tagAs: 'código'.
@ -252,6 +227,7 @@ GrafoscopioNode >> becomeDefaultTree [
body: ''; body: '';
tagAs: 'text'. tagAs: 'text'.
self addNode: node1. self addNode: node1.
^ self
] ]
{ #category : #accessing } { #category : #accessing }
@ -401,8 +377,8 @@ GrafoscopioNode >> exportCodeBlockTo: aStream [
{ #category : #exporting } { #category : #exporting }
GrafoscopioNode >> exportCodeNodeTo: aStream [ GrafoscopioNode >> exportCodeNodeTo: aStream [
"I convert the content of a node taged as 'código' (code) as pandoc markdown and put it "I convert the content of a node taged as 'código' (code) as pandoc markdown
into aStream." and put it into aStream."
((self headerStartsWith: '%output') or: [ self headerStartsWith: '%metadata' ]) ((self headerStartsWith: '%output') or: [ self headerStartsWith: '%metadata' ])
ifTrue: [ self exportCodeOutputTo: aStream ] ifTrue: [ self exportCodeOutputTo: aStream ]
ifFalse: [ self exportCodeBlockTo: aStream ] ifFalse: [ self exportCodeBlockTo: aStream ]
@ -410,8 +386,8 @@ GrafoscopioNode >> exportCodeNodeTo: aStream [
{ #category : #exporting } { #category : #exporting }
GrafoscopioNode >> exportCodeOutputTo: aStream [ GrafoscopioNode >> exportCodeOutputTo: aStream [
"I convert the output of a node taged as 'código' (code) as pandoc markdown and put it "I convert the output of a node taged as 'código' (code) as pandoc markdown and
into aStream." put it into aStream."
(self headerStartsWith: '%metadata') ifTrue: [ ^ self ]. (self headerStartsWith: '%metadata') ifTrue: [ ^ self ].
aStream nextPutAll: ('~~~{.numberLines}'); lf. aStream nextPutAll: ('~~~{.numberLines}'); lf.
aStream nextPutAll: (self output asString withInternetLineEndings); lf. aStream nextPutAll: (self output asString withInternetLineEndings); lf.
@ -565,6 +541,7 @@ GrafoscopioNode >> initialize [
super initialize. super initialize.
self self
header: 'newHeader'; header: 'newHeader';
tagAs: 'text';
body: ''; body: '';
level: 0 level: 0
] ]
@ -697,13 +674,16 @@ GrafoscopioNode >> margins [
{ #category : #exporting } { #category : #exporting }
GrafoscopioNode >> markdownContent [ GrafoscopioNode >> markdownContent [
"I extract the markdown of a node using body as content, header as title and level as hierarchical level of the title. "I extract the markdown of a node using body as content, header as title and level as
If special nodes types are present, that use %keywords in its header or body I convert them into proper markup" 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 |
markdownStream := '' writeStream. markdownStream := '' writeStream.
(self class specialWords includes: self header) not & (self class specialWords includes: self header) not
(self class specialWords includes: ((self header findTokens: $ ) at: 1)) not & (self tags ~= 'código') & & (self class specialWords includes: ((self header findTokens: $ ) at: 1)) not
(self hasAncestorHeaderWith: '%invisible') not & (self isTaggedAs: 'código') not
& (self hasAncestorHeaderWith: '%invisible') not
ifTrue: [ ifTrue: [
self headerAsMarkdownInto: markdownStream. self headerAsMarkdownInto: markdownStream.
self bodyAsMarkdownInto: markdownStream ]. self bodyAsMarkdownInto: markdownStream ].
@ -713,9 +693,10 @@ GrafoscopioNode >> markdownContent [
ifTrue: [ self itemAsMarkdownInto: markdownStream ]. ifTrue: [ self itemAsMarkdownInto: markdownStream ].
(self headerStartsWith: '%footnote') (self headerStartsWith: '%footnote')
ifTrue: [ self footnoteAsMarkdownInto: markdownStream ]. ifTrue: [ self footnoteAsMarkdownInto: markdownStream ].
((self tags = 'código') and: [(self hasAncestorHeaderWith: '%invisible') not ((self isTaggedAs: 'código')
& (self headerStartsWith: '%embed') not ]) and: [(self hasAncestorHeaderWith: '%invisible') not
ifTrue: [ self exportCodeNodeTo: markdownStream ]. & (self headerStartsWith: '%embed') not ])
ifTrue: [ self exportCodeNodeTo: markdownStream ].
^ markdownStream contents ^ markdownStream contents
] ]
@ -723,31 +704,32 @@ GrafoscopioNode >> markdownContent [
GrafoscopioNode >> metadata [ GrafoscopioNode >> metadata [
| mnode | | mnode |
mnode := self root preorderTraversal mnode := self root preorderTraversal
detect: [:n | n headerStartsWith: '%metadata' ] detect: [ :n | n headerStartsWith: '%metadata' ]
ifNone: [^ nil]. ifNone: [ ^ nil ].
^ mnode output. ^ mnode output.
] ]
{ #category : #exporting } { #category : #exporting }
GrafoscopioNode >> metadataAsYamlIn: markdownStream [ GrafoscopioNode >> metadataAsYamlIn: markdownStream [
"I convert the first '%metadata' node into a YAML preamble to be used by Pandoc exportation." "I convert the first '%metadata' node into a YAML preamble contents to be used by Pandoc
markdownStream exportation."
nextPutAll: '---';
lf;
nextPutAll: 'exportedFrom: ', self checksum;
lf.
self metadata self metadata
ifNotNil: [ ifNotNil: [
self metadata self metadata
keysAndValuesDo: [ :k :v | keysAndValuesDo: [ :k :v |
markdownStream k = 'pandocOptions'
nextPutAll: (k , ': ' , v asString) withInternetLineEndings; ifTrue: [
nextPutAll: String cr ]]. markdownStream
markdownStream nextPutAll:
nextPutAll: '---'; (k, ': ', self pandocOptionsPrettyYaml) ]
lf; ifFalse: [
lf markdownStream
nextPutAll:
(k , ': ' , v asString) withInternetLineEndings;
lf] ]].
markdownStream
nextPutAll: String cr, String cr.
] ]
{ #category : #movement } { #category : #movement }
@ -788,7 +770,7 @@ GrafoscopioNode >> newNode [
{ #category : #accessing } { #category : #accessing }
GrafoscopioNode >> output [ GrafoscopioNode >> output [
self tags ~= 'código' ifTrue: [ ^ self ]. (self isTaggedAs: 'código') ifFalse: [ ^ self ].
self body ifNil: [ ^ nil ]. self body ifNil: [ ^ nil ].
^ (Compiler evaluate: self body) ^ (Compiler evaluate: self body)
] ]
@ -803,6 +785,24 @@ GrafoscopioNode >> pandocOptions [
^ self metadata at: 'pandocOptions' ifAbsent: [ ^ '' ] ^ self metadata at: 'pandocOptions' ifAbsent: [ ^ '' ]
] ]
{ #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 } { #category : #accessing }
GrafoscopioNode >> parent [ GrafoscopioNode >> parent [
"Returns the parent of the current node" "Returns the parent of the current node"
@ -921,11 +921,13 @@ GrafoscopioNode >> specModelClass [
{ #category : #accessing } { #category : #accessing }
GrafoscopioNode >> tagAs: aTag [ GrafoscopioNode >> tagAs: aTag [
"Tags the recipient node with aTag. For the moment we will have only one tag. "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 In the future we will have several and there will be rules to know how tags interact with
each other" each other"
aTag = 'código' ifTrue: [ ^ self toggleCodeText ].
(self tags includes: aTag) (self tags includes: aTag)
ifFalse: [ self tags add: aTag ] ifFalse: [ self tags add: aTag ].
^ self
] ]
@ -958,9 +960,9 @@ GrafoscopioNode >> toggleCodeText [
In that case, I replace the ocurrence of one tag by the other to warranty that both are not In that case, I replace the ocurrence of one tag by the other to warranty that both are not
in the same node." in the same node."
(self isTaggedAs: 'text') (self isTaggedAs: 'text')
ifTrue: [ ^ self tags replaceAll: 'text' with: 'código'. ]. ifTrue: [ ^ self tags replaceAll: 'text' with: 'código'].
(self isTaggedAs: 'código') (self isTaggedAs: 'código')
ifTrue: [ ^ self tags replaceAll: 'código' with: 'text'. ]. ifTrue: [ ^ self tags replaceAll: 'código' with: 'text' ].
] ]
{ #category : #operation } { #category : #operation }

View File

@ -57,6 +57,12 @@ GrafoscopioNotebook class >> open: aFileReference [
self newDefault openFromFile: aFileReference self newDefault openFromFile: aFileReference
] ]
{ #category : #utilities }
GrafoscopioNotebook >> addCommandFrom: dictionary into: stream [
dictionary keysAndValuesDo: [ :k :v |
k = 'thisNotebook' ifTrue: [ stream nextPutAll: (self perform: #markdownFileChecksumUpto: with: 10) ] ]
]
{ #category : #'editing nodes' } { #category : #'editing nodes' }
GrafoscopioNotebook >> addNode [ GrafoscopioNotebook >> addNode [
| addedNode | | addedNode |
@ -91,12 +97,12 @@ GrafoscopioNotebook >> body: anObject [
{ #category : #utilities } { #category : #utilities }
GrafoscopioNotebook >> checksum [ GrafoscopioNotebook >> checksum [
"I return the cryptographic signature of the workingFile where this notebook is being stored. "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 related with this source I'm useful for data provenance and traceability of derivated files coming from this source
notebook." notebook."
self workingFile ifNil: [ ^ self ]. self workingFile ifNil: [ ^ self ].
self workingFile contents = '' ifTrue: [ ^ self ]. self workingFile contents = '' ifTrue: [ ^ self ].
^ (SHA1 new hashMessage: (self workingFile contents)) hex. ^ GrafoscopioUtils checksumFor: self workingFile
] ]
{ #category : #'editing nodes' } { #category : #'editing nodes' }
@ -201,8 +207,8 @@ GrafoscopioNotebook >> exportAsPDF [
self markdownFile exists ifFalse: [ self exportAsMarkdown ]. self markdownFile exists ifFalse: [ self exportAsMarkdown ].
pdfFile := self markdownFile parent fullName,'/', self markdownFile basenameWithoutExtension, '.pdf'. pdfFile := self markdownFile parent fullName,'/', self markdownFile basenameWithoutExtension, '.pdf'.
pdfFile asFileReference exists ifTrue: [ pdfFile asFileReference delete ]. pdfFile asFileReference exists ifTrue: [ pdfFile asFileReference delete ].
pandocCommand := 'pandoc ', pandocCommand := 'cd ', self workingFile parent fullName,'; pandoc ',
self notebook pandocOptions, ' ', self pandocOptionsComputed, ' ',
self markdownFile fullName, ' -o ', pdfFile. self markdownFile fullName, ' -o ', pdfFile.
Transcript show: pandocCommand. Transcript show: pandocCommand.
ExternalUnixOSProcess command: pandocCommand. ExternalUnixOSProcess command: pandocCommand.
@ -222,10 +228,19 @@ GrafoscopioNotebook >> exportAsSton: aNotebook on: aFileStream [
{ #category : #persistence } { #category : #persistence }
GrafoscopioNotebook >> exportNode: aGrafoscopioNode asMarkdownIn: aFile [ GrafoscopioNotebook >> exportNode: aGrafoscopioNode asMarkdownIn: aFile [
"I export the current tree/document to a markdown file" "I export the current tree/document to a markdown file"
aFile exists ifTrue: [ aFile delete ]. aFile ensureDelete.
aFile aFile
ensureCreateFile; ensureCreateFile;
writeStreamDo: [:stream | stream nextPutAll: aGrafoscopioNode asMarkdown]. writeStreamDo: [:stream |
stream
nextPutAll:
'---', String cr,
'exportedFrom: ', self checksum, String cr.
aGrafoscopioNode metadataAsYamlIn: stream.
stream
nextPutAll:
'---', String cr, String cr,
aGrafoscopioNode asMarkdown ].
self inform: 'Exported as: ', String cr, aFile fullName self inform: 'Exported as: ', String cr, aFile fullName
] ]
@ -311,6 +326,15 @@ GrafoscopioNotebook >> links: anObject [
links := anObject links := anObject
] ]
{ #category : #persistence }
GrafoscopioNotebook >> loadFromFile: aFileReference [
"I load the contents of aFileReference into a GrafoscopioNotebook, without opening it."
self workingFile: aFileReference.
self notebook: ((STON fromString: self workingFile contents) at: 1) parent.
self title: self workingFile basenameWithIndicator, ' | Grafoscopio notebook'.
self notebookContent: self notebook.
]
{ #category : #persistence } { #category : #persistence }
GrafoscopioNotebook >> markdownFile [ GrafoscopioNotebook >> markdownFile [
"I define the location of the markdown file where the notebook will be exported" "I define the location of the markdown file where the notebook will be exported"
@ -319,6 +343,18 @@ GrafoscopioNotebook >> markdownFile [
^ markdownFile ^ markdownFile
] ]
{ #category : #utilities }
GrafoscopioNotebook >> markdownFileChecksum [
self workingFile ifNil: [ ^ self ].
self workingFile contents = '' ifTrue: [ ^ self ].
^ GrafoscopioUtils checksumFor: self markdownFile
]
{ #category : #utilities }
GrafoscopioNotebook >> markdownFileChecksumUpto: anInteger [
^ self markdownFileChecksum copyFrom: 1 to: anInteger.
]
{ #category : #'editing nodes' } { #category : #'editing nodes' }
GrafoscopioNotebook >> moveNodeAfter [ GrafoscopioNotebook >> moveNodeAfter [
| editedNode | | editedNode |
@ -451,10 +487,7 @@ GrafoscopioNotebook >> openDefault [
{ #category : #persistence } { #category : #persistence }
GrafoscopioNotebook >> openFromFile: aFileReference [ GrafoscopioNotebook >> openFromFile: aFileReference [
self workingFile: aFileReference. self loadFromFile: aFileReference.
self notebook: ((STON fromString: self workingFile contents) at: 1) parent.
self title: self workingFile basenameWithIndicator, ' | Grafoscopio notebook'.
self notebookContent: self notebook.
^ self openWithSpec. ^ self openWithSpec.
] ]
@ -501,6 +534,28 @@ GrafoscopioNotebook >> openFromUrlUI [
self class new openFromUrl: fileUrl self class new openFromUrl: fileUrl
] ]
{ #category : #utilities }
GrafoscopioNotebook >> pandocOptions [
^ self notebook pandocOptions
]
{ #category : #utilities }
GrafoscopioNotebook >> pandocOptionsComputed [
"I convert the pandoc options array into a single line that can be used with the pandoc command."
| result |
result := '' writeStream.
self pandocOptions
do: [ :option |
option isDictionary
ifTrue: [
self addCommandFrom: option into: result ]
ifFalse: [
result
nextPutAll: option] ].
^ result contents
]
{ #category : #'editing nodes' } { #category : #'editing nodes' }
GrafoscopioNotebook >> pasteNodeFromClipboard [ GrafoscopioNotebook >> pasteNodeFromClipboard [
tree highlightedItem content pasteFromClipboard. tree highlightedItem content pasteFromClipboard.
@ -573,11 +628,11 @@ GrafoscopioNotebook >> removeNode [
GrafoscopioNotebook >> saveToFile: aFileReference [ GrafoscopioNotebook >> saveToFile: aFileReference [
"I save the current tree/document to a file." "I save the current tree/document to a file."
aFileReference ifNil: [ self inform: 'No file selected for saving. Save NOT done'. ^ self ]. aFileReference ifNil: [ self inform: 'No file selected for saving. Save NOT done.'. ^ self ].
workingFile := aFileReference. workingFile := aFileReference.
self workingFile ensureDelete. self workingFile ensureDelete.
self workingFile writeStreamDo: [:stream | self workingFile writeStreamDo: [:stream |
self exportAsSton: self notebook on:stream ]. self exportAsSton: self notebook on: stream ].
self title: self workingFile basenameWithIndicator, ' | Grafoscopio notebook'. self title: self workingFile basenameWithIndicator, ' | Grafoscopio notebook'.
self inform: ('File saved at: ', String cr, self workingFile fullName). self inform: ('File saved at: ', String cr, self workingFile fullName).
GrafoscopioDockingBar updateRecentNotebooksWith: aFileReference. GrafoscopioDockingBar updateRecentNotebooksWith: aFileReference.
@ -828,6 +883,6 @@ GrafoscopioNotebook >> workingFile [
] ]
{ #category : #accessing } { #category : #accessing }
GrafoscopioNotebook >> workingFile: aFile [ GrafoscopioNotebook >> workingFile: aFileReference [
workingFile := aFile. workingFile := aFileReference.
] ]