SmalltalkChunkFileSourceWriter.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 09 Apr 2011 18:19:04 +0100
branchjv
changeset 17834 04ff72c5039a
parent 17814 b75a7f0c346b
child 17841 7abcc4aef871
permissions -rw-r--r--
Merged with /trunk

"
 COPYRIGHT (c) 2004 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:libbasic' }"

AbstractSourceFileWriter subclass:#SmalltalkChunkFileSourceWriter
	instanceVariableNames:'classBeingSaved methodsAlreadySaved'
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Classes'
!

!SmalltalkChunkFileSourceWriter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2004 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.
"
! !

!SmalltalkChunkFileSourceWriter methodsFor:'source writing'!

fileOut:aClass on:outStreamArg withTimeStamp:stampIt withInitialize:initIt withDefinition:withDefinition methodFilter:methodFilter encoder:encoderOrNil
    "file out my definition and all methods onto aStream.
     If stampIt is true, a timeStamp comment is prepended.
     If initIt is true, and the class implements a class-initialize method,
     append a corresponding doIt expression for initialization.
     The order by which the fileOut is done is used to put the version string at the end.
     Thus, if the version string is expanded (by CVS), the characterPositions of methods should not move"

    |collectionOfCategories comment versionMethods
     nonMeta meta classesImplementingInitialize outStream|

    classBeingSaved := nonMeta := aClass theNonMetaclass.
    meta := nonMeta class.
    methodsAlreadySaved := Set new.

    nonMeta isLoaded ifFalse:[
        ^ ClassDescription fileOutErrorSignal 
            raiseRequestWith:nonMeta
            errorString:' - will not fileOut unloaded class: ', nonMeta name
    ].

    encoderOrNil isNil ifTrue:[
        outStream := outStreamArg.
    ] ifFalse:[
        outStream := EncodedStream stream:outStreamArg encoder:encoderOrNil.
        outStream nextPutAll:'"{ Encoding: ' , encoderOrNil nameOfEncoding , ' }"'; cr; cr.
    ].

    "
     if there is a copyright method, add a copyright comment
     at the beginning, taking the string from the copyright method.
     We cannot do this unconditionally - that would lead to my copyrights
     being put on your code ;-).
     On the other hand: I want every file created by myself to have the
     copyright string at the beginning be preserved .... even if the
     code was edited in the browser and filedOut.
    "
    self generateHeaderWithCopyrightOn:outStream.

    stampIt ifTrue:[
        "/
        "/ first, a timestamp
        "/
        outStream nextPutAll:(Smalltalk timeStamp).
        outStream nextPutChunkSeparator. 
        outStream cr; cr.
    ].

    withDefinition ifTrue:[
        "/
        "/ then the definition(s)
        "/
        self fileOutAllDefinitionsOf:nonMeta on:outStream.
        "/
        "/ a comment - if any
        "/
        (comment := nonMeta comment) notNil ifTrue:[
            nonMeta fileOutCommentOn:outStream.
            outStream cr.
        ].
        "/
        "/ ST/X primitive definitions - if any
        "/
        nonMeta fileOutPrimitiveSpecsOn:outStream.
    ].

    "/
    "/ methods from all categories in metaclass (i.e. class methods)
    "/ EXCEPT: the version method is placed at the very end, to
    "/         avoid sourcePosition-shifts when checked out later.
    "/         (RCS expands this string, so its size is not constant)
    "/
    collectionOfCategories := meta categories asSortedCollection.
    versionMethods := meta methodDictionary values select:[:mthd | mthd isVersionMethod].

    collectionOfCategories notNil ifTrue:[
        "/
        "/ documentation first (if any), but not the version method
        "/
        (collectionOfCategories includes:'documentation') ifTrue:[

            versionMethods do:[:versionMethod |
                |source|

                source := versionMethod source.
                (source isEmptyOrNil or:[(source startsWith:nonMeta nameOfVersionMethod) not]) ifTrue:[
                    "something bad happend to the classes code"

                    Class fileOutErrorSignal 
                        raiseRequestWith:aClass
                        errorString:' - bad source for version method (uncompiled class file?): ', (versionMethod displayString)
                ].
            ].

            self fileOutCategory:'documentation' of:meta except:versionMethods only:nil methodFilter:methodFilter on:outStream.
            outStream cr.
        ].

        "/
        "/ initialization next (if any)
        "/
        (collectionOfCategories includes:'initialization') ifTrue:[
            self fileOutCategory:'initialization' of:meta methodFilter:methodFilter on:outStream.
            outStream cr.
        ].

        "/
        "/ instance creation next (if any)
        "/
        (collectionOfCategories includes:'instance creation') ifTrue:[
            self fileOutCategory:'instance creation' of:meta methodFilter:methodFilter on:outStream.
            outStream cr.
        ].
        collectionOfCategories do:[:aCategory |
            ((aCategory ~= 'documentation')
            and:[(aCategory ~= 'initialization')
            and:[aCategory ~= 'instance creation']]) ifTrue:[
                self fileOutCategory:aCategory of:meta methodFilter:methodFilter on:outStream.
                outStream cr
            ]
        ]
    ].

    "/ if there are any primitive definitions (vw-like ffi-primitives),
    "/ file them out first in the order: defines, types.
    "/ Otherwise, we might have trouble when filing in later, because the types are needed
    "/ for the primitive calls.
    nonMeta methodDictionary keysAndValuesDo:[:sel :m |
        m isVisualWorksTypedef ifTrue:[
            self fileOutCategory:m category of:nonMeta except:nil only:(Array with:m) methodFilter:methodFilter on:outStream.
        ].
    ].

    "/
    "/ methods from all categories
    "/
    collectionOfCategories := nonMeta categories asSortedCollection.
    collectionOfCategories notNil ifTrue:[
        collectionOfCategories do:[:aCategory |
            self fileOutCategory:aCategory of:nonMeta methodFilter:methodFilter on:outStream.
            outStream cr
        ]
    ].

    "/
    "/ any private classes' methods
    "/
    nonMeta privateClassesSorted do:[:aClass |
        self fileOutAllMethodsOf:aClass on:outStream methodFilter:methodFilter
    ].


    "/
    "/ finally, the previously skipped version method
    "/
    versionMethods notEmpty ifTrue: [
        self fileOutCategory:'documentation' of:meta except:nil only:versionMethods methodFilter:methodFilter on:outStream.
    ].

    initIt ifTrue:[
        "/
        "/ optionally an initialize message
        "/
        classesImplementingInitialize := OrderedCollection new.

        (meta includesSelector:#initialize) ifTrue:[
            classesImplementingInitialize add:nonMeta
        ].
        nonMeta privateClassesSorted do:[:aPrivateClass |
            (aPrivateClass theMetaclass includesSelector:#initialize) ifTrue:[
                classesImplementingInitialize add:aPrivateClass
            ]
        ].
        classesImplementingInitialize size ~~ 0 ifTrue:[
            classesImplementingInitialize topologicalSort:[:a :b | b isSubclassOf:a].
            outStream cr.
            classesImplementingInitialize do:[:eachClass |
                eachClass printClassNameOn:outStream. outStream nextPutAll:' initialize'.
                outStream nextPutChunkSeparator.
                outStream cr.
            ].
        ].
    ]

    "Created: / 15-11-1995 / 12:53:06 / cg"
    "Modified: / 01-04-1997 / 16:01:05 / stefan"
    "Modified: / 04-10-2006 / 17:28:33 / cg"
