src/JavaFinalizationRegistry.st
author vranyj1
Sat, 28 Jul 2012 01:51:28 +0000
branchjk_new_structure
changeset 1564 48e14e6b3eab
parent 1563 20048accea65
child 1565 09ba1af5dcf6
permissions -rw-r--r--
- JavaFinalizationRegistry changed: #allObjectsIncludingContextsDo: #finalizeNow - JavaVM comment/format in: #_FileDescriptor_initSystemFD: changed: #_java_io_FileInputStream_available: #anyStream_close: #validateFile: #validateFileNo:

"
 COPYRIGHT (c) 1996-2011 by Claus Gittinger

 New code and modifications done at SWING Research Group [1]:

 COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
                            SWING Research Group, Czech Technical University in Prague

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.

 [1] Code written at SWING Research Group contains a signature
     of one of the above copright owners. For exact set of such code,
     see the differences between this version and version stx:libjava
     as of 1.9.2010
"
"{ Package: 'stx:libjava' }"

Object subclass:#JavaFinalizationRegistry
	instanceVariableNames:'accessLock referees refereesTally new newTally
		finalizationSemaphore finalizationProcess'
	classVariableNames:''
	poolDictionaries:''
	category:'Languages-Java-Support'
!

!JavaFinalizationRegistry class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1996-2011 by Claus Gittinger

 New code and modifications done at SWING Research Group [1]:

 COPYRIGHT (c) 2010-2011 by Jan Vrany, Jan Kurs and Marcel Hlopko
                            SWING Research Group, Czech Technical University in Prague

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.

 [1] Code written at SWING Research Group contains a signature
     of one of the above copright owners. For exact set of such code,
     see the differences between this version and version stx:libjava
     as of 1.9.2010

"
!

documentation
"
    A tricky class that implements Java-style finalization.
    Future versions may involve some C / VM optimization,
    if this algorithm prooves usefull

    [author:]
        Jan Vrany <jan.vrany@fit.cvut.cz>

    [instance variables:]

    [class variables:]

    [see also:]

"
! !

!JavaFinalizationRegistry class methodsFor:'instance creation'!

new
    "return an initialized instance"

    ^ self basicNew initialize.
! !

!JavaFinalizationRegistry methodsFor:'finalization'!

finalizationCycle

    | references living firstPendingReference lastPendingReference ref finished|

    references := Array new: refereesTally.
    living := Array new: refereesTally.
    firstPendingReference := nil.
    finished := self allObjectsIncludingContextsDo:[:o|
        | index |
        (o ~~ referees) ifTrue:[
            (index := self references: o anyOf: referees tally: refereesTally) ~~ 0 ifTrue:[
                o class name == #'java/lang/ref/Finalizer' ifTrue:[
                    self assert: (self getNextOf: o) isNil.
                    references at: index put: o                
                ] ifFalse:[
                    living at: index put: o.
                ]
            ].
        ].
    ].
    finished ifFalse:[ ^ self ].
    living withIndexDo:[:each :index|
        each isNil ifTrue:[
            ref := references at: index.    
            self unregisterAt: index.
            ref notNil ifTrue:[
                firstPendingReference isNil ifTrue:[
                    firstPendingReference := lastPendingReference := ref
                ] ifFalse:[
                    self setNextOf: lastPendingReference to: ref.
                    lastPendingReference := ref.
                ].
                self setNextOf: lastPendingReference to: lastPendingReference
            ] ifFalse:[
                Logger log: 'background finalizer: referee registered but reference gone' severity: #error facility: #JVM
            ]
        ].
    ].
    accessLock critical:[
        "Copy new to referees, this somewhat delays finalization"
        refereesTally + newTally > referees size ifTrue:[
            referees := self grow: referees min: refereesTally + newTally.
        ].
        referees replaceFrom: refereesTally + 1 to: refereesTally + newTally with: new startingAt: 1.
        new from: 1 to: newTally put: nil.
        refereesTally := refereesTally + newTally.
        newTally := 0.
    ].

    self informReferenceHandler: firstPendingReference

    "Created: / 24-07-2012 / 15:14:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

finalizationLoop

    [ 
        finalizationSemaphore waitWithTimeoutMs: 10000"10sec".
        self finalizationCycle    
    ] loop

    "Created: / 24-07-2012 / 15:16:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaFinalizationRegistry methodsFor:'initialization'!

