Timeouts for BlockClosures

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

Timeouts for BlockClosures

Holger Freyther
Hi Paolo,

I would like to write code like this:

[
     self sendStuff
     self handleReply
     self sendStuff
     self handleReply
     success...
] timeout: 10 do: [didn't finish]


My first idea was to do something like this:

BlockClosure extend [
   timeout: aDelay do: aBlock [
        | ctx ret |
        ctx := thisContext.
        [
         [TimeOutHandler with: self on: ctx delay: aDelay] fork.
         ret := self value.
        ] on: TimeOutOccured: [:e | aBlock value]
        ^ ret
   ]
]

and TimeOutHandler would use process queueInterrupt: [TimeOutOccured signal].
This all looks quite nice but what if I write code like this?

[
        [] whileTrue: [
                [
                self handleReply
                ] on: (Pokemon)Exception do: [].
        ]
       
] timeout: 10 do: []


So my questions are. Is there a kind of Exception that can be thrown but not
caught by a 'imprecise' on:do? E.g. this exception can only be handled by this
specific handler? Or should I use thisContext and play with the IP or is this
whole idea just not the right thing to be done in smalltalk?








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

Re: Timeouts for BlockClosures

Paolo Bonzini-2
> Is there a kind of Exception that can be thrown but not
> caught by a 'imprecise' on:do?

No.  One may say that "on: Exception" and "on: Notification" are
always wrong and should never be used ("on: Warning" and "on: Error"
instead are usually fine).  Feel free to write code as if they never
appeared in code.

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/03/2011 03:34 PM, Paolo Bonzini wrote:
>> Is there a kind of Exception that can be thrown but not
>> caught by a 'imprecise' on:do?
>
> No.  One may say that "on: Exception" and "on: Notification" are
> always wrong and should never be used ("on: Warning" and "on: Error"
> instead are usually fine).  Feel free to write code as if they never
> appeared in code.

Hi,
maybe you could help me to understand the Process/BlockClosure/Exception
interaction. I do have two issues. The first is that even if I manage to call
the timeout block I am still returning to the Delay and do not leave the
block. Any idea how I could leave the delay, execute all ensure blocks inside
the timeout?

Eval [
    [(Delay forSeconds: 100000) wait] timeout: 1 do: ['Timedout' printNl].
]




Notification subclass: TimeoutNotification [
]

BlockClosure extend [
    timeout: seconds do: aBlock [
        | delay sem proc value |
        sem := Semaphore new.
        proc := Processor activeProcess.

        "Start the waiting."
        [[

            "Start a process to wait in and then signal"
            [| delay |
                delay := Delay forSeconds: seconds.

                "Wait and see if it is timed out"
                (delay timedWaitOn: sem) ifTrue: [
                    proc queueInterrupt: [ ^ TimeoutNotification signal].
                ].
            ] fork.

            ^ self value.
        ] ensure: [sem signal]
        ] on: TimeoutNotification do: [
            thisContext backtrace.
            ^ aBlock value]
    ]
]

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/03/2011 04:58 PM, Holger Hans Peter Freyther wrote:

>
> Hi,
> maybe you could help me to understand the Process/BlockClosure/Exception
> interaction. I do have two issues. The first is that even if I manage to call
> the timeout block I am still returning to the Delay and do not leave the
> block. Any idea how I could leave the delay, execute all ensure blocks inside
> the timeout?
>
> Eval [
>     [(Delay forSeconds: 100000) wait] timeout: 1 do: ['Timedout' printNl].
> ]

Hey again,

okay this is somehow related to Delay waiting on a Semaphore. Any idea how
this could be solved?

regards
        holger

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/03/2011 05:43 PM, Holger Hans Peter Freyther wrote:

> On 04/03/2011 04:58 PM, Holger Hans Peter Freyther wrote:
>
>>
>> Hi,
>> maybe you could help me to understand the Process/BlockClosure/Exception
>> interaction. I do have two issues. The first is that even if I manage to call
>> the timeout block I am still returning to the Delay and do not leave the
>> block. Any idea how I could leave the delay, execute all ensure blocks inside
>> the timeout?
>>
>> Eval [
>>     [(Delay forSeconds: 100000) wait] timeout: 1 do: ['Timedout' printNl].
>> ]
>

Hi again,

so Process>>#queueInterrupt: will leave the process suspended if it was
suspended during the interrupt. In my case I end with semaphore wait and no
other link is in the list. What will be the sequence of adding my own
queueInterrupt which will resume the process at the end? E.g. what happens if
we are on a socket?


                                [semaphore isNil
                                    ifTrue: [[self evaluate: aBlock
ifNotTerminated: [self suspend]]]
                                    ifFalse: [[self evaluate: aBlock
ifNotTerminated: [semaphore wait]]]].

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/03/2011 06:57 PM, Holger Hans Peter Freyther wrote:

>
> Hi again,
>
> so Process>>#queueInterrupt: will leave the process suspended if it was
> suspended during the interrupt. In my case I end with semaphore wait and no
> other link is in the list. What will be the sequence of adding my own
> queueInterrupt which will resume the process at the end? E.g. what happens if
> we are on a socket?
>

Hi Paolo,

this is my current version that seems to work on first sight. It would be
appreciated if you could comment about this approach and how wild it is and if
we could host this code in GST itself, maybe as a TimeOut module or such?


Notification subclass: TimeoutNotification [
    | blk |
    <category: 'osmo-misc'>
    <comment: 'I get send by the timeout handling of BlockClosures
and I am the indication that the time is up and that one should come
to and end.'>

    TimeoutNotification class >> on: aBlk [
        ^ self new
            block: aBlk; yourself
    ]

    block: aBlock [
        blk := aBlock
    ]

    block [
        ^ blk
    ]
]

Process extend [
    finishProcess: aBlock [
        "Stolen from queueInterrupt: but always resumes the Process"
        self interruptLock critical:
                [| block suspended |
                self isActive
                    ifTrue:
                        [aBlock value.
                        ^self].
                self isTerminated
                    ifTrue: [^SystemExceptions.ProcessTerminated signalOn: self].
                suspended := self isReady not.
                block := suspended
                            ifFalse:
                                [self suspend.
                                aBlock]
                            ifTrue:
                                [
                                 [self evaluate: aBlock ifNotTerminated: [self
resume]]].
                suspendedContext := block asContext: suspendedContext.
                self resume]
    ]
]

BlockClosure extend [
    timeout: seconds do: aBlock [
        "I will execute myself for up to seconds and if a timeout
        occurs I will invoke the aBlock. If the timeout occurs early
        not much of the block is executed yet. I also have some issues
        with Delays and not breaking these properly.
        "
        | delay sem proc value timeout |

        "Use the semaphore to signal that we executed everything"
        sem := Semaphore new.

        "Remember the current process"
        proc := Processor activeProcess.

        timeout := false.

        "Start the waiting."
        [[

            "Start a process to wait in and then signal"
            [| delay |
                delay := Delay forSeconds: seconds.

                "Wait and see if it is timed out. If so send a signal."
                (delay timedWaitOn: sem) ifTrue: [
                    proc finishProcess: [ ^ (TimeoutNotification on: self) signal].
                ].
            ] fork.

            value := self value.
        ] ensure: [sem signal]
        ] on: TimeoutNotification do: [:e |
            e block = self
                ifTrue:  [timeout := true]
                ifFalse: [e pass].
        ].

        "Make sure we call the ensure's first."
        ^ timeout
            ifTrue:  [^aBlock value]
            ifFalse: [^value].
    ]
]

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

Re: Timeouts for BlockClosures

Paolo Bonzini-2
On Sun, Apr 3, 2011 at 19:21, Holger Hans Peter Freyther
<[hidden email]> wrote:

> On 04/03/2011 06:57 PM, Holger Hans Peter Freyther wrote:
>
>>
>> Hi again,
>>
>> so Process>>#queueInterrupt: will leave the process suspended if it was
>> suspended during the interrupt. In my case I end with semaphore wait and no
>> other link is in the list. What will be the sequence of adding my own
>> queueInterrupt which will resume the process at the end? E.g. what happens if
>> we are on a socket?
>>
>
> Hi Paolo,
>
> this is my current version that seems to work on first sight. It would be
> appreciated if you could comment about this approach and how wild it is and if
> we could host this code in GST itself, maybe as a TimeOut module or such?

Nice code!

I think you need to change the handling of a suspended process too.
Perhaps it's better to have #finishProcess: implemented in terms of
exceptions, like #signalInterrupt:.  This way we know that the
resumption will look for an exception handler.

Also, for completeness I'd make the TimeoutNotification non-resumable.

Process extend [
 Â   signalInterrupt: anException [
 Â       self interruptLock critical:
 Â               [| block suspended |
 Â               self isActive
 Â                   ifTrue:
 Â                       [anException signal.
 Â                       ^self].
 Â               suspended := self isReady not.
 Â               block := [self evaluate: [anException signal]
                    ifNotTerminated: [suspended ifTrue: [self suspend]].
 Â               suspendedContext := block asContext: suspendedContext.
 Â               self resume]
 Â   ]
]

BlockClosure extend [
    "perhaps pass a Delay here? so you can timeout at a given
     clock value"
 Â   timeout: seconds do: aBlock [
       "I will execute myself for up to seconds and if a timeout
       occurs I will invoke the aBlock. If the timeout occurs early
       not much of the block is executed yet."

       | delay sem proc value timeout |
       "Use the semaphore to signal that we executed everything"
       sem := Semaphore new.

       "Remember the current process"
       proc := Processor activeProcess.

       timeout := false.

       "Start the waiting."
           "Start a process to wait in and then signal"
           [| delay |
               delay := Delay forSeconds: seconds.

               "Wait and see if it is timed out. If so send a signal."
               (delay timedWaitOn: sem) ifTrue: [
                      proc signalInterrupt: (TimeoutNotification on: self) ].
           ] fork.

       [[value := self value] ensure: [sem signal]]
              on: TimeoutNotification do: [:e |
   Â           e block = self
 Â               ifTrue:  [timeout := true. e return]
 Â               ifFalse: [e pass].
 Â       ].

       "Make sure we call the ensure's first."
       ^ timeout
           ifTrue:  [aBlock value]
           ifFalse: [value].
   ]
]

Untested---but if you have testcases I'll gladly merge it!  In
particular, I'd have said the last part could be written as

       ^[self ensure: [sem signal]]
              on: TimeoutNotification do: [:e |
              e block = self
                ifTrue:  [^aBlock value]
                ifFalse: [e pass] ]

but I suspect you found out it's not.

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/05/2011 08:57 AM, Paolo Bonzini wrote:

Hey,

thanks for your review!


>                 suspended := self isReady not.
>                 block := [self evaluate: [anException signal]
>                     ifNotTerminated: [suspended ifTrue: [self suspend]].
>                 suspendedContext := block asContext: suspendedContext.
>                 self resume]

The issue with the 'self suspend' is that if I use a Delay.. or Socket>>#next
my process is suspended so even if I 'break' the execution of this I will
suspend the process and it will not be woken up. From a VM safety point of
view, is it okay to just continue executing in the unwinded context? My
understanding is that when resuming the process the suspendContext (our
signal) will be executed and we just return from there then.


>
> Untested---but if you have testcases I'll gladly merge it!  In
> particular, I'd have said the last part could be written as
>
>        ^[self ensure: [sem signal]]
>               on: TimeoutNotification do: [:e |
>               e block = self
>                 ifTrue:  [^aBlock value]
>                 ifFalse: [e pass] ]
>
> but I suspect you found out it's not.
It depends of which semantic is nice. I somehow want to have all ensures be
handled before I dispatch the timeout. With the above the timeout would be
before the individual ensures. My test case is testing the order and you could
print the events Collection to see the change.

I have attached my current patch and test case and look forward for another
review of this change.

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

0001-timeout-Add-code-for-timeout-handling-on-BlockClosur.patch (9K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Timeouts for BlockClosures

Paolo Bonzini-2
Almost there indeed, thanks for clarifying!

First comment: please move the TimeoutNotification under the Kernel
namespace.

> +BlockClosure extend [
> +    timeout: seconds do: aBlock [

So what do you think about passing a delay here?  Or even making this
method Delay>>#value:onTimeout:?  Do you know what other Smalltalks do?

> +<category: '*timeout-private'>
> + "I will execute myself for up to seconds and if a timeout
> + occurs I will invoke the aBlock. If the timeout occurs early
> + not much of the block is executed yet. I also have some issues
> + with Delays and not breaking these properly.

Is the comment still accurate?

> +        [[
> +
> +            "Start a process to wait in and then signal"
> +            [| delay |
> +                delay := Delay forSeconds: seconds.
> +
> +                "Wait and see if it is timed out. If so send a signal."
> +                (delay timedWaitOn: sem) ifTrue: [
> +    proc signalInterrupt: (TimeoutNotification on: self).
> +                ].
> +            ] fork.
> +
> +            value := self value.
> +        ] ensure: [sem signal]

This can be written in a lighter way:

         [

             "Start a process to wait in and then signal"
             [| delay |
                 delay := Delay forSeconds: seconds.

                 "Wait and see if it is timed out. If so send a signal."
                 (delay timedWaitOn: sem) ifTrue: [
                   proc signalInterrupt: (TimeoutNotification on: self)]
             ] fork.

             value := self ensure: [sem signal]

> +        ] on: TimeoutNotification do: [:e |
> +            e block = self
> +                ifTrue:  [timeout := true]
> +                ifFalse: [e pass].
> +        ].
> +
> +        "Make sure we call the ensure's first."
> +        ^ timeout
> +            ifTrue:  [^aBlock value]
> +            ifFalse: [^value].

No returns within ifTrue/ifFalse blocks.

> +    ]
> +]

> +            ] timeout: 1 do: [events add: 'timeout'].

Larger timeout, please (1s for example).

Thanks!

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/06/2011 08:45 AM, Paolo Bonzini wrote:
> Almost there indeed, thanks for clarifying!
>
> First comment: please move the TimeoutNotification under the Kernel namespace.
>
>> +BlockClosure extend [
>> +    timeout: seconds do: aBlock [
>
> So what do you think about passing a delay here?  Or even making this method
> Delay>>#value:onTimeout:?  Do you know what other Smalltalks do?

I am not sure. So far I have only seen individual timeouts for socket
operations. I am going to browse the Pharo code and see if there are some
constructs for timeout handling. I would like to be able to either pass a
Delay (for subseconds) or the seconds as Number. Maybe have two selectors and
make the one with a Number create the delay?



>
>> +<category: '*timeout-private'>
>> +    "I will execute myself for up to seconds and if a timeout
>> +    occurs I will invoke the aBlock. If the timeout occurs early
>> +    not much of the block is executed yet. I also have some issues
>> +    with Delays and not breaking these properly.
>
> Is the comment still accurate?

No, I will update it.



>> +    ]
>> +]
>
>> +            ] timeout: 1 do: [events add: 'timeout'].
>
> Larger timeout, please (1s for example).

The number is treated as a second already. The result will make sure that the
internal blocks has been executed, on a slow system the 1s might be too low.

will send an updated patch later today
        holger

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

Re: Timeouts for BlockClosures

Paolo Bonzini-2
On 04/06/2011 10:56 AM, Holger Hans Peter Freyther wrote:
> The number is treated as a second already. The result will make sure that the
> internal blocks has been executed, on a slow system the 1s might be too low.

No, I thought it was milliseconds.

I think I made up my mind on the Delay :)

Let's make this method Delay>>#value:onTimeoutDo:.

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/06/2011 11:06 AM, Paolo Bonzini wrote:
> On 04/06/2011 10:56 AM, Holger Hans Peter Freyther wrote:
>> The number is treated as a second already. The result will make sure that the
>> internal blocks has been executed, on a slow system the 1s might be too low.
>
> No, I thought it was milliseconds.
>
> I think I made up my mind on the Delay :)
>
> Let's make this method Delay>>#value:onTimeoutDo:.