!

fileOutAllDefinitionsOf:aNonMetaClass on:aStream
    "append expressions on aStream, which defines myself and all of my private classes."

    aNonMetaClass fileOutDefinitionOn:aStream.
    aStream nextPutChunkSeparator. 
    aStream cr; cr.

    "/
    "/ optional classInstanceVariables
    "/
    aNonMetaClass class instanceVariableString isBlank ifFalse:[
        aNonMetaClass fileOutClassInstVarDefinitionOn:aStream.
        aStream nextPutChunkSeparator. 
        aStream cr; cr
    ].

    "/ here, the full nameSpace prefixes are output,
    "/ to avoid confusing stc 
    "/ (which otherwise could not find the correct superclass)
    "/
    Class fileOutNameSpaceQuerySignal answer:false do:[
        Class forceNoNameSpaceQuerySignal answer:true do:[
            aNonMetaClass privateClassesSorted do:[:aClass |
                 self fileOutAllDefinitionsOf:aClass on:aStream
            ]
        ]
    ].

    "Created: 15.10.1996 / 11:15:19 / cg"
    "Modified: 22.3.1997 / 16:11:56 / cg"
!

fileOutAllMethodsOf:aClass on:aStream methodFilter:methodFilter
    |collectionOfCategories|

    collectionOfCategories := aClass class categories asSortedCollection.
    collectionOfCategories notNil ifTrue:[
        collectionOfCategories do:[:aCategory |
            self fileOutCategory:aCategory of:aClass class  methodFilter:methodFilter on:aStream.
            aStream cr
        ]
    ].
    collectionOfCategories := aClass categories asSortedCollection.
    collectionOfCategories notNil ifTrue:[
        collectionOfCategories do:[:aCategory |
            self fileOutCategory:aCategory of:aClass methodFilter:methodFilter on:aStream.
            aStream cr
        ]
    ].

    aClass privateClassesSorted do:[:aClass |
        self fileOutAllMethodsOf:aClass on:aStream methodFilter:methodFilter
    ].

    "Created: 15.10.1996 / 11:13:00 / cg"
    "Modified: 22.3.1997 / 16:12:17 / cg"
!

fileOutCategory:aCategory of:aClass except:skippedMethods only:savedMethods methodFilter:methodFilter on:aStream
    "file out all methods belonging to aCategory, aString onto aStream.
     If skippedMethods is nonNil, those are not saved.
     If savedMethods is nonNil, only those are saved.
     If both are nil, all are saved. See version-method handling in
     fileOut for what this is needed."

    |sortedSelectors first prevPrivacy privacy interestingMethods cat|

    interestingMethods := OrderedCollection new.
    aClass methodsDo:[:aMethod |
        |method wanted|
        wanted := false.
        method := aMethod.
        "Check all overridden methods as well"
        [ wanted not and:[method notNil]]
            whileTrue:[
        (methodsAlreadySaved includes:method) ifFalse:[
            (aCategory = method category) ifTrue:[
                (methodFilter isNil or:[methodFilter value:method]) ifTrue:[
                    skippedMethods notNil ifTrue:[
                        wanted := (skippedMethods includesIdentical:method) not
                    ] ifFalse:[
                        wanted := savedMethods isNil or:[ savedMethods includesIdentical:method ].
                    ].
                    wanted ifTrue:[
                        "JV@2010-07-01: Changed to support selector/language namespaces"
                        "Namespaced methods are stored in class under string selector"
                        (method selector isSymbol or:[method nameSpace notNil]) ifTrue:[
                            interestingMethods add:method
                        ] ifFalse:[
                            Transcript showCR:'skipping non-symbol method ',method selector.
                        ].
                    ].
                ]
            ]
        ].
        method := method overriddenMethod.
        ].
    ].
    interestingMethods notEmpty ifTrue:[
        first := true.
        prevPrivacy := nil.

        "/
        "/ sort by selector
        "/
        sortedSelectors := interestingMethods collect:[:m | aClass selectorAtMethod:m].
        sortedSelectors sortWith:interestingMethods.

        interestingMethods do:[:eachMethod |
            privacy := eachMethod privacy.

            first ifFalse:[
                privacy ~~ prevPrivacy ifTrue:[
                    first := true.
                    aStream space.
                    aStream nextPutChunkSeparator.
                ].
                aStream cr; cr
            ].

            first ifTrue:[
                aStream nextPutChunkSeparator.
                aClass printClassNameOn:aStream.
                privacy ~~ #public ifTrue:[
                    aStream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'.
                ] ifFalse:[
                    aStream nextPutAll:' methodsFor:'.
                ].
                cat := aCategory.
                cat isNil ifTrue:[ cat := '' ].
                aStream nextPutAll:aCategory asString storeString.
                aStream nextPutChunkSeparator; cr; cr.
                first := false.
            ].
            self fileOutMethod:eachMethod on:aStream.
            methodsAlreadySaved add:eachMethod.

            prevPrivacy := privacy.
        ].
        aStream space.
        aStream nextPutChunkSeparator.
        aStream cr
    ]

    "Modified: / 28-08-1995 / 14:30:41 / claus"
    "Modified: / 15-11-1996 / 11:32:21 / cg"
    "Created: / 01-04-1997 / 16:04:33 / stefan"
    "Modified: / 21-08-2009 / 23:57:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 01-07-2010 / 21:45:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileOutCategory:aCategory of:aClass methodFilter:methodFilter on:aStream
    "file out all methods belonging to aCategory, aString onto aStream"

    self fileOutCategory:aCategory of:aClass except:nil only:nil methodFilter:methodFilter on:aStream

    "Created: 1.4.1997 / 16:04:44 / stefan"
!

fileOutCommentEndOn:aStream
    "Writes a comment end mark on aStream."

    "/ intentionally left blank - make each line an EOL-comment instead
!