initialize
    "Invoked when a new instance is created."

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

    referees := Array new: 200.
    refereesTally := 0.
    new := Array new: 200.
    newTally := 0.
    accessLock := RecursionLock new.
    "/ super initialize.   -- commented since inherited method does nothing

    "Modified: / 28-07-2012 / 01:32:34 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaFinalizationRegistry methodsFor:'private'!

allObjectsIncludingContextsDo:aBlock

    | wasBlocked |

    wasBlocked := OperatingSystem blockInterrupts.

    (ObjectMemory allObjectsDo:aBlock) ifFalse:[ 
        wasBlocked ifTrue:[
            OperatingSystem unblockInterrupts.
        ].
        ^false
    ].
    ProcessorScheduler knownProcesses do:[:p |
        |con|

        con := p suspendedContext.
        [con notNil] whileTrue:[
            aBlock value:con.
            con := con sender.
        ].
    ].
    wasBlocked ifTrue:[
        OperatingSystem unblockInterrupts.
    ].

    ^ true

    "Created: / 28-07-2012 / 02:14:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

getNextOf: reference

    ^reference instVarAt: 3

    "Created: / 24-07-2012 / 11:22:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

grow: array
    ^self grow: array min: 30

    "Created: / 28-07-2012 / 01:14:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

grow: array min: min
    | grown |

    grown := Array new: ((array size * 2) max: min).
    grown replaceFrom: 1 with: array.
    ^grown

    "Created: / 28-07-2012 / 01:27:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

