c1/DragonFly__C1LLVMTypes.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Thu, 23 Jun 2016 22:26:37 +0100
changeset 29 5693302d4e24
parent 28 4bdee0ee3d83
child 37 ec41dca68283
permissions -rw-r--r--
Initial support for message sends. For now, the C1 compiler uses simple `__SSENDx`s so no need to bother with inline caches. This can (and will) be addressed in a future.

"
    Copyright (C) 2016-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:dragonfly/c1' }"

"{ NameSpace: DragonFly }"

SharedPool subclass:#C1LLVMTypes
	instanceVariableNames:''
	classVariableNames:'TyInstance TyInstanceFields TyInstanceFieldIndexClass
		TyInstanceFieldIndexSize TyInstanceFieldIndexSpace
		TyInstanceFieldIndexFlags TyInstanceFieldIndexAge
		TyInstanceFieldIndexHashLow TyOBJ TyOBJVec TyInlineCache
		TyInlineCacheIndexFunc TyInlineCacheIndexClass
		TyInlineCacheIndexLineNo TyInlineCachePtr TyOBJFUNC TyOBJFUNCs
		TyContextFields TyContextFieldIndexStack TyContexts
		TyContextFieldIndexFlags TyContextFieldIndexSenderS
		TyContextFieldIndexHome TyContextFieldIndexReceiver
		TyContextFieldIndexSelector TyContextFieldIndexSearchClass
		TyContextFieldIndexMethod TyContextFieldIndexLineNr
		TyContextFieldIndexRetvalTemp TyContextFieldIndexHandleS
		TyMKREALCONTEXT5 TySSENDSs'
	poolDictionaries:''
	category:'DragonFly-C1'
!

!C1LLVMTypes class methodsFor:'documentation'!

copyright
"
    Copyright (C) 2016-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.

"
! !

!C1LLVMTypes class methodsFor:'initialization'!

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

    "/ please change as required (and remove this comment)

    TyInstance := LLVMType named: '__instance'.
    TyOBJ := TyInstance pointer.
    TyOBJVec := TyOBJ pointer.
    TyInstanceFields := {
        TyOBJ.                      "/ o_class
        LLVMType int32.             "/ o_size
        LLVMType int8.              "/ o_space
        LLVMType int8.              "/ o_flags
        LLVMType int8.              "/ o_age
        LLVMType int8.              "/ o_hashLow
    }.
    TyInstance elementTypes: TyInstanceFields.

    TyInstanceFieldIndexClass := 0.
    TyInstanceFieldIndexSize := 1.
    TyInstanceFieldIndexSpace := 2.
    TyInstanceFieldIndexFlags := 3.
    TyInstanceFieldIndexAge := 4.
    TyInstanceFieldIndexHashLow := 5.

    TyContextFields := TyInstanceFields , (Context instVarNames collect: [ :nm | nm last == $* ifTrue:[ LLVMType intptr pointer ] ifFalse:[ TyOBJ ] ]).
    TyContextFieldIndexFlags := TyInstanceFields size - 1 + (Context instVarIndexFor: #flags).
    TyContextFieldIndexSenderS  := TyInstanceFields size - 1 + (Context instVarIndexFor: #'sender*').
    TyContextFieldIndexHome  := TyInstanceFields size - 1 + (Context instVarIndexFor: #home).
    TyContextFieldIndexReceiver  := TyInstanceFields size - 1 + (Context instVarIndexFor: #receiver).
    TyContextFieldIndexSelector  := TyInstanceFields size - 1 + (Context instVarIndexFor: #selector).
    TyContextFieldIndexSearchClass  := TyInstanceFields size - 1 + (Context instVarIndexFor: #searchClass).
    TyContextFieldIndexMethod  := TyInstanceFields size - 1 + (Context instVarIndexFor: #method).
    TyContextFieldIndexLineNr  := TyInstanceFields size - 1 + (Context instVarIndexFor: #lineNr).
    TyContextFieldIndexRetvalTemp  := TyInstanceFields size - 1 + (Context instVarIndexFor: #retvalTemp).
    TyContextFieldIndexHandleS := TyInstanceFields size - 1 + (Context instVarIndexFor: #'handle*').
    TyContextFieldIndexStack := TyInstanceFields size + Context instSize.

    TyContexts := #().

    TyInlineCache := LLVMType named: 'inlineCache'.
    TyInlineCachePtr := TyInlineCache pointer.
    TyOBJFUNC := LLVMType function: {
        TyOBJ.                      "/ self
        TyOBJ.                      "/ selector
        TyOBJ.                      "/ searchClass or nil
        TyInlineCachePtr .          "/ pIlc
    } varargs: true returning: TyOBJ.

    TyInlineCache elementTypes: {
        TyOBJFUNC pointer .         "/ ilc_func
        TyOBJ.                      "/ ilc_class
        TyInlineCachePtr .          "/ ilc_link
        TyOBJ .                     "/ ilc_lineNo
        LLVMType char pointer .     "/ ilc_poly
    }.
    TyInlineCacheIndexFunc := 0.
    TyInlineCacheIndexClass := 1.
    TyInlineCacheIndexLineNo := 3.

    TyOBJFUNCs := {
        "/ 0 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
        } returning: TyOBJ .
        "/ 1 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ .
        } returning: TyOBJ .
        "/ 2 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 3 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 4 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 5 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 6 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 7 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 8 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 9 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 10 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 11 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 12 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 13 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 14 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 16 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            TyOBJ.                      "/ searchClass or nil
            TyInlineCachePtr .          "/ pIlc
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
    }.

    TyMKREALCONTEXT5 := LLVMType function: { TyOBJ } returning: TyOBJ.

    TySSENDSs := {
        "/ 0 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
        } returning: TyOBJ .
        "/ 1 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ .
        } returning: TyOBJ .
        "/ 2 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 3 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 4 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 5 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 6 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 7 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 8 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 9 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 10 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 11 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 12 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 13 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 14 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
        "/ 16 args
        LLVMType function: {
            TyOBJ.                      "/ self
            TyOBJ.                      "/ selector
            LLVMType int32.             "/ lineNr
            TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ . TyOBJ .
        } returning: TyOBJ .
    }.

    "Modified: / 23-06-2016 / 22:08:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!C1LLVMTypes class methodsFor:'accessing'!

tyContext: size
    "Return a type for context with given `size`. Size should
     be numArgs + numVars + numTemps"

    | tyContext |

    TyContexts size < (size + 1) ifTrue:[
	| tmp |

	tmp := Array new: size + 1.
	tmp replaceFrom: 1 to: TyContexts size with: TyContexts.
	TyContexts := tmp.
    ].
    tyContext := TyContexts at: size + 1.
    tyContext isNil ifTrue:[
	tyContext := LLVMType named: '__context' , size printString.
	size == 0 ifTrue:[
	    tyContext elementTypes: TyContextFields
	] ifFalse:[
	    tyContext elementTypes: (TyContextFields copyWith: (LLVMType arrayOf: TyOBJ size: size))
	].
	TyContexts at: size + 1 put: tyContext.
    ].
    ^ tyContext

    "
    DragonFly::C1LLVMTypes tyContext: 3
    "

    "Created: / 20-04-2016 / 23:06:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 21-04-2016 / 08:41:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!C1LLVMTypes class methodsFor:'documentation'!

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


C1LLVMTypes initialize!