CompiledCodeObject.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 15 Jun 2016 23:46:29 +0100
changeset 23 d2d9a2d4d6bf
parent 19 51a3540a2a10
child 24 5aace704e3c8
permissions -rw-r--r--
Added README, licenses and copyright notices.

"
Copyright (c) 2015-now Jan Vrany <jan.vrany@fit.cvut.cz>

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the 'Software'), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.  IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.
"
"{ Package: 'jv:dragonfly' }"

"{ NameSpace: Smalltalk }"

ExternalAddress subclass:#CompiledCodeObject
	instanceVariableNames:'compiledCode sections'
	classVariableNames:''
	poolDictionaries:''
	category:'System-Compiler-Interface'
!

!CompiledCodeObject primitiveDefinitions!
%{

/*
 * includes, defines, structure definitions
 * and typedefs come here.
 */
#include "../librun/mcompiler.h"

%}
! !

!CompiledCodeObject class methodsFor:'documentation'!

copyright
"
Copyright (c) 2015-now Jan Vrany <jan.vrany@fit.cvut.cz>

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the 'Software'), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.  IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.
"
! !

!CompiledCodeObject class methodsFor:'instance creation'!

forCompiledCode: aCompiledCode
    "Given a method or block, return coresponding code object for it. 
     If the method or block is not yet dynamically compiled, throw an exception. 

     If you want to create a new compiled code object for given method or block, 
     use forCompiledCode:text:literals:ilcs:. For details, see comment there."

    | instance |

    instance := self new.
%{
    stx_compiled_code_object code_object;
    code_object = stxCompiledCodeObjectForCompiledCode(aCompiledCode);
    if (code_object == NULL) {
        instance = nil;
    } else {
        __externalAddressVal(instance) = code_object;
    }
%}.
    instance isNil ifTrue:[ 
        self error: 'No code object associated with given method. Method not yet compiled?'
    ].
    instance setCompiledCode: aCompiledCode.
    ^ instance.

    "Created: / 07-12-2015 / 10:58:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 11-01-2016 / 09:39:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified (comment): / 11-01-2016 / 16:26:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

forCompiledCode: compiledCode text: textSize"in bytes" literals: numLits ilcs: numILCs
    "Given a method or block, allocate a *new* code object for it. The text size
     passed may be 0 and could be allocated later using #allocateTextSection:.

     If the method or block is already compiled, i.e., it has a compiled code object
     associated with it, throw an error.

     If you want to create compiled code object for already compiled code,
     use forCompiledCode:.
    "

    | instance failureReason |

    instance := self new.
    failureReason := nil.
%{    
    stx_compiled_code_object code_object;
    INT _textSize;
    INT _numLits;
    INT _numILCs;

    if (!( __isSmallInteger( textSize ) && ( _textSize = __intVal( textSize ), (_textSize >= 0) && (_textSize <= UINT32_MAX) ) ) ) {
        failureReason = @symbol(BadArg2);
        goto done;
    }

    if (!( __isSmallInteger( numLits ) && ( _numLits = __intVal( numLits ), (_numLits >= 0) && (_numLits <= UINT16_MAX) ) ) ) {       
        failureReason = @symbol(BadArg3);
        goto done;
    }

    if (!( __isSmallInteger( numILCs ) && ( _numILCs = __intVal( numILCs ), (_numILCs >= 0) && (_numILCs <= UINT16_MAX) ) ) ) {       
        failureReason = @symbol(BadArg4);
        goto done;
    }
    code_object = stxCompiledCodeObjectForCompiledCode(compiledCode);
    if (code_object != NULL) {
        instance = nil;
        failureReason = @symbol(BadArg1);
    } else {
        code_object = stxCompiledCodeObjectAlloc(compiledCode, _textSize, _numLits, _numILCs);
        __externalAddressVal(instance) = code_object;
    }
    done:;
%}.
    failureReason == #BadArg1 ifTrue:[ 
        self error: 'Bad Argument "compiledCode": not a compiled code or already associated'.
        ^ nil
    ].
    failureReason == #BadArg2 ifTrue:[ 
        self error: 'Bad Argument "textSize": not a SmallInteger or out of range'.
        ^ nil
    ].
    failureReason == #BadArg2 ifTrue:[ 
        self error: 'Bad Argument "numLits": not a SmallInteger or out of range'.
        ^ nil
    ].
    failureReason == #BadArg2 ifTrue:[ 
        self error: 'Bad Argument "numILCs": not a SmallInteger or out of range'.
        ^ nil
    ].
    instance setCompiledCode: compiledCode.
    ^ instance

    "Created: / 11-01-2016 / 16:42:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 11-01-2016 / 21:17:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject methodsFor:'accessing'!

compiledCode
    "Return method or block associated with this code object."

    | compiledCodeFromObject |

    compiledCodeFromObject := compiledCode.
%{
    if (__ExecutableCodeInstPtr(__INST(compiledCode))->ex_code != NULL) {
        if ( (INT)(__ExecutableCodeInstPtr(__INST(compiledCode))->ex_flags) & __MASKSMALLINT(F_DYNAMIC)  ) {
            stx_compiled_code_object code_object = (stx_compiled_code_object)(__externalAddressVal(self));
            if (code_object != NULL) {
                compiledCodeFromObject = stxCompiledCodeObjectGetCompiledCode(code_object);
            }
        }
    }
%}.
    self assert: compiledCode == compiledCodeFromObject
         description: 'compiled code mismatch'.
    ^ compiledCode.

    "Created: / 11-01-2016 / 09:31:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sectionNamed: aString
    ^ self sectionNamed: aString ifAbsent:[ self error: 'No section named "', aString , '"' ]

    "Created: / 19-01-2016 / 21:28:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 24-01-2016 / 20:51:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sectionNamed: aString ifAbsent: aBlock
    ^ self sections detect:[:section | section name = aString ] ifNone: aBlock

    "Created: / 24-01-2016 / 20:51:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

