[Cuis-dev] How to filein a fileout from Pharo?
Aik-Siong Koh
askoh at askoh.com
Tue Mar 22 10:06:14 PDT 2022
Thanks for helping. The fileout is attached. Aik-Siong Koh
H. Fernandes wrote:
> Hi Aik-Siong,
>
> The Fileout/Filein is the option I am using to port DrGeo from Pharo
> to Cuis. Note I am porting from Pharo7 (I think).
> I think the Fielout from newer Pharo should still export to the
> traditional .st format. You have to deal with the end line character,
> conversion from \t to \n.
> On line can be done with:
> tr '\r' '\n' < PharoFileout.st > CuisFilein.st
>
> Can you make public your fileout from Pharo, so I can take a look?
>
> Hilaire
>
> Dr. Geo -- http://drgeo.eu
>
> ------------------------------------------------------------------------
>
> Hi:
>
> I fileout from Pharo five very small classes that I wrote.
> I tried to filein from Cuis without success.
> Please advise.
>
> Thanks,
> Aik-Siong Koh
> --
> Cuis-dev mailing list
> Cuis-dev at lists.cuis.st
> https://lists.cuis.st/mailman/listinfo/cuis-dev
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://lists.cuis.st/mailman/archives/cuis-dev/attachments/20220322/c7b13241/attachment.htm>
-------------- next part --------------
Object subclass: #ASKoh
instanceVariableNames: ''
classVariableNames: ''
package: 'ASKoh'!
ASKoh subclass: #ASKStack
instanceVariableNames: 'logFile lines id'
classVariableNames: ''
package: 'ASKoh'!
!ASKStack methodsFor: 'initialization' stamp: 'ASK 3/8/2022 13:52'!
initialize
lines := OrderedCollection new! !
!ASKStack methodsFor: 'accessing' stamp: 'ASK 3/8/2022 19:54'!
id
^ id! !
!ASKStack methodsFor: 'accessing' stamp: 'ASK 3/8/2022 17:18'!
cleanLines
lines do: [ :l | l cleanup ].
lines := lines reversed.
1 to: lines size do: [ :i | (lines at: i) indent: i - 1 ]! !
!ASKStack methodsFor: 'accessing' stamp: 'ASK 3/8/2022 13:54'!
lines
^ lines! !
!ASKStack methodsFor: 'accessing' stamp: 'ASK 3/8/2022 10:06'!
logFile: _logFile
logFile := _logFile! !
!ASKStack methodsFor: 'accessing' stamp: 'ASK 3/8/2022 19:53'!
id: _id
id := _id! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ASKStack class
instanceVariableNames: ''!
!ASKStack class methodsFor: 'as yet unclassified' stamp: 'ASK 3/6/2022 23:45'!
logFile: logFile
^self new logFile: logFile ; yourself.! !
!ASKStack class methodsFor: 'as yet unclassified' stamp: 'ASK 3/11/2022 22:21'!
readFromLinesStream: linesStream
| stack stackLines found stackLine line |
stack := self new.
stackLines := stack lines.
found := false.
[ linesStream atEnd not and: found not ] whileTrue: [
stackLine := linesStream next.
stackLine hasBacktrace ifTrue: [
[ linesStream atEnd not and: found not ] whileTrue: [
stackLine := linesStream next.
stackLine isValid
ifTrue: [ stackLines add: stackLine ]
ifFalse: [ found := true ] ] ] ].
^ stack! !
ASKoh subclass: #ASKStackLine
instanceVariableNames: 'indent line'
classVariableNames: ''
package: 'ASKoh'!
!ASKStackLine methodsFor: 'testing' stamp: 'ASK 3/11/2022 22:32'!
isValid
"#0 0x00007ffef4be5570 in sltp::mm::core::Source::Source(sltp::mm::core::Source&&)"
| stream string block token |
stream := line readStream.
block := [
string := stream upToAnyOf: Character separators.
stream skipSeparators.
string ].
token := block value.
(token at: 1) ~= $# ifTrue: [^false].
token := block value.
(token first: 2) ~= '0x' ifTrue: [^false].
token := block value.
token ~= 'in' ifTrue: [^false].
^true
! !
!ASKStackLine methodsFor: 'testing' stamp: 'ASK 3/11/2022 22:22'!
hasBacktrace
^ line = '+backtrace'! !
!ASKStackLine methodsFor: 'accessing' stamp: 'ASK 3/8/2022 20:01'!
indent: _indent
indent := _indent! !
!ASKStackLine methodsFor: 'accessing' stamp: 'ASK 3/11/2022 23:07'!
cleanup
"#0 0x00007ffef4be5570 in sltp::mm::core::Source::Source(sltp::mm::core::Source&&)"
"Keep function name only."
| stream block string writeStream token |
stream := line readStream.
block := [
string := stream upToAnyOf: Character separators.
stream skipSeparators.
string ].
token := block value.
(token at: 1) = $# ifTrue: [
token := block value.
(token first: 2) = '0x' ifTrue: [
token := block value.
token = 'in' ifTrue: [
line := stream upTo: $(.
line isEmpty ifTrue: [
writeStream := (String new: 100) writeStream.
line := writeStream
nextPut: $(;
nextPutAll: (stream upTo: $();
contents ].
line := line truncateTo: 100 ].
^ self ] ].
self assert: false description: 'Not a valid stack line.'! !
!ASKStackLine methodsFor: 'accessing' stamp: 'ASK 3/8/2022 22:56'!
indent
^ indent! !
!ASKStackLine methodsFor: 'accessing' stamp: 'ASK 3/8/2022 10:06'!
line: _line
line := _line! !
!ASKStackLine methodsFor: 'accessing' stamp: 'ASK 3/8/2022 14:01'!
line
^ line! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ASKStackLine class
instanceVariableNames: ''!
!ASKStackLine class methodsFor: 'instance creation' stamp: 'ASK 3/8/2022 10:00'!
new: _line
^self new line: _line; yourself.! !
ASKStackLine subclass: #ASKStackEndLine
instanceVariableNames: 'ids'
classVariableNames: ''
package: 'ASKoh'!
ASKoh subclass: #ASKStackLog
instanceVariableNames: 'logFile stacks lines combinedStack'
classVariableNames: ''
package: 'ASKoh'!
!ASKStackLog methodsFor: 'ops' stamp: 'ASK 3/8/2022 15:34'!
cleanStacks
stacks do: [ :s | s cleanLines ]! !
!ASKStackLog methodsFor: 'ops' stamp: 'ASK 3/9/2022 19:41'!
combineStacks
| stackLines offset stackLinei ii lineii indent found j linej |
lines := OrderedCollection new.
stacks do: [ :stack |
stackLines := stack lines.
offset := 0.
1 to: stackLines size do: [ :i |
stackLinei := stackLines at: i.
" 'SLCompPropagation' = stackLinei line ifTrue: [ self halt ].
'SLCompLibrariesMdlRefAndVariants' = stackLinei line ifTrue: [
self halt ]."
ii := offset + i.
ii > lines size
ifTrue: [ lines add: stackLinei ]
ifFalse: [
lineii := lines at: ii.
lineii line = stackLinei line ifFalse: [
"self halt."
indent := i - 1.
[ indent = stackLinei indent ] assert.
found := false.
j := ii.
[ j <= lines size and: found not ] whileTrue: [
linej := lines at: j.
(indent = linej indent and: linej line = stackLinei line)
ifTrue: [
found := true.
offset := j - i ].
j := j + 1 ].
"self halt."
found ifFalse: [
ii := lines size + 1.
offset := ii - i.
lines add: stackLinei ] ] ] ] ]! !
!ASKStackLog methodsFor: 'ops' stamp: 'ASK 3/8/2022 19:52'!
collectStacks
| stream stack |
stacks := OrderedCollection new.
stream := lines readStream.
[ stream atEnd ] whileFalse: [
stack := ASKStack readFromLinesStream: stream.
stacks add: stack.
stack id: stacks size ]! !
!ASKStackLog methodsFor: 'printing' stamp: 'ASK 3/10/2022 23:38'!
printCombinedStack
| writeStream indents b d firstIndent indent outputFile fileStream fileReference |
writeStream := String new writeStream.
indents := lines collect: [ :x | x indent ].
b := indents asBag.
d := b sortedElements.
firstIndent := (d findFirst: [ :x | x value > 1 ]) - 1.
lines do: [ :l |
indent := l indent + 1 - firstIndent.
indent > firstIndent negated ifTrue: [
indent > 0 ifTrue: [
1 * indent timesRepeat: [ writeStream nextPut: $| "space" ] ].
writeStream
nextPutAll: l line;
cr ] ].
outputFile := logFile copyReplaceAll: '.log' with: '.txt'.
fileReference := outputFile asFileReference.
fileReference delete.
fileStream := fileReference writeStream.
fileStream nextPutAll: writeStream contents.
fileStream close! !
!ASKStackLog methodsFor: 'printing' stamp: 'ASK 3/9/2022 19:55'!
indexOfFirstRepeatIndents! !
!ASKStackLog methodsFor: 'printing' stamp: 'ASK 3/10/2022 23:28'!
printCombinedStack1
| writeStream indents b d firstIndent indent outputFile fileStream fileReference |
writeStream := String new writeStream.
indents := lines collect: [ :x | x indent ].
b := indents asBag.
d := b sortedElements.
firstIndent := (d findFirst: [ :x | x value > 1 ]) - 1.
lines do: [ :l |
indent := l indent + 1 - firstIndent.
indent > -10 ifTrue: [
indent > 0 ifTrue: [
1 * indent timesRepeat: [ writeStream nextPut: $| "space" ] ].
writeStream
nextPutAll: l line;
cr ] ].
outputFile := logFile copyReplaceAll: '.log' with: '.txt'.
fileReference := outputFile asFileReference.
fileReference delete.
fileStream := fileReference writeStream.
fileStream nextPutAll: writeStream contents.
fileStream close! !
!ASKStackLog methodsFor: 'accessing' stamp: 'ASK 3/8/2022 10:30'!
logFile: _logFile
logFile := _logFile! !
!ASKStackLog methodsFor: 'running' stamp: 'ASK 3/8/2022 15:14'!
run
self
collectLines;
collectStacks;
cleanStacks;
combineStacks;
printCombinedStack! !
!ASKStackLog methodsFor: 'running' stamp: 'ASK 3/8/2022 12:26'!
collectLines
| stream line stackLine |
lines := OrderedCollection new.
stream := logFile asFileReference readStream.
[
line := stream nextLine.
stackLine := ASKStackLine new: line.
lines add: stackLine.
stream atEnd ] whileFalse.
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
ASKStackLog class
instanceVariableNames: ''!
!ASKStackLog class methodsFor: 'accessing' stamp: 'ASK 3/8/2022 10:17'!
logFile: logFile
^ self new
logFile: logFile;
yourself! !
More information about the Cuis-dev
mailing list