Continuation.st
author ca
Mon, 27 Sep 2004 12:16:12 +0200
changeset 8596 5433434a9bf0
parent 8582 115869898a97
child 8687 d6e6e2c0c27c
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 2004 by eXept Software AG
              All Rights Reserved

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

"{ Package: 'stx:libbasic' }"

Object subclass:#Continuation
	instanceVariableNames:'process id suspendContext'
	classVariableNames:''
	poolDictionaries:''
	category:'Kernel-Processes'
!

!Continuation class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2004 by eXept Software AG
              All Rights Reserved

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

documentation
"
    Initial attempt - Contnuations do not work yet.

    [Instance variables:]

        id                     <SmallInteger>   a unique continuation-id;
                                                Used to identify a corresponding 
                                                data-structure in the VM.

        process                <Process>        the process which created this continuation.

    [Class variables:]

    [see also:]
        Process Context Block

    [author:]
        Claus Gittinger
"
!

supported
    ^ false
! !

!Continuation class methodsFor:'instance creation'!

current
        ^ self new
"/        ^ self fromContext: thisContext sender
!

currentDo: aBlock
        ^ aBlock value:self new

        "/ ^ aBlock value: (self fromContext: thisContext sender)
!

fromContext: aStack
        aStack == thisContext sender ifFalse:[
            self error.
        ].
        ^ self new

"/        ^ self new initializeFromContext: aStack
!

new
    |cont id|

    cont := super new.
%{
    int __cId;
    extern int __continuationCreate();

    __cId = __continuationCreate(cont);
    if (__cId) {
        id = __MKSMALLINT(__cId);
    }
%}.
    id isNil ifTrue:[
        self error:'could not create continuation' mayProceed:true.
        ^ nil.
    ].
    cont setId:id process:(Processor activeProcess).
    ^ cont

    "
     self new
    "
! !

!Continuation methodsFor:'as yet unclassified'!

restoreValues
self halt.
"/        | valueStream context |
"/
"/        valueStream _ values readStream.
"/        [valueStream atEnd] whileFalse:
"/                [context _ valueStream next.
"/                1 to: context class instSize do: [:i | context instVarAt: i put: valueStream next].
"/                1 to: context localSize do: [:i | context localAt: i put: valueStream next]]
! !

!Continuation methodsFor:'invocation'!

numArgs
	^ 1
!

value
	self value: nil
!

value: v
    |cID|

    (cID := id) notNil ifTrue:[
%{
        __continuationResume(__intVal(cID));
%}
    ].
self halt.

"/        self terminate: thisContext.
"/        self restoreValues.
"/        thisContext swapSender: values first.
"/        ^v
!

valueWithArguments: v
	v size == 1 ifFalse: [^self error: 'continuations can only be resumed with one argument'].
	self value: v first
! !

!Continuation methodsFor:'private'!

initializeFromContext: aContext
self halt.
"/        | valueStream context |
"/
"/        valueStream _ WriteStream on: (Array new: 20).
"/        context _ aContext.
"/        [context notNil] whileTrue:
"/                [valueStream nextPut: context.
"/                1 to: context class instSize do: [:i | valueStream nextPut: (context instVarAt: i)].
"/                1 to: context localSize do: [:i | valueStream nextPut: (context localAt: i)].
"/                context _ context sender].
"/        values _ valueStream contents
!

terminate: aContext
self halt.
"/        | context |
"/        context _ aContext.
"/        [context notNil] whileTrue: [context _ context swapSender: nil]
! !

!Continuation methodsFor:'private accessing'!

finalize
    |cId|

    (cId := id) notNil ifTrue:[
        id := nil.
%{
        __continuationDestroy(__intVal(cId));
%}
    ].
!

setId:idArg process:aProcess
    id := idArg.
    process := aProcess.
    self registerForFinalization.
! !

!Continuation class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Continuation.st,v 1.7 2004-09-27 10:16:12 ca Exp $'
! !