On the rejection of Promises due to errors

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

On the rejection of Promises due to errors

Jakob Reschke
Hi all,

Tony has recently fixed our Promise implementation to make it more
Promises/A+ compliant, thank you!

In the discussion that lead to this fix [1], I already pointed out a
difference between exceptions in Smalltalk and in JavaScript, where
the Promises/A+ specification originates: Smalltalk exceptions can be
resumed, while JavaScript exceptions cannot be resumed and always
unroll the stack.

The spec [2] says that if the onFulfilled or onRejected callback of a
#then call on a promise throws an exception, then the promise returned
by the #then call shall be rejected with the exception thrown.

Our current Promise implementation matches this for the blocks
supplied to #then:, #ifRejected: or #then:ifRejected, by catching all
Errors in the blocks and rejecting the promise. But this does not
allow a Squeak user to deal with exceptions in a debugger if they are
signalled in the callbacks, because they are caught. The same also
applies to #future promises. The latter are not really covered by the
Promises/A+ spec (because it does not force the resolution or
rejection of a promise that is not the result of a #then, and there is
no #future in JavaScript), but futures exhibit the same problem of not
being resumable in the debugger. Example:

promise := 1 future / 0. "<= inspect it => promise is rejected,
regardless of your actions in the debugger"
Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 future methodWithTypo. "<= inspect it => promise is
rejected, no chance to fix the misspelling of asString in the debugger
and proceed"

I could imagine instead letting all exceptions pass during the future
or callback block evaluation, and only reject the promise if the
evaluation is eventually curtailed due to the exception (be it an
Error or not, think of Warning or ModificationForbidden). Example
expectations:

promise := 1 future / 0. "<= inspect it, press Proceed in the
debugger, => promise is resolved"
promise := 1 future / 0. "<= inspect it, press Abandon in the
debugger, => promise is rejected"
promise := 1 future methodWithTypo. "<= inspect it, fix the typo of
asString in the debugger, proceed, => promise is resolved with '1'"

It could be done by fulfilling a Promise about aBlock similar to this:

[ self resolveWith: aBlock value ]
   on: Exception
   do: [ :ex | | resumed |
      resumed := false.
      [ | result |
      result := ex outer.
      resumed := true.
      ex resume: result]
         ifCurtailed: [resumed ifFalse: [self future rejectWith: ex]]]

(Find the current implementations here:
Promise>>#fulfillWith:passErrors: and Promise>>#then:ifRejected:)

Note that the #outer send would only trigger handlers in the
Project/World loop, or the defaultAction of the exception. The #future
in front of #rejectWith: is there to avoid curtailing the unwind block
context of ifCurtailed: itself if there are further errors in the
rejection callbacks of the promise. The behavior of non-local exits
from unwind contexts is undefined in the Smalltalk ANSI standard (just
like resume: or return: in a defaultAction, or not sending resume: or
return: in an on:do: exception handler at all -- VA Smalltalk
interprets that as resume, while Squeak does return, for example).

This implementation would also allow all deferred Notifications to
pass and not reject the promise. That is because true notifications
just resume silently if they are not handled.

promise := [Notification signal: 'hi there'. 42] future value. "<=
inspect it => Expected: resolved with 42. Actual (today): it is
needlessly rejected with Notification 'hi there'"

Pressing Proceed in the debugger on officially non-resumable errors
(which is possible) would also not reject the promise. But further
errors/debuggers are likely to appear, of which one may eventually be
used to abort the execution. If the execution finishes after
repeatedly pressing Proceed, then fine, resolve the promise with
whatever the outcome was.

promise := [self error: 'Fatal error'. 42] future value. "<= inspect
it, proceed after the so-called fatal error, => Expected: resolved
with 42. Actual: there is no debugger, the promise is immediately
rejected."

promise := [1 / 0 + 3] future value. "<= Cannot be resumed/proceeded
because if ZeroDivide is resumed, it will return the exception, and
ZeroDivide does not understand +, which cannot be resumed without
changing the code. So you'd have to curtail the block execution =>
Expected: rejected with ZeroDivide or MessageNotUnderstood (depending
on when you press Abandon or recompile the DoIt)."

promise := [1 / 0 + 3] future value. "... or instead of changing the
code or aborting, you could choose 'return entered value' in one of
the debuggers, and thereby complete the evaluation of the block =>
Expected: resolved with whatever you entered to return in the
debugger"

Promises with whenRejected:/ifRejected: callbacks would no longer
swallow errors, and would only be rejected when the user aborts in the
debuggers, or if the future execution catches errors by itself and
converts them to rejected promises, so the future promise will also be
rejected. This could pose a compatibility problem for existing code.

promise := (1 future / 0) then: [:result | result + 3] ifRejected:
[:reason | #cancelled]. "<= inspect it => Actual: resolved with
#cancelled immediately. Expected with my proposed changes: it would
first show the ZeroDivide debugger, which you can abandon to resolve
with #cancelled, or proceed to a MessageNotUnderstood +. If you
abandon the MNU, the promise would be rejected with the MNU, not
#cancelled, in accordance with the Promises/A+ spec."

How to get back a catch-all->reject-immediately future under these
circumstances:

promise := [[1 / 0] on: Error do: [:e | e return: (Promise new
rejectWith: e)]] future value.
promise := [1 future + 1 then: [:n | [n / 0] on: Error do: [:e | e
return: (Promise new rejectWith: e)]] future value.

We could also introduce a convenience constructor for
immediately-rejected promises like in JavaScript: Promise rejected: e.
Or a convenience exception handler: [...] rejectOn: Error.  Or [...]
rejectIfCurtailed (the fullfill/then methods would probably use this
as well).

What do you think?

As Tom Beckmann has already suggested in the last thread on the topic
[1], I could also use a custom class of Promise to get just the
behavior I want. But then I cannot solve it for the use of #future. At
least not without patching something about the compiler in my package
preamble... ;-)

[1] http://lists.squeakfoundation.org/pipermail/squeak-dev/2020-April/208546.html
[2] https://promisesaplus.com/

Kind regards,
Jakob

Reply | Threaded
Open this post in threaded view
|

Re: On the rejection of Promises due to errors

Squeak - Dev mailing list

Hi Jakob,

I also have a promises implementation for Squeak and Java, that was derived from ERights, which precedes the JavaScript impl, both by Mark Miller. They do NOT throw up exceptions but they do resolve the promise to a BrokenERef, encapsulating the exception.

You can load the following and run the tests.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Then I converted the first code you presented as the following.

promise := 1 eventual / 0.

Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 eventual methodWithTypo.

They both resolve to BrokenERefs.

I got a little lost in capturing exceptions, within the Vat's event loop #processSends. I have tickled my implementation a little to try and get the Vat event thread to throw an exception, which presents a Debugger. I have been unable to pop up the Debugger on the error, but the promise does get smashed.

These Promises also pipelines the failure to subsequent message sends, with subsequent broken promises. So this also breaks with ZeroDivide.

(1 eventual / 0) * 10.

Here are the immediate promise return and the smashed promise to a BrokenERef.


Kindly,
Robert

On 6/21/20 4:57 PM, Jakob Reschke wrote:
Hi all,

Tony has recently fixed our Promise implementation to make it more
Promises/A+ compliant, thank you!

In the discussion that lead to this fix [1], I already pointed out a
difference between exceptions in Smalltalk and in JavaScript, where
the Promises/A+ specification originates: Smalltalk exceptions can be
resumed, while JavaScript exceptions cannot be resumed and always
unroll the stack.

The spec [2] says that if the onFulfilled or onRejected callback of a
#then call on a promise throws an exception, then the promise returned
by the #then call shall be rejected with the exception thrown.

Our current Promise implementation matches this for the blocks
supplied to #then:, #ifRejected: or #then:ifRejected, by catching all
Errors in the blocks and rejecting the promise. But this does not
allow a Squeak user to deal with exceptions in a debugger if they are
signalled in the callbacks, because they are caught. The same also
applies to #future promises. The latter are not really covered by the
Promises/A+ spec (because it does not force the resolution or
rejection of a promise that is not the result of a #then, and there is
no #future in JavaScript), but futures exhibit the same problem of not
being resumable in the debugger. Example:

promise := 1 future / 0. "<= inspect it => promise is rejected,
regardless of your actions in the debugger"
Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 future methodWithTypo. "<= inspect it => promise is
rejected, no chance to fix the misspelling of asString in the debugger
and proceed"

I could imagine instead letting all exceptions pass during the future
or callback block evaluation, and only reject the promise if the
evaluation is eventually curtailed due to the exception (be it an
Error or not, think of Warning or ModificationForbidden). Example
expectations:

promise := 1 future / 0. "<= inspect it, press Proceed in the
debugger, => promise is resolved"
promise := 1 future / 0. "<= inspect it, press Abandon in the
debugger, => promise is rejected"
promise := 1 future methodWithTypo. "<= inspect it, fix the typo of
asString in the debugger, proceed, => promise is resolved with '1'"

It could be done by fulfilling a Promise about aBlock similar to this:

[ self resolveWith: aBlock value ]
   on: Exception
   do: [ :ex | | resumed |
      resumed := false.
      [ | result |
      result := ex outer.
      resumed := true.
      ex resume: result]
         ifCurtailed: [resumed ifFalse: [self future rejectWith: ex]]]

(Find the current implementations here:
Promise>>#fulfillWith:passErrors: and Promise>>#then:ifRejected:)

Note that the #outer send would only trigger handlers in the
Project/World loop, or the defaultAction of the exception. The #future
in front of #rejectWith: is there to avoid curtailing the unwind block
context of ifCurtailed: itself if there are further errors in the
rejection callbacks of the promise. The behavior of non-local exits
from unwind contexts is undefined in the Smalltalk ANSI standard (just
like resume: or return: in a defaultAction, or not sending resume: or
return: in an on:do: exception handler at all -- VA Smalltalk
interprets that as resume, while Squeak does return, for example).

This implementation would also allow all deferred Notifications to
pass and not reject the promise. That is because true notifications
just resume silently if they are not handled.

promise := [Notification signal: 'hi there'. 42] future value. "<=
inspect it => Expected: resolved with 42. Actual (today): it is
needlessly rejected with Notification 'hi there'"

Pressing Proceed in the debugger on officially non-resumable errors
(which is possible) would also not reject the promise. But further
errors/debuggers are likely to appear, of which one may eventually be
used to abort the execution. If the execution finishes after
repeatedly pressing Proceed, then fine, resolve the promise with
whatever the outcome was.

promise := [self error: 'Fatal error'. 42] future value. "<= inspect
it, proceed after the so-called fatal error, => Expected: resolved
with 42. Actual: there is no debugger, the promise is immediately
rejected."

promise := [1 / 0 + 3] future value. "<= Cannot be resumed/proceeded
because if ZeroDivide is resumed, it will return the exception, and
ZeroDivide does not understand +, which cannot be resumed without
changing the code. So you'd have to curtail the block execution =>
Expected: rejected with ZeroDivide or MessageNotUnderstood (depending
on when you press Abandon or recompile the DoIt)."

promise := [1 / 0 + 3] future value. "... or instead of changing the
code or aborting, you could choose 'return entered value' in one of
the debuggers, and thereby complete the evaluation of the block =>
Expected: resolved with whatever you entered to return in the
debugger"

Promises with whenRejected:/ifRejected: callbacks would no longer
swallow errors, and would only be rejected when the user aborts in the
debuggers, or if the future execution catches errors by itself and
converts them to rejected promises, so the future promise will also be
rejected. This could pose a compatibility problem for existing code.

promise := (1 future / 0) then: [:result | result + 3] ifRejected:
[:reason | #cancelled]. "<= inspect it => Actual: resolved with
#cancelled immediately. Expected with my proposed changes: it would
first show the ZeroDivide debugger, which you can abandon to resolve
with #cancelled, or proceed to a MessageNotUnderstood +. If you
abandon the MNU, the promise would be rejected with the MNU, not
#cancelled, in accordance with the Promises/A+ spec."

How to get back a catch-all->reject-immediately future under these
circumstances:

promise := [[1 / 0] on: Error do: [:e | e return: (Promise new
rejectWith: e)]] future value.
promise := [1 future + 1 then: [:n | [n / 0] on: Error do: [:e | e
return: (Promise new rejectWith: e)]] future value.

We could also introduce a convenience constructor for
immediately-rejected promises like in JavaScript: Promise rejected: e.
Or a convenience exception handler: [...] rejectOn: Error.  Or [...]
rejectIfCurtailed (the fullfill/then methods would probably use this
as well).

What do you think?

As Tom Beckmann has already suggested in the last thread on the topic
[1], I could also use a custom class of Promise to get just the
behavior I want. But then I cannot solve it for the use of #future. At
least not without patching something about the compiler in my package
preamble... ;-)

[1] http://lists.squeakfoundation.org/pipermail/squeak-dev/2020-April/208546.html
[2] https://promisesaplus.com/

Kind regards,
Jakob



Reply | Threaded
Open this post in threaded view
|

Re: On the rejection of Promises due to errors

Squeak - Dev mailing list

Hi Jakob,

I changed my code a little bit to open a Debugger. Yet I still have two issues.

On 6/21/20 5:53 PM, Robert Withers wrote:

You can load the following and run the tests.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

The latest PromisesLocal-rww.2.mcz  has the changes. You can load with the above Installer doIt.

I got a little lost in capturing exceptions, within the Vat's event loop #processSends. I have tickled my implementation a little to try and get the Vat event thread to throw an exception, which presents a Debugger. I have been unable to pop up the Debugger on the error, but the promise does get smashed.

I removed catch-all error handling from the PriorityVat>>#processSends. I then added to the error handling in EventualMessageSend>>#value to open a debugger after smashing the resolver.

value

    | value |
    [value := receiver
        perform: selector
        withArguments: (self collectArguments: arguments)
        inSuperclass: receiver class.
    self resolver notNil
        ifTrue: [ self resolver resolve: value ] ]
            on: Exception
            do: [:ex |
                self resolver notNil
                    ifTrue: [self resolver smash: ex].
                Processor activeProcess signalException: ex].

I have a couple of issues with this:

  1. When I close the debugger, the EventualProcess with the stack that ended up in this exception is terminated. I would need this process to restart and continue, after clearing the stack from this exception. I am unsure how to make that happen. Any suggestions are MOST WELCOME!
  2. The stack in the Debugger is not opened on the stack frame that causes the failure. I would like to rewind the stack to the bolded line, where the exception is produced, in this case it would be the method: ZeroDivide(Exception)>>signal. Is this not where the Debugger should be opened? Again, I am unsure how to do this and all suggestions are MOST WELCOME!

--- The full stack ---
EventualProcess(Process)>>signalException:
[] in EventualMessageSend>>value
FullBlockClosure(BlockClosure)>>cull:
[] in Context>>handleSignal:
FullBlockClosure(BlockClosure)>>ensure:
Context>>handleSignal:
ZeroDivide(Exception)>>signal
SmallInteger>>/
[] in EventualMessageSend>>value
FullBlockClosure(BlockClosure)>>on:do:
EventualMessageSend>>value
PriorityVat>>processSends
[] in EventualProcess>>setupContext


Kindly,
Rabbit



Walkback.text (7K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: On the rejection of Promises due to errors

Squeak - Dev mailing list

Hi Jakob,

On 6/23/20 8:40 AM, Robert Withers wrote:
I removed catch-all error handling from the PriorityVat>>#processSends. I then added to the error handling in EventualMessageSend>>#value to open a debugger after smashing the resolver.

I forgot to specify that I use the following code to test these changes:

1 eventual / 0

After running this and seeing the Debugger and closing this Debugger, you have to restart the localVat to refresh the event loop, with the following code:

PriorityVat class>>#clearLocalVat

K, r



Reply | Threaded
Open this post in threaded view
|

stack manipulation on signaled Exception (was Re: On the rejection of Promises due to errors)

Squeak - Dev mailing list
In reply to this post by Squeak - Dev mailing list

Hi Jakob,

I have new ideas, in thinking on this problem, one per point I made.

On 6/23/20 8:40 AM, Robert Withers wrote:

I removed catch-all error handling from the PriorityVat>>#processSends. I then added to the error handling in EventualMessageSend>>#value to open a debugger after smashing the resolver.

value

    | value |
    [value := receiver
        perform: selector
        withArguments: (self collectArguments: arguments)
        inSuperclass: receiver class.
    self resolver notNil
        ifTrue: [ self resolver resolve: value ] ]
            on: Exception
            do: [:ex |
                self resolver notNil
                    ifTrue: [self resolver smash: ex].
                Processor activeProcess signalException: ex].

I have a couple of issues with this:

  1. When I close the debugger, the EventualProcess with the stack that ended up in this exception is terminated. I would need this process to restart and continue, after clearing the stack from this exception. I am unsure how to make that happen. Any suggestions are MOST WELCOME!
  1. I would like to copy the stack to the side and restart the Vat's eventLoop right away so that it does not deadlock the event loop process. And so continue processing message sends.

  1. The stack in the Debugger is not opened on the stack frame that causes the failure. I would like to rewind the stack to the bolded line, where the exception is produced, in this case it would be the method: ZeroDivide(Exception)>>signal. Is this not where the Debugger should be opened? Again, I am unsure how to do this and all suggestions are MOST WELCOME!

--- The full stack ---
EventualProcess(Process)>>signalException:
[] in EventualMessageSend>>value
FullBlockClosure(BlockClosure)>>cull:
[] in Context>>handleSignal:
FullBlockClosure(BlockClosure)>>ensure:
Context>>handleSignal:
ZeroDivide(Exception)>>signal
SmallInteger>>/
[] in EventualMessageSend>>value
FullBlockClosure(BlockClosure)>>on:do:
EventualMessageSend>>value
PriorityVat>>processSends
[] in EventualProcess>>setupContext


  1. With the stack copied to the side, I want to massage the stack so the top frame is the Exception's frame where the Exception gets signaled. Then I would like to remove the frames below the frame that causes the Exception signal or perhaps the stack down to the EventualMessageSend>>#value. This is the stack I envision opening in a Debugger:

ZeroDivide(Exception)>>signal
SmallInteger>>/
[] in EventualMessageSend>>value
FullBlockClosure(BlockClosure)>>on:do:
EventualMessageSend>>value

What do you think? How can I do each of these?

  1. Copy stack
  2. Restart eventLoop
  3. Prune stack
  4. Open Debugger

K, r



Reply | Threaded
Open this post in threaded view
|

Re: On the rejection of Promises due to errors

Squeak - Dev mailing list
In reply to this post by Squeak - Dev mailing list

Hi Jakob,

I was wondering if you had any thoughts regarding PromisesLocal. Have you had a chance to look at this project? I suppose the promise protocol could be extended to capture the protocol specified in Promises/A+, but the same behavior is there (#whenResolved:). I added the ability to open a debugger when an exception gets thrown. Unfortunately, for now this exception blocks the event loop Process. I have another email on how to unblock the event loop Process, yet still open an appropriate Debugger Notifier.

I would welcome any feedback you may have. I am working on the Remote version (PromisesRemote). You can load PromisesLocal and run the tests.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Kindly,
rabbit

On 6/21/20 5:53 PM, Robert Withers wrote:

Hi Jakob,

I also have a promises implementation for Squeak and Java, that was derived from ERights, which precedes the JavaScript impl, both by Mark Miller. They do NOT throw up exceptions but they do resolve the promise to a BrokenERef, encapsulating the exception.

You can load the following and run the tests.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Then I converted the first code you presented as the following.

promise := 1 eventual / 0.

Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 eventual methodWithTypo.

They both resolve to BrokenERefs.

I got a little lost in capturing exceptions, within the Vat's event loop #processSends. I have tickled my implementation a little to try and get the Vat event thread to throw an exception, which presents a Debugger. I have been unable to pop up the Debugger on the error, but the promise does get smashed.

These Promises also pipelines the failure to subsequent message sends, with subsequent broken promises. So this also breaks with ZeroDivide.

(1 eventual / 0) * 10.

Here are the immediate promise return and the smashed promise to a BrokenERef.


Kindly,
Robert

On 6/21/20 4:57 PM, Jakob Reschke wrote:
Hi all,

Tony has recently fixed our Promise implementation to make it more
Promises/A+ compliant, thank you!

In the discussion that lead to this fix [1], I already pointed out a
difference between exceptions in Smalltalk and in JavaScript, where
the Promises/A+ specification originates: Smalltalk exceptions can be
resumed, while JavaScript exceptions cannot be resumed and always
unroll the stack.

The spec [2] says that if the onFulfilled or onRejected callback of a
#then call on a promise throws an exception, then the promise returned
by the #then call shall be rejected with the exception thrown.

Our current Promise implementation matches this for the blocks
supplied to #then:, #ifRejected: or #then:ifRejected, by catching all
Errors in the blocks and rejecting the promise. But this does not
allow a Squeak user to deal with exceptions in a debugger if they are
signalled in the callbacks, because they are caught. The same also
applies to #future promises. The latter are not really covered by the
Promises/A+ spec (because it does not force the resolution or
rejection of a promise that is not the result of a #then, and there is
no #future in JavaScript), but futures exhibit the same problem of not
being resumable in the debugger. Example:

promise := 1 future / 0. "<= inspect it => promise is rejected,
regardless of your actions in the debugger"
Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 future methodWithTypo. "<= inspect it => promise is
rejected, no chance to fix the misspelling of asString in the debugger
and proceed"

I could imagine instead letting all exceptions pass during the future
or callback block evaluation, and only reject the promise if the
evaluation is eventually curtailed due to the exception (be it an
Error or not, think of Warning or ModificationForbidden). Example
expectations:

promise := 1 future / 0. "<= inspect it, press Proceed in the
debugger, => promise is resolved"
promise := 1 future / 0. "<= inspect it, press Abandon in the
debugger, => promise is rejected"
promise := 1 future methodWithTypo. "<= inspect it, fix the typo of
asString in the debugger, proceed, => promise is resolved with '1'"

It could be done by fulfilling a Promise about aBlock similar to this:

[ self resolveWith: aBlock value ]
   on: Exception
   do: [ :ex | | resumed |
      resumed := false.
      [ | result |
      result := ex outer.
      resumed := true.
      ex resume: result]
         ifCurtailed: [resumed ifFalse: [self future rejectWith: ex]]]

(Find the current implementations here:
Promise>>#fulfillWith:passErrors: and Promise>>#then:ifRejected:)

Note that the #outer send would only trigger handlers in the
Project/World loop, or the defaultAction of the exception. The #future
in front of #rejectWith: is there to avoid curtailing the unwind block
context of ifCurtailed: itself if there are further errors in the
rejection callbacks of the promise. The behavior of non-local exits
from unwind contexts is undefined in the Smalltalk ANSI standard (just
like resume: or return: in a defaultAction, or not sending resume: or
return: in an on:do: exception handler at all -- VA Smalltalk
interprets that as resume, while Squeak does return, for example).

This implementation would also allow all deferred Notifications to
pass and not reject the promise. That is because true notifications
just resume silently if they are not handled.

promise := [Notification signal: 'hi there'. 42] future value. "<=
inspect it => Expected: resolved with 42. Actual (today): it is
needlessly rejected with Notification 'hi there'"

Pressing Proceed in the debugger on officially non-resumable errors
(which is possible) would also not reject the promise. But further
errors/debuggers are likely to appear, of which one may eventually be
used to abort the execution. If the execution finishes after
repeatedly pressing Proceed, then fine, resolve the promise with
whatever the outcome was.

promise := [self error: 'Fatal error'. 42] future value. "<= inspect
it, proceed after the so-called fatal error, => Expected: resolved
with 42. Actual: there is no debugger, the promise is immediately
rejected."

promise := [1 / 0 + 3] future value. "<= Cannot be resumed/proceeded
because if ZeroDivide is resumed, it will return the exception, and
ZeroDivide does not understand +, which cannot be resumed without
changing the code. So you'd have to curtail the block execution =>
Expected: rejected with ZeroDivide or MessageNotUnderstood (depending
on when you press Abandon or recompile the DoIt)."

promise := [1 / 0 + 3] future value. "... or instead of changing the
code or aborting, you could choose 'return entered value' in one of
the debuggers, and thereby complete the evaluation of the block =>
Expected: resolved with whatever you entered to return in the
debugger"

Promises with whenRejected:/ifRejected: callbacks would no longer
swallow errors, and would only be rejected when the user aborts in the
debuggers, or if the future execution catches errors by itself and
converts them to rejected promises, so the future promise will also be
rejected. This could pose a compatibility problem for existing code.

promise := (1 future / 0) then: [:result | result + 3] ifRejected:
[:reason | #cancelled]. "<= inspect it => Actual: resolved with
#cancelled immediately. Expected with my proposed changes: it would
first show the ZeroDivide debugger, which you can abandon to resolve
with #cancelled, or proceed to a MessageNotUnderstood +. If you
abandon the MNU, the promise would be rejected with the MNU, not
#cancelled, in accordance with the Promises/A+ spec."

How to get back a catch-all->reject-immediately future under these
circumstances:

promise := [[1 / 0] on: Error do: [:e | e return: (Promise new
rejectWith: e)]] future value.
promise := [1 future + 1 then: [:n | [n / 0] on: Error do: [:e | e
return: (Promise new rejectWith: e)]] future value.

We could also introduce a convenience constructor for
immediately-rejected promises like in JavaScript: Promise rejected: e.
Or a convenience exception handler: [...] rejectOn: Error.  Or [...]
rejectIfCurtailed (the fullfill/then methods would probably use this
as well).

What do you think?

As Tom Beckmann has already suggested in the last thread on the topic
[1], I could also use a custom class of Promise to get just the
behavior I want. But then I cannot solve it for the use of #future. At
least not without patching something about the compiler in my package
preamble... ;-)

[1] http://lists.squeakfoundation.org/pipermail/squeak-dev/2020-April/208546.html
[2] https://promisesaplus.com/

Kind regards,
Jakob



Reply | Threaded
Open this post in threaded view
|

Re: On the rejection of Promises due to errors

Squeak - Dev mailing list
In reply to this post by Squeak - Dev mailing list

Hi Jakob,

Whew! I got her done! Exceptions now work with the event loop in the Vat. Using a suggestion from the Squeak Slack channel, I am using StandardToolSet>>#debugEventualException:, a method I defined in PromisesLocal, modifying #debugException:, called from EventualMessageSend>>#value, on Exception. Yay!

  1. Unblocks the event loop and discards the exception in this context.
  2. Resolves the promise to broken.
  3. Displays a Debugger on the signaler context, pruned.
  4. Debugger is proceedable, and schedules the context back into the vat for resumption on the event loop process.

I intend to ask you your view of PromisesLocal as adhering to Promises A+ standard. With #whenResolved: & #whenRejected: this implementation has the equivalent of #then:. Exceptions are captured and linked back to the Vat it came from.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Then run this script:

(1 eventual / 0) explore.
1 eventual explore.

You should get two explorers on ERefs ( 1 PromiseERef that #become: a BrokenERef and one NearERef) and one Debugger on ZeroDivide. The second line guarantees the event loop is not blocked.

I am working on ASN1 encoding of Remote Promise objects (EventualMessage & EventualDesc), so they can be bit identical between Squeak & Java. Bringing remote capabilities, following the Promise A+ specification.

Since you were working with Futures in Squeak, I welcome your views on this implementation.

Kindly,
rabbit

On 6/21/20 5:53 PM, Robert Withers wrote:

Hi Jakob,

I also have a promises implementation for Squeak and Java, that was derived from ERights, which precedes the JavaScript impl, both by Mark Miller. They do NOT throw up exceptions but they do resolve the promise to a BrokenERef, encapsulating the exception.

You can load the following and run the tests.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Then I converted the first code you presented as the following.

promise := 1 eventual / 0.

Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 eventual methodWithTypo.

They both resolve to BrokenERefs.

I got a little lost in capturing exceptions, within the Vat's event loop #processSends. I have tickled my implementation a little to try and get the Vat event thread to throw an exception, which presents a Debugger. I have been unable to pop up the Debugger on the error, but the promise does get smashed.

These Promises also pipelines the failure to subsequent message sends, with subsequent broken promises. So this also breaks with ZeroDivide.

(1 eventual / 0) * 10.

Here are the immediate promise return and the smashed promise to a BrokenERef.


Kindly,
Robert

On 6/21/20 4:57 PM, Jakob Reschke wrote:
Hi all,

Tony has recently fixed our Promise implementation to make it more
Promises/A+ compliant, thank you!

In the discussion that lead to this fix [1], I already pointed out a
difference between exceptions in Smalltalk and in JavaScript, where
the Promises/A+ specification originates: Smalltalk exceptions can be
resumed, while JavaScript exceptions cannot be resumed and always
unroll the stack.

The spec [2] says that if the onFulfilled or onRejected callback of a
#then call on a promise throws an exception, then the promise returned
by the #then call shall be rejected with the exception thrown.

Our current Promise implementation matches this for the blocks
supplied to #then:, #ifRejected: or #then:ifRejected, by catching all
Errors in the blocks and rejecting the promise. But this does not
allow a Squeak user to deal with exceptions in a debugger if they are
signalled in the callbacks, because they are caught. The same also
applies to #future promises. The latter are not really covered by the
Promises/A+ spec (because it does not force the resolution or
rejection of a promise that is not the result of a #then, and there is
no #future in JavaScript), but futures exhibit the same problem of not
being resumable in the debugger. Example:

promise := 1 future / 0. "<= inspect it => promise is rejected,
regardless of your actions in the debugger"
Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 future methodWithTypo. "<= inspect it => promise is
rejected, no chance to fix the misspelling of asString in the debugger
and proceed"

I could imagine instead letting all exceptions pass during the future
or callback block evaluation, and only reject the promise if the
evaluation is eventually curtailed due to the exception (be it an
Error or not, think of Warning or ModificationForbidden). Example
expectations:

promise := 1 future / 0. "<= inspect it, press Proceed in the
debugger, => promise is resolved"
promise := 1 future / 0. "<= inspect it, press Abandon in the
debugger, => promise is rejected"
promise := 1 future methodWithTypo. "<= inspect it, fix the typo of
asString in the debugger, proceed, => promise is resolved with '1'"

It could be done by fulfilling a Promise about aBlock similar to this:

[ self resolveWith: aBlock value ]
   on: Exception
   do: [ :ex | | resumed |
      resumed := false.
      [ | result |
      result := ex outer.
      resumed := true.
      ex resume: result]
         ifCurtailed: [resumed ifFalse: [self future rejectWith: ex]]]

(Find the current implementations here:
Promise>>#fulfillWith:passErrors: and Promise>>#then:ifRejected:)

Note that the #outer send would only trigger handlers in the
Project/World loop, or the defaultAction of the exception. The #future
in front of #rejectWith: is there to avoid curtailing the unwind block
context of ifCurtailed: itself if there are further errors in the
rejection callbacks of the promise. The behavior of non-local exits
from unwind contexts is undefined in the Smalltalk ANSI standard (just
like resume: or return: in a defaultAction, or not sending resume: or
return: in an on:do: exception handler at all -- VA Smalltalk
interprets that as resume, while Squeak does return, for example).

This implementation would also allow all deferred Notifications to
pass and not reject the promise. That is because true notifications
just resume silently if they are not handled.

promise := [Notification signal: 'hi there'. 42] future value. "<=
inspect it => Expected: resolved with 42. Actual (today): it is
needlessly rejected with Notification 'hi there'"

Pressing Proceed in the debugger on officially non-resumable errors
(which is possible) would also not reject the promise. But further
errors/debuggers are likely to appear, of which one may eventually be
used to abort the execution. If the execution finishes after
repeatedly pressing Proceed, then fine, resolve the promise with
whatever the outcome was.

promise := [self error: 'Fatal error'. 42] future value. "<= inspect
it, proceed after the so-called fatal error, => Expected: resolved
with 42. Actual: there is no debugger, the promise is immediately
rejected."

promise := [1 / 0 + 3] future value. "<= Cannot be resumed/proceeded
because if ZeroDivide is resumed, it will return the exception, and
ZeroDivide does not understand +, which cannot be resumed without
changing the code. So you'd have to curtail the block execution =>
Expected: rejected with ZeroDivide or MessageNotUnderstood (depending
on when you press Abandon or recompile the DoIt)."

promise := [1 / 0 + 3] future value. "... or instead of changing the
code or aborting, you could choose 'return entered value' in one of
the debuggers, and thereby complete the evaluation of the block =>
Expected: resolved with whatever you entered to return in the
debugger"

Promises with whenRejected:/ifRejected: callbacks would no longer
swallow errors, and would only be rejected when the user aborts in the
debuggers, or if the future execution catches errors by itself and
converts them to rejected promises, so the future promise will also be
rejected. This could pose a compatibility problem for existing code.

promise := (1 future / 0) then: [:result | result + 3] ifRejected:
[:reason | #cancelled]. "<= inspect it => Actual: resolved with
#cancelled immediately. Expected with my proposed changes: it would
first show the ZeroDivide debugger, which you can abandon to resolve
with #cancelled, or proceed to a MessageNotUnderstood +. If you
abandon the MNU, the promise would be rejected with the MNU, not
#cancelled, in accordance with the Promises/A+ spec."

How to get back a catch-all->reject-immediately future under these
circumstances:

promise := [[1 / 0] on: Error do: [:e | e return: (Promise new
rejectWith: e)]] future value.
promise := [1 future + 1 then: [:n | [n / 0] on: Error do: [:e | e
return: (Promise new rejectWith: e)]] future value.

We could also introduce a convenience constructor for
immediately-rejected promises like in JavaScript: Promise rejected: e.
Or a convenience exception handler: [...] rejectOn: Error.  Or [...]
rejectIfCurtailed (the fullfill/then methods would probably use this
as well).

What do you think?

As Tom Beckmann has already suggested in the last thread on the topic
[1], I could also use a custom class of Promise to get just the
behavior I want. But then I cannot solve it for the use of #future. At
least not without patching something about the compiler in my package
preamble... ;-)

[1] http://lists.squeakfoundation.org/pipermail/squeak-dev/2020-April/208546.html
[2] https://promisesaplus.com/

Kind regards,
Jakob



Reply | Threaded
Open this post in threaded view
|

Re: On the rejection of Promises due to errors

Squeak - Dev mailing list

Here's my images:





On 7/18/20 12:35 PM, Robert Withers wrote:

Hi Jakob,

Whew! I got her done! Exceptions now work with the event loop in the Vat. Using a suggestion from the Squeak Slack channel, I am using StandardToolSet>>#debugEventualException:, a method I defined in PromisesLocal, modifying #debugException:, called from EventualMessageSend>>#value, on Exception. Yay!

  1. Unblocks the event loop and discards the exception in this context.
  2. Resolves the promise to broken.
  3. Displays a Debugger on the signaler context, pruned.
  4. Debugger is proceedable, and schedules the context back into the vat for resumption on the event loop process.

I intend to ask you your view of PromisesLocal as adhering to Promises A+ standard. With #whenResolved: & #whenRejected: this implementation has the equivalent of #then:. Exceptions are captured and linked back to the Vat it came from.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Then run this script:

(1 eventual / 0) explore.
1 eventual explore.

You should get two explorers on ERefs ( 1 PromiseERef that #become: a BrokenERef and one NearERef) and one Debugger on ZeroDivide. The second line guarantees the event loop is not blocked.

I am working on ASN1 encoding of Remote Promise objects (EventualMessage & EventualDesc), so they can be bit identical between Squeak & Java. Bringing remote capabilities, following the Promise A+ specification.

Since you were working with Futures in Squeak, I welcome your views on this implementation.

Kindly,
rabbit

On 6/21/20 5:53 PM, Robert Withers wrote:

Hi Jakob,

I also have a promises implementation for Squeak and Java, that was derived from ERights, which precedes the JavaScript impl, both by Mark Miller. They do NOT throw up exceptions but they do resolve the promise to a BrokenERef, encapsulating the exception.

You can load the following and run the tests.

Installer ss project: 'Cryptography'; install: 'PromisesLocal'.

Then I converted the first code you presented as the following.

promise := 1 eventual / 0.

Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 eventual methodWithTypo.

They both resolve to BrokenERefs.

I got a little lost in capturing exceptions, within the Vat's event loop #processSends. I have tickled my implementation a little to try and get the Vat event thread to throw an exception, which presents a Debugger. I have been unable to pop up the Debugger on the error, but the promise does get smashed.

These Promises also pipelines the failure to subsequent message sends, with subsequent broken promises. So this also breaks with ZeroDivide.

(1 eventual / 0) * 10.

Here are the immediate promise return and the smashed promise to a BrokenERef.


Kindly,
Robert

On 6/21/20 4:57 PM, Jakob Reschke wrote:
Hi all,

Tony has recently fixed our Promise implementation to make it more
Promises/A+ compliant, thank you!

In the discussion that lead to this fix [1], I already pointed out a
difference between exceptions in Smalltalk and in JavaScript, where
the Promises/A+ specification originates: Smalltalk exceptions can be
resumed, while JavaScript exceptions cannot be resumed and always
unroll the stack.

The spec [2] says that if the onFulfilled or onRejected callback of a
#then call on a promise throws an exception, then the promise returned
by the #then call shall be rejected with the exception thrown.

Our current Promise implementation matches this for the blocks
supplied to #then:, #ifRejected: or #then:ifRejected, by catching all
Errors in the blocks and rejecting the promise. But this does not
allow a Squeak user to deal with exceptions in a debugger if they are
signalled in the callbacks, because they are caught. The same also
applies to #future promises. The latter are not really covered by the
Promises/A+ spec (because it does not force the resolution or
rejection of a promise that is not the result of a #then, and there is
no #future in JavaScript), but futures exhibit the same problem of not
being resumable in the debugger. Example:

promise := 1 future / 0. "<= inspect it => promise is rejected,
regardless of your actions in the debugger"
Number compile: 'methodWithTypo  ^ self asstring'.
promise := 1 future methodWithTypo. "<= inspect it => promise is
rejected, no chance to fix the misspelling of asString in the debugger
and proceed"

I could imagine instead letting all exceptions pass during the future
or callback block evaluation, and only reject the promise if the
evaluation is eventually curtailed due to the exception (be it an
Error or not, think of Warning or ModificationForbidden). Example
expectations:

promise := 1 future / 0. "<= inspect it, press Proceed in the
debugger, => promise is resolved"
promise := 1 future / 0. "<= inspect it, press Abandon in the
debugger, => promise is rejected"
promise := 1 future methodWithTypo. "<= inspect it, fix the typo of
asString in the debugger, proceed, => promise is resolved with '1'"

It could be done by fulfilling a Promise about aBlock similar to this:

[ self resolveWith: aBlock value ]
   on: Exception
   do: [ :ex | | resumed |
      resumed := false.
      [ | result |
      result := ex outer.
      resumed := true.
      ex resume: result]
         ifCurtailed: [resumed ifFalse: [self future rejectWith: ex]]]

(Find the current implementations here:
Promise>>#fulfillWith:passErrors: and Promise>>#then:ifRejected:)

Note that the #outer send would only trigger handlers in the
Project/World loop, or the defaultAction of the exception. The #future
in front of #rejectWith: is there to avoid curtailing the unwind block
context of ifCurtailed: itself if there are further errors in the
rejection callbacks of the promise. The behavior of non-local exits
from unwind contexts is undefined in the Smalltalk ANSI standard (just
like resume: or return: in a defaultAction, or not sending resume: or
return: in an on:do: exception handler at all -- VA Smalltalk
interprets that as resume, while Squeak does return, for example).

This implementation would also allow all deferred Notifications to
pass and not reject the promise. That is because true notifications
just resume silently if they are not handled.

promise := [Notification signal: 'hi there'. 42] future value. "<=
inspect it => Expected: resolved with 42. Actual (today): it is
needlessly rejected with Notification 'hi there'"

Pressing Proceed in the debugger on officially non-resumable errors
(which is possible) would also not reject the promise. But further
errors/debuggers are likely to appear, of which one may eventually be
used to abort the execution. If the execution finishes after
repeatedly pressing Proceed, then fine, resolve the promise with
whatever the outcome was.

promise := [self error: 'Fatal error'. 42] future value. "<= inspect
it, proceed after the so-called fatal error, => Expected: resolved
with 42. Actual: there is no debugger, the promise is immediately
rejected."

promise := [1 / 0 + 3] future value. "<= Cannot be resumed/proceeded
because if ZeroDivide is resumed, it will return the exception, and
ZeroDivide does not understand +, which cannot be resumed without
changing the code. So you'd have to curtail the block execution =>
Expected: rejected with ZeroDivide or MessageNotUnderstood (depending
on when you press Abandon or recompile the DoIt)."

promise := [1 / 0 + 3] future value. "... or instead of changing the
code or aborting, you could choose 'return entered value' in one of
the debuggers, and thereby complete the evaluation of the block =>
Expected: resolved with whatever you entered to return in the
debugger"

Promises with whenRejected:/ifRejected: callbacks would no longer
swallow errors, and would only be rejected when the user aborts in the
debuggers, or if the future execution catches errors by itself and
converts them to rejected promises, so the future promise will also be
rejected. This could pose a compatibility problem for existing code.

promise := (1 future / 0) then: [:result | result + 3] ifRejected:
[:reason | #cancelled]. "<= inspect it => Actual: resolved with
#cancelled immediately. Expected with my proposed changes: it would
first show the ZeroDivide debugger, which you can abandon to resolve
with #cancelled, or proceed to a MessageNotUnderstood +. If you
abandon the MNU, the promise would be rejected with the MNU, not
#cancelled, in accordance with the Promises/A+ spec."

How to get back a catch-all->reject-immediately future under these
circumstances:

promise := [[1 / 0] on: Error do: [:e | e return: (Promise new
rejectWith: e)]] future value.
promise := [1 future + 1 then: [:n | [n / 0] on: Error do: [:e | e
return: (Promise new rejectWith: e)]] future value.

We could also introduce a convenience constructor for
immediately-rejected promises like in JavaScript: Promise rejected: e.
Or a convenience exception handler: [...] rejectOn: Error.  Or [...]
rejectIfCurtailed (the fullfill/then methods would probably use this
as well).

What do you think?

As Tom Beckmann has already suggested in the last thread on the topic
[1], I could also use a custom class of Promise to get just the
behavior I want. But then I cannot solve it for the use of #future. At
least not without patching something about the compiler in my package
preamble... ;-)

[1] http://lists.squeakfoundation.org/pipermail/squeak-dev/2020-April/208546.html
[2] https://promisesaplus.com/

Kind regards,
Jakob