informReferenceHandler: reference
    | referenceClass lock |

    reference isNil ifTrue:[ ^ self ].

    referenceClass := Java classForName: 'java.lang.ref.Reference'.
    lock := JavaVM monitorFor: (referenceClass instVarNamed: #lock).


    lock enter.
    [
        referenceClass instVarNamed: #pending put: reference.
        lock notify.
    ] ensure:[
        lock exit.
    ].

    "Created: / 24-07-2012 / 03:42:37 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

references: object anyOf: aCollection tally: tally
    "If object references any object in a collection, return
     index of value which it references, zero otherwise"

%{
    OBJ cls, flags;
    int nInsts, inst;
    if (! __isNonNilObject(object)) {
        RETURN (__MKINT(0));
    }

    if (__isArrayLike(aCollection)) {
        int sz = __arraySize(aCollection);
        int tl = __intVal(tally);
        int nObjs = sz < tl ? sz : tl;
        char *minAddr = 0, *maxAddr = 0;

        if (nObjs == 0) {
            RETURN (__MKINT(0));
        }

        /*
         * a little optimization: use the fact that all old objects
         * refering to a new object are on the remSet; if I am not,
         * a trivial reject is possible, if all objects are newbees.
         * as a side effect, gather min/max addresses
         */
        if ((__qSpace(object) <= OLDSPACE) && !__isRemembered(object)) {
            int allNewBees = 1;
            int i;

            minAddr = (char *)(__ArrayInstPtr(aCollection)->a_element[0]);
            maxAddr = minAddr;

            for (i=0; i<nObjs; i++) {
                OBJ anObject;

                anObject = __ArrayInstPtr(aCollection)->a_element[i];

                if (__isNonNilObject(anObject)) {
                    int spc;

                    if (((spc = __qSpace(anObject)) != NEWSPACE) && (spc != SURVSPACE)) {
                        allNewBees = 0;
                    }
                }

                if ((char *)anObject < minAddr) {
                    minAddr = (char *)anObject;
                } else if ((char *)anObject > maxAddr) {
                    maxAddr = (char *)anObject;
                }
            }
            if (allNewBees) {
                RETURN (__MKINT(0));
            }
        }

        /*
         * fetch min/max in searchList (if not already done)
         */
        if (minAddr == 0) {
            int i;

            for (i=0; i<nObjs; i++) {
                OBJ anObject;

                anObject = __ArrayInstPtr(aCollection)->a_element[i];
                if ((char *)anObject < minAddr) {
                    minAddr = (char *)anObject;
                } else if ((char *)anObject > maxAddr) {
                    maxAddr = (char *)anObject;
                }
            }
        }

        cls = __qClass(object);
        flags = __ClassInstPtr(cls)->c_flags;
        if (((INT)flags & __MASKSMALLINT(ARRAYMASK)) == __MASKSMALLINT(POINTERARRAY)) {
            nInsts = __BYTES2OBJS__(__qSize(object) - OHDR_SIZE);
        } else {
            nInsts = __intVal(__ClassInstPtr(cls)->c_ninstvars);
        }
        if (! nInsts) {
            RETURN (__MKINT(0));
        }

        if (nObjs == 1) {
            /* better reverse the loop */
            OBJ anObject;

            anObject = __ArrayInstPtr(aCollection)->a_element[0];
#if defined(memsrch4)
            if (memsrch4(__InstPtr(object)->i_instvars, (INT)anObject, nInsts)) {
                RETURN (__MKINT(1));
            }
#else
            for (inst=0; inst<nInsts; inst++) {
                if ((__InstPtr(object)->i_instvars[inst]) == anObject) {
                    RETURN (__MKINT(1));
                }
            }
#endif
            RETURN ( __MKINT( 0 ) );
        }

        for (inst=0; inst<nInsts; inst++) {
            OBJ instVar = __InstPtr(object)->i_instvars[inst];
            int i;

            if (((char *)instVar >= minAddr) && ((char *)instVar <= maxAddr)) {
                for (i=0; i<nObjs; i++) {
                    OBJ anObject;

                    anObject = __ArrayInstPtr(aCollection)->a_element[i];
                    if (instVar == anObject) {
                        RETURN (__MKINT(i+1));
                    }
                }
            }
        }
        RETURN (__MKINT(0));
    }
%}.

    1 to: (aCollection size min: tally) do:[:eachi| | each |
        each := aCollection at: eachi.
        (object references: each) ifTrue:[^eachi].
    ].
    ^0

    "Created: / 28-07-2012 / 01:18:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

setNextOf: reference to: value

    ^reference instVarAt: 3 put: value

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

!JavaFinalizationRegistry methodsFor:'registering objects'!

register: object
    "Register an object for being finalized"

    | index finalizedClass |

    accessLock critical:[
        newTally = new size ifTrue:[
            new := self grow: new
        ].
        index := newTally := newTally + 1.
        new at: index put: object.
        finalizedClass := Java classForName:'java.lang.ref.Finalizer'.
        finalizedClass classInit.
        (finalizedClass methodDictionary at: #'register(Ljava/lang/Object;)V')
            valueWithReceiver: finalizedClass arguments: (Array with: object).
    ].

    "Created: / 24-07-2012 / 01:14:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

registerChange: anObject
    "/Nothing to do, to be polymprph with Registry"

    "Created: / 24-07-2012 / 03:31:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

unregisterAt: index
    "Unregister an object at index from being finalized"

    refereesTally < index ifTrue:[
        referees at: index put: (referees at: refereesTally).
    ].
    referees at: refereesTally put: nil.
    refereesTally := refereesTally - 1.

    "Created: / 28-07-2012 / 01:24:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaFinalizationRegistry methodsFor:'start & stop'!

startFinalizationProcessAt:aPriority

    |p|

    finalizationProcess notNil ifTrue:[
        finalizationProcess priority:aPriority.
        ^ self
    ].

    finalizationSemaphore := Semaphore new name:'FinalizationSemaphore (Java)'.

    p :=
        [
            [
                self finalizationLoop
            ] ifCurtailed:[
                finalizationProcess := nil.
                finalizationSemaphore := nil
            ]
        ] newProcess.
    p name:'background finalizer (Java)'.
    p priority:aPriority.
    p restartable:true.
    p beSystemProcess.
    p resume.
    finalizationProcess := p

    "Created: / 24-07-2012 / 15:25:06 / Jan Vrany <jan.vrany@fit.cvut.cz>"
!

stopFinalizationProcess
    "stop the background finalizer"

    finalizationProcess notNil ifTrue:[
        finalizationProcess terminate.
        finalizationProcess := nil
    ].

    "Created: / 24-07-2012 / 15:26:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaFinalizationRegistry methodsFor:'utilities'!

finalizeNow
    "Force finalization to run now"
    finalizationSemaphore signal.
    finalizationSemaphore signal.

    "Created: / 24-07-2012 / 15:28:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
! !

!JavaFinalizationRegistry class methodsFor:'documentation'!

version_SVN
    ^ '$Id::                                                                                                                        $'
! !