(Delay forSeconds: 3)
        value: [the block to execute]
        onTimeoutDo: [the block to handle on timeout?]


vs.

[
  the block to execute.
] timeout: (Delay forSeconds: 3) do: [the block to handle]


I still like the BlockClosure extension more as for me it looks like the main
thing that is happening is the block and the timeout case is just secondary.

Are you settled on Delay>>#value:onTimeoutDo:?

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

Re: Timeouts for BlockClosures

Paolo Bonzini-2
On 04/06/2011 11:16 AM, Holger Hans Peter Freyther wrote:
> I still like the BlockClosure extension more as for me it looks like the main
> thing that is happening is the block and the timeout case is just secondary.
>
> Are you settled on Delay>>#value:onTimeoutDo:?

Yes, as the primary method.  You can add an extension on BlockClosure
yourself.

Squeak has BlockClosure>>#valueWithin:onTimeoutDo: but it accepts a
Duration.

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/06/2011 11:29 AM, Paolo Bonzini wrote:

>
> Yes, as the primary method.  You can add an extension on BlockClosure yourself.
>
> Squeak has BlockClosure>>#valueWithin:onTimeoutDo: but it accepts a Duration.
>

drat, I thought I invented something. Should we do something similar? Or is
the summary:

Implement this as part of delay, provide syntactic sugar for BlockClosures
(myself)?

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

