Cface__CUserDefinedTypeNode.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 10 Jul 2008 20:56:08 +0000
changeset 6 ae25dce94003
parent 5 c110eef5b9ef
child 14 1f730d82496e
permissions -rw-r--r--
Added SVNMapping. Now it is able to parse libsvn.def

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

"{ NameSpace: Cface }"

CTypeNode subclass:#CUserDefinedTypeNode
	instanceVariableNames:'type'
	classVariableNames:''
	poolDictionaries:''
	category:'Cface-C AST'
!

!CUserDefinedTypeNode class methodsFor:'documentation'!

history

    "Created: / 25-10-2007 / 17:44:38 / haja"
    "Created: #name / 25-10-2007 / 17:44:44 / haja"
    "Created: #name: / 25-10-2007 / 17:44:44 / haja"
    "Created: #id / 25-10-2007 / 17:44:44 / haja"
    "Created: #id: / 25-10-2007 / 17:44:44 / haja"
    "Created: #acceptVisitor: / 02-11-2007 / 10:45:15 / haja"
    "Created: #name:id: / 02-11-2007 / 13:50:44 / haja"
    "Deleted: #id / 02-11-2007 / 13:50:50 / haja"
    "Deleted: #id: / 02-11-2007 / 13:50:50 / haja"
    "Deleted: #name / 02-11-2007 / 13:50:50 / haja"
    "Deleted: #name: / 02-11-2007 / 13:50:50 / haja"
    "Created: #names / 02-11-2007 / 13:51:15 / haja"
    "Created: #reference / 02-11-2007 / 13:51:15 / haja"
    "Created: #reference: / 02-11-2007 / 13:51:15 / haja"
    "Created: #names: / 02-11-2007 / 13:52:13 / haja"
    "Deleted: #name:id: / 02-11-2007 / 13:52:15 / haja"
    "Created: #acceptNameVisitor: / 05-11-2007 / 17:34:09 / haja"
    "Deleted: #acceptNameVisitor: / 12-11-2007 / 09:46:54 / haja"
    "Created: #buildTypeCheckFor:on: / 19-12-2007 / 15:24:03 / haja"
    "Created: #checkFundamentalType: / 19-12-2007 / 15:26:44 / haja"
    "Created: #checkDefinedType: / 19-12-2007 / 15:27:03 / haja"
    "Created: #fundamentalTypes / 19-12-2007 / 15:28:32 / haja"
    "Created: #buildTypeCheckForFundamentalType:on: / 19-12-2007 / 15:31:42 / haja"
    "Created: #buildTypeCheckForDefinedType:on: / 19-12-2007 / 15:31:52 / haja"
    "Deleted: #checkDefinedType: / 19-12-2007 / 15:34:33 / haja"
    "Deleted: #checkFundamentalType: / 19-12-2007 / 15:34:35 / haja"
    "Created: #buildObjectCreationOn: / 19-12-2007 / 16:34:44 / haja"
    "Created: #buildObjectCreationFundamentalTypeOn: / 19-12-2007 / 16:35:39 / haja"
    "Created: #buildObjectCreationOnDefinedTypeOn: / 19-12-2007 / 16:36:11 / haja"
    "Created: #buildValueExtractionFor:on: / 19-12-2007 / 17:26:12 / haja"
    "Created: #buildValueExtractionForDefinedType:on: / 19-12-2007 / 17:26:43 / haja"
    "Created: #buildValueExtractionForFundamentalType:on: / 19-12-2007 / 17:26:57 / haja"
    "Created: #buildObjectCreationFor:on: / 19-12-2007 / 17:40:07 / haja"
    "Created: #buildObjectCreationFundamentalTypeFor:on: / 19-12-2007 / 17:40:14 / haja"
    "Created: #buildObjectCreationOnDefinedTypeFor:on: / 19-12-2007 / 17:40:23 / haja"
    "Deleted: #buildObjectCreationOnDefinedTypeFor:on: / 19-12-2007 / 17:40:46 / haja"
    "Created: #buildObjectCreationDefinedTypeFor:on: / 19-12-2007 / 17:42:08 / haja"
    "Deleted: #buildObjectCreationFundamentalTypeOn: / 19-12-2007 / 17:42:14 / haja"
    "Deleted: #buildObjectCreationOn: / 19-12-2007 / 17:42:15 / haja"
    "Deleted: #buildObjectCreationOnDefinedTypeOn: / 19-12-2007 / 17:42:16 / haja"
    "Created: #buildCTypeOn: / 19-12-2007 / 18:13:30 / haja"
    "Created: #buildTypeDescriptionOn: / 20-12-2007 / 12:11:52 / haja"
