Cface__CFunctionNode.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sun, 28 Dec 2014 22:29:51 +0100
changeset 34 834ca32d06b2
parent 32 d7464405cbda
child 37 1ad7fb72801a
permissions -rw-r--r--
Minor fixes here and there (mainly because of Cairo bindings)

"{ Package: 'jv:cface' }"

"{ NameSpace: Cface }"

CDefinitionNode subclass:#CFunctionNode
	instanceVariableNames:'smalltalkClass smalltalkNamespace arguments return kind'
	classVariableNames:''
	poolDictionaries:''
	category:'Cface-C AST'
!

!CFunctionNode class methodsFor:'documentation'!

history

    "Created: / 25-10-2007 / 14:39:30 / haja"
    "Created: #name / 25-10-2007 / 14:39:35 / haja"
    "Created: #name: / 25-10-2007 / 14:39:35 / haja"
    "Created: #arguments / 25-10-2007 / 14:39:35 / haja"
    "Created: #arguments: / 25-10-2007 / 14:39:35 / haja"
    "Created: #return / 25-10-2007 / 14:39:35 / haja"
    "Created: #return: / 25-10-2007 / 14:39:35 / haja"
    "Created: #name:arguments:return: / 25-10-2007 / 14:41:52 / haja"
    "Created: #acceptVisitor: / 02-11-2007 / 10:44:22 / haja"
    "Created: #acceptNameVisitor: / 05-11-2007 / 17:41:59 / haja"
    "Deleted: #acceptNameVisitor: / 12-11-2007 / 09:46:47 / haja"
! !

!CFunctionNode methodsFor:'accessing'!

arguments
    ^ arguments

    "Created: / 25-10-2007 / 14:39:35 / haja"
!

arguments:something
    arguments := something.

    "Created: / 25-10-2007 / 14:39:35 / haja"
!

kind
    ^ kind ? #static

    "Created: / 01-03-2008 / 20:30:22 / janfrog"
    "Modified: / 04-03-2008 / 10:57:12 / janfrog"
!

kind:aSymbol

    self 
        assert:(#(static method) includes: aSymbol)
        message:'kind must be one of #static or #method'.
    
    kind := aSymbol.

    "Created: / 01-03-2008 / 20:30:22 / janfrog"
    "Modified: / 04-03-2008 / 10:57:12 / janfrog"
    "Modified: / 03-07-2008 / 22:06:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

priority

    ^25

    "Created: / 17-02-2008 / 18:00:13 / janfrog"
!

return
    ^ return

    "Created: / 25-10-2007 / 14:39:35 / haja"
!

return:something
    return := something.

    "Created: / 25-10-2007 / 14:39:35 / haja"
!

smalltalkArgumentNames
    ^self arguments collect:[:cArgument|cArgument smalltalkName]

    "Created: / 10-07-2008 / 08:52:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkClassName
    ^ smalltalkClass

    "Created: / 10-07-2008 / 08:01:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkClassName:something 
    smalltalkClass := something.

    "Created: / 10-07-2008 / 08:01:27 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkClassNameWithNamespace
    ^ self smalltalkNamespace isNilOrEmptyCollection 
        ifTrue:[ self smalltalkClassName ]
        ifFalse:[
            self smalltalkNamespace , '::' 
                , (self smalltalkClassName ? #ExternalFunctions)
        ]

    "Created: / 03-07-2008 / 21:27:11 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 10-07-2008 / 08:01:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkNamespace
    ^ smalltalkNamespace

    "Created: / 17-02-2008 / 20:54:34 / janfrog"
!

smalltalkNamespace:something
    smalltalkNamespace := something.

    "Created: / 17-02-2008 / 20:54:34 / janfrog"
!

smalltalkPrimitiveSelector

    ^ self smalltalkSelector

    "Created: / 10-07-2008 / 08:50:02 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 28-12-2014 / 10:30:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

smalltalkPrimitiveSelectorIterlacedWithArgumentNames

    ^self
        interlaceSelector: self smalltalkPrimitiveSelector
        withArgumentNames: self smalltalkArgumentNames

    "Created: / 10-07-2008 / 08:53:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkSelector

    ^smalltalkName asSymbol

    "Created: / 17-02-2008 / 22:12:23 / janfrog"
    "Modified: / 10-07-2008 / 08:50:08 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkSelector:aSymbol
    smalltalkName := aSymbol

    "Created: / 17-02-2008 / 22:12:14 / janfrog"
!

smalltalkSelectorIterlacedWithArgumentNames

    ^self
        interlaceSelector: self smalltalkSelector
        withArgumentNames: self smalltalkArgumentNames

    "Created: / 10-07-2008 / 08:51:12 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CFunctionNode methodsFor:'printing'!

printOn:stream indent:level

    self printLineOn: stream indent: level.
    self smalltalkNamespace 
        ifNotNil:[
            stream
                nextPutAll:';; Namespace: ';
                nextPutAll:self smalltalkNamespace;
                cr;
                next:level put:Character tab
        ].
    self smalltalkClassName 
        ifNotNil:[
            stream
                nextPutAll:';; Class: ';
                nextPutAll:self smalltalkClassName;
                cr;
                next:level put:Character tab
        ].
    self smalltalkClassName 
        ifNotNil:[
            stream
                nextPutAll:';; Selector: ';
                nextPutAll:self smalltalkSelector;
                cr;
                next:level put:Character tab
        ].
    self smalltalkClassName 
        ifNotNil:[
            stream
                nextPutAll:';; Kind: ';
                nextPutAll:self kind;
                cr;
                next:level put:Character tab
        ].
    stream
        nextPutAll:'(function ';
        nextPutAll:self cName;
        cr;
        next:level + 1 put:Character tab.
    arguments do:[:argNode | 
        argNode printOn:stream indent:level + 1.
        stream
            cr;
            next:level + 1 put:Character tab
    ].
    stream next:level + 1 put:Character tab.
    return printOn:stream indent:level + 1.
    stream
        nextPut:$);
        cr.

    "Created: / 18-02-2008 / 14:27:37 / janfrog"
    "Modified: / 04-03-2008 / 10:57:11 / janfrog"
    "Modified: / 10-07-2008 / 20:05:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CFunctionNode methodsFor:'private'!

interlaceSelector: selector withArgumentNames: argNames

    | stream |
    stream := String new writeStream.

    argNames size > 0 
        ifTrue:
            [selector keywords with: argNames do:
                [:keyword :argument|
                    stream nextPutAll: keyword; space; nextPutAll: argument; space]]
        ifFalse:
            [stream nextPutAll: selector].
    ^stream contents

    "Created: / 10-07-2008 / 08:54:10 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CFunctionNode methodsFor:'testing'!

isCFunctionNode
    ^ true

    "Created: / 17-02-2008 / 21:49:53 / janfrog"
!

isFirstArgumentCPointerToCStructure

    ^arguments size isZero
        ifTrue:[false]
        ifFalse:[arguments first type isCPointerToCStructure]

    "Created: / 04-07-2008 / 15:12:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CFunctionNode methodsFor:'visiting'!

acceptVisitor:aVisitor 
    "Double dispatch back to the visitor, passing my type encoded in
     the selector (visitor pattern)"
    "stub code automatically generated - please change if required"
    
    ^ aVisitor visitCFunctionNode:self

    "Created: / 02-11-2007 / 10:44:22 / haja"
    "Modified: / 10-02-2008 / 10:45:12 / janfrog"
! !

!CFunctionNode class methodsFor:'documentation'!

version
    ^ '$Id$'
!

version_SVN
    ^ '$Id$'
! !