AbstractSourceFileWriter.st
author fm
Thu, 08 Oct 2009 14:03:57 +0200
changeset 12182 8e65115f9c92
parent 12109 1e360b1a1062
child 13406 ab78d458b472
permissions -rw-r--r--
update #version_SVN with § as keyword expansion character

"{ Package: 'stx:libbasic' }"

Object subclass:#AbstractSourceFileWriter
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Classes'
!

Query subclass:#MethodSourceRewriteQuery
	instanceVariableNames:'method source'
	classVariableNames:''
	poolDictionaries:''
	privateIn:AbstractSourceFileWriter
!


!AbstractSourceFileWriter class methodsFor:'signal constants'!

methodSourceRewriteQuery
    "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.

    see SmalltalkChunkFileSourceWriter fileOutMethod:on:"

    ^ MethodSourceRewriteQuery
! !

!AbstractSourceFileWriter methodsFor:'fileout'!

fileOut:aClass on:outStreamArg 

    self 
        fileOut:aClass on:outStreamArg 
        withTimeStamp:true withInitialize:true 
        withDefinition:true 
        methodFilter:nil encoder:nil

    "Created: / 15-08-2009 / 13:11:31 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!AbstractSourceFileWriter methodsFor:'source writing'!

fileOut: class on:stream withTimeStamp: stampIt withInitialize: initIt withDefinition: withDefinition methodFilter:methodFilter encoder:encoderOrNil
    "raise an error: must be redefined in concrete subclass(es)"

    ^ self subclassResponsibility

    "Modified: / 16-08-2009 / 09:59:49 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!AbstractSourceFileWriter methodsFor:'source writing - comments'!

fileOutComment: aStringOrStringCollection on: aStream
    "Writes a comment to a stream using proper syntax"

    self fileOutCommentStartOn: aStream.
    aStringOrStringCollection isStringCollection
        ifTrue:
            [aStringOrStringCollection 
                do:[:line|self fileOutCommentLine: line on: aStream]
                separatedBy: [aStream cr]]
        ifFalse:
            [(aStringOrStringCollection includes: Character cr)
                ifTrue:"/hmm...multiline comment as string
                    [aStringOrStringCollection asStringCollection
                        do:[:line|self fileOutCommentLine: line on: aStream]
                        separatedBy: [aStream cr]]
                ifFalse:
                    [self fileOutCommentLine: aStringOrStringCollection on: aStream]].
    self fileOutCommentEndOn: aStream.

    "Created: / 21-08-2009 / 09:36:03 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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

    ^self subclassResponsibility

    "Created: / 21-08-2009 / 09:40:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

fileOutCommentLine: aString on: aStream

    "
        Writes a single line of comment on a comment to a stream.
        Should not put an cr to the stream!!
    "

    ^self subclassResponsibility

    "Created: / 21-08-2009 / 09:42:23 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

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

    ^self subclassResponsibility

    "Created: / 21-08-2009 / 09:40:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!AbstractSourceFileWriter::MethodSourceRewriteQuery class methodsFor:'documentation'!

documentation
"
    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.

    see SmalltalkChunkFileSourceWriter fileOutMethod:on:
"
! !

!AbstractSourceFileWriter::MethodSourceRewriteQuery methodsFor:'accessing'!

method
    ^ method
!

method:methodArg source:sourceArg 
    method := methodArg.
    source := sourceArg.
!

source
    ^ source
! !

!AbstractSourceFileWriter class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/AbstractSourceFileWriter.st,v 1.6 2009-10-08 12:03:57 fm Exp $'
!

version_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/AbstractSourceFileWriter.st,v 1.6 2009-10-08 12:03:57 fm Exp $'
!

version_SVN
    ^'§Id: AbstractSourceFileWriter.st 10468 2009-08-22 08:34:50Z vranyj1 §'
! !