Cface__TypeMapping.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Tue, 23 Sep 2014 16:52:40 +0100
changeset 32 d7464405cbda
parent 28 6a2e82ddbca1
child 34 834ca32d06b2
permissions -rw-r--r--
Package renamed from cvut:fel/cface to jv:cface

"{ Package: 'jv:cface' }"

"{ NameSpace: Cface }"

Object subclass:#TypeMapping
	instanceVariableNames:'definitions smalltalkPackage smalltalkNamespace'
	classVariableNames:''
	poolDictionaries:''
	category:'Cface-Mappings'
!


!TypeMapping methodsFor:'accessing'!

definitions
    ^ definitions

    "Created: / 22-02-2009 / 22:16:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

definitions:something
    definitions := something.

    "Created: / 22-02-2009 / 22:16:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkNamespace

    ^nil

    "Created: / 17-02-2008 / 20:51:05 / janfrog"
    "Modified: / 10-07-2008 / 20:34:14 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 07-09-2012 / 15:15:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

smalltalkNamespace:something
    smalltalkNamespace := something.

    "Created: / 10-07-2008 / 20:23:36 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkPackage
    ^ smalltalkPackage

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

smalltalkPackage:package
    smalltalkPackage := package.

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

!TypeMapping methodsFor:'filtering'!

shouldIgnoreEnum: cEnumNode

    ^false

    "Created: / 22-02-2009 / 15:13:07 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

shouldIgnoreStruct: cStructNode

    ^false

    "Created: / 22-02-2009 / 15:13:24 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

shouldIgnoreUnion: cUnionNode

    ^false

    "Created: / 22-02-2009 / 15:13:15 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!TypeMapping methodsFor:'mapping - categories'!

smalltalkCategoryForDerivedType:cType 

    ^(self smalltalkNamespaceForDerivedType: cType) , '-C Types'

    "Created: / 10-07-2008 / 08:06:58 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 10-07-2008 / 20:30:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 30-05-2012 / 21:59:21 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

smalltalkCategoryForEnum: enum
    ^ self smalltalkCategoryForDerivedType:enum

    "Created: / 10-07-2008 / 08:07:31 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 10-09-2012 / 09:35:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

smalltalkCategoryForStruct:struct 
    ^ self smalltalkCategoryForDerivedType:struct

    "Created: / 10-07-2008 / 08:07:12 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified (comment): / 10-09-2012 / 09:35:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

smalltalkCategoryForUnion:union 
    ^ self smalltalkCategoryForDerivedType:union

    "Created: / 10-07-2008 / 08:06:05 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified (comment): / 10-09-2012 / 09:35:12 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!TypeMapping methodsFor:'mapping - class names'!

smalltalkClassNameForDerivedType:cType 
    ^ (self smalltalkize:cType cName) capitalized asSymbol

    "Created: / 10-07-2008 / 08:05:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 10-07-2008 / 20:29:30 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkClassNameForEnum:cEnum 
    ^ self smalltalkClassNameForDerivedType:cEnum

    "Answers class which should contain function call"

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

smalltalkClassNameForFunction:cFunction 
    |firstArgType|

    cFunction arguments isEmpty ifTrue:[
        ^ nil
    ].
    firstArgType := cFunction arguments first type.
    ^ (firstArgType isCPointerNode and:[ firstArgType type isCStructNode ]) 
        ifTrue:[ firstArgType type smalltalkClassName ]
        ifFalse:[ nil ]

    "Answers class which should contain function call"

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

smalltalkClassNameForStruct:cStruct 
    ^ self smalltalkClassNameForDerivedType:cStruct

    "Answers class which should contain function call"

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

smalltalkClassNameForUnion:union 
    ^ self smalltalkClassNameForDerivedType:union

    "Answers class which should contain function call"

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

!TypeMapping methodsFor:'mapping - misc'!

smalltalkNameForEnumValue:cEnumField 
    ^ self smalltalkClassNameForDerivedType:cEnumField

    "Answers class which should contain function call"

    "Created: / 04-07-2008 / 11:32:01 / Jan Vrany <vranyj1@fel.cvut.cz>"
    "Modified: / 10-07-2008 / 08:05:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkNameForStructField:cStructField
    ^ self smalltalkize: cStructField cName

    "Created: / 17-02-2008 / 21:22:15 / janfrog"
! !

!TypeMapping methodsFor:'mapping - namespaces'!

kindForFunction:cFunction

    |firstArgType|

    cFunction arguments isEmpty ifTrue:[^#static].
    firstArgType := cFunction arguments first type.
    ^(firstArgType isCPointerNode and:[firstArgType type isCStructNode])
        ifTrue:[#method]
        ifFalse:[#static]





    "Answers class which should contain function call"

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

smalltalkNamespaceForDerivedType: cType

    ^self smalltalkNamespace

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

smalltalkNamespaceForEnum: cType

    ^self smalltalkNamespaceForDerivedType: cType

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

smalltalkNamespaceForFunction: cType

    ^self smalltalkNamespaceForDerivedType: cType

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

smalltalkNamespaceForStruct: cType

    ^self smalltalkNamespaceForDerivedType: cType

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

smalltalkNamespaceForUnion: cType

    ^self smalltalkNamespaceForDerivedType: cType

    "Created: / 10-07-2008 / 20:24:55 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!TypeMapping methodsFor:'mapping - selectors'!

smalltalkSelectorForFunction:cFunction

    ^self smalltalkizeSelector: cFunction cName forFunction: cFunction

    "Created: / 17-02-2008 / 22:15:44 / janfrog"
    "Modified: / 04-07-2008 / 15:16:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!TypeMapping methodsFor:'private - utilities'!

smalltalkize: input

    | inputStream outputStream |
    inputStream := input readStream.
    outputStream := (String new:input size) writeStream.
    [ inputStream atEnd ] whileFalse:
        [|c|
        c := inputStream next.
        c = $_ 
            ifTrue:[inputStream peek ifNotNil:[outputStream nextPut: inputStream next asUppercase]]
            ifFalse:[outputStream nextPut: c]].
    ^outputStream contents.

    "
        Cface::TypeMapping new smalltalkize:'test'   
        Cface::TypeMapping new smalltalkize:'test_of_smalltalkize'    
    "

    "Created: / 08-02-2008 / 09:34:40 / janfrog"
    "Modified: / 10-07-2008 / 23:05:50 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

smalltalkizeSelector: translatedFunctionName forFunction: cFunction

    ^String streamContents:
        [:s|
        s nextPutAll:(self smalltalkize: translatedFunctionName).
        cFunction arguments size > 0 ifTrue:
            [s nextPut:$:].
        cFunction arguments size > 1 ifTrue:
            [(cFunction arguments copyFrom:2) do:
                [:argument|
                s 
                    nextPutAll: (self smalltalkize: argument cName);
                    nextPut:$:]]]

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

!TypeMapping class methodsFor:'documentation'!

version
    ^ '$Id$'
!

version_SVN
    ^ '$Id$'
! !