CypressMethodStructure.st
author jv
Mon, 03 Sep 2012 11:09:18 +0000
changeset 8 5d48f4894483
parent 6 65414b4bbe93
permissions -rw-r--r--
- CypressPackageReader comment/format in: #readClassStructureFromEntry: - CypressPackageStructure added: #asChangeSet - CypressClassStructure changed: #changesOn: - CypressMethodStructure changed: #changesOn: #classStructure: - stx_goodies_cypress changed: #classNamesAndAttributes #extensionMethodNames #preRequisites - extensions ...

"{ Package: 'stx:goodies/cypress' }"

CypressStructure subclass:#CypressMethodStructure
	instanceVariableNames:'source isMetaclass classStructure timeStamp'
	classVariableNames:''
	poolDictionaries:''
	category:'Cypress-Structure'
!

CypressMethodStructure comment:'Main comment stating the purpose of this class and relevant relationship to other classes.

Possible useful expressions for doIt or printIt.

Structure:
 instVar1		type -- comment about the purpose of instVar1
 instVar2		type -- comment about the purpose of instVar2

Any further useful comments about the general approach of this implementation.'
!


!CypressMethodStructure class methodsFor:'instance creation'!

fromMethodDefinition: methodDefinition

	^self new
		fromMethodDefinition: methodDefinition;
		yourself
! !

!CypressMethodStructure methodsFor:'accessing'!

category

	^self properties at: 'category'
!

category: aString

	self properties at: 'category' put: aString
!

classStructure
	^classStructure
!

classStructure: aCypressClassStructure
        classStructure := aCypressClassStructure.
        packageStructure := aCypressClassStructure packageStructure.

    "Modified: / 03-09-2012 / 11:34:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

cypressSource

        | stream |
        stream := WriteStream on: String new.
        stream 
                nextPutAll: self category;
                cr;
                nextPutAll: self source.
        ^stream contents

    "Modified: / 30-08-2012 / 14:50:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isMetaclass

	isMetaclass ifNil: [ isMetaclass := false ].
	^isMetaclass
!

isMetaclass: aBoolean
	isMetaclass := aBoolean
!

selector
    ^ String
        streamContents: [ :stream | 
            self name
                do: [ :chara | 
                    stream
                        nextPut:
                            (chara = $.
                                ifTrue: [ $: ]
                                ifFalse: [ chara ]) ] ]
!

selector: aString
    name := String
        streamContents: [ :stream | 
            aString
                do: [ :chara | 
                    stream
                        nextPut:
                            (chara = $:
                                ifTrue: [ $. ]
                                ifFalse: [ chara ]) ] ]
!

source

	^source
!

source: aString

	source := aString
!

timeStamp

	^timeStamp
!

timeStamp: aTimeStamp

	timeStamp := aTimeStamp
! !

!CypressMethodStructure methodsFor:'converting'!

asCypressMethodDefinition

	^CypressMethodDefinition 
        	className: self classStructure className
		classIsMeta: self isMetaclass
		selector: self selector
		category: self category
		source: self source
		timeStamp: self timeStamp
!

changesOn:aStream
    | change parser |

    change := MethodDefinitionChange new.
    change className: (classStructure properties at:#name).
    isMetaclass ifTrue:[
        change className: (change className , ' class')
    ].
    change category: (properties at:#category).

    parser := Parser parseMethodSpecification: source. 
    change selector: parser selector.
    change source: source.
    change package: packageStructure name asSymbol.

    aStream nextPut: change

    "Modified: / 03-09-2012 / 11:09:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CypressMethodStructure methodsFor:'initialization'!

fromJs:jsObject
    "superclass CypressStructure says that I am responsible to implement this method"

    ^ self shouldImplement
!

fromJs: jsObject  named: methodNameParts

	| ext |
	(ext := methodNameParts at: 2) = '.st'
		ifTrue: [  self extractCypressSource: (jsObject at: 'contents') ]
		ifFalse: [ ext = '.json' ifTrue: [  properties := jsObject at: 'contents' ] ]
!

fromMethodDefinition: methodDefinition

	self isMetaclass: methodDefinition classIsMeta.
	self selector: methodDefinition selector.
	self category: methodDefinition category.
	self source: methodDefinition source.
	self timeStamp: methodDefinition timeStamp.
! !

!CypressMethodStructure methodsFor:'private'!

extractCypressSource: aString
    | stream categoryStream sourceStream readingCategory |
    stream := ReadStream on: aString.
    categoryStream := WriteStream on: String new.
    sourceStream := WriteStream on: String new.
    readingCategory := true.
    [ stream atEnd ]
        whileFalse: [ 
            | char |
            char := stream next.
            readingCategory
                ifTrue: [ 
                    char = Character lf
                        ifTrue: [ readingCategory := false ]
                        ifFalse: [ categoryStream nextPut: char ] ]
                ifFalse: [ sourceStream nextPut: char ] ].
    self category: categoryStream contents.
    self source: sourceStream contents

    "Modified: / 30-08-2012 / 13:58:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CypressMethodStructure methodsFor:'writing'!

writeJsonOn: aStream  indent: startIndent

        | indent |
        indent := startIndent.
        aStream 
                tab: indent;
                nextPutAll: '{';
                cr.
        indent := indent + 1.
        aStream
                tab: indent;
                nextPutAll: '"name"';
                nextPutAll: ' : ';
                nextPutAll: '"', self name, '.st",';
                cr.
        aStream
                tab: indent;
                nextPutAll: '"contents"';
                nextPutAll: ' : '.
        self cypressSource writeCypressJsonOn: aStream forHtml: true indent: indent.
        indent := indent - 1.
        aStream
                cr;
                tab: indent;
                nextPutAll: ' }'

    "Modified: / 30-08-2012 / 14:49:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CypressMethodStructure class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !