VSEFileSourceWriter.st
author Claus Gittinger <cg@exept.de>
Wed, 04 Feb 2015 11:06:48 +0100
changeset 3752 bb064c0c9e50
parent 3751 71fb12fc25e3
child 3766 f17fd01f67e8
permissions -rw-r--r--
class: VSEFileSourceWriter

"
 COPYRIGHT (c) 2015 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic3' }"

"{ NameSpace: Smalltalk }"

SmalltalkChunkFileSourceWriter subclass:#VSEFileSourceWriter
	instanceVariableNames:'classNameTranslations'
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Classes-Support'
!

Object subclass:#VSESourceRewriter
	instanceVariableNames:'source method methodClass classNamesToRewrite'
	classVariableNames:''
	poolDictionaries:''
	privateIn:VSEFileSourceWriter
!

!VSEFileSourceWriter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2015 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    fileout in a format which can be read by visualAge.
    For transporting software.
"
!

examples
"
                                                        [exBegin]
    |s|

    s := 'test.st' asFilename writeStream.
    [
        VSEChunkFileSourceWriter new
            fileOut:OrderedCollection on:s
    ] ensure:[
        s close
    ]
                                                        [exEnd]

                                                        [exBegin]
    |s|

    s := '' writeStream.
    [
        VSEChunkFileSourceWriter new
            fileOut:OrderedCollection on:s
    ] ensure:[
        s close
    ].
    s contents
                                                        [exEnd]
"
! !

!VSEFileSourceWriter class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!VSEFileSourceWriter class methodsFor:'api'!

fileOutPackage:currentProject on:aStream
    self new fileOutPackage:currentProject on:aStream
! !

!VSEFileSourceWriter class methodsFor:'class access'!

vseSourceRewriter
    ^ VSESourceRewriter
! !

!VSEFileSourceWriter class methodsFor:'defaults'!

defaultClassNameTranslations
    "for extensions"

    ^ Dictionary new
        at:#SequenceableCollection put:#IndexedCollection;
        at:#CharacterArray put:#String;
        at:#Unicode16String put:#DoubleByteString;
        at:#UnicodeString put:#DoubleByteString;
        at:#Timestamp put:#TimeStamp;
        yourself

    "
     self defaultClassNameTranslations
    "
! !

!VSEFileSourceWriter methodsFor:'initialization'!

initialize
    classNameTranslations := self class defaultClassNameTranslations
! !

!VSEFileSourceWriter methodsFor:'utilities'!

ensureNoUnicodeInClass:aClass
    "/ check if we need UTF8 encoding
    aClass withAllPrivateClasses do:[:cls |
         cls instAndClassMethods contains:[:m |
            self ensureNoUnicodeInMethod:m
         ]
    ].
!

ensureNoUnicodeInMethod:aMethod
    |src|

    src := aMethod source.
    src isNil ifTrue:[
        self error:'missing source in ',aMethod whoString
    ].
    src isWideString ifTrue:[
        self error:(aMethod whoString , ' contains unicode strings or character contants. Cannot be exported to VSE')
    ].
!

extensionMethodsFor:packageID
    |methodsToFileOut|

    methodsToFileOut := OrderedCollection new.
    Smalltalk allClassesDo:[:eachClass |
        eachClass instAndClassSelectorsAndMethodsDo:[:sel :mthd |
            |mPckg|

            mPckg := mthd package.
            (mPckg = packageID and:[mPckg ~= eachClass package]) ifTrue:[
                methodsToFileOut add:mthd.
            ]
        ]
    ].
    ^ methodsToFileOut
!

rewrittenClassNameOf:aClass
    |stxName vseName idx|

    stxName := aClass name.
    vseName := classNameTranslations at:stxName ifAbsent:[stxName].
    
    (vseName includesString:'::') ifTrue:[
        idx := vseName indexOfSubCollection:'::'.
        ^ (vseName copyTo:idx-1) , VSESourceRewriter nameSpaceSeparatorReplacement , (vseName copyFrom:idx+2)
    ].
    ^ vseName    
! !

!VSEFileSourceWriter::VSESourceRewriter class methodsFor:'defaults'!

nameSpaceSeparatorReplacement
    ^ '__'
! !

!VSEFileSourceWriter::VSESourceRewriter class methodsFor:'translation'!

rewriteMethod:method 
    ^ self new rewriteMethod:method 
! !

!VSEFileSourceWriter::VSESourceRewriter methodsFor:'accessing'!

classNamesToRewrite:something
    classNamesToRewrite := something.
!

method
    ^ method
!

method:something
    method := something.
!

methodClass
    ^ methodClass
!

methodClass:something
    methodClass := something.
!

source
    ^ source
!

source:something
    source := something.
! !

!VSEFileSourceWriter::VSESourceRewriter methodsFor:'translation'!