Re: Timeouts for BlockClosures

Paolo Bonzini-2
On 04/06/2011 11:35 AM, Holger Hans Peter Freyther wrote:
>> >  Yes, as the primary method.  You can add an extension on BlockClosure yourself.
>> >
>> >  Squeak has BlockClosure>>#valueWithin:onTimeoutDo: but it accepts a Duration.
>> >
> drat, I thought I invented something. Should we do something similar?

No, accepting a Duration is clearly wrong because it doesn't allow
untilMilliseconds waits.

> Implement this as part of delay, provide syntactic sugar for BlockClosures
> (myself)?

Yes, thanks for putting up with me. :)

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/06/2011 11:42 AM, Paolo Bonzini wrote:

>
> Yes, thanks for putting up with me. :)

Thanks for your time and input. Feel free to remove the syntactic sugar part
or ask me to do it.

holger

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

0001-timeout-Add-code-for-timeout-handling-on-BlockClosur.patch (10K) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Timeouts for BlockClosures

Paolo Bonzini-2
On 04/11/2011 11:23 PM, Holger Hans Peter Freyther wrote:
> Thanks for your time and input. Feel free to remove the syntactic sugar part
> or ask me to do it.

Done, and moved everything to kernel/ and tests/delays.st.

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/12/2011 09:40 AM, Paolo Bonzini wrote:
> On 04/11/2011 11:23 PM, Holger Hans Peter Freyther wrote:
>> Thanks for your time and input. Feel free to remove the syntactic sugar part
>> or ask me to do it.
>
> Done, and moved everything to kernel/ and tests/delays.st.
>

