LLVMType.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 27 Jan 2016 14:20:58 +0000
changeset 54 a288aced3dd1
parent 53 bbf3a88e2358
child 59 e6ff053f430c
permissions -rw-r--r--
LLVM C API Extensions: Fixed DIBuilerCreateFunction() and DIBuilderCreateSubroutineType() for LLVM 3.9 In LLVM 3.9 some parameters to these functions were dropped. The DIBuilder interface has been changed to reflect these changes (i.e., C functions no longer require dropped argument). The LLVM C Extensions library can still be compiled against LLVM 3.8 (via #ifdef), but the API will be different. Also, the Smalltallks bindings will make use of LLVM 3.9 interface. That said, LLVM C API Extensions library may still be used by *other* projects on top of LLVM 3.8, though Smalltalk bindings require LLVM 3.9 from now on.

"
    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 Int8 Int16 Int32 Int64 IntPtr Void Half Float Double X86FP80
		FP128 PPCFP128 X86MMX KindToClassMapping'
	poolDictionaries:'LLVMTypeKind'
	category:'LLVM-S-Core-Types'
!

!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:'initialization'!

initialize
    "Invoked at system start or when the class is dynamically loaded."

    LLVMTypeKind initialize.
    KindToClassMapping := Dictionary withKeysAndValues: {
        LLVMHalfTypeKind .      LLVMTypeHalt .
        LLVMFloatTypeKind .     LLVMTypeFloat .
        LLVMDoubleTypeKind .    LLVMTypeDouble .
        LLVMX86_FP80TypeKind .  LLVMTypeX86_FP80 .
        LLVMFP128TypeKind .     LLVMTypeFP128.
        LLVMPPC_FP128TypeKind . LLVMTypePPC_FP128 .
        LLVMIntegerTypeKind .   LLVMTypeInteger .
        LLVMVectorTypeKind .    LLVMTypeVector .
        LLVMArrayTypeKind .     LLVMTypeArray .
        LLVMStructTypeKind .    LLVMTypeStruct .
        LLVMPointerTypeKind .   LLVMTypePointer .
        LLVMFunctionTypeKind .  LLVMTypeFunction .
        LLVMMetadataTypeKind .  LLVMTypeMetadata .
        LLVMVoidTypeKind .      LLVMTypeVoid .
        LLVMLabelTypeKind .     LLVMTypeLabel .
        LLVMX86_MMXTypeKind .   LLVMTypeX86_MMX .
    }

    "Modified: / 13-08-2015 / 17:00:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'instance creation'!

newAddress:addr
    ^ (super newAddress: addr)
        initialize;
        yourself

    "Created: / 13-08-2015 / 17:14:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'queries'!

isAbstract
    "Return if this class is an abstract class.
     True is returned here for myself only; false for subclasses.
     Abstract subclasses must redefine again."

    ^ self == LLVMType.
! !

!LLVMType class methodsFor:'types - C'!

char
    ^ self int8

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

void
    Void isNil ifTrue:[ Void := LLVM VoidType ].
    ^ Void

    "Created: / 13-08-2015 / 17:20:05 / 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 - floating points'!

double
    Double isNil ifTrue:[ Double := LLVM DoubleType ].
    ^ Double

    "Created: / 13-08-2015 / 17:24:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

float
    Float isNil ifTrue:[ Float := LLVM FloatType ].
    ^ Float

    "Created: / 13-08-2015 / 17:24:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

fp128
    FP128 isNil ifTrue:[ FP128 := LLVM FP128Type ].
    ^ FP128

    "Created: / 13-08-2015 / 17:26:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

half
    Half isNil ifTrue:[ Half := LLVM HalfType ].
    ^ Half

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

ppcfp128
    PPCFP128 isNil ifTrue:[ PPCFP128 := LLVM PPCFP128Type ].
    ^ PPCFP128

    "Created: / 13-08-2015 / 17:26:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

x86fp80
    X86FP80 isNil ifTrue:[ X86FP80 := LLVM X86FP80Type ].
    ^ X86FP80

    "Created: / 13-08-2015 / 17:25:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

x86mmx
    X86MMX isNil ifTrue:[ X86MMX := LLVM X86MMXType ].
    ^ X86MMX

    "Created: / 13-08-2015 / 17:26:48 / 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>"
    "Modified (format): / 13-08-2015 / 17:21:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int16
    Int16 isNil ifTrue:[ Int16 := LLVM Int16Type ].
    ^ Int16

    "Created: / 07-07-2015 / 21:21:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2015 / 18:48:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int32
    Int32 isNil ifTrue:[ Int32 := LLVM Int32Type ].
    ^ Int32

    "Created: / 07-07-2015 / 21:21:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2015 / 17:22:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int64
    Int64 isNil ifTrue:[ Int64 := LLVM Int64Type ].
    ^ Int64

    "Created: / 07-07-2015 / 21:21:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2015 / 17:22:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

int8
    Int8 isNil ifTrue:[ Int8 := LLVM Int8Type ].
    ^ Int8

    "Created: / 07-07-2015 / 21:21:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2015 / 18:47:13 / 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>"
    "Modified (format): / 13-08-2015 / 17:22:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'types - structures'!

named: aString
    "Create an (opaque) named structure with no members (elements).
     Use LLVMStructType>>elementTypes: to set members.

     This method comes handy when one needs to create
     a recursive type, such as an element of linked list:

     | listElemTy |

     listElemTy := LLVMType named: 'listElemTy'.
     listElemTy elementTypes: { LLVMType int32 . listElemTy pointer }.
     listElemTy

    "

    self assertIsString: aString.  
    ^ LLVM StructCreateNamed: LLVM GetGlobalContext _: aString.

    "Created: / 12-10-2015 / 14:55:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

struct: memberTypes 
    ^ self struct: memberTypes packed: false

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

struct: memberTypes packed: packed

    self assert: memberTypes isSequenceable message: '`memberTypes` parameter is not an array of types'.
    self assert: (memberTypes allSatisfy:[:e|e isLLVMType]) message: 'element of a `memberTypes` parameter is not an LLVM type'.
    self assert: packed isBoolean message: '`packed` parameter is not a boolean'.

    ^ LLVM StructType: memberTypes asLLVMObjectArray  _: memberTypes size _: packed

    "Created: / 13-08-2015 / 19:15:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 05-10-2015 / 13:57:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'accessing'!

alignmentInBits
    "Return an alignment of the type in bits"

    ^ self alignmentInBytes * 8

    "Created: / 14-08-2015 / 09:16:54 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

alignmentInBytes
    "Return an alignment of the type in bytes"

    | alignmentAsValue |

    alignmentAsValue := LLVM AlignOf: self.
    self assert: alignmentAsValue isConstant.
    self assert: alignmentAsValue type isIntegerType.
    ^ LLVMCEXT ValueAsUInt64: alignmentAsValue.

    "Created: / 14-08-2015 / 09:16:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 17-09-2015 / 19:25:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

kind
    ^ LLVM GetTypeKind: self

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

sizeInBits
    "For integer, pointer, FP  types, return the size in bits. For all 
     other types, throw an LLVMTypeError.

     LLVMType int32 sizeInBits -> 32
     LLVMType int1 sizeInBits  -> 1
    "
    LLVMTypeError new signal: 'type size not known'

    "Created: / 13-08-2015 / 16:25:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sizeInBytes
    "For integer, pointer, FP  types, return the size in bytes (rounded up). For all 
     other types, throw an LLVMTypeError.

     LLVMType int32 sizeInBytes -> 4
     LLVMType int1 sizeInBytes  -> 1
    "
    ^ (self sizeInBits // 8) + (self sizeInBits \\ 8)

    "Created: / 14-08-2015 / 07:27:06 / 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'!

array: numberOfElements
    "Create a fixed-size array whose elements are of type of receiver
     `LLVMType int8 array: 13` returns `[ 13 x i8 ]`"

    self assertIsIntegerUnsigned: numberOfElements.  
    ^ LLVM ArrayType: self _:  numberOfElements

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

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>"
!

vector: numberOfElements
    "Create a fixed-size vector whose elements are of type of receiver."

   self shouldNotImplement

    "Created: / 12-10-2015 / 18:27:55 / 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:'initialization'!

initialize
    self class == LLVMType ifTrue:[
        self changeClassTo: (KindToClassMapping at: self kind)
    ].

    "Created: / 13-08-2015 / 16:53:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2015 / 18:43:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType methodsFor:'testing'!

isArrayType
    ^ false

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

isDoubleType
    ^ false

    "Created: / 13-08-2015 / 16:14:36 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isFP128Type
    ^ false

    "Created: / 13-08-2015 / 16:15:28 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isFloatType
    ^ false

    "Created: / 13-08-2015 / 16:14:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isFunctionType
    ^ false

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

isHalfType
    ^ false

    "Created: / 13-08-2015 / 16:14:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isIntegerType
    ^ false

    "Created: / 11-07-2015 / 14:56:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 13-08-2015 / 16:49:40 / 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>"
!

isLabelType
    ^ false

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

isMetadataType
    ^ false

    "Created: / 13-08-2015 / 16:20:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isPPC_FP128Type
    ^ false

    "Created: / 13-08-2015 / 16:15:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isPointerType
    ^ false

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

isStructType
    ^ false

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

isVectorType
    ^ false

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

isVoidType
    ^false

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

isX86_FP80Type
    ^ false

    "Created: / 13-08-2015 / 16:14:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

isX86_MMXType
    ^ false

    "Created: / 13-08-2015 / 16:20:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!LLVMType class methodsFor:'documentation'!

version_HG

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


LLVMType initialize!