sections
    | numSections |

    numSections := self numSections.
    (sections isNil or:[ sections size ~= numSections ]) ifTrue:[ 
        sections := (1 to: numSections) collect:[ :i | self getSection: i ].
    ].
    ^ sections

    "Created: / 07-12-2015 / 17:09:02 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

text
    "Return text (code) section"

    ^ self sections detect:[:section | section isTextSection ] ifNone:[ nil ].

    "Created: / 11-01-2016 / 21:14:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject methodsFor:'allocation'!

allocateDataSection: dataSize named: dataName
    "Alocates new data section for the receiver."

    | failureReason |

    failureReason := nil.
%{    
    stx_compiled_code_object code_object;
    INT _dataSize;

    if (!( __isSmallInteger( dataSize ) && ( _dataSize = __intVal( dataSize ), (_dataSize >= 0) && (_dataSize <= UINT32_MAX) ) ) ) {
        failureReason = @symbol(BadArg1);
        goto done;
    }
    if (! (__isString( dataName ))) {
        failureReason = @symbol(BadArg2);
        goto done;    
    }
    code_object = (stx_compiled_code_object)(__externalAddressVal(self));
    if (code_object == NULL) {        
        failureReason = @symbol(BadSelf);
    } else {
        stxCompiledCodeObjectAllocDataSection(code_object, _dataSize, __stringVal( dataName ));
        RETURN ( self );
    }
    done:;
%}.
    self primitiveFailed: failureReason


!

allocateTextSection: textSize
    "Alocates new text section for the receiver. Throw an error if there's
     already a text section allocated for this object."

    | failureReason |

    failureReason := nil.
%{    
    stx_compiled_code_object code_object;
    INT _textSize;

    if (!( __isSmallInteger( textSize ) && ( _textSize = __intVal( textSize ), (_textSize >= 0) && (_textSize <= UINT32_MAX) ) ) ) {
        failureReason = @symbol(BadArg1);
        goto done;
    }
    code_object = (stx_compiled_code_object)(__externalAddressVal(self));
    if (code_object == NULL) {        
        failureReason = @symbol(BadSelf);
    } else {
        /* Check whether a text section has been allocated already */
        uint32_t nSections = stxCompiledCodeObjectGetSectionCount(code_object);
        uint32_t i;
        for (i = 0; i < nSections; i++) {
            stx_compiled_code_object_section code_section;
            code_section = stxCompiledCodeObjectGetSection ( code_object , i);
            if (code_section->section_format == SectionFormatText) {
            	failureReason = @symbol(TextAlreadyAllocayed);
            	goto done;
            }            
        }
        stxCompiledCodeObjectAllocTextSection(code_object, _textSize, CODE_OBJECT_SECTION_TEXT_NAME);
        RETURN ( self );
    }
    done:;
%}.
    self primitiveFailed: failureReason


    "Created: / 11-01-2016 / 20:18:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject methodsFor:'initialization'!

setCompiledCode: aCompiledCode
    compiledCode := aCompiledCode

    "Created: / 11-01-2016 / 09:50:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject methodsFor:'inspecting'!

inspector2TabText
    <inspector2Tab>   

    self sections do:[:section | 
        section format == SectionFormatText ifTrue:[ 
            | tab |

            tab := section inspector2TabAssembly.
            tab notNil ifTrue:[
                tab label: '.text'.
                ^ tab.
            ].                    
        ].
    ].
    ^ nil

    "Created: / 11-12-2015 / 12:04:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 21-04-2016 / 15:39:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject methodsFor:'private'!

getSection: index
    | section name size format |

    section := CompiledCodeObjectSection basicNew.
%{
    if (__isSmallInteger(index)) {
        stx_compiled_code_object code_object = (stx_compiled_code_object)(__externalAddressVal(self));
        stx_compiled_code_object_section code_section;

        code_section = stxCompiledCodeObjectGetSection ( code_object , __intVal( index ) - 1 );
        if (code_section) {
            __externalAddressVal(section) = (OBJ)code_section->section_addr;
            size = __MKSMALLINT ( code_section->section_size );                     
            format = __MKSMALLINT ( code_section->section_format );
            name = __MKSTRING ( code_section->section_name );
        }
    }
%}.
    (name notNil and:[ size notNil and:[ format notNil]]) ifTrue:[ 
        section setObject: self name: name size: size format: format.
        ^ section
    ].
    self primitiveFailed.

    "Created: / 07-12-2015 / 17:15:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
    "Modified: / 11-12-2015 / 10:06:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

numSections
    "Return the number of sections of this code object"

%{
    stx_compiled_code_object code_object = (stx_compiled_code_object)(__externalAddressVal(self));
    RETURN ( __MKSMALLINT( stxCompiledCodeObjectGetSectionCount ( code_object ) ) );
%}.
    self primitiveFailed.

    "Created: / 07-12-2015 / 16:36:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject methodsFor:'queries'!

hasSectionNamed: aString
    self sectionNamed: aString ifAbsent: [ ^ false ].
    ^ true

    "Created: / 24-01-2016 / 20:53:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!CompiledCodeObject class methodsFor:'documentation'!

version_HG

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