! !

!CUserDefinedTypeNode class methodsFor:'instance creation'!

names:aNames

    | anIdNode |

    anIdNode := self new.
    anIdNode names:aNames.

    ^anIdNode

    "Created: / 02-11-2007 / 13:52:13 / haja"
! !

!CUserDefinedTypeNode methodsFor:'accessing'!

cByteSize

    ^type cByteSize

    "Created: / 09-07-2008 / 19:39:45 / Jan Vrany <vranyj1@fel.cvut.cz>"
!

ffiTypeSymbol
    "Superclass Cface::CTypeNode says that I am responsible to implement this method"

    ^type ffiTypeSymbol

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

type
    ^ type

    "Created: / 12-02-2008 / 23:21:13 / janfrog"
!

type:something
    type := something.

    "Created: / 12-02-2008 / 23:21:13 / janfrog"
! !

!CUserDefinedTypeNode methodsFor:'builder'!

buildCTypeOn:aBuilder

    ((reference references:EnumNode) | (reference references:StructNode) | (reference references:UnionNode)) ifTrue:[
      (reference typedef) ifFalse:[
        (reference references:EnumNode) ifTrue:[ aBuilder nextPutString:'enum ' ].
        (reference references:StructNode) ifTrue:[ aBuilder nextPutString:'struct ' ].
        (reference references:UnionNode) ifTrue:[ aBuilder nextPutString:'union ' ].
      ].
    ].

    aBuilder idNamesWith:names.

    "Created: / 19-12-2007 / 18:13:30 / haja"
!

buildObjectCreationDefinedTypeFor:aVariable on:aBuilder

    (reference references:EnumNode) ifTrue:[
      ^aBuilder buildIntegerCreationFor:aVariable.
    ].

    ^aBuilder buildPointerCreationFor:aVariable.

    "Created: / 19-12-2007 / 17:42:08 / haja"
!

buildObjectCreationFor:aVariable on:aBuilder

    self fundamentalTypes do:[:aType| (aType = names last) ifTrue:[ ^self buildObjectCreationFundamentalTypeFor:aVariable on:aBuilder. ] ].

    ^self buildObjectCreationDefinedTypeFor:aVariable on:aBuilder.

    "Created: / 19-12-2007 / 16:34:44 / haja"
    "Modified: / 19-12-2007 / 17:44:19 / haja"
!

buildObjectCreationFundamentalTypeFor:aVariable on:aBuilder

      (((names last = 'int') | (names last = 'short') | (names last = 'long')) & ((names includes:'unsigned')not)) ifTrue:[
        ^aBuilder buildIntegerCreationFor:aVariable.
      ].

      (((names last = 'int') | (names last = 'short') | (names last = 'long') | (names last = 'unsigned')) & ((names includes:'signed')not)) ifTrue:[
        ^aBuilder buildUnsignedIntegerCreationFor:aVariable.
      ].

      (names last = 'char') ifTrue:[
        ^aBuilder buildCharacterCreationFor:aVariable.
      ].

      (names last = 'float') ifTrue:[
        ^aBuilder buildFloatCreationFor:aVariable.
      ].
      (names last = 'double') ifTrue:[
        ^aBuilder buildDoubleCreationFor:aVariable.
      ].

    ^aBuilder buildPointerCreationFor:aVariable.

    "Created: / 19-12-2007 / 17:40:14 / haja"
!

buildTypeCheckFor:aVariable on:aBuilder

    self fundamentalTypes do:[:aType| (aType = names last) ifTrue:[ ^self buildTypeCheckForFundamentalType:aVariable on:aBuilder. ] ].

    ^self buildTypeCheckForDefinedType:aVariable on:aBuilder.

    "Created: / 19-12-2007 / 15:24:02 / haja"
!

buildTypeCheckForDefinedType:aVariable on:aBuilder

    (reference references:EnumNode) ifTrue:[
      ^aBuilder buildIntegerCheckFor:aVariable.
    ].

    ^aBuilder buildPointerCheckFor:aVariable.

    "Created: / 19-12-2007 / 15:31:52 / haja"
!