fileOutCommentLine:aString on:aStream
    "Writes a single line of comment on a comment to a stream."

    aStream 
        nextPutAll:'"/ ';
        nextPutAll: aString.

    "Modified: / 14-02-2010 / 10:24:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileOutCommentStartOn:aStream
    "Writes a comment start mark on aStream."

    "/ intentionally left blank - make each line an EOL-comment instead
!

fileOutMethod:aMethod on:aStream
    "file a single method onto aStream."

    |source possiblyRewrittenSource rewriteQuery|

    source := aMethod source.
    source isNil ifTrue:[
        Class fileOutErrorSignal 
            raiseRequestWith:aMethod mclass
            errorString:' - no source for method: ', (aMethod displayString)
    ] ifFalse:[
        "/ hook to allow for just-in-time rewriting of a method's sourceCode while filing out
        "/ used when saving version_XXX methods in a non-XXX sourceCodeManager
        "/ (i.e. to rewrite all non-CVS version methods while saving into a CVS repository)
        "/ this is required because we cannot save an SVN version method (dollar-ID-...-dollar) into a
        "/ CVS repository without loosing the original string with the next checkout, because it also gets  
        "/ expanded by CVS. The same is true vice-versa for CVS-Ids, which get clobbered by SVN.
        rewriteQuery := AbstractSourceFileWriter methodSourceRewriteQuery new.
        rewriteQuery method:aMethod source:source.
        possiblyRewrittenSource := (rewriteQuery query) ? source.
        aStream nextChunkPut:possiblyRewrittenSource.
"/possiblyRewrittenSource ~= source ifTrue: [
"/    Transcript showCR: possiblyRewrittenSource.
"/].
    ].
!

fileOutMethods: methods on: stream

    methods do:
        [:method| |cat source privacy|

        stream nextPutChunkSeparator.
        method mclass name printOn:stream.
        "/        self printClassNameOn:aStream.

        (privacy := method privacy) ~~ #public ifTrue:[
            stream space; nextPutAll:privacy; nextPutAll:'MethodsFor:'.
        ] ifFalse:[
            stream nextPutAll:' methodsFor:'.
        ].

        cat := method category ? ''.
        stream nextPutAll:cat asString storeString.
        stream nextPutChunkSeparator; cr; cr.

        self fileOutMethod: method on: stream.

        stream space.
        stream nextPutChunkSeparator.
        stream cr]

    "Created: / 30-12-2009 / 18:43:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileOutPackageDefinition:pkg on:aStream 
    (pkg notNil and:[ pkg ~= PackageId noProjectID ]) ifTrue:[
        aStream nextPutAll:'"{ Package: '''.
        aStream nextPutAll:pkg asString.
        aStream
            nextPutAll:''' }"'; cr; cr;
            nextPut:$!!; cr; cr
    ]
!

generateHeaderWithCopyrightOn:outStream
    |copyrightMethod copyrightText|

    "if there is a copyright method, add a copyright comment
     at the beginning, taking the string from the copyright method.
     We cannot do this unconditionally - that would lead to my copyrights
     being put on your code ;-).
     On the other hand: I want every file created by myself to have the
     copyright string at the beginning be preserved .... even if the
     code was edited in the browser and filedOut."

    (copyrightMethod := classBeingSaved theMetaclass compiledMethodAt:#copyright) notNil ifTrue:[
        "
         get the copyright method's comment-text, strip off empty and blank lines
         and insert at beginning.
        "
        copyrightText := copyrightMethod comment.
        copyrightText notEmptyOrNil ifTrue:[
            copyrightText := copyrightText asCollectionOfLines asStringCollection.
            copyrightText := copyrightText withoutLeadingBlankLines.
            copyrightText := copyrightText withoutTrailingBlankLines.
            copyrightText notEmpty ifTrue:[
                copyrightText addFirst:'"'.
                copyrightText addLast:'"'.
                copyrightText := copyrightText asString.
                outStream nextPutAllAsChunk:copyrightText.
            ].
        ].
    ].
! !

!SmalltalkChunkFileSourceWriter class methodsFor:'documentation'!

version
    ^ '$Id: SmalltalkChunkFileSourceWriter.st 10632 2011-04-09 17:19:04Z vranyj1 $'
!

version_CVS
    ^ 'Header: /var/local/cvs/stx/libbasic/SmalltalkChunkFileSourceWriter.st,v 1.12 2009-10-02 14:30:07 cg Exp '
!

version_SVN
    ^ '$Id: SmalltalkChunkFileSourceWriter.st 10632 2011-04-09 17:19:04Z vranyj1 $'
! !