Cface__SmalltalkXGenerator.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 03 Jul 2008 22:00:07 +0000
changeset 2 cfd2c393abfe
parent 1 b6c0180314d1
child 3 110a9cbf8594
permissions -rw-r--r--
Smalltalk/X generator improvements: - generate C enums as SharedPools with accessors - generate externa function calls using FFI. Not yet finished! - CairoMappings improved.

"{ Package: 'cvut:fel/cface' }"

"{ NameSpace: Cface }"

Generator subclass:#SmalltalkXGenerator
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Cface-Generators'
!


!SmalltalkXGenerator class methodsFor:'instance creation'!

generate:aStringOrFilename class:aClass namespace:aNameSpace 
    |temp|

    temp := Generator onFile:aStringOrFilename.
    temp 
        startGeneration:aClass
        nameSpace:aNameSpace
        toFile:aStringOrFilename , '.st'.
    ^ temp.

    "Created: / 08-02-2008 / 08:55:08 / janfrog"
!

new
    ^ self basicNew initialize.

    "Created: / 08-02-2008 / 08:55:08 / janfrog"
!

on: aStream

    |gen|

    gen := self new.
    gen inputStream: aStream;
        parseDef;
        analyse.
    ^gen

    "Modified: / 24-11-2007 / 12:20:27 / haja"
    "Created: / 08-02-2008 / 08:55:08 / janfrog"
!

onFile: aStringOrFilename

    ^self on: aStringOrFilename asFilename readStream

    "Created: / 08-02-2008 / 08:55:08 / janfrog"
! !

!SmalltalkXGenerator methodsFor:'processing'!

process: node

    super process: node.
    ^changeset

    "Created: / 03-07-2008 / 21:01:19 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!SmalltalkXGenerator methodsFor:'visiting'!

visitCEnumNode: cEnumNode

    (changeset add: ClassDefinitionChange new)
        superClassName: 
            SharedPool fullName;
        className: 
            cEnumNode smalltalkClassNameWithNamespace;
        classVariableNames:
            (String streamContents:
                [:s|
                cEnumNode values do:
                    [:cEnumValueNode|
                    s nextPutAll: cEnumValueNode cName; space]]);
        category:
            cEnumNode smalltalkCategory;
        package:
            cEnumNode smalltalkPackage.

    (changeset add: MethodDefinitionChange new)
        className:
            cEnumNode smalltalkClassNameWithNamespace, ' class';
        selector:
            #initialize;
        category:
            #initialization;
        source:
            (String streamContents:
                [:s|
                s nextPutAll:'initialize' ; cr; cr.
                cEnumNode values do:
                    [:cEnumValueNode|
                    s 
                        tab; 
                        nextPutAll: cEnumValueNode cName;
                        nextPutAll: ' := ';
                        nextPutAll: cEnumValueNode intValue;
                        nextPut:$.; cr]]).

    cEnumNode values do:
        [:cEnumValueNode|
        (changeset add: MethodDefinitionChange new)
            className:
                cEnumNode smalltalkClassNameWithNamespace, ' class';
            selector:
                cEnumValueNode cName asSymbol;
            category:
                #constants;
            source:
                (String streamContents:
                    [:s|
                    s nextPutAll: cEnumValueNode cName; cr; cr.
                    s tab; nextPut:$^; nextPutAll: cEnumValueNode cName])]

    "Created: / 03-07-2008 / 20:10:34 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 03-07-2008 / 22:07:20 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

visitCFunctionNode:functionNode

    (changeset add: MethodDefinitionChange new)
        className: functionNode smalltalkClassNameWithNamespace , ' class';
        category: 'external functions';
        selector: functionNode smalltalkSelector;
        source:
            (String streamContents:
                [:s|
                s 
                    nextPutAll: functionNode smalltalkSelector; cr; cr; tab;
                    nextPutAll: '<cdecl:';
                    space;
                    nextPutAll: functionNode return ffiTypeSymbol;
                    space;
                    nextPutAll: functionNode cName;
                    space;
                    nextPut:$(;
                    space.
                functionNode arguments do:
                    [:argument|
                    s nextPutAll: argument type ffiTypeSymbol; space].
                s 
                    nextPut:$);
                    space;
                    nextPut:$>])

    "Created: / 03-07-2008 / 21:26:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 03-07-2008 / 23:42:47 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

visitCStructNode: cStructNode

    cStructNode isAnonymous ifTrue:[^self].

    (changeset add: ClassDefinitionChange new)
        superClassName: 
            ExternalStructure fullName;
        className: 
            cStructNode smalltalkClassNameWithNamespace;
        category:
            cStructNode smalltalkCategory;
        package:
            cStructNode smalltalkPackage.

    "Created: / 03-07-2008 / 21:31:31 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 03-07-2008 / 23:42:54 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

visitCTypedefNode: typedefNode

    "Created: / 03-07-2008 / 22:00:49 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!SmalltalkXGenerator class methodsFor:'documentation'!

version
    ^ '$Header: /opt/data/cvs/cvut-fel/cface/Cface__SmalltalkXGenerator.st,v 1.1 2008/02/26 18:25:12 vranyj1 Exp $'
! !