Re: [Pharo-project] Another finalization concern: error handling

2010-10-12 Thread Henrik Johansen


Den 11. okt. 2010 kl. 22:17 skrev Igor Stasenko siguc...@gmail.com:

 
 Also, i used #ensure: and #ifCurtailed: but i tend to forget where
 they are applicable and how.
 So, little help in this regard will be wellcome.
Ensure: block always execute. IfCurtailed blocks only run if an error is 
encountered, or the thread is terminated.

Cheers,
Henry


___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-12 Thread Henrik Johansen

On Oct 11, 2010, at 10:17 18PM, Igor Stasenko wrote:

 On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,
 
 The most important words in there are critical section.  Carry on :)
 
 
 Oh, please. This is not too hard to code.
 
 My mind rolling around following choice(s)  (there may be others i don't see).
 What would be a proper way to handle error during #finalize.
 
 [ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
 ].
 
 or:
 
 [ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
 ].
 
 
 of course, i should catch this error in test, so i can verify that:
 
 a) test is get notified upon synthetically made error
 b) no matter what i do inside error handler (up to 'Processor
 activeProcess terminate'), a finalization process continues working
 (or restarts without losing remainder of executors).
 

I agree it should be the executor doing handling.
However, if you get to this point, the executor already had the chance to do so 
in the finalize method itself, so I don't really see the point of sending it 
back..

Personally, I feel the only promises FinalizationRegistry should make wrt. to 
errors during finalization, is it should never lead to:
- termination of the (or a) finalization process, 
- discarding another finalization action.

IE I am perfectly fine with an error here being thrown in your face (hopefully 
in a somewhat debuggable way, unlike what happened in your first example when 
removing the error-swallowing), as you've already passed the point a correction 
should be made, and there's nothing more intelligible to do than making sure 
everything keeps working, and inform of the error.
(Pretty sure the error swallowing was a quick hack for keeping everything 
working in the first place ;) )

Cheers,
Henry
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-12 Thread Igor Stasenko
On 12 October 2010 14:25, Henrik Johansen henrik.s.johan...@veloxit.no wrote:

 On Oct 11, 2010, at 10:17 18PM, Igor Stasenko wrote:

 On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The most important words in there are critical section.  Carry on :)


 Oh, please. This is not too hard to code.

 My mind rolling around following choice(s)  (there may be others i don't 
 see).
 What would be a proper way to handle error during #finalize.

 [ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
 ].

 or:

 [ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
 ].


 of course, i should catch this error in test, so i can verify that:

 a) test is get notified upon synthetically made error
 b) no matter what i do inside error handler (up to 'Processor
 activeProcess terminate'), a finalization process continues working
 (or restarts without losing remainder of executors).


 I agree it should be the executor doing handling.
 However, if you get to this point, the executor already had the chance to do 
 so in the finalize method itself, so I don't really see the point of sending 
 it back..


well,  its easier to add a default error handler in Object class, so
any executor will have a default handler,
and then some specific one may choose to override it, without putting
a boilerplate of [ ] on: .. do: [] in every #finalize method.
Besides, its natural , when you writing a code, you always expect that
it will work w/o errors,
and even if it fails, then in some concrete place, which means you
usually not wrapping whole thing with exception handler.
This leaves a chance to make another mistakes, like 'hey, despite i
put error handler in my #finalize, something is still hangs
finalization process'.


 Personally, I feel the only promises FinalizationRegistry should make wrt. to 
 errors during finalization, is it should never lead to:
 - termination of the (or a) finalization process,
 - discarding another finalization action.

Yes this is the main intent.


 IE I am perfectly fine with an error here being thrown in your face 
 (hopefully in a somewhat debuggable way, unlike what happened in your first 
 example when removing the error-swallowing), as you've already passed the 
 point a correction should be made, and there's nothing more intelligible to 
 do than making sure everything keeps working, and inform of the error.

 (Pretty sure the error swallowing was a quick hack for keeping everything 
 working in the first place ;) )

What i like in doing #finalize in forked process, that it doesn't
matter where you screwed up: in finalization code or even in error
handling code, you still don't have a chance to damage the system. And
moreover, you can open debugger and debug it.

Spice must flooow :)

 Cheers,
 Henry
 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-12 Thread Henrik Johansen

On Oct 12, 2010, at 2:00 42PM, Igor Stasenko wrote:

 On 12 October 2010 14:25, Henrik Johansen henrik.s.johan...@veloxit.no 
 wrote:
 
 On Oct 11, 2010, at 10:17 18PM, Igor Stasenko wrote:
 
 On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,
 
 The most important words in there are critical section.  Carry on :)
 
 
 Oh, please. This is not too hard to code.
 
 My mind rolling around following choice(s)  (there may be others i don't 
 see).
 What would be a proper way to handle error during #finalize.
 
 [ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
 ].
 
 or:
 
 [ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
 ].
 
 
 of course, i should catch this error in test, so i can verify that:
 
 a) test is get notified upon synthetically made error
 b) no matter what i do inside error handler (up to 'Processor
 activeProcess terminate'), a finalization process continues working
 (or restarts without losing remainder of executors).
 
 
 I agree it should be the executor doing handling.
 However, if you get to this point, the executor already had the chance to do 
 so in the finalize method itself, so I don't really see the point of sending 
 it back..
 
 
 well,  its easier to add a default error handler in Object class, so
 any executor will have a default handler,
 and then some specific one may choose to override it, without putting
 a boilerplate of [ ] on: .. do: [] in every #finalize method.
 Besides, its natural , when you writing a code, you always expect that
 it will work w/o errors,
 and even if it fails, then in some concrete place, which means you
 usually not wrapping whole thing with exception handler.
 This leaves a chance to make another mistakes, like 'hey, despite i
 put error handler in my #finalize, something is still hangs
 finalization process'.

At which point I'd go Fix the damn handlers in the finalize method rather 
than add more indirection ;) KISS.
You still have to write the handling if you do encounter an error, whether that 
initial error is #dnu handleFinalizationError:, or the actual error is of 
little consequence.  
What we want away from, is the default case now where an unhandled error is 
assumed to be inconsequential and simply skipped over by default

 
 
 Personally, I feel the only promises FinalizationRegistry should make wrt. 
 to errors during finalization, is it should never lead to:
 - termination of the (or a) finalization process,
 - discarding another finalization action.
 
 Yes this is the main intent.
 
 
 IE I am perfectly fine with an error here being thrown in your face 
 (hopefully in a somewhat debuggable way, unlike what happened in your first 
 example when removing the error-swallowing), as you've already passed the 
 point a correction should be made, and there's nothing more intelligible to 
 do than making sure everything keeps working, and inform of the error.
 
 (Pretty sure the error swallowing was a quick hack for keeping everything 
 working in the first place ;) )
 
 What i like in doing #finalize in forked process, that it doesn't
 matter where you screwed up: in finalization code or even in error
 handling code, you still don't have a chance to damage the system. And
 moreover, you can open debugger and debug it.
 
 Spice must flooow :)
