Continuation.st
author Jan Vrany <jan.vrany@labware.com>
Wed, 22 Mar 2023 13:57:18 +0000
branchjv
changeset 25445 1623217d2268
parent 18079 7b5afc0ad3d5
permissions -rw-r--r--
Cherry-picked OrderedCollection.st from 0b286fd51da7: * d4c86d7c0bfc: #TUNING by stefan, Stefan Vogel <sv@exept.de> * 692b6497a669: #DOCUMENTATION by stefan, Stefan Vogel <sv@exept.de> * d47bb2912953: #DOCUMENTATION by stefan, Stefan Vogel <sv@exept.de> * abb4316c6bff: #FEATURE by cg, Claus Gittinger <cg@exept.de> * 3a8fce0e8d11: #TUNING by stefan, Stefan Vogel <sv@exept.de> * 03d29bf8c5bb: #REFACTORING by stefan, Stefan Vogel <sv@exept.de> * cccc6c4abcfc: #REFACTORING by stefan, Stefan Vogel <sv@exept.de> * 35d957c7a840: #FEATURE by cg, Claus Gittinger <cg@exept.de> * 6b11890f5f2c: #OTHER by cg, Claus Gittinger <cg@exept.de> * abb6108fb06b: #FEATURE by cg, Claus Gittinger <cg@exept.de> * 2c4768bb2e89: #FEATURE by cg, Claus Gittinger <cg@exept.de> * 4029e964d0f1: #FEATURE by cg, Claus Gittinger <cg@exept.de> * ddcab3a9c2df: #OTHER by cg, Claus Gittinger <cg@exept.de> * 2213eb56e0c7: #REFACTORING by exept, Claus Gittinger <cg@exept.de> * 09ca874a6160: #REFACTORING by exept, Claus Gittinger <cg@exept.de> * 30b332af1f33: #BUGFIX by stefan, Stefan Vogel <sv@exept.de> * 779764ba117b: #REFACTORING by cg, Claus Gittinger <cg@exept.de> * b3d232a613c9: #BUGFIX by stefan, Stefan Vogel <sv@exept.de> * c417f7edaec1: #BUGFIX by stefan, Stefan Vogel <sv@exept.de> * 904b6538f379: #FEATURE by exept, Claus Gittinger <cg@exept.de> * c5887f03e01f: #REFACTORING by stefan, Stefan Vogel <sv@exept.de> * 8912d03aff48: #BUGFIX by exept, Claus Gittinger <cg@exept.de> * de5cd1dab4c3: #DOCUMENTATION by exept, Claus Gittinger <cg@exept.de> * 9bbd26603378: #OTHER by exept, Claus Gittinger <cg@exept.de> * c2c9dc110f42: #FEATURE by stefan, Stefan Vogel <sv@exept.de> * 81d123c6703d: #DOCUMENTATION by stefan, Stefan Vogel <sv@exept.de> * 8aadbb21458a: #BUGFIX by stefan, Stefan Vogel <sv@exept.de> * f210dbb8b2f6: #TUNING by stefan, Stefan Vogel <sv@exept.de> * c2c774fc53c0: #FEATURE by exept, Claus Gittinger <cg@exept.de> * b6f462670875: #DOCUMENTATION by exept, Claus Gittinger <cg@exept.de> * 27ae4021d5d6: #FEATURE by stefan, Stefan Vogel <sv@exept.de> * 10d9e9d85594: #TUNING by exept, Claus Gittinger <cg@exept.de> * 2653d855dcc7: #DOCUMENTATION by exept, Claus Gittinger <cg@exept.de> * 6ea1698a1a34: #FEATURE by stefan, Stefan Vogel <sv@exept.de> * 28762315e664: #OTHER by exept, Claus Gittinger <cg@exept.de> * 7142ea786f3e: #TUNING by stefan, Stefan Vogel <sv@exept.de> * 7875acb42b53: #BUGFIX by stefan, Stefan Vogel <sv@exept.de> * 163a0eebc97e: #BUGFIX by Maren, matilk

"
 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 comment:'declared from: ..\..\..\stx\libbasic\abbrev.stc'
!

!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 - Unfinished.
    Continuations do not work yet - there is more support needed in the VM.

    [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
    "this is called current-continuation in scheme"

    |cont id|

    cont := self basicNew.
%{
    int __cId;
    extern int __continuationCreate();

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

    "
     self current
    "

    "Modified: / 25-07-2013 / 11:37:27 / cg"
!

currentDo: aBlock
    "this is is called call/cc in scheme"

    ^ aBlock value:self current

    "Modified: / 29-11-2006 / 10:14:03 / cg"
    "Modified (comment): / 25-07-2013 / 11:37:00 / cg"
!

new
    self error:'continuations must be created with #current'

    "Modified: / 29-11-2006 / 10:13:19 / cg"
! !

!Continuation methodsFor:'invocation'!

argumentCount
    "VisualAge/ANSI compatibility"

    ^ 1
!

numArgs
	^ 1
!

value
	self value: nil
!

value: v
    |cID|

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

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

terminate: aContext
    self shouldImplement. 
"/        | 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 methodsFor:'restoration'!

restoreValues
    self shouldImplement. 
"/        | 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 class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/Continuation.st,v 1.16 2013-07-25 09:37:35 cg Exp $'
!

version_SVN
    ^ '$Id: Continuation.st 10761 2012-01-19 11:46:00Z vranyj1 $'
! !