I have found a funny bug but I don't know the source of it and could need a
pointer.


a) socket := Socket remote: ... port...
b) write N bytes into the socket


a) socket next: N.
a) socket readBuffer inspect (ptr is beyond endPtr)

(Delay forSeconds: 3)
        value: [socket next: N]
        onTimeoutDo: [a) socket readBuffer.. -> ptr is back to 1]

so there must be some ensure: [] block that resets the endptr. Would you know
where to find it? is there also some kind of watchpoint support in GST?

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

Re: Timeouts for BlockClosures

Paolo Bonzini-2
On 04/20/2011 08:35 PM, Holger Hans Peter Freyther wrote:
> (Delay forSeconds: 3)
> value: [socket next: N]
> onTimeoutDo: [a) socket readBuffer.. ->  ptr is back to 1]
>
> so there must be some ensure: [] block that resets the endptr.

No, it's just that "ptr := 1" is set before calling the fillBlock.  I
can apply this patch:

diff --git a/packages/sockets/Buffers.st b/packages/sockets/Buffers.st
index 2084797..de02511 100644
--- a/packages/sockets/Buffers.st
+++ b/packages/sockets/Buffers.st
@@ -137,8 +137,8 @@ evaluates an user defined block to try to get some more data.'>
  <category: 'buffer handling'>
  self basicAtEnd ifFalse: [^false].
  fillBlock isNil ifTrue: [^true].
- ptr := 1.
  endPtr := fillBlock value: collection value: collection size.
+ ptr := 1.
  ^self basicAtEnd
     ]
 

but you're walking on thin ice here.  Every time you have a timeout,
you should assume that the data structures are in an inconsistent
state (just like when you #terminate a Process).  I suggest making
your sockets unbuffered if it's not too much overhead.

Paolo

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

Re: Timeouts for BlockClosures

Holger Freyther
On 04/21/2011 07:52 AM, Paolo Bonzini wrote:

> but you're walking on thin ice here.  Every time you have a timeout,
> you should assume that the data structures are in an inconsistent
> state (just like when you #terminate a Process).  I suggest making
> your sockets unbuffered if it's not too much overhead.

Right. It is not Erlang after all and we have side-effects. I am not sure on
the semantics of the following. My work around would be something like

[
        socket waitUntilItCanRead
] timeout...


but I am not sure if canRead and such will behave better.

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