How about something like: (warning, untested code)

WeakArray  finalizationProcess

^[[[true] whileTrue:
[FinalizationSemaphore wait.
FinalizationLock critical:
[FinalizationDependents do:
[:weakDependent |
weakDependent ifNotNil:
[weakDependent finalizeValues] 
ifCurtailed: [self startFinalizationProcess]] newProcess 
priority:  Processor userInterruptPriority

WeakArray startFinalizationProcess


FinalizationSemaphore := Smalltalk specialObjectsArray at: 42.
FinalizationDependents ifNil: [FinalizationDependents := WeakArray new: 
10].
FinalizationLock := Semaphore forMutualExclusion.
FinalizationProcess := self finalizationProcess.
FinalizationProcess resume

WeakArray restartFinalizationProcess
Killing the current Finalization process will start a new one
FinalizationProcess terminate

WeakRegistry finalizeValues:

snip
self finalize: finiObjects

WeakArray  finalize: finalizationObjects
[[finalizationObjects isEmpty] 
whileFalse: [finalizationObjects removeFirst finalize]]
 on: Error
do: [:error | 
self finalize: (finalizationObjects).
error pass].

The last has some issues of course, if more than one error is encountered, the 
first ones won't be passed if the last ones are terminated.
Changing it to fork of the error block would mean having to 

Re: [Pharo-project] Another finalization concern: error handling

2010-10-12 Thread Igor Stasenko
On 12 October 2010 15:33, Henrik Johansen henrik.s.johan...@veloxit.no wrote:

 On Oct 12, 2010, at 2:00 42PM, Igor Stasenko wrote:

 On 12 October 2010 14:25, Henrik Johansen henrik.s.johan...@veloxit.no 
 wrote:

 On Oct 11, 2010, at 10:17 18PM, Igor Stasenko wrote:

 On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The most important words in there are critical section.  Carry on :)


 Oh, please. This is not too hard to code.

 My mind rolling around following choice(s)  (there may be others i don't 
 see).
 What would be a proper way to handle error during #finalize.

 [ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
 ].

 or:

 [ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
 ].


 of course, i should catch this error in test, so i can verify that:

 a) test is get notified upon synthetically made error
 b) no matter what i do inside error handler (up to 'Processor
 activeProcess terminate'), a finalization process continues working
 (or restarts without losing remainder of executors).


 I agree it should be the executor doing handling.
 However, if you get to this point, the executor already had the chance to 
 do so in the finalize method itself, so I don't really see the point of 
 sending it back..


 well,  its easier to add a default error handler in Object class, so
 any executor will have a default handler,
 and then some specific one may choose to override it, without putting
 a boilerplate of [ ] on: .. do: [] in every #finalize method.
 Besides, its natural , when you writing a code, you always expect that
 it will work w/o errors,
 and even if it fails, then in some concrete place, which means you
 usually not wrapping whole thing with exception handler.
 This leaves a chance to make another mistakes, like 'hey, despite i
 put error handler in my #finalize, something is still hangs
 finalization process'.

 At which point I'd go Fix the damn handlers in the finalize method rather 
 than add more indirection ;) KISS.
 You still have to write the handling if you do encounter an error, whether 
 that initial error is #dnu handleFinalizationError:, or the actual error is 
 of little consequence.
 What we want away from, is the default case now where an unhandled error is 
 assumed to be inconsequential and simply skipped over by default



 Personally, I feel the only promises FinalizationRegistry should make wrt. 
 to errors during finalization, is it should never lead to:
 - termination of the (or a) finalization process,
 - discarding another finalization action.

 Yes this is the main intent.


 IE I am perfectly fine with an error here being thrown in your face 
 (hopefully in a somewhat debuggable way, unlike what happened in your first 
 example when removing the error-swallowing), as you've already passed the 
 point a correction should be made, and there's nothing more intelligible to 
 do than making sure everything keeps working, and inform of the error.

 (Pretty sure the error swallowing was a quick hack for keeping everything 
 working in the first place ;) )

 What i like in doing #finalize in forked process, that it doesn't
 matter where you screwed up: in finalization code or even in error
 handling code, you still don't have a chance to damage the system. And
 moreover, you can open debugger and debug it.

 Spice must flooow :)
 How about something like: (warning, untested code)

 WeakArray  finalizationProcess

        ^[[[true] whileTrue:
                [FinalizationSemaphore wait.
                FinalizationLock critical:
                        [FinalizationDependents do:
                                [:weakDependent |
                                weakDependent ifNotNil:
                                        [weakDependent finalizeValues]
                ifCurtailed: [self startFinalizationProcess]] newProcess 
 priority:  Processor userInterruptPriority

 WeakArray startFinalizationProcess


        FinalizationSemaphore := Smalltalk specialObjectsArray at: 42.
        FinalizationDependents ifNil: [FinalizationDependents := WeakArray 
 new: 10].
        FinalizationLock := Semaphore forMutualExclusion.
        FinalizationProcess := self finalizationProcess.
        FinalizationProcess resume

 WeakArray restartFinalizationProcess
        Killing the current Finalization process will start a new one
        FinalizationProcess terminate

 WeakRegistry finalizeValues:

 snip
 self finalize: finiObjects

 WeakArray  finalize: finalizationObjects
        [[finalizationObjects isEmpty]
                whileFalse: [finalizationObjects removeFirst finalize]]
                 on: Error
                do: [:error |
                        self finalize: (finalizationObjects).
                        error pass].

 The last has some issues of course, if more than one error is encountered, 
 the first ones won't be passed if the last ones are 

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 11 October 2010 14:40, Igor Stasenko siguc...@gmail.com wrote:
 Hello,

 here a situation, with which we can deal in more safer manner:

 Suppose you have a weak registry, populated by different objects and
 their executors.

 Now, when some of them died, a weak registry performs finalization.

 The potential danger is , that if there's an error triggered by some
 executor(s),
 then rest of executors will have no chance to run and will be
 forgotten, causing memory leakage.

 What you think, should we handle this more graciously?

 (Consider a following meta-code)

 WeakRegistryfinalizeValues
 | executors |
  executors := self gatherExecutorsToRun.

  executors do: [:ex |
     [ ex finalize ] fork.
  ].


oh, and this gets even more complicated, if we keep supporting
multiple finalizers per single object. :)

executors do: [:ex |
  ex hasMultipleExecutors ifTrue: [ ex do: [ :eex |   [ eex finalize ] fork ] ]
  ifFalse: [  [ ex finalize ] fork ].



 in this way, if any executor's #finalize causing error, it won't
 interfere with other executors, and they will accomplish their task
 normally.
 Of course, i'm not saying that we should use #fork for this, because
 it is costly. Similar could be done w/o forking.
 I just wanted to show a simplest code with which we could achieve a
 more gracious error handling.

 P.S. of course, in a first place it would be good to make sure that we
 writing executors, which can't cause an error during finalization.
 But bad things happen, and we should make sure that rest of system
 won't be put on its knees because of some stupid bug in a single
 #finalize.

 --
 Best regards,
 Igor Stasenko AKA sig.




-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Levente Uzonyi

On Mon, 11 Oct 2010, Igor Stasenko wrote:


Hello,

here a situation, with which we can deal in more safer manner:

Suppose you have a weak registry, populated by different objects and
their executors.

Now, when some of them died, a weak registry performs finalization.

The potential danger is , that if there's an error triggered by some
executor(s),
then rest of executors will have no chance to run and will be
forgotten, causing memory leakage.

What you think, should we handle this more graciously?

(Consider a following meta-code)

WeakRegistryfinalizeValues
| executors |
 executors := self gatherExecutorsToRun.

 executors do: [:ex |
[ ex finalize ] fork.
 ].


The gatherExecutorsToRun part was implemented in the previous version 
of WeakRegistry (history is not available from the image...). #finalize 
wasn't sent from the protected block. The current version lacks it, so it 
will deadlock if a finalizer will try to access the same WeakRegistry. 
Other kind of deadlocks are also possible. For example when a finalizer 
can access a semaphore which is also used by another process that 
uses the same semaphore and also uses the WeakRegistry, but locks them in 
a different order (JNIPort).
This only happens if the VM doesn't support the new finalization scheme 
which is the case for most current VMs.


There is another issue with removal, and this affects the new finalization 
scheme too, because the finalizer of valuesDictionary is #finalizeValues. 
This means that finalization can happen in a process other than the

finalization process. This can lead to random errors.

So I think parts of the old WeakRegistry implementation should be 
restored, like:

- WeakRegistry should collect executors
- executors should be evaluated outside the protected block



in this way, if any executor's #finalize causing error, it won't
interfere with other executors, and they will accomplish their task
normally.
Of course, i'm not saying that we should use #fork for this, because
it is costly. Similar could be done w/o forking.
I just wanted to show a simplest code with which we could achieve a
more gracious error handling.


Wouldn't it be better to use an exception handler?


Levente



P.S. of course, in a first place it would be good to make sure that we
writing executors, which can't cause an error during finalization.
But bad things happen, and we should make sure that rest of system
won't be put on its knees because of some stupid bug in a single
#finalize.

--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project



___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Levente,

Ok, but just because the system saves us at the last instant does not mean that 
we should be going out of our way to multiply free external resources.  Files 
are well known to the vm; other things (GSL vectors/matrices comes to mind) 
will not enjoy such protections.  This strikes me as a feature that got added 
when errors arose from attempts to add redundant executors, ultimately due to 
lack of thread safety.  Many things that are being fixed at great cost got 
started (it sure seems) because someone added a feature or placed something in 
or too near to Object only to avoid errors vs. finding and fixing the real 
problem.

Maybe you have made a strong argument for multiple executors; if so, I've 
missed it.  Right now, it looks like a design flaw instead of a feature.

Bill




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
[le...@elte.hu]
Sent: Monday, October 11, 2010 10:24 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:

 Levente,

 A similar discussion arose around Dolphin's event (#trigger*) mechanism.  My 
 recollection is that it was not fully addressed due to performance concerns.  
 Forking and error handlers both have their costs.  I'm not saying we should 
 necessarily follow (we probably should not), though with careful design, an 
 interrupted chain of events might survive to be handled on a subsequent 
 attempt.

 I am far more worried about having multiple executors per object (when did 
 p=malloc();free(p);free(p);free(p) become good style?) than I am about 
 getting the finalizer process itself completely robust at this point.

Smalltalk is not C. Try this:

| file |
file := StandardFileStream fileNamed: 'foo.txt'.
file close.
file primClose: (file instVarNamed: #fileID).
Those pesky plugins save us all the time. ;)


Levente


 Bill



 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
 [le...@elte.hu]
 Sent: Monday, October 11, 2010 9:51 AM
 To: Pharo Development
 Cc: The general-purpose Squeak developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On Mon, 11 Oct 2010, Igor Stasenko wrote:

 Hello,

 here a situation, with which we can deal in more safer manner:

 Suppose you have a weak registry, populated by different objects and
 their executors.

 Now, when some of them died, a weak registry performs finalization.

 The potential danger is , that if there's an error triggered by some
 executor(s),
 then rest of executors will have no chance to run and will be
 forgotten, causing memory leakage.

 What you think, should we handle this more graciously?

 (Consider a following meta-code)

 WeakRegistryfinalizeValues
 | executors |
  executors := self gatherExecutorsToRun.

  executors do: [:ex |
 [ ex finalize ] fork.
  ].

 The gatherExecutorsToRun part was implemented in the previous version
 of WeakRegistry (history is not available from the image...). #finalize
 wasn't sent from the protected block. The current version lacks it, so it
 will deadlock if a finalizer will try to access the same WeakRegistry.
 Other kind of deadlocks are also possible. For example when a finalizer
 can access a semaphore which is also used by another process that
 uses the same semaphore and also uses the WeakRegistry, but locks them in
 a different order (JNIPort).
 This only happens if the VM doesn't support the new finalization scheme
 which is the case for most current VMs.

 There is another issue with removal, and this affects the new finalization
 scheme too, because the finalizer of valuesDictionary is #finalizeValues.
 This means that finalization can happen in a process other than the
 finalization process. This can lead to random errors.

 So I think parts of the old WeakRegistry implementation should be
 restored, like:
 - WeakRegistry should collect executors
 - executors should be evaluated outside the protected block


 in this way, if any executor's #finalize causing error, it won't
 interfere with other executors, and they will accomplish their task
 normally.
 Of course, i'm not saying that we should use #fork for this, because
 it is costly. Similar could be done w/o forking.
 I just wanted to show a simplest code with which we could achieve a
 more gracious error handling.

 Wouldn't it be better to use an exception handler?


 Levente


 P.S. of course, in a first place it would be good to make sure that we
 writing executors, which can't cause an error during finalization.
 But bad things happen, and we should make sure that rest of system
 won't be put on its knees because of some stupid bug in a single
 #finalize.

 --
 Best regards,
 Igor Stasenko AKA sig

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 11 October 2010 17:24, Levente Uzonyi le...@elte.hu wrote:
 On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:

 Levente,

 A similar discussion arose around Dolphin's event (#trigger*) mechanism.
  My recollection is that it was not fully addressed due to performance
 concerns.  Forking and error handlers both have their costs.  I'm not saying
 we should necessarily follow (we probably should not), though with careful
 design, an interrupted chain of events might survive to be handled on a
 subsequent attempt.

 I am far more worried about having multiple executors per object (when did
 p=malloc();free(p);free(p);free(p) become good style?) than I am about
 getting the finalizer process itself completely robust at this point.

 Smalltalk is not C. Try this:

 | file |
 file := StandardFileStream fileNamed: 'foo.txt'.
 file close.
 file primClose: (file instVarNamed: #fileID).
 Those pesky plugins save us all the time. ;)



Don't let me starting again on this.
You proposing to care about it in multiple various places, where we
could fix it in a single one.
It is like adding ifNotNil: test at each place you using setter,
instead of putting a single ifNotNil: test inside a setter itself.


try this:

coll := OrderedCollection new.
obj := Object new.
wrapper := WeakArray with: obj.
coll add: wrapper.

obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.

obj := nil.
Smalltalk garbageCollect.


The above works silently only because ObjectFinalizer simply swallows
any errors:

ObjectFinalizerfinalize
Finalize the resource associated with the receiver. This message
should only be sent during the finalization process. There is NO
garantuee that the resource associated with the receiver hasn't been
free'd before so take care that you don't run into trouble - this all
may happen with interrupt priority.
[self value] on: Error do:[:ex| ex return].

now, replace this implementation with just
self value
and you'll see what will happen.

Such behavior is completely unacceptable in terms of finding the bugs
 problems in your code.



-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Levente Uzonyi

On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:


Levente,

Ok, but just because the system saves us at the last instant does not mean that 
we should be going out of our way to multiply free external resources.  Files 
are well known to the vm; other things (GSL vectors/matrices comes to mind) 
will not enjoy such protections.  This strikes me as a feature that got added 
when errors arose from attempts to add redundant executors, ultimately due to 
lack of thread safety.  Many things that are being fixed at great cost got 
started (it sure seems) because someone added a feature or placed something in 
or too near to Object only to avoid errors vs. finding and fixing the real 
problem.

Maybe you have made a strong argument for multiple executors; if so, I've 
missed it.  Right now, it looks like a design flaw instead of a feature.


There's code that relies on multiple executors. Every object understands 
#toFinalizeSend:to:with:. When you use it, you expect that your finalizer 
will be evaluated when the object is garbage collected.


Btw I offered a simple solution for cases like yours. The behavior of 
WeakRegistry  #add:executor: can be easily made pluggable when an 
object has an executor in the registry.



Levente

P.S.: how will you use GSL knowing that it's license is GPL? Will you 
keep the code for yourself or release it under the GPL license?




Bill




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
[le...@elte.hu]
Sent: Monday, October 11, 2010 10:24 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:


Levente,

A similar discussion arose around Dolphin's event (#trigger*) mechanism.  My 
recollection is that it was not fully addressed due to performance concerns.  
Forking and error handlers both have their costs.  I'm not saying we should 
necessarily follow (we probably should not), though with careful design, an 
interrupted chain of events might survive to be handled on a subsequent attempt.

I am far more worried about having multiple executors per object (when did 
p=malloc();free(p);free(p);free(p) become good style?) than I am about getting 
the finalizer process itself completely robust at this point.


Smalltalk is not C. Try this:

| file |
file := StandardFileStream fileNamed: 'foo.txt'.
file close.
file primClose: (file instVarNamed: #fileID).
Those pesky plugins save us all the time. ;)


Levente



Bill




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
[le...@elte.hu]
Sent: Monday, October 11, 2010 9:51 AM
To: Pharo Development
Cc: The general-purpose Squeak developers list
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Mon, 11 Oct 2010, Igor Stasenko wrote:


Hello,

here a situation, with which we can deal in more safer manner:

Suppose you have a weak registry, populated by different objects and
their executors.

Now, when some of them died, a weak registry performs finalization.

The potential danger is , that if there's an error triggered by some
executor(s),
then rest of executors will have no chance to run and will be
forgotten, causing memory leakage.

What you think, should we handle this more graciously?

(Consider a following meta-code)

WeakRegistryfinalizeValues
| executors |
 executors := self gatherExecutorsToRun.

 executors do: [:ex |
[ ex finalize ] fork.
 ].


The gatherExecutorsToRun part was implemented in the previous version
of WeakRegistry (history is not available from the image...). #finalize
wasn't sent from the protected block. The current version lacks it, so it
will deadlock if a finalizer will try to access the same WeakRegistry.
Other kind of deadlocks are also possible. For example when a finalizer
can access a semaphore which is also used by another process that
uses the same semaphore and also uses the WeakRegistry, but locks them in
a different order (JNIPort).
This only happens if the VM doesn't support the new finalization scheme
which is the case for most current VMs.

There is another issue with removal, and this affects the new finalization
scheme too, because the finalizer of valuesDictionary is #finalizeValues.
This means that finalization can happen in a process other than the
finalization process. This can lead to random errors.

So I think parts of the old WeakRegistry implementation should be
restored, like:
- WeakRegistry should collect executors
- executors should be evaluated outside the protected block



in this way, if any executor's #finalize causing error, it won't
interfere with other executors, and they will accomplish their task
normally.
Of course, i'm not saying that we should use #fork for this, because
it is costly. Similar could

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Levente Uzonyi

On Mon, 11 Oct 2010, Igor Stasenko wrote:


On 11 October 2010 17:24, Levente Uzonyi le...@elte.hu wrote:
On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:


Levente,

A similar discussion arose around Dolphin's event (#trigger*) mechanism.
 My recollection is that it was not fully addressed due to performance
concerns.  Forking and error handlers both have their costs.  I'm not saying
we should necessarily follow (we probably should not), though with careful
design, an interrupted chain of events might survive to be handled on a
subsequent attempt.

I am far more worried about having multiple executors per object (when did
p=malloc();free(p);free(p);free(p) become good style?) than I am about
getting the finalizer process itself completely robust at this point.


Smalltalk is not C. Try this:

| file |
file := StandardFileStream fileNamed: 'foo.txt'.
file close.
file primClose: (file instVarNamed: #fileID).
Those pesky plugins save us all the time. ;)




Don't let me starting again on this.
You proposing to care about it in multiple various places, where we
could fix it in a single one.
It is like adding ifNotNil: test at each place you using setter,
instead of putting a single ifNotNil: test inside a setter itself.


try this:

coll := OrderedCollection new.
obj := Object new.
wrapper := WeakArray with: obj.
coll add: wrapper.

obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.

obj := nil.
Smalltalk garbageCollect.


The above works silently only because ObjectFinalizer simply swallows
any errors:

ObjectFinalizerfinalize
Finalize the resource associated with the receiver. This message
should only be sent during the finalization process. There is NO
garantuee that the resource associated with the receiver hasn't been
free'd before so take care that you don't run into trouble - this all
may happen with interrupt priority.
[self value] on: Error do:[:ex| ex return].

now, replace this implementation with just
self value
and you'll see what will happen.

Such behavior is completely unacceptable in terms of finding the bugs
 problems in your code.



Interrupting the finalization process is also a bad idea, so we need a 
better solution.



Levente

--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Sig,

I'm not saying to leave the finalizer wide open to the wrath of errors from 
poorly coded objects.  I am saying that we should strive for one finalizer per 
object (preferably the object itself) and that to get there, we need to make 
the registry thread safe and have some vm support.  Failing the latter, the 
object can't be its own executor, but there still should be at most one 
executor per object.  Any errors should be raised on the attempt to create the 
second executor.  Arrange for that, and somebody somewhere will ask whether all 
of this should be thread safe.

BTW, Dolphin treats #beFinalizable/#beUnfinalizable by manipulating a mask that 
controls the vm behavior - haven't looked in a while, but it must be part of 
the object header.  An object can thus be marked as finalizable or not any 
number of times during its life; no objects are created thanks to the vm 
support.

Bill





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
[siguc...@gmail.com]
Sent: Monday, October 11, 2010 10:47 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On 11 October 2010 17:24, Levente Uzonyi le...@elte.hu wrote:
 On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:

 Levente,

 A similar discussion arose around Dolphin's event (#trigger*) mechanism.
  My recollection is that it was not fully addressed due to performance
 concerns.  Forking and error handlers both have their costs.  I'm not saying
 we should necessarily follow (we probably should not), though with careful
 design, an interrupted chain of events might survive to be handled on a
 subsequent attempt.

 I am far more worried about having multiple executors per object (when did
 p=malloc();free(p);free(p);free(p) become good style?) than I am about
 getting the finalizer process itself completely robust at this point.

 Smalltalk is not C. Try this:

 | file |
 file := StandardFileStream fileNamed: 'foo.txt'.
 file close.
 file primClose: (file instVarNamed: #fileID).
 Those pesky plugins save us all the time. ;)



Don't let me starting again on this.
You proposing to care about it in multiple various places, where we
could fix it in a single one.
It is like adding ifNotNil: test at each place you using setter,
instead of putting a single ifNotNil: test inside a setter itself.


try this:

coll := OrderedCollection new.
obj := Object new.
wrapper := WeakArray with: obj.
coll add: wrapper.

obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.

obj := nil.
Smalltalk garbageCollect.


The above works silently only because ObjectFinalizer simply swallows
any errors:

ObjectFinalizerfinalize
Finalize the resource associated with the receiver. This message
should only be sent during the finalization process. There is NO
garantuee that the resource associated with the receiver hasn't been
free'd before so take care that you don't run into trouble - this all
may happen with interrupt priority.
[self value] on: Error do:[:ex| ex return].

now, replace this implementation with just
self value
and you'll see what will happen.

Such behavior is completely unacceptable in terms of finding the bugs
 problems in your code.



--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 11 October 2010 17:34, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Levente,

 Ok, but just because the system saves us at the last instant does not mean 
 that we should be going out of our way to multiply free external resources.  
 Files are well known to the vm; other things (GSL vectors/matrices comes to 
 mind) will not enjoy such protections.  This strikes me as a feature that got 
 added when errors arose from attempts to add redundant executors, ultimately 
 due to lack of thread safety.  Many things that are being fixed at great cost 
 got started (it sure seems) because someone added a feature or placed 
 something in or too near to Object only to avoid errors vs. finding and 
 fixing the real problem.

 Maybe you have made a strong argument for multiple executors; if so, I've 
 missed it.  Right now, it looks like a design flaw instead of a feature.


I second that. Knowing that VM/OS does the best to not pushish those
who attempting to free already freed resource, doesn't means that we
should be careless about it!

OS tries the best to not give away a same file handle for newly opened
file as recently closed file(s).
malloc() tries the best to not give away the pointer to same memory
region, which was recently freed.
But obviously, a well-designed application should never rely on such behavior.


-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
GPL is a problem.  It means that nothing I write on top of GSL gets out the 
door.  However, I see no reason not to give others the same mix of capability 
and concern in the form of an interface to it.




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
[le...@elte.hu]
Sent: Monday, October 11, 2010 10:59 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:

 Levente,

 Ok, but just because the system saves us at the last instant does not mean 
 that we should be going out of our way to multiply free external resources.  
 Files are well known to the vm; other things (GSL vectors/matrices comes to 
 mind) will not enjoy such protections.  This strikes me as a feature that got 
 added when errors arose from attempts to add redundant executors, ultimately 
 due to lack of thread safety.  Many things that are being fixed at great cost 
 got started (it sure seems) because someone added a feature or placed 
 something in or too near to Object only to avoid errors vs. finding and 
 fixing the real problem.

 Maybe you have made a strong argument for multiple executors; if so, I've 
 missed it.  Right now, it looks like a design flaw instead of a feature.

There's code that relies on multiple executors. Every object understands
#toFinalizeSend:to:with:. When you use it, you expect that your finalizer
will be evaluated when the object is garbage collected.

Btw I offered a simple solution for cases like yours. The behavior of
WeakRegistry  #add:executor: can be easily made pluggable when an
object has an executor in the registry.


Levente

P.S.: how will you use GSL knowing that it's license is GPL? Will you
keep the code for yourself or release it under the GPL license?


 Bill



 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
 [le...@elte.hu]
 Sent: Monday, October 11, 2010 10:24 AM
 To: Pharo-project@lists.gforge.inria.fr
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:

 Levente,

 A similar discussion arose around Dolphin's event (#trigger*) mechanism.  My 
 recollection is that it was not fully addressed due to performance concerns. 
  Forking and error handlers both have their costs.  I'm not saying we should 
 necessarily follow (we probably should not), though with careful design, an 
 interrupted chain of events might survive to be handled on a subsequent 
 attempt.

 I am far more worried about having multiple executors per object (when did 
 p=malloc();free(p);free(p);free(p) become good style?) than I am about 
 getting the finalizer process itself completely robust at this point.

 Smalltalk is not C. Try this:

 | file |
 file := StandardFileStream fileNamed: 'foo.txt'.
 file close.
 file primClose: (file instVarNamed: #fileID).
 Those pesky plugins save us all the time. ;)


 Levente


 Bill



 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
 [le...@elte.hu]
 Sent: Monday, October 11, 2010 9:51 AM
 To: Pharo Development
 Cc: The general-purpose Squeak developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On Mon, 11 Oct 2010, Igor Stasenko wrote:

 Hello,

 here a situation, with which we can deal in more safer manner:

 Suppose you have a weak registry, populated by different objects and
 their executors.

 Now, when some of them died, a weak registry performs finalization.

 The potential danger is , that if there's an error triggered by some
 executor(s),
 then rest of executors will have no chance to run and will be
 forgotten, causing memory leakage.

 What you think, should we handle this more graciously?

 (Consider a following meta-code)

 WeakRegistryfinalizeValues
 | executors |
  executors := self gatherExecutorsToRun.

  executors do: [:ex |
 [ ex finalize ] fork.
  ].

 The gatherExecutorsToRun part was implemented in the previous version
 of WeakRegistry (history is not available from the image...). #finalize
 wasn't sent from the protected block. The current version lacks it, so it
 will deadlock if a finalizer will try to access the same WeakRegistry.
 Other kind of deadlocks are also possible. For example when a finalizer
 can access a semaphore which is also used by another process that
 uses the same semaphore and also uses the WeakRegistry, but locks them in
 a different order (JNIPort).
 This only happens if the VM doesn't support the new finalization scheme
 which is the case for most current VMs.

 There is another issue with removal, and this affects the new finalization
 scheme too, because

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Stéphane Ducasse
Argh

 
 
 ObjectFinalizerfinalize
   Finalize the resource associated with the receiver. This message
 should only be sent during the finalization process. There is NO
 garantuee that the resource associated with the receiver hasn't been
 free'd before so take care that you don't run into trouble - this all
 may happen with interrupt priority.
   [self value] on: Error do:[:ex| ex return].
 
 now, replace this implementation with just
 self value
 and you'll see what will happen.
 
 Such behavior is completely unacceptable in terms of finding the bugs
  problems in your code.

yes please fix arg

Stef

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Henrik Johansen

On Oct 11, 2010, at 4:10 13PM, Schwab,Wilhelm K wrote:

 
 I am far more worried about having multiple executors per object (when did 
 p=malloc();free(p);free(p);free(p) become good style?) than I am about 
 getting the finalizer process itself completely robust at this point.
 
 Bill

I fail to see how a blatantly obvious misuse of a feature becomes a valid 
argument against supporting that feature, or something you should worry alot 
about.
You can do Object become: nil, which is also not good style, but it's certainly 
not an valid argument for not allowing #become:.
Nor do I lose any sleep thinking of ways people could possibly abuse #become: 

Cheers,
Henry
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Henry,

Ok, what valid use of multiple executors have I missed?

Bill




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Henrik Johansen 
[henrik.s.johan...@veloxit.no]
Sent: Monday, October 11, 2010 11:23 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Oct 11, 2010, at 4:10 13PM, Schwab,Wilhelm K wrote:


 I am far more worried about having multiple executors per object (when did 
 p=malloc();free(p);free(p);free(p) become good style?) than I am about 
 getting the finalizer process itself completely robust at this point.

 Bill

I fail to see how a blatantly obvious misuse of a feature becomes a valid 
argument against supporting that feature, or something you should worry alot 
about.
You can do Object become: nil, which is also not good style, but it's certainly 
not an valid argument for not allowing #become:.
Nor do I lose any sleep thinking of ways people could possibly abuse #become:

Cheers,
Henry
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
Meanwhile, i'll try to implement two test cases for WeakRegistryTest.

One, should cover following:

coll := OrderedCollection new.
obj := Object new.
wrapper := WeakArray with: obj.
coll add: wrapper.

obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.
obj toFinalizeSend: #remove: to: coll with: wrapper.

obj := nil.
Smalltalk garbageCollect.

i.e somehow, user should be notified that there is an error during finalization.

And second test case is to make sure that if one finalizer unable to
complete due to error,
the other ones (and finalization process itself) should continue
running, skipping over errorneous finalizer.

-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Levente Uzonyi

On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:


Henry,

Ok, what valid use of multiple executors have I missed?


I described it earlier how the AXAnnouncements project uses this feature.


Levente



Bill




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Henrik Johansen 
[henrik.s.johan...@veloxit.no]
Sent: Monday, October 11, 2010 11:23 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Oct 11, 2010, at 4:10 13PM, Schwab,Wilhelm K wrote:



I am far more worried about having multiple executors per object (when did 
p=malloc();free(p);free(p);free(p) become good style?) than I am about getting 
the finalizer process itself completely robust at this point.

Bill


I fail to see how a blatantly obvious misuse of a feature becomes a valid 
argument against supporting that feature, or something you should worry alot 
about.
You can do Object become: nil, which is also not good style, but it's certainly 
not an valid argument for not allowing #become:.
Nor do I lose any sleep thinking of ways people could possibly abuse #become:

Cheers,
Henry
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project



___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Ok,  I'll dig around for that and have a look.



From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Levente Uzonyi 
[le...@elte.hu]
Sent: Monday, October 11, 2010 12:31 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On Mon, 11 Oct 2010, Schwab,Wilhelm K wrote:

 Henry,

 Ok, what valid use of multiple executors have I missed?

I described it earlier how the AXAnnouncements project uses this feature.


Levente


 Bill



 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Henrik Johansen 
 [henrik.s.johan...@veloxit.no]
 Sent: Monday, October 11, 2010 11:23 AM
 To: Pharo-project@lists.gforge.inria.fr
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On Oct 11, 2010, at 4:10 13PM, Schwab,Wilhelm K wrote:


 I am far more worried about having multiple executors per object (when did 
 p=malloc();free(p);free(p);free(p) become good style?) than I am about 
 getting the finalizer process itself completely robust at this point.

 Bill

 I fail to see how a blatantly obvious misuse of a feature becomes a valid 
 argument against supporting that feature, or something you should worry alot 
 about.
 You can do Object become: nil, which is also not good style, but it's 
 certainly not an valid argument for not allowing #become:.
 Nor do I lose any sleep thinking of ways people could possibly abuse #become:

 Cheers,
 Henry
 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 11 October 2010 19:28, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The Dolphin approach is to restart any of the finalizer, main, timer, idler 
 threads (I *think* there is one more in a baseline image) any time they quit; 
 an #ensure: block forks a new thread of the type that terminated.  That way, 
 whether they are taken down by an error doing what they are supposed to do or 
 just by a stray #terminate or mistake with an attached debugger, the system 
 rolls onward intact.


If it would be only about restarting, then its a piece of cake.
We should make sure that all finalizations detected prior to error,
did not get lost and are able to proceed as if nothing happens,
except a single one, which failed with error.

 Bill


 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
 [siguc...@gmail.com]
 Sent: Monday, October 11, 2010 12:14 PM
 To: Pharo-project@lists.gforge.inria.fr; The general-purpose Squeak 
 developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 Meanwhile, i'll try to implement two test cases for WeakRegistryTest.

 One, should cover following:

 coll := OrderedCollection new.
 obj := Object new.
 wrapper := WeakArray with: obj.
 coll add: wrapper.

 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.

 obj := nil.
 Smalltalk garbageCollect.

 i.e somehow, user should be notified that there is an error during 
 finalization.

 And second test case is to make sure that if one finalizer unable to
 complete due to error,
 the other ones (and finalization process itself) should continue
 running, skipping over errorneous finalizer.

 --
 Best regards,
 Igor Stasenko AKA sig.

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Sig,

Understood, but are they all that different?  The ones that were served ahead 
of the error should stay that way (proper recording of same is what needs 
attention), and those yet to be served, if it's done well, should be ready for 
the new thread to handle.  Just something to consider.

Bill




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
[siguc...@gmail.com]
Sent: Monday, October 11, 2010 1:02 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On 11 October 2010 19:28, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The Dolphin approach is to restart any of the finalizer, main, timer, idler 
 threads (I *think* there is one more in a baseline image) any time they quit; 
 an #ensure: block forks a new thread of the type that terminated.  That way, 
 whether they are taken down by an error doing what they are supposed to do or 
 just by a stray #terminate or mistake with an attached debugger, the system 
 rolls onward intact.


If it would be only about restarting, then its a piece of cake.
We should make sure that all finalizations detected prior to error,
did not get lost and are able to proceed as if nothing happens,
except a single one, which failed with error.

 Bill


 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
 [siguc...@gmail.com]
 Sent: Monday, October 11, 2010 12:14 PM
 To: Pharo-project@lists.gforge.inria.fr; The general-purpose Squeak 
 developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 Meanwhile, i'll try to implement two test cases for WeakRegistryTest.

 One, should cover following:

 coll := OrderedCollection new.
 obj := Object new.
 wrapper := WeakArray with: obj.
 coll add: wrapper.

 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.

 obj := nil.
 Smalltalk garbageCollect.

 i.e somehow, user should be notified that there is an error during 
 finalization.

 And second test case is to make sure that if one finalizer unable to
 complete due to error,
 the other ones (and finalization process itself) should continue
 running, skipping over errorneous finalizer.

 --
 Best regards,
 Igor Stasenko AKA sig.

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Sig,

As a friend here: when did I say I'd remove all?  Remove and process one at a 
time.  I will admit to having a bias toward doing this with a single executor 
per object, but even if multiples turn out to have value (need to hunt down and 
read Levente's description of that), the same idea should apply.

Bill



From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
[siguc...@gmail.com]
Sent: Monday, October 11, 2010 1:39 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On 11 October 2010 20:04, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 Understood, but are they all that different?  The ones that were served ahead 
 of the error should stay that way (proper recording of same is what needs 
 attention), and those yet to be served, if it's done well, should be ready 
 for the new thread to handle.  Just something to consider.

Devil is always in details.

The problem can be illustrated by following:

| todoList |
todoList := collection select: [ some criteria ].
collection removeAllFoundIn: todoList.

todoList do: [ :each | each doSomething ].

now, if inside of #doSomething you got an error, a loop is interrupted,
and if you restart the process, your todoList temp is gone, since it
is local to particular context, which will be discarded.
You also can't restore todoList by rescanning a collection, since you
removed all elements, which met your criteria.

 Bill



 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
 [siguc...@gmail.com]
 Sent: Monday, October 11, 2010 1:02 PM
 To: Pharo-project@lists.gforge.inria.fr
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On 11 October 2010 19:28, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The Dolphin approach is to restart any of the finalizer, main, timer, idler 
 threads (I *think* there is one more in a baseline image) any time they 
 quit; an #ensure: block forks a new thread of the type that terminated.  
 That way, whether they are taken down by an error doing what they are 
 supposed to do or just by a stray #terminate or mistake with an attached 
 debugger, the system rolls onward intact.


 If it would be only about restarting, then its a piece of cake.
 We should make sure that all finalizations detected prior to error,
 did not get lost and are able to proceed as if nothing happens,
 except a single one, which failed with error.

 Bill


 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
 [siguc...@gmail.com]
 Sent: Monday, October 11, 2010 12:14 PM
 To: Pharo-project@lists.gforge.inria.fr; The general-purpose Squeak 
 developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 Meanwhile, i'll try to implement two test cases for WeakRegistryTest.

 One, should cover following:

 coll := OrderedCollection new.
 obj := Object new.
 wrapper := WeakArray with: obj.
 coll add: wrapper.

 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.
 obj toFinalizeSend: #remove: to: coll with: wrapper.

 obj := nil.
 Smalltalk garbageCollect.

 i.e somehow, user should be notified that there is an error during 
 finalization.

 And second test case is to make sure that if one finalizer unable to
 complete due to error,
 the other ones (and finalization process itself) should continue
 running, skipping over errorneous finalizer.

 --
 Best regards,
 Igor Stasenko AKA sig.

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




 --
 Best regards,
 Igor Stasenko AKA sig.

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 11 October 2010 21:07, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 As a friend here: when did I say I'd remove all?  Remove and process one at a 
 time.  I will admit to having a bias toward doing this with a single executor 
 per object, but even if multiples turn out to have value (need to hunt down 
 and read Levente's description of that), the same idea should apply.


Removing and processing one at a time could do the job, but it will be
very inefficient (especially on VMs which
not support new finalization).
Because:
 - you have to enter critical section for scanning valueDictionary
 - you then have to leave critical section for sending a single #finalize
 - then you should start over and look for next element with nil key (if any)

So, as i said, devil in details.

 Bill




-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Levente Uzonyi

On Mon, 11 Oct 2010, Igor Stasenko wrote:


On 11 October 2010 21:07, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
Sig,

As a friend here: when did I say I'd remove all?  Remove and process one at a 
time.  I will admit to having a bias toward doing this with a single executor 
per object, but even if multiples turn out to have value (need to hunt down and 
read Levente's description of that), the same idea should apply.



Removing and processing one at a time could do the job, but it will be
very inefficient (especially on VMs which
not support new finalization).
Because:
 - you have to enter critical section for scanning valueDictionary
 - you then have to leave critical section for sending a single #finalize
 - then you should start over and look for next element with nil key (if any)

So, as i said, devil in details.


You can select the executors to a collection and finalize them later, so 
you don't have to restart the scanning of valueDictionary.



Levente


Bill





--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Sig,

The most important words in there are critical section.  Carry on :)

Bill



From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
[siguc...@gmail.com]
Sent: Monday, October 11, 2010 2:36 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On 11 October 2010 21:07, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 As a friend here: when did I say I'd remove all?  Remove and process one at a 
 time.  I will admit to having a bias toward doing this with a single executor 
 per object, but even if multiples turn out to have value (need to hunt down 
 and read Levente's description of that), the same idea should apply.


Removing and processing one at a time could do the job, but it will be
very inefficient (especially on VMs which
not support new finalization).
Because:
 - you have to enter critical section for scanning valueDictionary
 - you then have to leave critical section for sending a single #finalize
 - then you should start over and look for next element with nil key (if any)

So, as i said, devil in details.

 Bill




--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project


Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The most important words in there are critical section.  Carry on :)


Oh, please. This is not too hard to code.

My mind rolling around following choice(s)  (there may be others i don't see).
What would be a proper way to handle error during #finalize.

[ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
 ].

or:

[ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
 ].


of course, i should catch this error in test, so i can verify that:

a) test is get notified upon synthetically made error
b) no matter what i do inside error handler (up to 'Processor
activeProcess terminate'), a finalization process continues working
(or restarts without losing remainder of executors).


Also, i used #ensure: and #ifCurtailed: but i tend to forget where
they are applicable and how.
So, little help in this regard will be wellcome.

 Bill

-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Igor Stasenko
On 12 October 2010 00:32, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 How hard it is or isn't is not nearly as important as your tackling it and 
 doing so with the right tools.  So again I say, carry on :)

 On self vs. executor as the receiver of #handleFinalizationError:, I might 
 lean toward self as it will be closer to the system.  There is probably 
 little the executor can do, and it either missed or raised the error in the 
 first place, right?  I *think* the most you are going to to do is log that 
 something went wrong, but I could be missing something.


I'm not sure about that .
From other size, a finalizer could better know why error can occur and
how to handle it graciously, if its possible, and not just showing
'you suck' at the center of screen ;)

Because weak registry can tell even less about nature of error,
because it propably knows nothing about its finalizers, except that
they understand #finalize message.

 #ensure: attempts to evaluate the argument block whenever the receiver of it 
 is completed (modulo some ominous sounding questions raised in the past 
 months to a year??).  #ifCurtailed: should be similar, but evaluating the 
 argument/block only on abnormal (including, I think, ^) exit of the block.

 Does that help at all?

Yes. Thanks. I now remember semantics of it. Been there when dealt
with Processterminate voodo.


 Bill


 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
 [siguc...@gmail.com]
 Sent: Monday, October 11, 2010 4:17 PM
 To: Pharo-project@lists.gforge.inria.fr; The general-purpose Squeak 
 developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The most important words in there are critical section.  Carry on :)


 Oh, please. This is not too hard to code.

 My mind rolling around following choice(s)  (there may be others i don't see).
 What would be a proper way to handle error during #finalize.

 [ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
  ].

 or:

 [ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
  ].


 of course, i should catch this error in test, so i can verify that:

 a) test is get notified upon synthetically made error
 b) no matter what i do inside error handler (up to 'Processor
 activeProcess terminate'), a finalization process continues working
 (or restarts without losing remainder of executors).


 Also, i used #ensure: and #ifCurtailed: but i tend to forget where
 they are applicable and how.
 So, little help in this regard will be wellcome.

 Bill

 --
 Best regards,
 Igor Stasenko AKA sig.

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




-- 
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Another finalization concern: error handling

2010-10-11 Thread Schwab,Wilhelm K
Sig,

You seem to be doing a good job of this, so if you think I'm off, feel free to 
prove it.   The executors (in Dolphin, the objects themselves) probably know 
more than the registry about how to handle errors, and (it seems to me) either 
generated them or could have readily caught them if there were something 
different to do based on the information.

Maybe the crux of the matter is as follows: are you thinking of an executor 
class with subclasses that implement #handleFinalizationError: (a hook), or is 
it more this happened, thought you might like to know.  I think I read it 
more as the latter, probably assuming that #finalize would retry if that could 
reasonably be expected to help.  

Bill





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
[siguc...@gmail.com]
Sent: Monday, October 11, 2010 6:35 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Another finalization concern: error handling

On 12 October 2010 00:32, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 How hard it is or isn't is not nearly as important as your tackling it and 
 doing so with the right tools.  So again I say, carry on :)

 On self vs. executor as the receiver of #handleFinalizationError:, I might 
 lean toward self as it will be closer to the system.  There is probably 
 little the executor can do, and it either missed or raised the error in the 
 first place, right?  I *think* the most you are going to to do is log that 
 something went wrong, but I could be missing something.


I'm not sure about that .
From other size, a finalizer could better know why error can occur and
how to handle it graciously, if its possible, and not just showing
'you suck' at the center of screen ;)

Because weak registry can tell even less about nature of error,
because it propably knows nothing about its finalizers, except that
they understand #finalize message.

 #ensure: attempts to evaluate the argument block whenever the receiver of it 
 is completed (modulo some ominous sounding questions raised in the past 
 months to a year??).  #ifCurtailed: should be similar, but evaluating the 
 argument/block only on abnormal (including, I think, ^) exit of the block.

 Does that help at all?

Yes. Thanks. I now remember semantics of it. Been there when dealt
with Processterminate voodo.


 Bill


 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Igor Stasenko 
 [siguc...@gmail.com]
 Sent: Monday, October 11, 2010 4:17 PM
 To: Pharo-project@lists.gforge.inria.fr; The general-purpose Squeak 
 developers list
 Subject: Re: [Pharo-project] Another finalization concern: error handling

 On 11 October 2010 22:49, Schwab,Wilhelm K bsch...@anest.ufl.edu wrote:
 Sig,

 The most important words in there are critical section.  Carry on :)


 Oh, please. This is not too hard to code.

 My mind rolling around following choice(s)  (there may be others i don't see).
 What would be a proper way to handle error during #finalize.

 [ executor finalize ] on: Error do: [:ex |
  self handleFinalizationError: ex  where self is registry
  ].

 or:

 [ executor finalize ] on: Error do: [:ex |
  executor handleFinalizationError: ex
  ].


 of course, i should catch this error in test, so i can verify that:

 a) test is get notified upon synthetically made error
 b) no matter what i do inside error handler (up to 'Processor
 activeProcess terminate'), a finalization process continues working
 (or restarts without losing remainder of executors).


 Also, i used #ensure: and #ifCurtailed: but i tend to forget where
 they are applicable and how.
 So, little help in this regard will be wellcome.

 Bill

 --
 Best regards,
 Igor Stasenko AKA sig.

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

 ___
 Pharo-project mailing list
 Pharo-project@lists.gforge.inria.fr
 http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project




--
Best regards,
Igor Stasenko AKA sig.

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project