[Q] On Implementing Continuation...

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
3 messages Options
Reply | Threaded
Open this post in threaded view
|

[Q] On Implementing Continuation...

Chun, Sungjin
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

Hi,

Attached files are for testing continuation in gst. Contuation is my
trial of porting Squeak version of Seaside's Continuation. It seems that
most parts are very easily 1 to 1 matched between gst and squeak but
swapSender: is not. I've just blindly copy squeak's code to create
swapSender: for gst but this does not work.

Can anyone help me on this?

Thanks in advance.
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.2.2 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFF7Mm5QqspS1+XJHgRAhFCAKCphxZGdue6vHxfZg6SLrloVg943QCgxAqg
rNUPGAL23//y/fC52m8IAe0=
=H+KJ
-----END PGP SIGNATURE-----

Smalltalk.Object subclass: #Continuation
    instanceVariableNames: 'values'
    classVariableNames: ''
    poolDictionaries: ''
    category: 'Seaside-Continuations'!

Continuation comment: nil!

!Continuation class methodsFor: 'instance creation'!

current
    ^ self fromContext: thisContext sender
!

currentDo: aBlock
    ^ aBlock value: (self fromContext: thisContext sender)
!

fromContext: aStack
    ^ self new initializeFromContext: aStack
! !


!Continuation methodsFor: 'private'!

initializeFromContext: aContext
    | valueStream context |
    valueStream _ WriteStream on: (Array new: 20).
    context _ aContext.
    [context notNil] whileTrue: [
        valueStream nextPut: aContext.
        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
    | context |
    context _ aContext.
    [context notNil] whileTrue: [context _ context swapSender: nil]
! !


!Continuation methodsFor: 'invocation'!

numArgs
    ^ 1
!

value
    self value: nil
!

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

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


!Continuation methodsFor: 'resuming'!

restoreValues
    | 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
        ]
    ]
! !


!ContextPart methodsFor: 'continuation'!

homeReceiver
    ^ self home receiver
!

localAt: aNumber
    ^ self at: aNumber
!

localAt: aNumber put: anObject
    ^ self at: aNumber put: anObject
!

localSize
    ^ self size
!

swapSender: coroutine
    | oldSender |
    oldSender _ parent.
    parent _ coroutine.
    ^ oldSender
! !


Smalltalk.Object subclass: #TestCont
    instanceVariableNames: 'temp temp2'
    classVariableNames: ''
    poolDictionaries: ''
    category: ''!

TestCont comment: nil!

!TestCont methodsFor: 'testing'!

run
    | x |
    'Now1' printNl.
    temp _ 0.
    'Now2' printNl.
    x _ [temp _ temp + 1. temp2 value].
    'Now3' printNl.
    Continuation currentDo: [:cc | temp2 _ cc. x value].
    'Now4' printNl.
    temp2 _ [].
    'Now5' printNl.
    x value.
    'Now6' printNl.
    temp printNl. "should print 2"
! !

_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [Q] On Implementing Continuation...

Paolo Bonzini
I suggest that you replace your Continuation.st with the file examples/Continuations.st in GNU Smalltalk's distribution, applying this patch which I just committed to both 2.3 and trunk.

Thanks!

Paolo

--- orig/examples/Continuations.st
+++ mod/examples/Continuations.st
@@ -58,6 +58,12 @@ valueWithArguments: v
 
 !Continuation class methodsFor: 'instance creation'!
 
+current
+    ^self fromContext: thisContext sender!
+
+currentDo: aBlock
+    ^aBlock value: (self fromContext: thisContext sender)!
+
 fromContext: aStack
     ^self new stack: aStack copyStack! !
 
@@ -99,6 +105,6 @@ copyStack
        ifTrue:[^self copy]
        ifFalse: [^self copy parentContext: self parentContext copyStack]! !
 
-(Continuation factorialExample: 4) printNl!
-(Undeclared.RetryCC value: 10) printNl!
-Undeclared removeKey: #RetryCC!
+"(Continuation factorialExample: 4) printNl!"
+"(Undeclared.RetryCC value: 10) printNl!"
+"Undeclared removeKey: #RetryCC!"



_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk
Reply | Threaded
Open this post in threaded view
|

Re: [Q] On Implementing Continuation...

Chun, Sungjin
-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

Thanks for your help. I did not find there already is Continuation class!

Thanks again.

Paolo Bonzini wrote:
> I suggest that you replace your Continuation.st with the file examples/Continuations.st in GNU Smalltalk's distribution, applying this patch which I just committed to both 2.3 and trunk.
>
> Thanks!
>
> Paolo

-----BEGIN PGP SIGNATURE-----
Version: GnuPG v1.4.2.2 (GNU/Linux)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org

iD8DBQFF7hGvQqspS1+XJHgRAs6vAKChWsMF/+5Nz8yaXKeODiwXJimRygCeN4IF
erz9/o0fzesLr68AKrpYtAg=
=qzsm
-----END PGP SIGNATURE-----


_______________________________________________
help-smalltalk mailing list
[hidden email]
http://lists.gnu.org/mailman/listinfo/help-smalltalk