LLVMType.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Sat, 08 Aug 2015 04:43:00 +0100
changeset 22 789a35bd30ac
parent 19 706be0fcef22
child 27 b26354bbff25
permissions -rw-r--r--
Added example for compiling conditional. Added convenience API to simply code generation.

"
    Copyright (C) 2015-now Jan Vrany

    This code is not an open-source (yet). You may use this code
    for your own experiments and projects, given that:

    * all modification to the code will be sent to the
      original author for inclusion in future releases
    * this is not used in any commercial software

    This license is provisional and may (will) change in
    a future.
"
"{ Package: 'jv:llvm_s' }"

"{ NameSpace: Smalltalk }"

LLVMObject subclass:#LLVMType
	instanceVariableNames:''
	classVariableNames:'Int1 Int16 Int32 Int64 IntPtr'
	poolDictionaries:'LLVMTypeKind'
	category:'LLVM-S-Core'
!

!LLVMType class methodsFor:'documentation'!

copyright
"
    Copyright (C) 2015-now Jan Vrany

    This code is not an open-source (yet). You may use this code
    for your own experiments and projects, given that:

    * all modification to the code will be sent to the
      original author for inclusion in future releases
    * this is not used in any commercial software

    This license is provisional and may (will) change in
    a future.
"
! !

!LLVMType class methodsFor:'types - C'!

char
    ^ self int8

    "Created: / 04-08-2015 / 19:32:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

wchar
    ^ self int16

    "Created: / 04-08-2015 / 19:32:13 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'types - functions'!

function: argumentTypes returning: returnType
    ^ self function: argumentTypes varargs: false returning: returnType

    "Created: / 07-07-2015 / 21:53:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 04-08-2015 / 19:44:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

function: argumentTypes varargs: varargs returning: returnType
    ^ LLVM FunctionType: returnType  _: argumentTypes asLLVMObjectArray _: argumentTypes size _: varargs

    "Created: / 04-08-2015 / 19:27:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'types - integers'!

int1
    Int1 isNil ifTrue:[  
        Int1 := LLVM Int1Type
    ].
    ^ Int1

    "Created: / 07-07-2015 / 21:21:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-08-2015 / 04:23:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int16
    ^ LLVM Int16Type

    "Created: / 07-07-2015 / 21:21:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int32
    ^ LLVM Int32Type

    "Created: / 07-07-2015 / 21:21:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int64
    ^ LLVM Int64Type

    "Created: / 07-07-2015 / 21:21:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int8
    ^ LLVM Int8Type

    "Created: / 07-07-2015 / 21:21:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

intptr
    IntPtr isNil ifTrue:[
        IntPtr := LLVM IntPtrType: LLVMTargetData new.  
    ].
    ^ IntPtr

    "Created: / 11-07-2015 / 07:05:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'accessing'!

kind
    ^ LLVM GetTypeKind: self

    "Created: / 07-07-2015 / 21:59:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'comparing'!

= anotherType
    ^ anotherType isLLVMType and:[ self address == anotherType address ]

    "Created: / 08-08-2015 / 02:56:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

hash
    ^ self address

    "Created: / 08-08-2015 / 02:50:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'converting'!

pointer
    "Return a pointer to the type represented by the receiver.
     `LLVMType int32 pointer` returns int32_t*"

    ^ LLVM PointerType: self  _: "AddressSpace"0

    "Created: / 04-08-2015 / 19:31:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'debugging-dumping'!

dumpOn: aStream
    aStream nextPutAll: self dumpString

    "Created: / 10-07-2015 / 14:32:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

dumpString
    | cstr str|

    cstr := LLVM PrintTypeToString: self.
    str := cstr copyCStringFromHeap.
    LLVM DisposeMessage: cstr.
    ^ str

    "Created: / 10-07-2015 / 14:31:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

printOn: aStream
    | kind |

    self class name printOn:aStream.
    aStream nextPut:$(.
    self address printOn:aStream base:16.    
    aStream space.
    aStream nextPutAll: self dumpString.
    "
    aStream nextPutAll: ' ['.
    kind := self kind.
    kind == LLVMVoidTypeKind ifTrue:[ 
        aStream nextPutAll:'void'  
    ] ifFalse:[ kind == LLVMHalfTypeKind ifTrue:[ 
        aStream nextPutAll:'half'  
    ] ifFalse:[ kind == LLVMFloatTypeKind ifTrue:[ 
        aStream nextPutAll:'float'  
    ] ifFalse:[ kind == LLVMDoubleTypeKind ifTrue:[ 
        aStream nextPutAll:'double'  
    ] ifFalse:[ kind == LLVMX86_FP80TypeKind ifTrue:[ 
        aStream nextPutAll:'x86-fp80'  
    ] ifFalse:[ kind == LLVMFP128TypeKind ifTrue:[ 
        aStream nextPutAll:'fp128'  
    ] ifFalse:[ kind == LLVMLabelTypeKind ifTrue:[ 
        aStream nextPutAll:'label'  
    ] ifFalse:[ kind == LLVMIntegerTypeKind ifTrue:[ 
        aStream nextPutAll:'int'  
    ] ifFalse:[ kind == LLVMFunctionTypeKind ifTrue:[ 
        aStream nextPutAll:'funct'  
    ] ifFalse:[ kind == LLVMStructTypeKind ifTrue:[ 
        aStream nextPutAll:'struct'  
    ] ifFalse:[ kind == LLVMArrayTypeKind ifTrue:[ 
        aStream nextPutAll:'array'  
    ] ifFalse:[ kind == LLVMPointerTypeKind ifTrue:[ 
        aStream nextPutAll:'ptr'  
    ] ifFalse:[ kind == LLVMVectorTypeKind ifTrue:[ 
        aStream nextPutAll:'vector'  
    ] ifFalse:[ kind == LLVMMetadataTypeKind ifTrue:[ 
        aStream nextPutAll:'md'  
    ] ifFalse:[ kind == LLVMX86_MMXTypeKind ifTrue:[ 
        aStream nextPutAll:'x86-mmx'  
    ]]]]]]]]]]]]]]].
    aStream nextPutAll: ']'.
    "
    aStream nextPut:$).

    "Created: / 11-07-2015 / 07:08:09 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 08-08-2015 / 04:21:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'testing'!

isIntegerType
    ^ self kind == LLVMIntegerTypeKind

    "Created: / 11-07-2015 / 14:56:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isLLVMType
    "Return true, if receiver represents an LLVM type"

    ^ true

    "Created: / 08-08-2015 / 02:46:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isVectorType
    ^ self kind == LLVMVectorTypeKind

    "Created: / 11-07-2015 / 14:56:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'documentation'!

version_HG

    ^ '$Changeset: <not expanded> $'
! !