checkForOldStyleAssignments
    "check for underscore as assignment token; VSE does not handle those"

    |parser|

    "/ all references to namespace variables
    parser := Parser new.
    parser parserFlags 
        allowOldStyleAssignment:true;
        warnOldStyleAssignment:true.

    parser
        parseMethod:source 
        in:methodClass
        ignoreErrors:false
        ignoreWarnings:false.

    parser didWarnAboutOldStyleAssignment ifTrue:[
        self error:'OldStyle assignment. Please rewrite "_" assignments to ":=" in ',method whoString
    ].
    parser didWarnAboutSqueakExtensions ifTrue:[
        self error:'Squeak sytax. Please rewrite "{..}" to "Array with:" in ',method whoString
    ].
!

checkForUnimplementedMessages
    "a naive search for messages which are known to be not implemented,
     and which should be replaced by other messages"

    |parser|

    "/ all references to namespace variables
    parser := Parser 
                parseMethod:source 
                in:methodClass
                ignoreErrors:false
                ignoreWarnings:true.

    (parser messagesSent includesAny: #( 
            'answer:do:' 
            'ignoreIn:'
            'codePoint'
            '->'
    )) ifTrue:[
        self error:'please rewrite unimplemented messages in ',method whoString
    ].
!

doRewrite
    self checkForOldStyleAssignments.
    self checkForUnimplementedMessages.

    self rewriteEOLComments.
    self rewriteAnnotationsToComments.
    "/ self rewriteGlobalsWithNamespace.
    self rewriteClassReferences.    
    self rewriteExceptionHandlers.    
    ^ source.
!

rewriteAnnotationsToComments
    |parser annots|

    parser := Parser new.
    parser saveComments:true.
    parser parseMethod:source in:methodClass ignoreErrors:true ignoreWarnings:true.

    (annots := parser annotationInfo) isEmptyOrNil ifTrue:[^ self].
    annots := annots copy sort:[:a :b | a endPosition < b endPosition].
"/ methodClass == SOAP::XeComponent class ifTrue:[self halt].
    "/ last one first, so we don't have to care for changed positions due to insertions
    annots reverseDo:[:annot |
        source := (source copyTo:annot startPosition-1)
                  , '"' , (source copyFrom:annot startPosition to:annot endPosition)
                  , '"' , (source copyFrom:annot endPosition+1).
    ].
!

rewriteClassReferences
    |parser globalsToRename symbolsToRename replacer newSource tree|

    "/ all references to namespace variables
    parser := Parser 
                parseMethod:source 
                in:methodClass
                ignoreErrors:false
                ignoreWarnings:false.

    globalsToRename := Dictionary new.
    symbolsToRename := Dictionary new.

    parser usedGlobals do:[:eachGlobal |
        |idx nsName clsName|

        (eachGlobal includes:$:) ifTrue:[
            idx := eachGlobal indexOfSubCollection:'::'.   
            nsName := eachGlobal copyTo:idx-1.
            clsName := eachGlobal copyFrom:idx+2.
            globalsToRename at:eachGlobal put:(nsName,(self class nameSpaceSeparatorReplacement),clsName).

            nsName = methodClass nameSpace name ifTrue:[
                globalsToRename at:clsName put:(nsName,(self class nameSpaceSeparatorReplacement),clsName).
            ]
        ] ifFalse:[
            (classNamesToRewrite includesKey:eachGlobal) ifTrue:[
                globalsToRename at:eachGlobal put:(classNamesToRewrite at:eachGlobal).
            ].
        ].
    ].
    parser usedSymbols do:[:eachSymbol |
        |idx nsName clsName|

        (eachSymbol includesString:'::') ifTrue:[
            idx := eachSymbol indexOfSubCollection:'::'.   
            nsName := eachSymbol copyTo:idx-1.
            clsName := eachSymbol copyFrom:idx+2.
            (nsName notEmpty 
                and:[ clsName notEmpty
                and:[ nsName knownAsSymbol
                and:[ (Smalltalk classNamed:nsName) isNameSpace ]]])
            ifTrue:[
                symbolsToRename at:eachSymbol put:(nsName,(self class nameSpaceSeparatorReplacement),clsName) asSymbol.
            ].
        ] ifFalse:[
            (methodClass nameSpace includesKey:eachSymbol asSymbol) ifTrue:[
                symbolsToRename at:eachSymbol put:(methodClass nameSpace name,(self class nameSpaceSeparatorReplacement),eachSymbol) asSymbol.
            ] ifFalse:[
                (classNamesToRewrite includesKey:eachSymbol) ifTrue:[
                    self breakPoint:#cg.
                    globalsToRename at:eachSymbol put:(classNamesToRewrite at:eachSymbol).
                ].
            ].
        ]
    ].
    (globalsToRename isEmpty and:[symbolsToRename isEmpty]) ifTrue:[^ self ].

    replacer := ParseTreeSourceRewriter new.
    replacer alwaysPerformAllSearches:true.

    globalsToRename keysAndValuesDo:[:oldName :newName |
        replacer replaceVariable: oldName with: newName.
    ].
    symbolsToRename keysAndValuesDo:[:oldName :newName |
        replacer replaceLiteral: oldName with: newName.
    ].
    tree := RBParser 
                parseMethod:source
                onError:[:aString :pos | self halt. ^self]. 

    replacer executeTree: tree.
    newSource := replacer executeReplacementsInSource:source.
    "/ self halt.

    "/ to verify, check parsability    
    RBParser 
        parseMethod:newSource
        onError:[:aString :pos | self halt.].           

    source := newSource.
