AbstractSourceFileWriter.st
author Stefan Vogel <sv@exept.de>
Wed, 29 Jan 2014 17:08:17 +0100
changeset 15923 6bc82606b914
parent 15419 a1da7568bcfe
child 16879 2b94ea863dda
child 18068 3e841ddcb18a
permissions -rw-r--r--
class: Win32OperatingSystem changed: #setBlocking:on: fix return value

"
 COPYRIGHT (c) 2006 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' }"

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

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

!AbstractSourceFileWriter class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2006 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
"
    Abstract common superclass for source file writers
"
! !

!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>"
!

fileOutMethods: methods on:stream

    "Files out a bunch of methods. This is used to file-out extension methods"    

    self subclassResponsibility

    "Modified: / 16-08-2009 / 09:59:49 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 30-12-2009 / 18:34:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fileOutPackageDefinition:packageId on:stream 
    "Files out a package definition on the stream, so all subsequent
     code entities will be placed in that package"
    
    self subclassResponsibility

    "Modified: / 16-08-2009 / 09:59:49 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Created: / 30-12-2009 / 18:34:33 / Jan Vrany <jan.vrany@fit.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_CVS
    ^ '$Header: /cvs/stx/stx/libbasic/AbstractSourceFileWriter.st,v 1.9 2013-06-23 22:22:16 cg Exp $'
!

version_SVN
    ^ '$ Id: AbstractSourceFileWriter.st 10643 2011-06-08 21:53:07Z vranyj1  $'
! !