buildTypeCheckForFundamentalType:aVariable on:aBuilder

      ((names last = 'int') | (names last = 'short') | (names last = 'long') | (names last = 'unsigned')) ifTrue:[
        ^aBuilder buildIntegerCheckFor:aVariable.
      ].

      (names last = 'char') ifTrue:[
        ^aBuilder buildCharacterCheckFor:aVariable.
      ].

      (names last = 'float') ifTrue:[
        ^aBuilder buildFloatCheckFor:aVariable.
      ].
      (names last = 'double') ifTrue:[
        ^aBuilder buildDoubleCheckFor:aVariable.
      ].

    ^aBuilder buildPointerCheckFor:aVariable.

    "Created: / 19-12-2007 / 15:31:42 / haja"
!

buildTypeDescriptionOn:aBuilder

    (reference references:Cface::EnumNode) ifTrue:[
        aBuilder nextPutString:'enumeration '.
    ].
    (reference references:Cface::StructNode) ifTrue:[
        aBuilder nextPutString:'structure '.
    ].
    (reference references:Cface::UnionNode) ifTrue:[
        aBuilder nextPutString:'union '.
    ].

    names do:[:aName| aBuilder nextPutString:aName asString,' ' ].

    "Created: / 20-12-2007 / 12:11:52 / haja"
!

buildValueExtractionFor:aVariable on:aBuilder

    self fundamentalTypes do:[:aType| (aType = names last) ifTrue:[ ^self buildValueExtractionForFundamentalType:aVariable on:aBuilder. ] ].

    ^self buildValueExtractionForDefinedType:aVariable on:aBuilder.

    "Created: / 19-12-2007 / 17:26:12 / haja"
!

buildValueExtractionForDefinedType:aVariable on:aBuilder

    (reference references:EnumNode) ifTrue:[
      ^aBuilder buildIntegerValueExtractionFor:aVariable.
    ].

    ^aBuilder buildPointerValueExtractionFor:aVariable.

    "Created: / 19-12-2007 / 17:26:43 / haja"
!

buildValueExtractionForFundamentalType:aVariable on:aBuilder

      (((names last = 'int') | (names last = 'short') | (names last = 'long')) & ((names includes:'unsigned')not)) ifTrue:[
        ^aBuilder buildIntegerValueExtractionFor:aVariable.
      ].

      (((names last = 'int') | (names last = 'short') | (names last = 'long') | (names last = 'unsigned')) & ((names includes:'signed')not)) ifTrue:[
        ^aBuilder buildUnsignedIntegerValueExtractionFor:aVariable.
      ].

      (names last = 'char') ifTrue:[
        ^aBuilder buildCharacterValueExtractionFor:aVariable.
      ].

      (names last = 'float') ifTrue:[
        ^aBuilder buildFloatValueExtractionFor:aVariable.
      ].
      (names last = 'double') ifTrue:[
        ^aBuilder buildDoubleValueExtractionFor:aVariable.
      ].

    ^aBuilder buildPointerValueExtractionFor:aVariable.

    "Created: / 19-12-2007 / 17:26:57 / haja"
! !

!CUserDefinedTypeNode methodsFor:'converting'!

resolved
    type 
        ifNil:[ self error:'User defined type ' , cName , ' not yet resolved' ].
    ^ type

    "Created: / 17-02-2008 / 17:56:03 / janfrog"
    "Modified: / 09-07-2008 / 19:51:28 / Jan Vrany <vranyj1@fel.cvut.cz>"
! !

!CUserDefinedTypeNode methodsFor:'printing'!

printOn: stream indent: level

    stream nextPutAll:  cName

    "Created: / 17-02-2008 / 18:18:11 / janfrog"
! !

!CUserDefinedTypeNode methodsFor:'private'!

fundamentalTypes

"
Possible combinations:

char
signed char
unsigned char

int, signed int
short int, short, signed short int, signed short
long int, long, signed long int,signed long

unsigned int, unsigned
unsigned short int, unsigned short
unsigned long int, unsigned long

float
double
long double
"

    ^#('char' 'short' 'int' 'long' 'float' 'double' 'void' 'signed' 'unsigned').

    "Created: / 19-12-2007 / 15:28:32 / haja"
! !

!CUserDefinedTypeNode 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 visitCUserDefinedTypeNode:self

    "Created: / 02-11-2007 / 13:50:44 / haja"
    "Modified: / 12-02-2008 / 22:59:33 / janfrog"
! !

!CUserDefinedTypeNode class methodsFor:'documentation'!

version
    ^ '$Header: /opt/data/cvs/cvut-fel/cface/Cface__CUserDefinedTypeNode.st,v 1.1 2008/02/26 15:57:04 vranyj1 Exp $'
! !