!

rewriteEOLComments
    |tree parser eolComments|

    parser := Parser new.
    parser saveComments:true.
    parser parseMethod:source in:methodClass ignoreErrors:true ignoreWarnings:true.

    tree := parser tree.
    eolComments := parser comments select:[:each | each isEndOfLineComment].

    "/ start with the last (so I don't have to update the positions)
    eolComments sort:[:a :b | a startPosition < b startPosition].

    eolComments reverseDo:[:each |
        (source at:each endPosition) = $" ifTrue:[
            "/ nothing to do...
        ] ifFalse:[
            source := (source copyTo:(each endPosition)),'"',(source copyFrom:(each endPosition + 1))
        ].
    ].

    "/ to verify, check parsability    
    RBParser 
        parseMethod:source
        onError:[:aString :pos | self halt.].           
!

rewriteExceptionHandlers
    |parser replacer newSource tree|

    "/ all references to namespace variables
    parser := Parser 
                parseMethod:source 
                in:methodClass
                ignoreErrors:false
                ignoreWarnings:false.

    (parser messagesSent includesAny: #( 'answer:do:' 'ignoreIn:' )) ifTrue:[
        self halt
    ].

    replacer := ParseTreeSourceRewriter new.
    replacer alwaysPerformAllSearches:true.

    replacer
        replace: '[| `@temps | ``@.Statements. ] valueNowOrOnUnwindDo: ``@block'
            "->"
           with: '[| `@temps | ``@.Statements. ] ensure: ``@block';

        replace: '[| `@temps | ``@.Statements. ] valueOnUnwindDo: ``@block'
            "->"
           with: '[| `@temps | ``@.Statements. ] ifCurtailed: ``@block';

        replace:'``@err handle:``@handler do: ``@expr'
            "->"
           with: '``@expr on: ``@err do: ``@handler'.

    tree := RBParser 
        parseMethod:source
        onError:[:aString :pos | self halt. ^ self].

    (replacer executeTree: tree) ifTrue:[
        newSource := replacer executeReplacementsInSource:source.
"/ self halt.
        source := newSource.
    ].

    "/ to verify, check parsability    
    RBParser 
        parseMethod:source
        onError:[:aString :pos | self halt.].           
!

rewriteGlobalsWithNamespace
    "obsolete old version - now done in rewriteClassReferences"

    |parser namesToRewrite|

    namesToRewrite := OrderedCollection new.

    parser := Parser new.
    parser saveComments:true.
    parser parseMethod:source in:methodClass ignoreErrors:true ignoreWarnings:true.
    parser tree isNil ifTrue:[ ^ self ].

    parser tree variableNodesDo:[:each |
        |nameInSource|

        each isGlobalVariable ifTrue:[
            (each name includes:$:) ifTrue:[
                nameInSource := source copyFrom:each startPosition to:each endPosition.
                (nameInSource includes:$:) ifTrue:[
                    namesToRewrite add:each.
                ].
            ].
        ].
    ].

    "/ start with the last (so I don't have to update the positions)
    namesToRewrite sort:[:a :b | a position < b position].
    namesToRewrite reverseDo:[:each |
        |idx nameInSource ns nm|

        nameInSource := source copyFrom:each startPosition to:each endPosition.
        idx := nameInSource indexOf:$:.
        ns := nameInSource copyTo:idx-1.
        idx := nameInSource indexOf:$: startingAt:idx+1.
        nm := nameInSource copyFrom:idx+1.
        (ns = methodClass nameSpace name) ifFalse:[
            Transcript show:'reference to other namespace'.
        ] ifTrue:[
            source := (source copyTo:(each startPosition-1)),nm,(source copyFrom:(each endPosition + 1))
        ].
    ].

    "/ to verify, check parsability    
    RBParser 
        parseMethod:source
        onError:[:aString :pos | self halt.].           
!

rewriteMethod:methodArg 
    method := methodArg.
    source := method source.
    methodClass := method mclass.
    ^ self doRewrite.
! !

!VSEFileSourceWriter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic3/VSEFileSourceWriter.st,v 1.14 2015-02-04 10:06:48 cg Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic3/VSEFileSourceWriter.st,v 1.14 2015-02-04 10:06:48 cg Exp $'
! !