Re: [Pharo-project] Stack should be reimplemented with Array

2010-10-18 Thread Levente Uzonyi

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 02:51, Levente Uzonyi  wrote:

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 00:25, Levente Uzonyi  wrote:


On Mon, 18 Oct 2010, Igor Stasenko wrote:


Stephane, i could say more:
- i don't like how LinkedList implemented.

I don't see why it should mimic things like #at: #at:put: at all..


It's not mimicing those methods. A list usually support things like this,
but the user should know the consequences.



The consequences of such approach is much more far-reaching: leads to
bad design practices, crappy application performance,
and then tons of bugs and workarounds.


Are programmers idiots? If not, then we shouldn't treat them like idiots.


No, of course not.
And that's why as non-idiot (i hope), i was wondering, what things
like #at: #at:put: doing in classes like Stack,
or LikedList.


Okay, it's not nice if a Stack allows indexing, but most linked list 
implementations support it.



You know, its like you driving the car and along the road you see a
beatiful park with pool and attractions for the kids to play to the
right side, and a toxic waste dump to the left side of road.. And you
keep driving, thinking about a diner and wife, which waits you at
home, but at some moment your attention gets back to that place and
you have a gut feeling that there was something wrong with a picture
you just seen, and then you got it: they are close to each other, just
across the road!




IMO this protocol should be pruned from it, to not provoke uses which
completely do not fit for given data structure.


I'm not sure if it's okay to remove features, because users lacking
really
basic CS knowledge may use them the wrong way.



Imo, we should prohibit this from the beginning. Standard, core
classes should not contain an API, which could lead to
careless, abusive programming techniques.


So we should get rid of SortedCollection, remove #includes: #indexOf: from
ArrayedCollections, get rid of OrderedCollection >> #remove:, etc. Am I
right?


Roughly speaking, yes. But they are inherited.. this is a little another story.
And should be handled in a way like Array>>add: does.


Array >> #add: is different, because Arrays are not resizable. You could 
say that one could use #become: to grow the array, but then I'd say that 
following your suggestions we have to remove #become: from the system, 
because it's slow and people may use it to write slow code.





IMO, a kernel APIs should serve not only as an implementation of basic
system funcionality, it also must serve as guide,
how to best use these facilities, so people will learn what is the
right way to use it.


That's right, but there's no need to remove useful features to achieve this.


you should convince me first, that things like LinkedList>>at: is userful.


Ok. Here's an example:

What happens if you remove OrderedCollection >> #remove: from the system? 
People will write code like this (or worse):


gotIt := false.
1 to: o size do: [ :index |
gotIt
ifTrue: [ o at: index - 1 put: (o at: index) ]
ifFalse: [
(o at: index) = myObject ifTrue: [ gotIt := true ] ].
gotIt ifTrue: [ o removeLast ].


This kind of code is a lot worse than using #remove:, because it's harder 
to understand, harder to debug, really easy to mess up. And it will be 
reimplemented several times.



Levente





We should teach users to use right tools for things they need.




Removing/inserting into the middle of list is quite ineffective
operation (O(n)),


As long as you don't give away the link objects, it's O(n), otherwise it
can
be O(1).


giving away link objects... oh, that's the worst thing, which could
possibly happen :)


No. It's the user's responsibility to use it wisely. If you don't need to
access a internal nodes, just adding/removing elements to/from the list,
then you probably shouldn't use a list at all.



I prefer making own lists and own classes for list items, because
implementation of
LinkedList raising many questions starting from being optimal, and up
to concerns i presented above.







while inserting at the begginning/end of list is O(1).

Lists are sequenceable.. but sequenceable ~~ indexable. Period.


Sequenceable is indexable, but good performance is not guaranteed.


Unless you representing an infinite collection(s).
Streams are good example of sequenceable, however non-indexable
containers.


Streams are more like external iterators, than containers IMHO. But you can
get/set the position of most streams.


Levente






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/list

Re: [Pharo-project] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Igor Stasenko
On 19 October 2010 06:29, Levente Uzonyi  wrote:
> On Tue, 19 Oct 2010, Igor Stasenko wrote:
>
>> On 19 October 2010 03:42, Levente Uzonyi  wrote:
>>>
>>> On Tue, 19 Oct 2010, Igor Stasenko wrote:
>>>
 On 19 October 2010 02:06, Levente Uzonyi  wrote:
>
> On Mon, 18 Oct 2010, Igor Stasenko wrote:
>
> snip
>
>>
>
> Thanks, Levente for giving a feedback.
> Please, feel free to shape my classes in more complete from (such as
> proper naming),
> to make them ready for inclusion in both Squeak's and Pharo cores.
> I propose the following names:
> AtomicQueue (base class) -> AtomicCollection
> FIFOQueue -> AtomicQueue
> LIFOQueue -> AtomicStack
> If you, or anyone else having better suggestions, speak now :)
>
>
>
> I think these should be the names:
>
> FIFOQueue -> SharedQueue

 this name already used by Kernel.
 So, unless my class will fully replace it, i see no way how i could
 use this name in separate package.
>>>
>>> Yes, it would be good to replace the implementation IMHO. The API seems
>>> to
>>> be complete to me (except for copying ;)).
>>>
>> You mean this:
>>
>> copy
>>        ^ self errorDontCopy
>>
>> errorDontCopy
>>        "copying a structure, involved in concurrent operations is a bad
>> idea"
>>        ^ self error: 'Copying not available'
>>
>> :)
>>
>> See how Squeak's EventSensor doing right thing to make a 'copy':
>>
>> EventSensor>>flushAllButDandDEvents
>>        | newQueue oldQueue  |
>>
>>        newQueue := SharedQueue new.
>>        self eventQueue ifNil:
>>                [eventQueue := newQueue.
>>                ^self].
>>        oldQueue := self eventQueue.
>>        [oldQueue size > 0] whileTrue:
>>                [| item type |
>>                item := oldQueue next.
>>                type := item at: 1.
>>                type = EventTypeDragDropFiles ifTrue: [ newQueue nextPut:
>> item]].
>>        eventQueue := newQueue.
>>
>> Well, you might be right, that #copy can be implemented as:
>>
>> copy
>>  | copy |
>>  copy := self class new.
>>  [ copy put: (self nextIfNone: [ ^ copy ] ) ] repeat
>>
>> if it makes any sense, to anyone..
>>
>> Its hard to imagine a situation where one may need to copy existing queue,
>> because he simply can keep using it.
>
> I didn't say that I find copying useful, but the API is different.
>
Why? #copy is implemented.. it just behaves differently :)

>>
>>

 Also, i must stress, that behavior of FIFOQueue only attempts to
 closely resemble the SharedQueue behavior.
 However, there is a situations (related to how scheduling works and
 use of #yield), where using them could lead to deadlocks.
 In this regard, an AtomicSharedQueue (a subclass of FIFOQueue) is much
 better analogy to current SharedQueue.
>>>
>>> If you mean the case: "if process A tries to read from an empty queue,
>>> later
>>> process B tries to do the same, then process A is guaranteed to read
>>> before
>>> process B", then that shouldn't be a problem. It would require an
>>> external
>>> synchronization step to make use of this feature with the current
>>> implementation. I doubt that anyone wrote such code ever.
>>>
>> No. The problems is not in that. The problem related to scheduling and
>> how #yield primitive works.
>>
>> Here the VM's primitiveYield:
>>
>> primitiveYield
>> "primitively do the equivalent of Process>yield"
>>        | activeProc priority processLists processList |
>>        activeProc := self fetchPointer: ActiveProcessIndex
>>                                                 ofObject: self
>> schedulerPointer.
>>        priority := self quickFetchInteger: PriorityIndex ofObject:
>> activeProc.
>>        processLists := self fetchPointer: ProcessListsIndex ofObject: self
>> schedulerPointer.
>>        processList := self fetchPointer: priority - 1 ofObject:
>> processLists.
>>
>>        (self isEmptyList: processList) ifFalse:[
>>                self addLastLink: activeProc toList: processList.
>>                self transferTo: self wakeHighestPriority]
>>
>> Note #wakeHighestPriority.
>>
>> So, a fetcher (which using #yield in spin loop) with priority higher
>> than pusher process, will loop infinitely
>> blocking pusher and all lower priority processes from advancing.
>>
>> To avoid this problem, one should make sure that process which pushing
>> new items to queue
>> having either higher or same priority as any fetching process(es)
>> using same queue.
>> Or use wait-free access to queue (avoid use #next, use #nextOrNil
>> instead).
>>
>> That's why in subclass - AtomicSharedQueue, i using semaphore to
>> workaround this issue.
>
> Okay. So AtomicSharedQueue is the class which can be used to replace
> SharedQueue. So the names could be:
>
> LIFOQueue -> AtomicStack
> FIFOQueue -> AtomicQueue
> AtomicSharedQueue -> SharedQueue
>

Right, and i think i'll move all non wait-free methods (like #next )
into SharedQueue,
so A

Re: [Pharo-project] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Levente Uzonyi

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 03:42, Levente Uzonyi  wrote:

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 02:06, Levente Uzonyi  wrote:


On Mon, 18 Oct 2010, Igor Stasenko wrote:

snip





Thanks, Levente for giving a feedback.
Please, feel free to shape my classes in more complete from (such as
proper naming),
to make them ready for inclusion in both Squeak's and Pharo cores.
I propose the following names:
AtomicQueue (base class) -> AtomicCollection
FIFOQueue -> AtomicQueue
LIFOQueue -> AtomicStack
If you, or anyone else having better suggestions, speak now :)



I think these should be the names:

FIFOQueue -> SharedQueue


this name already used by Kernel.
So, unless my class will fully replace it, i see no way how i could
use this name in separate package.


Yes, it would be good to replace the implementation IMHO. The API seems to
be complete to me (except for copying ;)).


You mean this:

copy
^ self errorDontCopy

errorDontCopy
"copying a structure, involved in concurrent operations is a bad idea"
^ self error: 'Copying not available'

:)

See how Squeak's EventSensor doing right thing to make a 'copy':

EventSensor>>flushAllButDandDEvents
| newQueue oldQueue  |

newQueue := SharedQueue new.
self eventQueue ifNil:
[eventQueue := newQueue.
^self].
oldQueue := self eventQueue.
[oldQueue size > 0] whileTrue:
[| item type |
item := oldQueue next.
type := item at: 1.
type = EventTypeDragDropFiles ifTrue: [ newQueue nextPut: 
item]].
eventQueue := newQueue.

Well, you might be right, that #copy can be implemented as:

copy
  | copy |
  copy := self class new.
  [ copy put: (self nextIfNone: [ ^ copy ] ) ] repeat

if it makes any sense, to anyone..

Its hard to imagine a situation where one may need to copy existing queue,
because he simply can keep using it.


I didn't say that I find copying useful, but the API is different.






Also, i must stress, that behavior of FIFOQueue only attempts to
closely resemble the SharedQueue behavior.
However, there is a situations (related to how scheduling works and
use of #yield), where using them could lead to deadlocks.
In this regard, an AtomicSharedQueue (a subclass of FIFOQueue) is much
better analogy to current SharedQueue.


If you mean the case: "if process A tries to read from an empty queue, later
process B tries to do the same, then process A is guaranteed to read before
process B", then that shouldn't be a problem. It would require an external
synchronization step to make use of this feature with the current
implementation. I doubt that anyone wrote such code ever.


No. The problems is not in that. The problem related to scheduling and
how #yield primitive works.

Here the VM's primitiveYield:

primitiveYield
"primitively do the equivalent of Process>yield"
| activeProc priority processLists processList |
activeProc := self fetchPointer: ActiveProcessIndex
 ofObject: self 
schedulerPointer.
priority := self quickFetchInteger: PriorityIndex ofObject: activeProc.
processLists := self fetchPointer: ProcessListsIndex ofObject: self
schedulerPointer.
processList := self fetchPointer: priority - 1 ofObject: processLists.

(self isEmptyList: processList) ifFalse:[
self addLastLink: activeProc toList: processList.
self transferTo: self wakeHighestPriority]

Note #wakeHighestPriority.

So, a fetcher (which using #yield in spin loop) with priority higher
than pusher process, will loop infinitely
blocking pusher and all lower priority processes from advancing.

To avoid this problem, one should make sure that process which pushing
new items to queue
having either higher or same priority as any fetching process(es)
using same queue.
Or use wait-free access to queue (avoid use #next, use #nextOrNil instead).

That's why in subclass - AtomicSharedQueue, i using semaphore to
workaround this issue.


Okay. So AtomicSharedQueue is the class which can be used to replace 
SharedQueue. So the names could be:


LIFOQueue -> AtomicStack
FIFOQueue -> AtomicQueue
AtomicSharedQueue -> SharedQueue



And potentially, it would be good some day to have a way to say to scheduler:
please stop current process and see if you can run anything with lower priority.


That would break the current scheduling policy.


Levente


(Another reason to move scheduling to language side, so we are free to
modify it in a way we like ;).



As i noted in another mail, i see that we might also provide a
separate wait-free interface. So we can guarantee,
that if you using only wait-free interface, a queue can never be the
cause of deadlock.


That's great, and it can be a future addition even if we push the current
implementation to the Trunk.



Yes. I th

Re: [Pharo-project] Stack should be reimplemented with Array

2010-10-18 Thread Igor Stasenko
On 19 October 2010 02:51, Levente Uzonyi  wrote:
> On Tue, 19 Oct 2010, Igor Stasenko wrote:
>
>> On 19 October 2010 00:25, Levente Uzonyi  wrote:
>>>
>>> On Mon, 18 Oct 2010, Igor Stasenko wrote:
>>>
 Stephane, i could say more:
 - i don't like how LinkedList implemented.

 I don't see why it should mimic things like #at: #at:put: at all..
>>>
>>> It's not mimicing those methods. A list usually support things like this,
>>> but the user should know the consequences.
>>>
>>
>> The consequences of such approach is much more far-reaching: leads to
>> bad design practices, crappy application performance,
>> and then tons of bugs and workarounds.
>
> Are programmers idiots? If not, then we shouldn't treat them like idiots.
>
No, of course not.
And that's why as non-idiot (i hope), i was wondering, what things
like #at: #at:put: doing in classes like Stack,
or LikedList.
You know, its like you driving the car and along the road you see a
beatiful park with pool and attractions for the kids to play to the
right side, and a toxic waste dump to the left side of road.. And you
keep driving, thinking about a diner and wife, which waits you at
home, but at some moment your attention gets back to that place and
you have a gut feeling that there was something wrong with a picture
you just seen, and then you got it: they are close to each other, just
across the road!

>>
 IMO this protocol should be pruned from it, to not provoke uses which
 completely do not fit for given data structure.
>>>
>>> I'm not sure if it's okay to remove features, because users lacking
>>> really
>>> basic CS knowledge may use them the wrong way.
>>>
>>
>> Imo, we should prohibit this from the beginning. Standard, core
>> classes should not contain an API, which could lead to
>> careless, abusive programming techniques.
>
> So we should get rid of SortedCollection, remove #includes: #indexOf: from
> ArrayedCollections, get rid of OrderedCollection >> #remove:, etc. Am I
> right?
>
Roughly speaking, yes. But they are inherited.. this is a little another story.
And should be handled in a way like Array>>add: does.

>> IMO, a kernel APIs should serve not only as an implementation of basic
>> system funcionality, it also must serve as guide,
>> how to best use these facilities, so people will learn what is the
>> right way to use it.
>
> That's right, but there's no need to remove useful features to achieve this.
>
you should convince me first, that things like LinkedList>>at: is userful.

>>
>> We should teach users to use right tools for things they need.
>>
>>

 Removing/inserting into the middle of list is quite ineffective
 operation (O(n)),
>>>
>>> As long as you don't give away the link objects, it's O(n), otherwise it
>>> can
>>> be O(1).
>>
>> giving away link objects... oh, that's the worst thing, which could
>> possibly happen :)
>
> No. It's the user's responsibility to use it wisely. If you don't need to
> access a internal nodes, just adding/removing elements to/from the list,
> then you probably shouldn't use a list at all.
>

I prefer making own lists and own classes for list items, because
implementation of
LinkedList raising many questions starting from being optimal, and up
to concerns i presented above.


>>
>>>
 while inserting at the begginning/end of list is O(1).

 Lists are sequenceable.. but sequenceable ~~ indexable. Period.
>>>
>>> Sequenceable is indexable, but good performance is not guaranteed.
>>>
>> Unless you representing an infinite collection(s).
>> Streams are good example of sequenceable, however non-indexable
>> containers.
>
> Streams are more like external iterators, than containers IMHO. But you can
> get/set the position of most streams.
>
>
> Levente
>
>>
>>
>>>
>>> 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
>>>
>>
>>
>>
>> --
>> 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] bad bracket autocompletion in Pharo Core 1.2

2010-10-18 Thread Igor Stasenko
On 18 October 2010 21:44, Stéphane Ducasse  wrote:
>>
>> > On Sun, Oct 17, 2010 at 10:51 AM, Stéphane Ducasse 
>> >  wrote:
>> > I have a question:
>> >        does shout support closing parenthesis behavior?
>> >
>> >
>> >
>> > I wonder the same. I don't see the difference between this and shout smart 
>> > characters.
>>
>> so may be we could remove this and keep smart characters.
>> Now that there is a setting we could try and see.
>>
>> Do you know where/why/who added this?  because I guess there is a reason 
>> that we don't see.
>
> In fact I do not understand :) since ithought that the code was coming from 
> cuis and cuis does not
> implement it at all. may this is evil autogenerating code :)
>

Maybe Pharo runs some hidden AI process, which refactors and changes
things under the hood? :)

> Stef
> ___
> 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] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Igor Stasenko
On 19 October 2010 03:42, Levente Uzonyi  wrote:
> On Tue, 19 Oct 2010, Igor Stasenko wrote:
>
>> On 19 October 2010 02:06, Levente Uzonyi  wrote:
>>>
>>> On Mon, 18 Oct 2010, Igor Stasenko wrote:
>>>
>>> snip
>>>

>>>
>>> Thanks, Levente for giving a feedback.
>>> Please, feel free to shape my classes in more complete from (such as
>>> proper naming),
>>> to make them ready for inclusion in both Squeak's and Pharo cores.
>>> I propose the following names:
>>> AtomicQueue (base class) -> AtomicCollection
>>> FIFOQueue -> AtomicQueue
>>> LIFOQueue -> AtomicStack
>>> If you, or anyone else having better suggestions, speak now :)
>>>
>>>
>>>
>>> I think these should be the names:
>>>
>>> FIFOQueue -> SharedQueue
>>
>> this name already used by Kernel.
>> So, unless my class will fully replace it, i see no way how i could
>> use this name in separate package.
>
> Yes, it would be good to replace the implementation IMHO. The API seems to
> be complete to me (except for copying ;)).
>
You mean this:

copy
^ self errorDontCopy

errorDontCopy
"copying a structure, involved in concurrent operations is a bad idea"
^ self error: 'Copying not available'

:)

See how Squeak's EventSensor doing right thing to make a 'copy':

EventSensor>>flushAllButDandDEvents
| newQueue oldQueue  |

newQueue := SharedQueue new.
self eventQueue ifNil:
[eventQueue := newQueue.
^self].
oldQueue := self eventQueue.
[oldQueue size > 0] whileTrue:
[| item type |
item := oldQueue next.
type := item at: 1.
type = EventTypeDragDropFiles ifTrue: [ newQueue nextPut: 
item]].
eventQueue := newQueue.

Well, you might be right, that #copy can be implemented as:

copy
   | copy |
   copy := self class new.
   [ copy put: (self nextIfNone: [ ^ copy ] ) ] repeat

if it makes any sense, to anyone..

Its hard to imagine a situation where one may need to copy existing queue,
because he simply can keep using it.


>>
>> Also, i must stress, that behavior of FIFOQueue only attempts to
>> closely resemble the SharedQueue behavior.
>> However, there is a situations (related to how scheduling works and
>> use of #yield), where using them could lead to deadlocks.
>> In this regard, an AtomicSharedQueue (a subclass of FIFOQueue) is much
>> better analogy to current SharedQueue.
>
> If you mean the case: "if process A tries to read from an empty queue, later
> process B tries to do the same, then process A is guaranteed to read before
> process B", then that shouldn't be a problem. It would require an external
> synchronization step to make use of this feature with the current
> implementation. I doubt that anyone wrote such code ever.
>
No. The problems is not in that. The problem related to scheduling and
how #yield primitive works.

Here the VM's primitiveYield:

primitiveYield
"primitively do the equivalent of Process>yield"
| activeProc priority processLists processList |
activeProc := self fetchPointer: ActiveProcessIndex
 ofObject: self 
schedulerPointer.
priority := self quickFetchInteger: PriorityIndex ofObject: activeProc.
processLists := self fetchPointer: ProcessListsIndex ofObject: self
schedulerPointer.
processList := self fetchPointer: priority - 1 ofObject: processLists.

(self isEmptyList: processList) ifFalse:[
self addLastLink: activeProc toList: processList.
self transferTo: self wakeHighestPriority]

Note #wakeHighestPriority.

So, a fetcher (which using #yield in spin loop) with priority higher
than pusher process, will loop infinitely
blocking pusher and all lower priority processes from advancing.

To avoid this problem, one should make sure that process which pushing
new items to queue
having either higher or same priority as any fetching process(es)
using same queue.
Or use wait-free access to queue (avoid use #next, use #nextOrNil instead).

That's why in subclass - AtomicSharedQueue, i using semaphore to
workaround this issue.

And potentially, it would be good some day to have a way to say to scheduler:
please stop current process and see if you can run anything with lower priority.
(Another reason to move scheduling to language side, so we are free to
modify it in a way we like ;).

>>
>> As i noted in another mail, i see that we might also provide a
>> separate wait-free interface. So we can guarantee,
>> that if you using only wait-free interface, a queue can never be the
>> cause of deadlock.
>
> That's great, and it can be a future addition even if we push the current
> implementation to the Trunk.
>

Yes. I think that for most cases in concurrent environment, a
wait-free access is preferable way to work with queues.


>
> Levente
>



-- 
Best regards,
Igor Stasenko AKA sig.

___
Pha

Re: [Pharo-project] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Levente Uzonyi

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 02:06, Levente Uzonyi  wrote:

On Mon, 18 Oct 2010, Igor Stasenko wrote:

snip





Thanks, Levente for giving a feedback.
Please, feel free to shape my classes in more complete from (such as
proper naming),
to make them ready for inclusion in both Squeak's and Pharo cores.
I propose the following names:
AtomicQueue (base class) -> AtomicCollection
FIFOQueue -> AtomicQueue
LIFOQueue -> AtomicStack
If you, or anyone else having better suggestions, speak now :)



I think these should be the names:

FIFOQueue -> SharedQueue


this name already used by Kernel.
So, unless my class will fully replace it, i see no way how i could
use this name in separate package.


Yes, it would be good to replace the implementation IMHO. The API seems to 
be complete to me (except for copying ;)).




Also, i must stress, that behavior of FIFOQueue only attempts to
closely resemble the SharedQueue behavior.
However, there is a situations (related to how scheduling works and
use of #yield), where using them could lead to deadlocks.
In this regard, an AtomicSharedQueue (a subclass of FIFOQueue) is much
better analogy to current SharedQueue.


If you mean the case: "if process A tries to read from an empty queue, 
later process B tries to do the same, then process A is guaranteed to 
read before process B", then that shouldn't be a problem. It would require 
an external synchronization step to make use of this feature with the 
current implementation. I doubt that anyone wrote such code ever.




As i noted in another mail, i see that we might also provide a
separate wait-free interface. So we can guarantee,
that if you using only wait-free interface, a queue can never be the
cause of deadlock.


That's great, and it can be a future addition even if we push the current 
implementation to the Trunk.



Levente




LIFOQueue -> SharedStack

I don't know a really good name for AtomicQueue, maybe SharedList,
SharedCollection or SharedListStub.


Levente



In any case, i'm am open to discuss further details and possible
caveats of using new classes
to anyone interested in using them.

P.S. As a side note, i now can explain (to myself at first place), why
i intuitively choosed to used atomic swap
instead of CAS.
Because it fits better fits with smalltalk language semantics:

A swap operation in smalltalk implemented as two assignments:
x := y. y := z.
An assignments is basic operation, which have nothing to do with
late-bound nature of language.
Unless we going to introduce a meta-object protocol(s), which could
turn a simple assignment
into some message sends under the hood, it will remain a basic,
early-bound operation.
And even if we do, it is highly unlikely, that even then we will throw
away the old,
simple assignment, which identifies an assignment source & target at
compile time.

In contrast, a CAS operation , if written in smalltalk looks like:

(a == b ) ifTrue: [ a := c ]

so, it having two message sends (#== , #ifTrue:), and from strict,
pure language perspective,
this using a late-bound semantics (a message sends),
and as any message send, the message result and behavior cannot be
predicted at compile time
and therefore its wrong to assume that such statement could be an
atomic operation.

Unless, of course, we introduce a new language syntax which will
denote a CAS operation explicitly.



Levente


snip




--
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






--
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] Stack should be reimplemented with Array

2010-10-18 Thread Levente Uzonyi

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 00:25, Levente Uzonyi  wrote:

On Mon, 18 Oct 2010, Igor Stasenko wrote:


Stephane, i could say more:
- i don't like how LinkedList implemented.

I don't see why it should mimic things like #at: #at:put: at all..


It's not mimicing those methods. A list usually support things like this,
but the user should know the consequences.



The consequences of such approach is much more far-reaching: leads to
bad design practices, crappy application performance,
and then tons of bugs and workarounds.


Are programmers idiots? If not, then we shouldn't treat them like idiots.




IMO this protocol should be pruned from it, to not provoke uses which
completely do not fit for given data structure.


I'm not sure if it's okay to remove features, because users lacking really
basic CS knowledge may use them the wrong way.



Imo, we should prohibit this from the beginning. Standard, core
classes should not contain an API, which could lead to
careless, abusive programming techniques.


So we should get rid of SortedCollection, remove #includes: #indexOf: from 
ArrayedCollections, get rid of OrderedCollection >> #remove:, etc. Am I 
right?



IMO, a kernel APIs should serve not only as an implementation of basic
system funcionality, it also must serve as guide,
how to best use these facilities, so people will learn what is the
right way to use it.


That's right, but there's no need to remove useful features to achieve 
this.




We should teach users to use right tools for things they need.




Removing/inserting into the middle of list is quite ineffective
operation (O(n)),


As long as you don't give away the link objects, it's O(n), otherwise it can
be O(1).


giving away link objects... oh, that's the worst thing, which could
possibly happen :)


No. It's the user's responsibility to use it wisely. If you don't need to 
access a internal nodes, just adding/removing elements to/from the list, 
then you probably shouldn't use a list at all.







while inserting at the begginning/end of list is O(1).

Lists are sequenceable.. but sequenceable ~~ indexable. Period.


Sequenceable is indexable, but good performance is not guaranteed.


Unless you representing an infinite collection(s).
Streams are good example of sequenceable, however non-indexable containers.


Streams are more like external iterators, than containers IMHO. But you 
can get/set the position of most streams.



Levente






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





--
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] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Igor Stasenko
On 19 October 2010 02:06, Levente Uzonyi  wrote:
> On Mon, 18 Oct 2010, Igor Stasenko wrote:
>
> snip
>
>>
>
> Thanks, Levente for giving a feedback.
> Please, feel free to shape my classes in more complete from (such as
> proper naming),
> to make them ready for inclusion in both Squeak's and Pharo cores.
> I propose the following names:
> AtomicQueue (base class) -> AtomicCollection
> FIFOQueue -> AtomicQueue
> LIFOQueue -> AtomicStack
> If you, or anyone else having better suggestions, speak now :)
>
>
>
> I think these should be the names:
>
> FIFOQueue -> SharedQueue

this name already used by Kernel.
So, unless my class will fully replace it, i see no way how i could
use this name in separate package.

Also, i must stress, that behavior of FIFOQueue only attempts to
closely resemble the SharedQueue behavior.
However, there is a situations (related to how scheduling works and
use of #yield), where using them could lead to deadlocks.
In this regard, an AtomicSharedQueue (a subclass of FIFOQueue) is much
better analogy to current SharedQueue.

As i noted in another mail, i see that we might also provide a
separate wait-free interface. So we can guarantee,
that if you using only wait-free interface, a queue can never be the
cause of deadlock.

> LIFOQueue -> SharedStack
>
> I don't know a really good name for AtomicQueue, maybe SharedList,
> SharedCollection or SharedListStub.
>
>
> Levente
>
>
>
> In any case, i'm am open to discuss further details and possible
> caveats of using new classes
> to anyone interested in using them.
>
> P.S. As a side note, i now can explain (to myself at first place), why
> i intuitively choosed to used atomic swap
> instead of CAS.
> Because it fits better fits with smalltalk language semantics:
>
> A swap operation in smalltalk implemented as two assignments:
> x := y. y := z.
> An assignments is basic operation, which have nothing to do with
> late-bound nature of language.
> Unless we going to introduce a meta-object protocol(s), which could
> turn a simple assignment
> into some message sends under the hood, it will remain a basic,
> early-bound operation.
> And even if we do, it is highly unlikely, that even then we will throw
> away the old,
> simple assignment, which identifies an assignment source & target at
> compile time.
>
> In contrast, a CAS operation , if written in smalltalk looks like:
>
> (a == b ) ifTrue: [ a := c ]
>
> so, it having two message sends (#== , #ifTrue:), and from strict,
> pure language perspective,
> this using a late-bound semantics (a message sends),
> and as any message send, the message result and behavior cannot be
> predicted at compile time
> and therefore its wrong to assume that such statement could be an
> atomic operation.
>
> Unless, of course, we introduce a new language syntax which will
> denote a CAS operation explicitly.
>
>>
>> Levente
>>
>>
>> snip
>>
>
>
> --
> 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
>
>



-- 
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] Stack should be reimplemented with Array

2010-10-18 Thread Igor Stasenko
On 19 October 2010 00:25, Levente Uzonyi  wrote:
> On Mon, 18 Oct 2010, Igor Stasenko wrote:
>
>> Stephane, i could say more:
>> - i don't like how LinkedList implemented.
>>
>> I don't see why it should mimic things like #at: #at:put: at all..
>
> It's not mimicing those methods. A list usually support things like this,
> but the user should know the consequences.
>

The consequences of such approach is much more far-reaching: leads to
bad design practices, crappy application performance,
and then tons of bugs and workarounds.

>> IMO this protocol should be pruned from it, to not provoke uses which
>> completely do not fit for given data structure.
>
> I'm not sure if it's okay to remove features, because users lacking really
> basic CS knowledge may use them the wrong way.
>

Imo, we should prohibit this from the beginning. Standard, core
classes should not contain an API, which could lead to
careless, abusive programming techniques.
IMO, a kernel APIs should serve not only as an implementation of basic
system funcionality, it also must serve as guide,
how to best use these facilities, so people will learn what is the
right way to use it.

We should teach users to use right tools for things they need.


>>
>> Removing/inserting into the middle of list is quite ineffective
>> operation (O(n)),
>
> As long as you don't give away the link objects, it's O(n), otherwise it can
> be O(1).

giving away link objects... oh, that's the worst thing, which could
possibly happen :)

>
>> while inserting at the begginning/end of list is O(1).
>>
>> Lists are sequenceable.. but sequenceable ~~ indexable. Period.
>
> Sequenceable is indexable, but good performance is not guaranteed.
>
Unless you representing an infinite collection(s).
Streams are good example of sequenceable, however non-indexable containers.


>
> 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
>



-- 
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] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Levente Uzonyi

On Mon, 18 Oct 2010, Igor Stasenko wrote:

snip





Thanks, Levente for giving a feedback.
Please, feel free to shape my classes in more complete from (such as
proper naming),
to make them ready for inclusion in both Squeak's and Pharo cores.
I propose the following names:
AtomicQueue (base class) -> AtomicCollection
FIFOQueue -> AtomicQueue
LIFOQueue -> AtomicStack
If you, or anyone else having better suggestions, speak now :)



I think these should be the names:

FIFOQueue -> SharedQueue
LIFOQueue -> SharedStack

I don't know a really good name for AtomicQueue, maybe SharedList, 
SharedCollection or SharedListStub.



Levente



In any case, i'm am open to discuss further details and possible
caveats of using new classes
to anyone interested in using them.

P.S. As a side note, i now can explain (to myself at first place), why
i intuitively choosed to used atomic swap
instead of CAS.
Because it fits better fits with smalltalk language semantics:

A swap operation in smalltalk implemented as two assignments:
x := y. y := z.
An assignments is basic operation, which have nothing to do with
late-bound nature of language.
Unless we going to introduce a meta-object protocol(s), which could
turn a simple assignment
into some message sends under the hood, it will remain a basic,
early-bound operation.
And even if we do, it is highly unlikely, that even then we will throw
away the old,
simple assignment, which identifies an assignment source & target at
compile time.

In contrast, a CAS operation , if written in smalltalk looks like:

(a == b ) ifTrue: [ a := c ]

so, it having two message sends (#== , #ifTrue:), and from strict,
pure language perspective,
this using a late-bound semantics (a message sends),
and as any message send, the message result and behavior cannot be
predicted at compile time
and therefore its wrong to assume that such statement could be an
atomic operation.

Unless, of course, we introduce a new language syntax which will
denote a CAS operation explicitly.



Levente


snip




--
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


[Pharo-project] SqueakSource are down

2010-10-18 Thread Igor Stasenko
Hello,

:(

Guys, are there a reason , why we can't address this problem once and for all?


-- 
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] Speeding up Pharo 1.1

2010-10-18 Thread Igor Stasenko
2010/10/19 Levente Uzonyi :
> On Tue, 19 Oct 2010, Igor Stasenko wrote:
>
>> On 19 October 2010 00:30, Henrik Sperre Johansen
>
>  wrote:
>>
>>  On 18.10.2010 23:21, Igor Stasenko wrote:
>>>
>>> 2010/10/19 Levente Uzonyi:

 On Mon, 18 Oct 2010, Nicolas Cellier wrote:

> 2010/10/18 Igor Stasenko:
>>
>> On 18 October 2010 23:18, Nicolas Cellier
>>   wrote:
>>>
>>> 2010/10/17 Levente Uzonyi:

 On Sat, 16 Oct 2010, Bart Veenstra wrote:

> Hi list,
>
> I have been working with Pharo for almost a month now, and I
> suspect
> that the performance is degrading fast. UI tasks takes several
> seconds
> to react to my keyboard.

 That kind of sluggishness is probably related to finalization/gc.
 Please
 send us the result of the following expression:

 (WeakArray classPool at: #FinalizationDependents)
        select: [ :each | each notNil ]
        thenCollect: [ :each | each class ->  each size ]

>>> While updating pharo 1.2, after an EndOfCentralDirectory error, I got
>>> a very unresponsive image...
>>>
>>> ((WeakArray classPool at: #FinalizationDependents) as: Array)
>>>       select: [ :each | each notNil ]
>>>       thenCollect: [ :each | each class ->  each size]
>>> ->
>>> {(WeakIdentityKeyDictionary->22370).
>>
>> This is an MC cache. And major reason of image slowdown.
>>
> Levente did this simplification in trunk:
>
> cachedDefinitions
>        ^definitions ifNil: [ definitions := WeakIdentityKeyDictionary
> new
> ]
>
> It would be worth a try in Pharo.

 IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if
 they're not registered to the finalization process. So this won't work
 as
 long as that's not fixed.

>>> Huh? Can you provide a code to show it? Test case please?
>>>
>> Just add lots of objects which will be GC'd to an unregistered
>> WeakKeyDictionary.
>> After X objects are gc'd, you'd still have X nil-keyed associations in the
>> dictionary.
>> Add Y objects, gc those, and you have X+Y nil-keys in the dict.
>> (If dict grown/rehashed, all nicely placed index 1 onwards)
>>
>
> it doesn't sounds like incorrect behavior (i.e. pruning a nil-ed keys
> before #finalizeValues could visit them).
>
>
> It's incorrect, because WeakKeyDictionaries are not designed to be accessed
> concurrently, but this can happen if the dictionary is registered to the
> finalization process.

True. Another reason to not register them like MC in Pharo currently does.

> It's inefficient, because someone has to send #finalizeValues, even when
> there's no finalization action.
>
That's why in my patch, i placed #finalizeValues on finishing package
load/unload actions.

>
> Levente
>
>
>> 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
> ___
> 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] Speeding up Pharo 1.1

2010-10-18 Thread Levente Uzonyi

On Tue, 19 Oct 2010, Igor Stasenko wrote:


On 19 October 2010 00:30, Henrik Sperre Johansen

 wrote:

 On 18.10.2010 23:21, Igor Stasenko wrote:


2010/10/19 Levente Uzonyi:


On Mon, 18 Oct 2010, Nicolas Cellier wrote:


2010/10/18 Igor Stasenko:


On 18 October 2010 23:18, Nicolas Cellier
  wrote:


2010/10/17 Levente Uzonyi:


On Sat, 16 Oct 2010, Bart Veenstra wrote:


Hi list,

I have been working with Pharo for almost a month now, and I suspect
that the performance is degrading fast. UI tasks takes several
seconds
to react to my keyboard.


That kind of sluggishness is probably related to finalization/gc.
Please
send us the result of the following expression:

(WeakArray classPool at: #FinalizationDependents)
       select: [ :each | each notNil ]
       thenCollect: [ :each | each class ->  each size ]


While updating pharo 1.2, after an EndOfCentralDirectory error, I got
a very unresponsive image...

((WeakArray classPool at: #FinalizationDependents) as: Array)
      select: [ :each | each notNil ]
      thenCollect: [ :each | each class ->  each size]
->
{(WeakIdentityKeyDictionary->22370).


This is an MC cache. And major reason of image slowdown.


Levente did this simplification in trunk:

cachedDefinitions
       ^definitions ifNil: [ definitions := WeakIdentityKeyDictionary
new
]

It would be worth a try in Pharo.


IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if
they're not registered to the finalization process. So this won't work as
long as that's not fixed.


Huh? Can you provide a code to show it? Test case please?


Just add lots of objects which will be GC'd to an unregistered
WeakKeyDictionary.
After X objects are gc'd, you'd still have X nil-keyed associations in the
dictionary.
Add Y objects, gc those, and you have X+Y nil-keys in the dict.
(If dict grown/rehashed, all nicely placed index 1 onwards)



it doesn't sounds like incorrect behavior (i.e. pruning a nil-ed keys
before #finalizeValues could visit them).


It's incorrect, because WeakKeyDictionaries are not designed to be 
accessed concurrently, but this can happen if the dictionary is 
registered to the finalization process.
It's inefficient, because someone has to send #finalizeValues, even when 
there's no finalization action.



Levente



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___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Speeding up Pharo 1.1

2010-10-18 Thread Henrik Sperre Johansen

 On 18.10.2010 23:43, Igor Stasenko wrote:

On 19 October 2010 00:30, Henrik Sperre Johansen
  wrote:

  On 18.10.2010 23:21, Igor Stasenko wrote:

2010/10/19 Levente Uzonyi:

On Mon, 18 Oct 2010, Nicolas Cellier wrote:


2010/10/18 Igor Stasenko:

On 18 October 2010 23:18, Nicolas Cellier
wrote:

2010/10/17 Levente Uzonyi:

On Sat, 16 Oct 2010, Bart Veenstra wrote:


Hi list,

I have been working with Pharo for almost a month now, and I suspect
that the performance is degrading fast. UI tasks takes several
seconds
to react to my keyboard.

That kind of sluggishness is probably related to finalization/gc.
Please
send us the result of the following expression:

(WeakArray classPool at: #FinalizationDependents)
select: [ :each | each notNil ]
thenCollect: [ :each | each class ->each size ]


While updating pharo 1.2, after an EndOfCentralDirectory error, I got
a very unresponsive image...

((WeakArray classPool at: #FinalizationDependents) as: Array)
   select: [ :each | each notNil ]
   thenCollect: [ :each | each class ->each size]
->
{(WeakIdentityKeyDictionary->22370).

This is an MC cache. And major reason of image slowdown.


Levente did this simplification in trunk:

cachedDefinitions
^definitions ifNil: [ definitions := WeakIdentityKeyDictionary
new
]

It would be worth a try in Pharo.

IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if
they're not registered to the finalization process. So this won't work as
long as that's not fixed.


Huh? Can you provide a code to show it? Test case please?


Just add lots of objects which will be GC'd to an unregistered
WeakKeyDictionary.
After X objects are gc'd, you'd still have X nil-keyed associations in the
dictionary.
Add Y objects, gc those, and you have X+Y nil-keys in the dict.
(If dict grown/rehashed, all nicely placed index 1 onwards)


it doesn't sounds like incorrect behavior (i.e. pruning a nil-ed keys
before #finalizeValues could visit them).

Except, you know, if they're not registered for finalization at all, 
they're probably not meant to be finalized.


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] Speeding up Pharo 1.1

2010-10-18 Thread Igor Stasenko
On 19 October 2010 00:30, Henrik Sperre Johansen
 wrote:
>  On 18.10.2010 23:21, Igor Stasenko wrote:
>>
>> 2010/10/19 Levente Uzonyi:
>>>
>>> On Mon, 18 Oct 2010, Nicolas Cellier wrote:
>>>
 2010/10/18 Igor Stasenko:
>
> On 18 October 2010 23:18, Nicolas Cellier
>   wrote:
>>
>> 2010/10/17 Levente Uzonyi:
>>>
>>> On Sat, 16 Oct 2010, Bart Veenstra wrote:
>>>
 Hi list,

 I have been working with Pharo for almost a month now, and I suspect
 that the performance is degrading fast. UI tasks takes several
 seconds
 to react to my keyboard.
>>>
>>> That kind of sluggishness is probably related to finalization/gc.
>>> Please
>>> send us the result of the following expression:
>>>
>>> (WeakArray classPool at: #FinalizationDependents)
>>>        select: [ :each | each notNil ]
>>>        thenCollect: [ :each | each class ->  each size ]
>>>
>> While updating pharo 1.2, after an EndOfCentralDirectory error, I got
>> a very unresponsive image...
>>
>> ((WeakArray classPool at: #FinalizationDependents) as: Array)
>>       select: [ :each | each notNil ]
>>       thenCollect: [ :each | each class ->  each size]
>> ->
>> {(WeakIdentityKeyDictionary->22370).
>
> This is an MC cache. And major reason of image slowdown.
>
 Levente did this simplification in trunk:

 cachedDefinitions
        ^definitions ifNil: [ definitions := WeakIdentityKeyDictionary
 new
 ]

 It would be worth a try in Pharo.
>>>
>>> IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if
>>> they're not registered to the finalization process. So this won't work as
>>> long as that's not fixed.
>>>
>> Huh? Can you provide a code to show it? Test case please?
>>
> Just add lots of objects which will be GC'd to an unregistered
> WeakKeyDictionary.
> After X objects are gc'd, you'd still have X nil-keyed associations in the
> dictionary.
> Add Y objects, gc those, and you have X+Y nil-keys in the dict.
> (If dict grown/rehashed, all nicely placed index 1 onwards)
>

it doesn't sounds like incorrect behavior (i.e. pruning a nil-ed keys
before #finalizeValues could visit them).

> 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] Speeding up Pharo 1.1

2010-10-18 Thread Henrik Sperre Johansen

 On 18.10.2010 23:21, Igor Stasenko wrote:

2010/10/19 Levente Uzonyi:

On Mon, 18 Oct 2010, Nicolas Cellier wrote:


2010/10/18 Igor Stasenko:

On 18 October 2010 23:18, Nicolas Cellier
  wrote:

2010/10/17 Levente Uzonyi:

On Sat, 16 Oct 2010, Bart Veenstra wrote:


Hi list,

I have been working with Pharo for almost a month now, and I suspect
that the performance is degrading fast. UI tasks takes several seconds
to react to my keyboard.

That kind of sluggishness is probably related to finalization/gc.
Please
send us the result of the following expression:

(WeakArray classPool at: #FinalizationDependents)
select: [ :each | each notNil ]
thenCollect: [ :each | each class ->  each size ]


While updating pharo 1.2, after an EndOfCentralDirectory error, I got
a very unresponsive image...

((WeakArray classPool at: #FinalizationDependents) as: Array)
   select: [ :each | each notNil ]
   thenCollect: [ :each | each class ->  each size]
->
{(WeakIdentityKeyDictionary->22370).

This is an MC cache. And major reason of image slowdown.


Levente did this simplification in trunk:

cachedDefinitions
^definitions ifNil: [ definitions := WeakIdentityKeyDictionary new
]

It would be worth a try in Pharo.

IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if
they're not registered to the finalization process. So this won't work as
long as that's not fixed.


Huh? Can you provide a code to show it? Test case please?

Just add lots of objects which will be GC'd to an unregistered 
WeakKeyDictionary.
After X objects are gc'd, you'd still have X nil-keyed associations in 
the dictionary.

Add Y objects, gc those, and you have X+Y nil-keys in the dict.
(If dict grown/rehashed, all nicely placed index 1 onwards)

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] Stack should be reimplemented with Array

2010-10-18 Thread Levente Uzonyi

On Mon, 18 Oct 2010, Igor Stasenko wrote:


Stephane, i could say more:
- i don't like how LinkedList implemented.

I don't see why it should mimic things like #at: #at:put: at all..


It's not mimicing those methods. A list usually support things like this, 
but the user should know the consequences.



IMO this protocol should be pruned from it, to not provoke uses which
completely do not fit for given data structure.


I'm not sure if it's okay to remove features, because users lacking really 
basic CS knowledge may use them the wrong way.




Removing/inserting into the middle of list is quite ineffective
operation (O(n)),


As long as you don't give away the link objects, it's O(n), otherwise it 
can be O(1).



while inserting at the begginning/end of list is O(1).

Lists are sequenceable.. but sequenceable ~~ indexable. Period.


Sequenceable is indexable, but good performance is not guaranteed.


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] Speeding up Pharo 1.1

2010-10-18 Thread Igor Stasenko
2010/10/19 Levente Uzonyi :
> On Mon, 18 Oct 2010, Nicolas Cellier wrote:
>
>> 2010/10/18 Igor Stasenko :
>>>
>>> On 18 October 2010 23:18, Nicolas Cellier
>>>  wrote:

 2010/10/17 Levente Uzonyi :
>
> On Sat, 16 Oct 2010, Bart Veenstra wrote:
>
>> Hi list,
>>
>> I have been working with Pharo for almost a month now, and I suspect
>> that the performance is degrading fast. UI tasks takes several seconds
>> to react to my keyboard.
>
> That kind of sluggishness is probably related to finalization/gc.
> Please
> send us the result of the following expression:
>
> (WeakArray classPool at: #FinalizationDependents)
>        select: [ :each | each notNil ]
>        thenCollect: [ :each | each class -> each size ]
>

 While updating pharo 1.2, after an EndOfCentralDirectory error, I got
 a very unresponsive image...

 ((WeakArray classPool at: #FinalizationDependents) as: Array)
       select: [ :each | each notNil ]
       thenCollect: [ :each | each class -> each size]
 ->
 {(WeakIdentityKeyDictionary->22370).
>>>
>>> This is an MC cache. And major reason of image slowdown.
>>>
>>
>> Levente did this simplification in trunk:
>>
>> cachedDefinitions
>>        ^definitions ifNil: [ definitions := WeakIdentityKeyDictionary new
>> ]
>>
>> It would be worth a try in Pharo.
>
> IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if
> they're not registered to the finalization process. So this won't work as
> long as that's not fixed.
>

Huh? Can you provide a code to show it? Test case please?


>
> Levente
>
>>
>> Nicolas
>>
 (WeakRegistry->0).
 (WeakRegistry->0). (WeakRegistry->0). (WeakRegistry->2)}

 I tried to inspect it 5 minutes ago, but hey, answer in another email...
 Ah, OK, cmd+shift+. just worked. I had to interrupt
 #finalizationProcess itself finally...
 Oh inspect is sorting the keys... unusable.
 So what's in the array ? Things like

 (ScriptLoader>>#update12125 "a CompiledMethod(0)")->a
 MCMethodDefinition(ScriptLoader>>update12125)
 (PragmaCollector>>#release "a CompiledMethod(964689920)")->a
 MCMethodDefinition(PragmaCollector>>release)
 (Float>>#arcSin "a CompiledMethod(358088704)")->a
 MCMethodDefinition(Float>>arcSin)

 I don't understand yet, but I begin to gather clues why updating pharo
 goes so badly...

 Nicolas

 ___
 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
>
> ___
> 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] Speeding up Pharo 1.1

2010-10-18 Thread Levente Uzonyi

On Mon, 18 Oct 2010, Nicolas Cellier wrote:


2010/10/18 Igor Stasenko :

On 18 October 2010 23:18, Nicolas Cellier
 wrote:

2010/10/17 Levente Uzonyi :

On Sat, 16 Oct 2010, Bart Veenstra wrote:


Hi list,

I have been working with Pharo for almost a month now, and I suspect
that the performance is degrading fast. UI tasks takes several seconds
to react to my keyboard.


That kind of sluggishness is probably related to finalization/gc. Please
send us the result of the following expression:

(WeakArray classPool at: #FinalizationDependents)
       select: [ :each | each notNil ]
       thenCollect: [ :each | each class -> each size ]



While updating pharo 1.2, after an EndOfCentralDirectory error, I got
a very unresponsive image...

((WeakArray classPool at: #FinalizationDependents) as: Array)
      select: [ :each | each notNil ]
      thenCollect: [ :each | each class -> each size]
->
{(WeakIdentityKeyDictionary->22370).


This is an MC cache. And major reason of image slowdown.



Levente did this simplification in trunk:

cachedDefinitions
^definitions ifNil: [ definitions := WeakIdentityKeyDictionary new ]

It would be worth a try in Pharo.


IIRC Pharo's WeakKeyDictionary (and subclasses) don't work properly if 
they're not registered to the finalization process. So this won't work 
as long as that's not fixed.



Levente



Nicolas


(WeakRegistry->0).
(WeakRegistry->0). (WeakRegistry->0). (WeakRegistry->2)}

I tried to inspect it 5 minutes ago, but hey, answer in another email...
Ah, OK, cmd+shift+. just worked. I had to interrupt
#finalizationProcess itself finally...
Oh inspect is sorting the keys... unusable.
So what's in the array ? Things like

(ScriptLoader>>#update12125 "a CompiledMethod(0)")->a
MCMethodDefinition(ScriptLoader>>update12125)
(PragmaCollector>>#release "a CompiledMethod(964689920)")->a
MCMethodDefinition(PragmaCollector>>release)
(Float>>#arcSin "a CompiledMethod(358088704)")->a
MCMethodDefinition(Float>>arcSin)

I don't understand yet, but I begin to gather clues why updating pharo
goes so badly...

Nicolas

___
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
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] Speeding up Pharo 1.1

2010-10-18 Thread Levente Uzonyi

On Mon, 18 Oct 2010, Nicolas Cellier wrote:


2010/10/17 Levente Uzonyi :

On Sat, 16 Oct 2010, Bart Veenstra wrote:


Hi list,

I have been working with Pharo for almost a month now, and I suspect
that the performance is degrading fast. UI tasks takes several seconds
to react to my keyboard.


That kind of sluggishness is probably related to finalization/gc. Please
send us the result of the following expression:

(WeakArray classPool at: #FinalizationDependents)
       select: [ :each | each notNil ]
       thenCollect: [ :each | each class -> each size ]



While updating pharo 1.2, after an EndOfCentralDirectory error, I got
a very unresponsive image...

((WeakArray classPool at: #FinalizationDependents) as: Array)
  select: [ :each | each notNil ]
  thenCollect: [ :each | each class -> each size]
->
{(WeakIdentityKeyDictionary->22370). (WeakRegistry->0).
(WeakRegistry->0). (WeakRegistry->0). (WeakRegistry->2)}

I tried to inspect it 5 minutes ago, but hey, answer in another email...
Ah, OK, cmd+shift+. just worked. I had to interrupt
#finalizationProcess itself finally...
Oh inspect is sorting the keys... unusable.
So what's in the array ? Things like

(ScriptLoader>>#update12125 "a CompiledMethod(0)")->a
MCMethodDefinition(ScriptLoader>>update12125)
(PragmaCollector>>#release "a CompiledMethod(964689920)")->a
MCMethodDefinition(PragmaCollector>>release)
(Float>>#arcSin "a CompiledMethod(358088704)")->a
MCMethodDefinition(Float>>arcSin)

I don't understand yet, but I begin to gather clues why updating pharo
goes so badly...


IIRC Igor already checked that most of the time is spend in the 
finalization process and gc.



Levente



Nicolas

___
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] Speeding up Pharo 1.1

2010-10-18 Thread Igor Stasenko
On 18 October 2010 23:41, Nicolas Cellier
 wrote:
> 2010/10/18 Igor Stasenko :
>> On 18 October 2010 23:18, Nicolas Cellier
>>  wrote:
>>> 2010/10/17 Levente Uzonyi :
 On Sat, 16 Oct 2010, Bart Veenstra wrote:

> Hi list,
>
> I have been working with Pharo for almost a month now, and I suspect
> that the performance is degrading fast. UI tasks takes several seconds
> to react to my keyboard.

 That kind of sluggishness is probably related to finalization/gc. Please
 send us the result of the following expression:

 (WeakArray classPool at: #FinalizationDependents)
        select: [ :each | each notNil ]
        thenCollect: [ :each | each class -> each size ]

>>>
>>> While updating pharo 1.2, after an EndOfCentralDirectory error, I got
>>> a very unresponsive image...
>>>
>>> ((WeakArray classPool at: #FinalizationDependents) as: Array)
>>>       select: [ :each | each notNil ]
>>>       thenCollect: [ :each | each class -> each size]
>>> ->
>>> {(WeakIdentityKeyDictionary->22370).
>>
>> This is an MC cache. And major reason of image slowdown.
>>
>
> Levente did this simplification in trunk:
>
> cachedDefinitions
>        ^definitions ifNil: [ definitions := WeakIdentityKeyDictionary new ]
>
> It would be worth a try in Pharo.
>

I disagree. Its not a simplification. Its a bug fix! :)

Recently, i provided the similar thing for Pharo (didn't knew it was
already fixed for Squeak):
http://code.google.com/p/pharo/issues/detail?id=3048

> Nicolas
>


-- 
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] Stack should be reimplemented with Array

2010-10-18 Thread Igor Stasenko
Stephane, i could say more:
- i don't like how LinkedList implemented.

I don't see why it should mimic things like #at: #at:put: at all..
IMO this protocol should be pruned from it, to not provoke uses which
completely do not fit for given data structure.

Removing/inserting into the middle of list is quite ineffective
operation (O(n)),
while inserting at the begginning/end of list is O(1).

Lists are sequenceable.. but sequenceable ~~ indexable. Period.

-- 
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] Some questions about pharo

2010-10-18 Thread Alexander Lazarević
2010/10/18 Adrien BARREAU :
> - If I run a headless Pharo, is it possible to display the graphical
> interface after? (for example, if something raises an exception, I want to
> open the GUI and use the debugger)

It depends. If your headless Pharo image is running on a unix VM you
could utilize the genius OSProcess/XDisplayControl plugin available
for this VM. Load the appropriate packages from [1] into your Pharo
image and then you can close and reopen the window even on another
machine if it's running X11. For example this

OSProcess thisOSProcess closeXDisplay.
(Delay forSeconds: 5) wait.
OSProcess thisOSProcess displayOnXServer: ':0.0'.

will close the Window (headless) and reopen it (headful) again on the
local X server after five seconds.
If you're using Seaside in that image you could trigger window
open/close via Seaside or you could change the default handler for
errors to make the window open on the local display as a default, ...

Alex

[1] http://www.squeaksource.com/OSProcess

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


Re: [Pharo-project] Speeding up Pharo 1.1

2010-10-18 Thread Nicolas Cellier
2010/10/18 Igor Stasenko :
> On 18 October 2010 23:18, Nicolas Cellier
>  wrote:
>> 2010/10/17 Levente Uzonyi :
>>> On Sat, 16 Oct 2010, Bart Veenstra wrote:
>>>
 Hi list,

 I have been working with Pharo for almost a month now, and I suspect
 that the performance is degrading fast. UI tasks takes several seconds
 to react to my keyboard.
>>>
>>> That kind of sluggishness is probably related to finalization/gc. Please
>>> send us the result of the following expression:
>>>
>>> (WeakArray classPool at: #FinalizationDependents)
>>>        select: [ :each | each notNil ]
>>>        thenCollect: [ :each | each class -> each size ]
>>>
>>
>> While updating pharo 1.2, after an EndOfCentralDirectory error, I got
>> a very unresponsive image...
>>
>> ((WeakArray classPool at: #FinalizationDependents) as: Array)
>>       select: [ :each | each notNil ]
>>       thenCollect: [ :each | each class -> each size]
>> ->
>> {(WeakIdentityKeyDictionary->22370).
>
> This is an MC cache. And major reason of image slowdown.
>

Levente did this simplification in trunk:

cachedDefinitions
^definitions ifNil: [ definitions := WeakIdentityKeyDictionary new ]

It would be worth a try in Pharo.

Nicolas

>> (WeakRegistry->0).
>> (WeakRegistry->0). (WeakRegistry->0). (WeakRegistry->2)}
>>
>> I tried to inspect it 5 minutes ago, but hey, answer in another email...
>> Ah, OK, cmd+shift+. just worked. I had to interrupt
>> #finalizationProcess itself finally...
>> Oh inspect is sorting the keys... unusable.
>> So what's in the array ? Things like
>>
>> (ScriptLoader>>#update12125 "a CompiledMethod(0)")->a
>> MCMethodDefinition(ScriptLoader>>update12125)
>> (PragmaCollector>>#release "a CompiledMethod(964689920)")->a
>> MCMethodDefinition(PragmaCollector>>release)
>> (Float>>#arcSin "a CompiledMethod(358088704)")->a
>> MCMethodDefinition(Float>>arcSin)
>>
>> I don't understand yet, but I begin to gather clues why updating pharo
>> goes so badly...
>>
>> Nicolas
>>
>> ___
>> 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] Speeding up Pharo 1.1

2010-10-18 Thread Igor Stasenko
On 18 October 2010 23:18, Nicolas Cellier
 wrote:
> 2010/10/17 Levente Uzonyi :
>> On Sat, 16 Oct 2010, Bart Veenstra wrote:
>>
>>> Hi list,
>>>
>>> I have been working with Pharo for almost a month now, and I suspect
>>> that the performance is degrading fast. UI tasks takes several seconds
>>> to react to my keyboard.
>>
>> That kind of sluggishness is probably related to finalization/gc. Please
>> send us the result of the following expression:
>>
>> (WeakArray classPool at: #FinalizationDependents)
>>        select: [ :each | each notNil ]
>>        thenCollect: [ :each | each class -> each size ]
>>
>
> While updating pharo 1.2, after an EndOfCentralDirectory error, I got
> a very unresponsive image...
>
> ((WeakArray classPool at: #FinalizationDependents) as: Array)
>       select: [ :each | each notNil ]
>       thenCollect: [ :each | each class -> each size]
> ->
> {(WeakIdentityKeyDictionary->22370).

This is an MC cache. And major reason of image slowdown.

> (WeakRegistry->0).
> (WeakRegistry->0). (WeakRegistry->0). (WeakRegistry->2)}
>
> I tried to inspect it 5 minutes ago, but hey, answer in another email...
> Ah, OK, cmd+shift+. just worked. I had to interrupt
> #finalizationProcess itself finally...
> Oh inspect is sorting the keys... unusable.
> So what's in the array ? Things like
>
> (ScriptLoader>>#update12125 "a CompiledMethod(0)")->a
> MCMethodDefinition(ScriptLoader>>update12125)
> (PragmaCollector>>#release "a CompiledMethod(964689920)")->a
> MCMethodDefinition(PragmaCollector>>release)
> (Float>>#arcSin "a CompiledMethod(358088704)")->a
> MCMethodDefinition(Float>>arcSin)
>
> I don't understand yet, but I begin to gather clues why updating pharo
> goes so badly...
>
> Nicolas
>
> ___
> 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] Stack should be reimplemented with Array

2010-10-18 Thread Eliot Miranda
On Mon, Oct 18, 2010 at 1:02 PM, Stéphane Ducasse  wrote:

> Eliot
>
> > There was a post on this list back in August complaining about Stack
> inheriting from LinkedList. There was some discussion, but apparently no
> resolution, as Stack still inherits from LinkedList in the Pharo 1.2 Core
> Image I just downloaded. Rather than reimplementing it to forward to a
> contained LinkedList, I think it should use an Array internally like
> OrderedCollection does. An Array-based implementation of Stack would be
> faster than one based on LinkedList due to the basic stack operations (push,
> pop and top) being able to rely more on primitives. This assumes that you
> know roughly how a big a stack you need; if you don't, reallocating the
> array and copying its contents over and over again will cost you, but this
> is an exceptional case;-- most stacks are small and when they aren't, the
> programmer usually has enough information to select a reasonable stack size.
> >
> > *No*.  Stack and OrderedCollection differ *usefully*.  Adding an item to
> a Stack is always O(1).  Adding an item to an OrderedCollection is O(N)
> because when the array overflows a new one must be allocated and the old
> objects copied to the new.  Why not apply your speedups to
> OrderedCollection, or is that not possible?  If not possible, then come up
> with a new name and add that.  Please /don't/ change Stack.
>
> I would really like not having Stack inheriting from LinkedList (I hate
> subclassing). Now from a VM point of view
> is there a constraint that Stack as to be a subclass of LList?
>

No.  The VM doesn't know anything about Stack.


>
>
> >
> >
> > Enclosed is a fileout of an Array-based Stack implementation. It trounces
> the LinkedList-based implementation easily, but more interestingly, it
> performs better than an OrderedCollection when used like a stack:
> >
> > Pushing is roughly ~30% faster:
> > r1 :=[10 timesRepeat: [
> >s := Stack new.
> >10 timesRepeat: [s push: #foo]]] timeToRun.
> > r2 := [10 timesRepeat: [
> >oc := OrderedCollection new.
> >10 timesRepeat: [oc addLast: #foo]]] timeToRun.
> > 100 - ((r1 / r2) asFloat * 100).
> >
> > as is pushing + popping:
> > r3 := [10 timesRepeat: [
> >s := Stack new.
> >10 timesRepeat: [s push: #foo].
> >10 timesRepeat: [s pop]]] timeToRun.
> > r4 := [10 timesRepeat: [
> >oc := OrderedCollection new.
> >10 timesRepeat: [oc addLast: #foo].
> >10 timesRepeat: [oc removeLast]]] timeToRun.
> > 100 - ((r3 / r4) asFloat * 100).
> > ___
> > 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] A Lazy Inspector?

2010-10-18 Thread Oscar E A Callau
Thanks Mariano. Now I understand :-)

Cheers

Óscar E A Callau

On 18 Oct 2010, at 16:52, Mariano Martinez Peck  wrote:

> 
> 
> 2010/10/18 Oscar E A Callau 
> 
> On Oct 18, 2010, at 14:44 , Mariano Martinez Peck wrote:
> 
>> On Mon, Oct 18, 2010 at 4:40 AM, Oscar E A Callau  
>> wrote:
>> Hello all,
>> 
>> I was wondering what actually the inspector does in the following case:
>> 
>> When you explore (or inspect) the expression: Class environment
>> you get all classes in the system dictionary. If you navigate inside a 
>> class, for example AColorSelectorMorph, you can see all its properties and 
>> one of them is environment, if you go inside it, you get again all classes 
>> in the system dictionary. So, you can repeat this infinitely (or until you 
>> get run out of memory, I guess)
>> 
>> Is it the behavior of a lazy inspector? If true, why I cannot inspect a 
>> mutually-recursive class definition, like this:
>> 
>> Object subclass: #Foo
>>instanceVariableNames: 'bar'
>>classVariableNames: ''
>>poolDictionaries: ''
>>category: ''
>> 
>> Foo>>initialize
>>bar:= Bar new
>> 
>> Object subclass: #Bar
>>instanceVariableNames: 'foo'
>>classVariableNames: ''
>>poolDictionaries: ''
>>category: ''
>> 
>> Foo>>initialize
>>bar:= Foo new
>> 
>> here should be foo := Foo new.
>> 
>> Anyway, you should be able to browse these classes without problems.
>> The problems is in instance creation. For example, if you evaluate: Foo new.
> 
> Thanks Mariano. May be my question was not well explained. Of course if I 
> evaluate: Foo new, I get into a infinite loop. 1st question, when I'm 
> inspecting, I'm evaluating?
> 
> hehehehe yes :)  
> Just open a Transcript and inspect:   Transcript show: 'welooo' 
> and you will see 'welooo' in the transcript ;) 
> 
> What you actually inspect, is the result of the expression.
> 
> 
> 
> In the case that I mention above (Class enviroment) I got all classes in the 
> system and each of them has an environment, that is all classes, and so on. 
> Here, we have a infinite recursion.
> 
> I understand now. 
>  
> So, how the inspector get a lazy visualization of the it?
> 
> 
> I have no idea. But in this case, #environment  is a method, not an instVar 
> as your case.
> Maybe in the case of the methods, they are only displayed when clicking on it 
> (they just execute the compiledMethod). But this is just a guess.
> You should check the class Inspector and NewInspector.
> 
> Cheers
> 
> Mariano
>  
> Greetings 
> 
> 
> 
> ___
> 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] Speeding up Pharo 1.1

2010-10-18 Thread Nicolas Cellier
2010/10/17 Levente Uzonyi :
> On Sat, 16 Oct 2010, Bart Veenstra wrote:
>
>> Hi list,
>>
>> I have been working with Pharo for almost a month now, and I suspect
>> that the performance is degrading fast. UI tasks takes several seconds
>> to react to my keyboard.
>
> That kind of sluggishness is probably related to finalization/gc. Please
> send us the result of the following expression:
>
> (WeakArray classPool at: #FinalizationDependents)
>        select: [ :each | each notNil ]
>        thenCollect: [ :each | each class -> each size ]
>

While updating pharo 1.2, after an EndOfCentralDirectory error, I got
a very unresponsive image...

((WeakArray classPool at: #FinalizationDependents) as: Array)
   select: [ :each | each notNil ]
   thenCollect: [ :each | each class -> each size]
->
{(WeakIdentityKeyDictionary->22370). (WeakRegistry->0).
(WeakRegistry->0). (WeakRegistry->0). (WeakRegistry->2)}

I tried to inspect it 5 minutes ago, but hey, answer in another email...
Ah, OK, cmd+shift+. just worked. I had to interrupt
#finalizationProcess itself finally...
Oh inspect is sorting the keys... unusable.
So what's in the array ? Things like

(ScriptLoader>>#update12125 "a CompiledMethod(0)")->a
MCMethodDefinition(ScriptLoader>>update12125)
(PragmaCollector>>#release "a CompiledMethod(964689920)")->a
MCMethodDefinition(PragmaCollector>>release)
(Float>>#arcSin "a CompiledMethod(358088704)")->a
MCMethodDefinition(Float>>arcSin)

I don't understand yet, but I begin to gather clues why updating pharo
goes so badly...

Nicolas

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


Re: [Pharo-project] call for scripting idea

2010-10-18 Thread Tudor Girba
How about getting the scripts from the Hudson integration (builder) of Lukas 
and translating them into Smalltalk?

Cheers,
Doru


On 18 Oct 2010, at 21:52, stephane ducasse wrote:

> Hi 
> 
> we would like to exercise a bit our scripting engine :) so if you have ideas 
> of scripts that we should be able to write let us know.
> 
> Stef
> ___
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

--
www.tudorgirba.com

"No matter how many recipes we know, we still value a chef."







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


Re: [Pharo-project] Some questions about pharo

2010-10-18 Thread Stéphane Ducasse
in this case we should focus on the next item and provide two images one for 
the debugging scenario and one for normal running of script.

Stef

On Oct 18, 2010, at 9:58 PM, Pavel Krivanek wrote:

> On Mon, Oct 18, 2010 at 9:05 PM, Schwab,Wilhelm K  
> wrote:
>> The Windows vm displays a system tray icon that allows the image to leave 
>> the headless state.  It has been quite useful, but there should be 
>> (hopefully is) a way to prevent that.
> 
> I think that someone asked on squeak-dev some time ago and Andreas
> told that it is not possible with the standard VM.
> 
> -- Pavel
> 
> 
>> 
>> From: pharo-project-boun...@lists.gforge.inria.fr 
>> [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Lukas Renggli 
>> [reng...@gmail.com]
>> Sent: Monday, October 18, 2010 2:09 PM
>> To: Pharo-project@lists.gforge.inria.fr
>> Subject: Re: [Pharo-project] Some questions about pharo
>> 
>> See .
>> 
>> Cheers,
>> Lukas
>> 
>> 2010/10/18 Adrien BARREAU :
>>> Hello =)
>>> 
>>> I have a few questions:
>>> 
>>> - If I run a headless Pharo, is it possible to display the graphical
>>> interface after? (for example, if something raises an exception, I want to
>>> open the GUI and use the debugger)
>>> 
>>> - I wanna run Pharo as a deamon; how can I interact with it after i launched
>>> it? (for example, if I want to give it a piece of code to execute).
>>> 
>>> Adrien.
>>> 
>>> ___
>>> Pharo-project mailing list
>>> Pharo-project@lists.gforge.inria.fr
>>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>> 
>> 
>> 
>> 
>> --
>> Lukas Renggli
>> www.lukas-renggli.ch
>> 
>> ___
>> 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] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Levente Uzonyi

On Mon, 18 Oct 2010, Stéphane Ducasse wrote:



This benchmark is the real concurrent stress test. 100 processes are adding 
10,000 elements to the queue while another 100 are reading from it. It clearly 
shows that Igor's queues are an order of magnitude faster. Also 200 concurrent 
processes cause much less slowdown compared to the sequential tests for them.

So, even though SharedQueue is now faster than SharedQueue2, both will have to 
go IMHO. :)


Hi Levente

Naively why?


Did you see the benchmarks?


and replace by what?


By Igor's new collections. Though the name should be kept for 
compatibility reasons.



Levente



Stef
___
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] Stack should be reimplemented with Array

2010-10-18 Thread Stéphane Ducasse
Eliot

> There was a post on this list back in August complaining about Stack 
> inheriting from LinkedList. There was some discussion, but apparently no 
> resolution, as Stack still inherits from LinkedList in the Pharo 1.2 Core 
> Image I just downloaded. Rather than reimplementing it to forward to a 
> contained LinkedList, I think it should use an Array internally like 
> OrderedCollection does. An Array-based implementation of Stack would be 
> faster than one based on LinkedList due to the basic stack operations (push, 
> pop and top) being able to rely more on primitives. This assumes that you 
> know roughly how a big a stack you need; if you don't, reallocating the array 
> and copying its contents over and over again will cost you, but this is an 
> exceptional case;-- most stacks are small and when they aren't, the 
> programmer usually has enough information to select a reasonable stack size.
> 
> *No*.  Stack and OrderedCollection differ *usefully*.  Adding an item to a 
> Stack is always O(1).  Adding an item to an OrderedCollection is O(N) because 
> when the array overflows a new one must be allocated and the old objects 
> copied to the new.  Why not apply your speedups to OrderedCollection, or is 
> that not possible?  If not possible, then come up with a new name and add 
> that.  Please /don't/ change Stack.

I would really like not having Stack inheriting from LinkedList (I hate 
subclassing). Now from a VM point of view 
is there a constraint that Stack as to be a subclass of LList?


>  
> 
> Enclosed is a fileout of an Array-based Stack implementation. It trounces the 
> LinkedList-based implementation easily, but more interestingly, it performs 
> better than an OrderedCollection when used like a stack:
> 
> Pushing is roughly ~30% faster:
> r1 :=[10 timesRepeat: [
>s := Stack new.
>10 timesRepeat: [s push: #foo]]] timeToRun.
> r2 := [10 timesRepeat: [
>oc := OrderedCollection new.
>10 timesRepeat: [oc addLast: #foo]]] timeToRun.
> 100 - ((r1 / r2) asFloat * 100).
> 
> as is pushing + popping:
> r3 := [10 timesRepeat: [
>s := Stack new.
>10 timesRepeat: [s push: #foo].
>10 timesRepeat: [s pop]]] timeToRun.
> r4 := [10 timesRepeat: [
>oc := OrderedCollection new.
>10 timesRepeat: [oc addLast: #foo].
>10 timesRepeat: [oc removeLast]]] timeToRun.
> 100 - ((r3 / r4) asFloat * 100).
> ___
> 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] Some questions about pharo

2010-10-18 Thread Pavel Krivanek
On Mon, Oct 18, 2010 at 9:05 PM, Schwab,Wilhelm K  wrote:
> The Windows vm displays a system tray icon that allows the image to leave the 
> headless state.  It has been quite useful, but there should be (hopefully is) 
> a way to prevent that.

I think that someone asked on squeak-dev some time ago and Andreas
told that it is not possible with the standard VM.

-- Pavel


> 
> From: pharo-project-boun...@lists.gforge.inria.fr 
> [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Lukas Renggli 
> [reng...@gmail.com]
> Sent: Monday, October 18, 2010 2:09 PM
> To: Pharo-project@lists.gforge.inria.fr
> Subject: Re: [Pharo-project] Some questions about pharo
>
> See .
>
> Cheers,
> Lukas
>
> 2010/10/18 Adrien BARREAU :
>> Hello =)
>>
>> I have a few questions:
>>
>> - If I run a headless Pharo, is it possible to display the graphical
>> interface after? (for example, if something raises an exception, I want to
>> open the GUI and use the debugger)
>>
>> - I wanna run Pharo as a deamon; how can I interact with it after i launched
>> it? (for example, if I want to give it a piece of code to execute).
>>
>> Adrien.
>>
>> ___
>> Pharo-project mailing list
>> Pharo-project@lists.gforge.inria.fr
>> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>>
>
>
>
> --
> Lukas Renggli
> www.lukas-renggli.ch
>
> ___
> 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] call for scripting idea

2010-10-18 Thread stephane ducasse
Hi 

we would like to exercise a bit our scripting engine :) so if you have ideas of 
scripts that we should be able to write let us know.

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] A Lazy Inspector?

2010-10-18 Thread Mariano Martinez Peck
2010/10/18 Oscar E A Callau 

>
> On Oct 18, 2010, at 14:44 , Mariano Martinez Peck wrote:
>
> On Mon, Oct 18, 2010 at 4:40 AM, Oscar E A Callau 
>  wrote:
>
>> Hello all,
>>
>> I was wondering what actually the inspector does in the following case:
>>
>> When you explore (or inspect) the expression: Class environment
>> you get all classes in the system dictionary. If you navigate inside a
>> class, for example AColorSelectorMorph, you can see all its properties and
>> one of them is environment, if you go inside it, you get again all classes
>> in the system dictionary. So, you can repeat this infinitely (or until you
>> get run out of memory, I guess)
>>
>> Is it the behavior of a lazy inspector? If true, why I cannot inspect a
>> mutually-recursive class definition, like this:
>>
>> Object subclass: #Foo
>>instanceVariableNames: 'bar'
>>classVariableNames: ''
>>poolDictionaries: ''
>>category: ''
>>
>> Foo>>initialize
>>bar:= Bar new
>>
>> Object subclass: #Bar
>>instanceVariableNames: 'foo'
>>classVariableNames: ''
>>poolDictionaries: ''
>>category: ''
>>
>> Foo>>initialize
>>bar:= Foo new
>>
>
> here should be foo := Foo new.
>
> Anyway, you should be able to browse these classes without problems.
> The problems is in instance creation. For example, if you evaluate: Foo
> new.
>
>
> Thanks Mariano. May be my question was not well explained. Of course if I
> evaluate: Foo new, I get into a infinite loop. 1st question, when I'm
> inspecting, I'm evaluating?
>

hehehehe yes :)
Just open a Transcript and inspect:   Transcript show: 'welooo'
and you will see 'welooo' in the transcript ;)

What you actually inspect, is the result of the expression.



> In the case that I mention above (Class enviroment) I got all classes in
> the system and each of them has an environment, that is all classes, and so
> on. Here, we have a infinite recursion.
>

I understand now.


> So, how the inspector get a lazy visualization of the it?
>
>
I have no idea. But in this case, #environment  is a method, not an instVar
as your case.
Maybe in the case of the methods, they are only displayed when clicking on
it (they just execute the compiledMethod). But this is just a guess.
You should check the class Inspector and NewInspector.

Cheers

Mariano


> Greetings
>
>
>
> ___
> 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] DisplayScreen actualScreenSize ???

2010-10-18 Thread Stéphane Ducasse
Now I could evaluate in the tiny screen 

 DisplayScreen actualScreenSize
 9...@643

and I got which is the size of the large window.

Stef


On Oct 18, 2010, at 9:48 PM, Stéphane Ducasse wrote:

> Hi adrien
> 
> I did the following: 
> 
> I commented the method startup of DisplayScreen
> saved the image
> 
> then in a file I put
> 
>   Display setExtent: DisplayScreen actualScreenSize depth: Display 
> nativeDepth.
>   Display beDisplay.
>   
> 
> /Applications/Squeak/Squeak\ 4.2.3beta1U.app/Contents/MacOS/Squeak\ VM\ Opt 
> PharoCore-1.2-12195.9.image display.st 
> 
> and it nearly worked :)
> I could interact with the little part. I do not understand why DisplayScreen 
> actualScreenSize does not return the correct size or why I only get that size
> 
> when I open a image with a display I get correct size so probably that the vm 
> returns a default value when the screen is not started?
> John?
> 
> 
> Now what I did was to use image with exactly the same size and use the size 
> returned by DisplayScreen actualScreenSize
> in one to open the other and I got the same problem
> 
> Stef 
> 
> 
>  PM.png>___
> 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] DisplayScreen actualScreenSize ???

2010-10-18 Thread Stéphane Ducasse
Hi adrien

I did the following: 

I commented the method startup of DisplayScreen
saved the image

then in a file I put

Display setExtent: DisplayScreen actualScreenSize depth: Display 
nativeDepth.
Display beDisplay.


/Applications/Squeak/Squeak\ 4.2.3beta1U.app/Contents/MacOS/Squeak\ VM\ Opt 
PharoCore-1.2-12195.9.image display.st 

and it nearly worked :)
I could interact with the little part. I do not understand why DisplayScreen 
actualScreenSize does not return the correct size or why I only get that size

when I open a image with a display I get correct size so probably that the vm 
returns a default value when the screen is not started?
John?


Now what I did was to use image with exactly the same size and use the size 
returned by DisplayScreen actualScreenSize
in one to open the other and I got the same problem

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] Some questions about pharo

2010-10-18 Thread Schwab,Wilhelm K
Possible?  Sure :)  You are of course asking whether it has been done, and I do 
not know the answer to that.  It is indeed a nice feature.  It is also one of 
those things that can also be classified as a bug ("The stupid user clicked 
this and caused all kinds of trouble..."), so it should be made conditional 
allowing truly headless operation when appropriate.

Another option is to remote into a headless image as Lukas suggested.

Bill





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Mariano Martinez 
Peck [marianop...@gmail.com]
Sent: Monday, October 18, 2010 3:30 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Some questions about pharo

On Mon, Oct 18, 2010 at 9:05 PM, Schwab,Wilhelm K 
mailto:bsch...@anest.ufl.edu>> wrote:
The Windows vm displays a system tray icon that allows the image to leave the 
headless state.  It has been quite useful, but there should be (hopefully is) a 
way to prevent that.



ahh yes?? That's cool!  do you know if this is possible also with other VMs ?




From: 
pharo-project-boun...@lists.gforge.inria.fr
 
[pharo-project-boun...@lists.gforge.inria.fr]
 On Behalf Of Lukas Renggli [reng...@gmail.com]
Sent: Monday, October 18, 2010 2:09 PM
To: 
Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Some questions about pharo

See .

Cheers,
Lukas

2010/10/18 Adrien BARREAU mailto:abarreau@live.fr>>:
> Hello =)
>
> I have a few questions:
>
> - If I run a headless Pharo, is it possible to display the graphical
> interface after? (for example, if something raises an exception, I want to
> open the GUI and use the debugger)
>
> - I wanna run Pharo as a deamon; how can I interact with it after i launched
> it? (for example, if I want to give it a piece of code to execute).
>
> Adrien.
>
> ___
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Lukas Renggli
www.lukas-renggli.ch

___
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] A Lazy Inspector?

2010-10-18 Thread Oscar E A Callau

On Oct 18, 2010, at 14:44 , Mariano Martinez Peck wrote:

> On Mon, Oct 18, 2010 at 4:40 AM, Oscar E A Callau  
> wrote:
> Hello all,
> 
> I was wondering what actually the inspector does in the following case:
> 
> When you explore (or inspect) the expression: Class environment
> you get all classes in the system dictionary. If you navigate inside a class, 
> for example AColorSelectorMorph, you can see all its properties and one of 
> them is environment, if you go inside it, you get again all classes in the 
> system dictionary. So, you can repeat this infinitely (or until you get run 
> out of memory, I guess)
> 
> Is it the behavior of a lazy inspector? If true, why I cannot inspect a 
> mutually-recursive class definition, like this:
> 
> Object subclass: #Foo
>instanceVariableNames: 'bar'
>classVariableNames: ''
>poolDictionaries: ''
>category: ''
> 
> Foo>>initialize
>bar:= Bar new
> 
> Object subclass: #Bar
>instanceVariableNames: 'foo'
>classVariableNames: ''
>poolDictionaries: ''
>category: ''
> 
> Foo>>initialize
>bar:= Foo new
> 
> here should be foo := Foo new.
> 
> Anyway, you should be able to browse these classes without problems.
> The problems is in instance creation. For example, if you evaluate: Foo new.

Thanks Mariano. May be my question was not well explained. Of course if I 
evaluate: Foo new, I get into a infinite loop. 1st question, when I'm 
inspecting, I'm evaluating?

In the case that I mention above (Class enviroment) I got all classes in the 
system and each of them has an environment, that is all classes, and so on. 
Here, we have a infinite recursion. So, how the inspector get a lazy 
visualization of the it?

Greetings 


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

Re: [Pharo-project] Some questions about pharo

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 9:05 PM, Schwab,Wilhelm K wrote:

> The Windows vm displays a system tray icon that allows the image to leave
> the headless state.  It has been quite useful, but there should be
> (hopefully is) a way to prevent that.
>
>
>
ahh yes?? That's cool!  do you know if this is possible also with other VMs
?


>
>
> 
> From: pharo-project-boun...@lists.gforge.inria.fr [
> pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Lukas Renggli [
> reng...@gmail.com]
> Sent: Monday, October 18, 2010 2:09 PM
> To: Pharo-project@lists.gforge.inria.fr
> Subject: Re: [Pharo-project] Some questions about pharo
>
> See .
>
> Cheers,
> Lukas
>
> 2010/10/18 Adrien BARREAU :
> > Hello =)
> >
> > I have a few questions:
> >
> > - If I run a headless Pharo, is it possible to display the graphical
> > interface after? (for example, if something raises an exception, I want
> to
> > open the GUI and use the debugger)
> >
> > - I wanna run Pharo as a deamon; how can I interact with it after i
> launched
> > it? (for example, if I want to give it a piece of code to execute).
> >
> > Adrien.
> >
> > ___
> > Pharo-project mailing list
> > Pharo-project@lists.gforge.inria.fr
> > http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> >
>
>
>
> --
> Lukas Renggli
> www.lukas-renggli.ch
>
> ___
> 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] Some questions about pharo

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 8:54 PM, Stéphane Ducasse  wrote:

> Adrien
>
> did you have a look at
>
> Display>>startUp  "DisplayScreen startUp"
>Display setExtent: self actualScreenSize depth: Display nativeDepth.
>Display beDisplay
>
> this is what is happening when an image is launched
> can you try to execute
>Display setExtent: self actualScreenSize depth: Display nativeDepth.
>Display beDisplay
>
> in a script?
>


The problem I think that if you send -headless to the VM.you cannot
change it...I mean, It doesn't care what you do in the image side.
But maybe i am wrong.


>
> Or may be you could
>- avoid the headless argument when running the image and
>- have a flag there and make sure that you invoke
>Display setExtent: self actualScreenSize depth: Display
> nativeDepth.
>Display beDisplay
>when an error have.
>

Yes, I think this way should be easier. Not sure if possible, thought.

Cheers

mariano


>
> ___
> 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] Questions related to a scripting language for pharo

2010-10-18 Thread Stéphane Ducasse
none :)

which are the difference with the ideas behind Coral ?


> 
> 
> ___
> 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] [ANN] TDD using static vs. dynamic languages

2010-10-18 Thread Stéphane Ducasse

On Oct 18, 2010, at 9:07 PM, Hernan Wilkinson wrote:

> Hi, 
>  I uploaded to youtube a video that compares how TDD behaves when using 
> statically typed languages vs. dynamically typed languages (java and 
> smalltalk :-) ). Sadly it is only in Spanish, but anyway, I wanted to share 
> with you.

Thanks 
this is really interesting. We should continue to improve our tools to be more 
efficient.


> http://www.youtube.com/watch?v=RLAZjiK4UHc (fist part)
> http://www.youtube.com/watch?v=wXW9WN9ay2E (second part)
>  
> 
> -- 
> Hernán Wilkinson
> Agile Software Development, Teaching & Coaching
> Mobile: +54 - 911 - 4470 - 7207
> email: hernan.wilkin...@10pines.com
> site: http://www.10Pines.com
> 
> ___
> 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] Questions related to a scripting language for pharo

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 8:49 PM, Stéphane Ducasse  wrote:

> The idea is that adrien is working on a scripting language and the scenario
> is the following:
>
>
Excellent!


> - you run your script but you got a bug, since you run your script with -db
> you can now get a debugger open
>
> So can we "reschedule/reopen" a display when it does not have been startup
> at startup
>
>
which are the difference with the ideas behind Coral ?


>
> Stef
>
>
> On Oct 18, 2010, at 7:36 PM, Adrien BARREAU wrote:
>
> > Hello =)
> >
> > I have a few questions:
> >
> > - If I run a headless Pharo, is it possible to display the graphical
> interface after? (for example, if something raises an exception, I want to
> open the GUI and use the debugger)
> >
> > - I wanna run Pharo as a deamon; how can I interact with it after i
> launched it? (for example, if I want to give it a piece of code to execute).
> >
> > Adrien.
> > ___
> > 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] Some questions about pharo

2010-10-18 Thread Schwab,Wilhelm K
The Windows vm displays a system tray icon that allows the image to leave the 
headless state.  It has been quite useful, but there should be (hopefully is) a 
way to prevent that.  





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Lukas Renggli 
[reng...@gmail.com]
Sent: Monday, October 18, 2010 2:09 PM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] Some questions about pharo

See .

Cheers,
Lukas

2010/10/18 Adrien BARREAU :
> Hello =)
>
> I have a few questions:
>
> - If I run a headless Pharo, is it possible to display the graphical
> interface after? (for example, if something raises an exception, I want to
> open the GUI and use the debugger)
>
> - I wanna run Pharo as a deamon; how can I interact with it after i launched
> it? (for example, if I want to give it a piece of code to execute).
>
> Adrien.
>
> ___
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



--
Lukas Renggli
www.lukas-renggli.ch

___
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] [ANN] TDD using static vs. dynamic languages

2010-10-18 Thread Hernan Wilkinson
Hi,
 I uploaded to youtube a video that compares how TDD behaves when using
statically typed languages vs. dynamically typed languages (java and
smalltalk :-) ). Sadly it is only in Spanish, but anyway, I wanted to share
with you.

http://www.youtube.com/watch?v=RLAZjiK4UHc (fist part)
http://www.youtube.com/watch?v=wXW9WN9ay2E (second part)


-- 
*Hernán Wilkinson
Agile Software Development, Teaching & Coaching
Mobile: +54 - 911 - 4470 - 7207
email: hernan.wilkin...@10pines.com
site: http://www.10Pines.com *
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

[Pharo-project] How to change keyboard bindings

2010-10-18 Thread Torsten Bergmann
See 

   World commandKeySelectors inspect

implemented in PasteUpMorph>>defaultDesktopCommandKeyTriplets.

If you change it you have to reinitialize using 
#initializeDesktopCommandKeySelectors.

Have fun
T.

-- 
GMX DSL Doppel-Flat ab 19,99 €/mtl.! Jetzt auch mit 
gratis Notebook-Flat! http://portal.gmx.net/de/go/dsl

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


Re: [Pharo-project] PharoKernel #12196

2010-10-18 Thread Stéphane Ducasse
thanks pavel :)

On Oct 18, 2010, at 7:23 PM, Pavel Krivanek wrote:

> Hi,
> 
> I uploaded an updated version of PharoKernel:
> 
> https://gforge.inria.fr/frs/download.php/27655/PharoKernel-1.2-12196.zip
> 
> The patch.st file is now organized by related issues.
> 
> Cheers,
> -- Pavel
> 
> ___
> 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] Missing Close in About Dialog

2010-10-18 Thread Stéphane Ducasse
thanks alain


On Oct 18, 2010, at 7:35 PM, Alain Plantec wrote:

> fixed
> http://code.google.com/p/pharo/issues/detail?id=3127
> Cheers
> Alain
> 
> Le 18/10/2010 19:01, Gary Chambers a écrit :
>> Since the auto-sizing if effectively overridden by the caller
>> 
>> Change
>> 
>> SmalltalkImage>>aboutThisSystem
>> "Identify software version"
>> | text dialog width |
>> text := Smalltalk systemInformationString withCRs.
>> width := 0.
>> text linesDo: [:l | width := width max: (UITheme current textFont 
>> widthOfStringOrText: l)].
>> dialog := LongMessageDialogWindow new entryText: text.
>> dialog iconMorph image: ThemeIcons pharoIcon.
>> dialog title: 'About Pharo'.
>> dialog open. dialog width: (width + 120 min: Display width - 50).
>> dialog position: 2...@25.
>> 
>> to
>> 
>> SmalltalkImage>>aboutThisSystem
>> "Identify software version"
>> | text dialog width |
>> text := Smalltalk systemInformationString withCRs.
>> width := 0.
>> text linesDo: [:l | width := width max: (UITheme current textFont 
>> widthOfStringOrText: l)].
>> dialog := LongMessageDialogWindow new entryText: text.
>> dialog iconMorph image: ThemeIcons pharoIcon.
>> dialog title: 'About Pharo'.
>> dialog open.
>> dialog textMorph minWidth: 20; minHeight: 20.
>> dialog width: (width + 120 min: Display width - 50).
>> dialog position: 2...@25.
>> 
>> Though already looks hacked for this purpose, to be fair.
>> 
>> Regards, Gary
>> 
>> - Original Message - From: "Stéphane Ducasse" 
>> 
>> To: 
>> Sent: Monday, October 18, 2010 5:28 PM
>> Subject: Re: [Pharo-project] Missing Close in About Dialog
>> 
>> 
>> thanks Bernhard :)
>> Welcome too :)
>> 
>> Stef (busy running).
>> 
>> On Oct 17, 2010, at 4:30 PM, Bernhard Pieber wrote:
>> 
>>> Ah, interesting! I just tested it again more thoroughly and I found out 
>>> that it has to do with the size of the Pharo window. If I maximize it on my 
>>> 30" display the dialog truncated so that the OK button is not visible. If I 
>>> make the window is much smaller it appears. See 
>>> http://dl.dropbox.com/u/6204244/Pharo%20About%20Dialog.png.
>>> 
>>> Thanks for the fast response!
>>> 
>>> Cheers,
>>> Bernhard
>>> 
>>> Am 17.10.2010 um 16:08 schrieb Schwab,Wilhelm K:
>>> 
 Are you sure?  I see an OK button at the bottom right of About in an image 
 that identifies itself the same way.
 
 
 
 
 From: pharo-project-boun...@lists.gforge.inria.fr 
 [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bernhard Pieber 
 [bernh...@pieber.com]
 Sent: Sunday, October 17, 2010 10:05 AM
 To: Pharo-project@lists.gforge.inria.fr
 Subject: [Pharo-project] Missing Close in About Dialog
 
 Dear Pharo Folks,
 
 It is a very minor thing but I wanted to let you know that the About 
 Dialog (World Menu > System > About…) in the latest stable Pharo Dev image 
 (Pharo-1.1.1-dev10.09.1) has not got any Close button.
 
 Cheers,
 Bernhard
 ___
 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
>> 
>> ___
>> 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] How to change keyboard bindings

2010-10-18 Thread Stéphane Ducasse
this is an area where we should improve. Now you can hack the table in 
paragraphEditor and get an impact on all the texteditor.

Stef

On Oct 18, 2010, at 8:40 PM, Bart Veenstra wrote:

> HI list,
> 
> Using VW and VAST a lot, I got used to the key bindings.
> For instance, I would like to use control-q for bringing up the
> inspector instead of alt-i. Could someone point me in the right
> direction where I can change the bindings? Also, It is often unclear
> when I should use Control or Alt. For instance:
> 
> In the System Browser, I can use Alt-X to remove a method, and
> Control-B to browse the class, but both are shown between the
> parenthesis.
> 
> Regards,
> 
> Bart
> 
> ___
> 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] Some questions about pharo

2010-10-18 Thread Stéphane Ducasse
Adrien

did you have a look at 

Display>>startUp  "DisplayScreen startUp"
Display setExtent: self actualScreenSize depth: Display nativeDepth.
Display beDisplay

this is what is happening when an image is launched
can you try to execute 
Display setExtent: self actualScreenSize depth: Display nativeDepth.
Display beDisplay

in a script?

Or may be you could 
- avoid the headless argument when running the image and 
- have a flag there and make sure that you invoke
Display setExtent: self actualScreenSize depth: Display 
nativeDepth.
Display beDisplay
when an error have.

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


[Pharo-project] Questions related to a scripting language for pharo

2010-10-18 Thread Stéphane Ducasse
The idea is that adrien is working on a scripting language and the scenario is 
the following:

- you run your script but you got a bug, since you run your script with -db you 
can now get a debugger open 

So can we "reschedule/reopen" a display when it does not have been startup at 
startup


Stef


On Oct 18, 2010, at 7:36 PM, Adrien BARREAU wrote:

> Hello =)
> 
> I have a few questions:
> 
> - If I run a headless Pharo, is it possible to display the graphical 
> interface after? (for example, if something raises an exception, I want to 
> open the GUI and use the debugger)
> 
> - I wanna run Pharo as a deamon; how can I interact with it after i launched 
> it? (for example, if I want to give it a piece of code to execute).
> 
> Adrien.
> ___
> 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] bad bracket autocompletion in Pharo Core 1.2

2010-10-18 Thread Stéphane Ducasse
> 
> > On Sun, Oct 17, 2010 at 10:51 AM, Stéphane Ducasse 
> >  wrote:
> > I have a question:
> >does shout support closing parenthesis behavior?
> >
> >
> >
> > I wonder the same. I don't see the difference between this and shout smart 
> > characters.
> 
> so may be we could remove this and keep smart characters.
> Now that there is a setting we could try and see.
> 
> Do you know where/why/who added this?  because I guess there is a reason that 
> we don't see.

In fact I do not understand :) since ithought that the code was coming from 
cuis and cuis does not 
implement it at all. may this is evil autogenerating code :)

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


[Pharo-project] How to change keyboard bindings

2010-10-18 Thread Bart Veenstra
HI list,

Using VW and VAST a lot, I got used to the key bindings.
For instance, I would like to use control-q for bringing up the
inspector instead of alt-i. Could someone point me in the right
direction where I can change the bindings? Also, It is often unclear
when I should use Control or Alt. For instance:

In the System Browser, I can use Alt-X to remove a method, and
Control-B to browse the class, but both are shown between the
parenthesis.

Regards,

Bart

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


Re: [Pharo-project] Some questions about pharo

2010-10-18 Thread Lukas Renggli
See .

Cheers,
Lukas

2010/10/18 Adrien BARREAU :
> Hello =)
>
> I have a few questions:
>
> - If I run a headless Pharo, is it possible to display the graphical
> interface after? (for example, if something raises an exception, I want to
> open the GUI and use the debugger)
>
> - I wanna run Pharo as a deamon; how can I interact with it after i launched
> it? (for example, if I want to give it a piece of code to execute).
>
> Adrien.
>
> ___
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
>



-- 
Lukas Renggli
www.lukas-renggli.ch

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


Re: [Pharo-project] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread Igor Stasenko
On 18 October 2010 21:04, Eliot Miranda  wrote:
>
>
> On Mon, Oct 18, 2010 at 5:07 AM, Igor Stasenko  wrote:
>>
>> On 18 October 2010 14:55, nullPointer  wrote:
>> >
>> > Now works :|
>> >
>>
>> yes, but probably you found a Cog issue.
>
> What's the definition for BlockClosure>>newProcessWith: ?

In Pharo it is:

newProcessWith: anArray
"Answer a Process running the code in the receiver. The receiver's block
arguments are bound to the contents of the argument, anArray. The
process is not scheduled."
 "Simulation guard"
^Process
forContext:
[self valueWithArguments: anArray.
Processor terminateActive] asContext
priority: Processor activePriority


In Squeak, this method is missing in BlockClosure, and exists only for
BlockContext.

> TIA
> Eliot
>
>>
>> >
>> > pvtStartProcess
>> >
>> >        internalProcess := [ self pvtCallProcess: self] fork.
>> >
>> >
>> >
>> > pvtGetNewProcessBlock
>> >
>> >        ^[:timer || intervalDelay |
>> >
>> >                [timer enabled] whileTrue:[
>> >
>> >                        (Delay forMilliseconds: timer interval) wait.
>> >
>> >                        timer enabled ifTrue:[
>> >
>> >                                timer raiseOnElapsedTimeForProcessThread:
>> > (timer getProcess).
>> >
>> >                                WorldState addDeferredUIMessage:[
>> >                                        timer
>> > raiseOnElapsedTimeForUIThread: (timer getProcess)
>> >                                ].
>> >                        ]
>> >                ].
>> >        ].
>> >
>> >
>> >
>> > pvtCallProcess: oneParam
>> >
>> >        | processBlock |
>> >
>> >        processBlock := self pvtGetNewProcessBlock.
>> >        processBlock value: oneParam.
>> >
>> >
>> > Anyway I understand than the other way must be go. Something I did bad.
>> >
>> > Many thanks for the help
>> >
>> >
>> > --
>> > View this message in context:
>> > http://forum.world.st/Implementing-a-Timer-newProcessWith-anArray-fails-tp2999831p383.html
>> > Sent from the Pharo Smalltalk mailing list archive at Nabble.com.
>> >
>> > ___
>> > 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.
>
>



-- 
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] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread Eliot Miranda
On Mon, Oct 18, 2010 at 5:07 AM, Igor Stasenko  wrote:

> On 18 October 2010 14:55, nullPointer  wrote:
> >
> > Now works :|
> >
>
> yes, but probably you found a Cog issue.
>

What's the definition for BlockClosure>>newProcessWith: ?

TIA
Eliot


>
> >
> > pvtStartProcess
> >
> >internalProcess := [ self pvtCallProcess: self] fork.
> >
> >
> >
> > pvtGetNewProcessBlock
> >
> >^[:timer || intervalDelay |
> >
> >[timer enabled] whileTrue:[
> >
> >(Delay forMilliseconds: timer interval) wait.
> >
> >timer enabled ifTrue:[
> >
> >timer raiseOnElapsedTimeForProcessThread:
> (timer getProcess).
> >
> >WorldState addDeferredUIMessage:[
> >timer
> raiseOnElapsedTimeForUIThread: (timer getProcess)
> >].
> >]
> >].
> >].
> >
> >
> >
> > pvtCallProcess: oneParam
> >
> >| processBlock |
> >
> >processBlock := self pvtGetNewProcessBlock.
> >processBlock value: oneParam.
> >
> >
> > Anyway I understand than the other way must be go. Something I did bad.
> >
> > Many thanks for the help
> >
> >
> > --
> > View this message in context:
> http://forum.world.st/Implementing-a-Timer-newProcessWith-anArray-fails-tp2999831p383.html
> > Sent from the Pharo Smalltalk mailing list archive at Nabble.com.
> >
> > ___
> > 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] Some questions about pharo

2010-10-18 Thread Mariano Martinez Peck
2010/10/18 Adrien BARREAU 

>  Hello =)
>
> I have a few questions:
>
> - If I run a headless Pharo, is it possible to display the graphical
> interface after? (for example, if something raises an exception, I want to
> open the GUI and use the debugger)
>
>
Not that I am aware of. However, what you can do is to run the image as
headless and have VNC running on in. Then, from any machine with a VNC
client you can connect, see the World, and use it.

Once I was thinking to hack a little and see if I can use the
UIDummyMananger of PharoKernel but on a Pharo non-headless. And see if there
was a way to not show any way, but then, after if you wanted, you just
needed to change the UIManager. But I have no idea if this could work.


> - I wanna run Pharo as a deamon; how can I interact with it after i
> launched it? (for example, if I want to give it a piece of code to execute).
>
>
I don't know :(


> Adrien.
>
> ___
> 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] bad bracket autocompletion in Pharo Core 1.2

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 6:41 PM, Stéphane Ducasse  wrote:

>
> On Oct 17, 2010, at 1:00 PM, Mariano Martinez Peck wrote:
>
> >
> >
> > On Sun, Oct 17, 2010 at 10:51 AM, Stéphane Ducasse <
> stephane.duca...@inria.fr> wrote:
> > I have a question:
> >does shout support closing parenthesis behavior?
> >
> >
> >
> > I wonder the same. I don't see the difference between this and shout
> smart characters.
>
> so may be we could remove this and keep smart characters.
> Now that there is a setting we could try and see.
>

Do you know where/why/who added this?  because I guess there is a reason
that we don't see.




>
>
>
> >
> >
> > Stef
> >
> > On Oct 16, 2010, at 10:27 PM, Pavel Krivanek wrote:
> >
> > > Can we add a setting for it? (issue
> > > http://code.google.com/p/pharo/issues/detail?id=3113)
> > >
> > > Cheers,
> > > -- Pavel
> > >
> > > On Tue, Oct 12, 2010 at 8:58 AM, Stéphane Ducasse
> > >  wrote:
> > >> thanks!
> > >>
> > >>
> > >> On Oct 11, 2010, at 9:37 AM, Fernando olivero wrote:
> > >>
> > >>> Hi , it was a enhancement i did starting from a Chris Muller
> enhancement for Squeak.
> > >>>
> > >>> ISSUE 2653.
> > >>>
> http://code.google.com/p/pharo/issues/detail?id=2653&can=1&q=auto&colspec=ID%20Type%20Status%20Summary%20Milestone%20Difficulty
> > >>>
> > >>> I did a test, maybe a good start would be to see if its failing now.
> > >>>
> > >>> Fernando
> > >>>
> > >>> On Oct 9, 2010, at 2:18 PM, Juan Vuletich wrote:
> > >>>
> >  Hi Folks,
> > 
> >  Cuis doesn't include #autoEnclose, so I don't know how it should
> behave.
> > 
> >  Cheers,
> >  Juan Vuletich
> > 
> >  Mariano Martinez Peck wrote:
> > > Guille, if I remember correctly (not sure), these new classes like
> > > TextEditor and Smalltalk editor came from Cuis. Juan (Cuis author)
> i
> > > think he is in the mailing list but not read it so frequently. So,
> for
> > > this issues maybe you can cc'ed him.
> > >
> > > Cheers
> > >
> > > Mariano
> > >
> > > 2010/10/9 Guillermo Polito  > > >
> > >
> > >Here is the piece of code that's behaving weird
> > >
> > >TextEditor>>dispatchOn:
> > >
> > >...
> > >...
> > >char := aKeyboardEvent keyCharacter.
> > > openers := '([{'.
> > >closers := ')]}'.
> > >   ( closers includes: char) ifTrue: [ self blinkPrevParen:
> > >char ].
> > >   result := self normalCharacter: aKeyboardEvent.
> > >   (self class autoEnclose and: [ openers includes: char ])
> > >not ifTrue: [ ^ result  ].
> > >suffix := closers at: (openers indexOf: char).
> > >paragraph text append: suffix asString.
> > >  self moveCursor: [ : position | position  ] forward: true
> > >specialBlock: [ : pos | "no special behavior" ] event:
> > >aKeyboardEvent .
> > >self userHasEdited.
> > >
> > >-
> > >
> > >So, if I evaluate "TextEditor autoEnclose: false", it is stops
> > >behaving like that :)
> > >
> > >What should be the desired behavior?  Having it configurable as
> it
> > >is today but fix the strange bracket adding? remove this
> behavior?
> > >I can't find now how ParagraphEditor did this.
> > >
> > >Guille
> > >
> > >
> > >On Wed, Oct 6, 2010 at 10:34 PM, Guillermo Polito
> > >mailto:guillermopol...@gmail.com>>
> wrote:
> > >
> > >Yes, the issue can be reduced to:
> > >
> > >open parenthesis (or brackets), then something else
> (anywhere
> > >in the editor).
> > >
> > >2010/10/6 Mariano Martinez Peck  > >>
> > >
> > >I detected a similar problem:
> > >
> > >once you type an opening parenthesis, and then something
> > >else, it adds a new one at the END of the code
> > >
> > >check
> http://code.google.com/p/pharo/issues/detail?id=2939
> > >
> > >2010/10/6 Guillermo Polito  > >>
> > >
> > >
> http://code.google.com/p/pharo/issues/detail?id=3069
> > >
> > >if you type:
> > >
> > >[] -> []]
> > >
> > >() -> ())
> > >
> > >{} -> {}}
> > >
> > >
> > >
> > >
> > >Bye!
> > >
> > >___
> > >Pharo-project mailing list
> > >Pharo-project@lists.gforge.inria.fr
> > >
> > >
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project
> > >
> > >>>

Re: [Pharo-project] A Lazy Inspector?

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 4:40 AM, Oscar E A Callau wrote:

> Hello all,
>
> I was wondering what actually the inspector does in the following case:
>
> When you explore (or inspect) the expression: Class environment
> you get all classes in the system dictionary. If you navigate inside a
> class, for example AColorSelectorMorph, you can see all its properties and
> one of them is environment, if you go inside it, you get again all classes
> in the system dictionary. So, you can repeat this infinitely (or until you
> get run out of memory, I guess)
>
> Is it the behavior of a lazy inspector? If true, why I cannot inspect a
> mutually-recursive class definition, like this:
>
> Object subclass: #Foo
>instanceVariableNames: 'bar'
>classVariableNames: ''
>poolDictionaries: ''
>category: ''
>
> Foo>>initialize
>bar:= Bar new
>
> Object subclass: #Bar
>instanceVariableNames: 'foo'
>classVariableNames: ''
>poolDictionaries: ''
>category: ''
>
> Foo>>initialize
>bar:= Foo new
>

here should be foo := Foo new.

Anyway, you should be able to browse these classes without problems.
The problems is in instance creation. For example, if you evaluate: Foo new.

Cheers

mariano


> Thanks in advance.
>
> P.S.: How can I stop my execution in the pharo image when it is in a
> infinite loop? I can't remember what the shortcut was.
>
>
> ___
> 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] Some questions about pharo

2010-10-18 Thread Adrien BARREAU

Hello =)

I have a few questions:

- If I run a headless Pharo, is it possible to display the graphical interface 
after? (for example, if something raises an exception, I want to open the GUI 
and use the debugger)

- I wanna run Pharo as a deamon; how can I interact with it after i launched 
it? (for example, if I want to give it a piece of code to execute).

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

Re: [Pharo-project] Missing Close in About Dialog

2010-10-18 Thread Alain Plantec

 fixed
http://code.google.com/p/pharo/issues/detail?id=3127
Cheers
Alain

Le 18/10/2010 19:01, Gary Chambers a écrit :

Since the auto-sizing if effectively overridden by the caller

Change

SmalltalkImage>>aboutThisSystem
"Identify software version"
| text dialog width |
text := Smalltalk systemInformationString withCRs.
width := 0.
text linesDo: [:l | width := width max: (UITheme current textFont 
widthOfStringOrText: l)].

dialog := LongMessageDialogWindow new entryText: text.
dialog iconMorph image: ThemeIcons pharoIcon.
dialog title: 'About Pharo'.
dialog open. dialog width: (width + 120 min: Display width - 50).
dialog position: 2...@25.

to

SmalltalkImage>>aboutThisSystem
"Identify software version"
| text dialog width |
text := Smalltalk systemInformationString withCRs.
width := 0.
text linesDo: [:l | width := width max: (UITheme current textFont 
widthOfStringOrText: l)].

dialog := LongMessageDialogWindow new entryText: text.
dialog iconMorph image: ThemeIcons pharoIcon.
dialog title: 'About Pharo'.
dialog open.
dialog textMorph minWidth: 20; minHeight: 20.
dialog width: (width + 120 min: Display width - 50).
dialog position: 2...@25.

Though already looks hacked for this purpose, to be fair.

Regards, Gary

- Original Message - From: "Stéphane Ducasse" 


To: 
Sent: Monday, October 18, 2010 5:28 PM
Subject: Re: [Pharo-project] Missing Close in About Dialog


thanks Bernhard :)
Welcome too :)

Stef (busy running).

On Oct 17, 2010, at 4:30 PM, Bernhard Pieber wrote:

Ah, interesting! I just tested it again more thoroughly and I found 
out that it has to do with the size of the Pharo window. If I 
maximize it on my 30" display the dialog truncated so that the OK 
button is not visible. If I make the window is much smaller it 
appears. See http://dl.dropbox.com/u/6204244/Pharo%20About%20Dialog.png.


Thanks for the fast response!

Cheers,
Bernhard

Am 17.10.2010 um 16:08 schrieb Schwab,Wilhelm K:

Are you sure?  I see an OK button at the bottom right of About in an 
image that identifies itself the same way.





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bernhard 
Pieber [bernh...@pieber.com]

Sent: Sunday, October 17, 2010 10:05 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: [Pharo-project] Missing Close in About Dialog

Dear Pharo Folks,

It is a very minor thing but I wanted to let you know that the About 
Dialog (World Menu > System > About…) in the latest stable Pharo Dev 
image (Pharo-1.1.1-dev10.09.1) has not got any Close button.


Cheers,
Bernhard
___
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

___
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] PharoKernel #12196

2010-10-18 Thread Pavel Krivanek
Hi,

I uploaded an updated version of PharoKernel:

https://gforge.inria.fr/frs/download.php/27655/PharoKernel-1.2-12196.zip

The patch.st file is now organized by related issues.

Cheers,
-- Pavel

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


Re: [Pharo-project] Missing Close in About Dialog

2010-10-18 Thread Gary Chambers

Since the auto-sizing if effectively overridden by the caller

Change

SmalltalkImage>>aboutThisSystem
"Identify software version"
| text dialog width |
text := Smalltalk systemInformationString withCRs.
width := 0.
text linesDo: [:l | width := width max: (UITheme current textFont 
widthOfStringOrText: l)].

dialog := LongMessageDialogWindow new entryText: text.
dialog iconMorph image: ThemeIcons pharoIcon.
dialog title: 'About Pharo'.
dialog open. dialog width: (width + 120 min: Display width - 50).
dialog position: 2...@25.

to

SmalltalkImage>>aboutThisSystem
"Identify software version"
| text dialog width |
text := Smalltalk systemInformationString withCRs.
width := 0.
text linesDo: [:l | width := width max: (UITheme current textFont 
widthOfStringOrText: l)].

dialog := LongMessageDialogWindow new entryText: text.
dialog iconMorph image: ThemeIcons pharoIcon.
dialog title: 'About Pharo'.
dialog open.
dialog textMorph minWidth: 20; minHeight: 20.
dialog width: (width + 120 min: Display width - 50).
dialog position: 2...@25.

Though already looks hacked for this purpose, to be fair.

Regards, Gary

- Original Message - 
From: "Stéphane Ducasse" 

To: 
Sent: Monday, October 18, 2010 5:28 PM
Subject: Re: [Pharo-project] Missing Close in About Dialog


thanks Bernhard :)
Welcome too :)

Stef (busy running).

On Oct 17, 2010, at 4:30 PM, Bernhard Pieber wrote:

Ah, interesting! I just tested it again more thoroughly and I found out 
that it has to do with the size of the Pharo window. If I maximize it on 
my 30" display the dialog truncated so that the OK button is not visible. 
If I make the window is much smaller it appears. See 
http://dl.dropbox.com/u/6204244/Pharo%20About%20Dialog.png.


Thanks for the fast response!

Cheers,
Bernhard

Am 17.10.2010 um 16:08 schrieb Schwab,Wilhelm K:

Are you sure?  I see an OK button at the bottom right of About in an 
image that identifies itself the same way.





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bernhard 
Pieber [bernh...@pieber.com]

Sent: Sunday, October 17, 2010 10:05 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: [Pharo-project] Missing Close in About Dialog

Dear Pharo Folks,

It is a very minor thing but I wanted to let you know that the About 
Dialog (World Menu > System > About…) in the latest stable Pharo Dev 
image (Pharo-1.1.1-dev10.09.1) has not got any Close button.


Cheers,
Bernhard
___
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 



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


Re: [Pharo-project] bad bracket autocompletion in Pharo Core 1.2

2010-10-18 Thread Stéphane Ducasse

On Oct 17, 2010, at 1:00 PM, Mariano Martinez Peck wrote:

> 
> 
> On Sun, Oct 17, 2010 at 10:51 AM, Stéphane Ducasse 
>  wrote:
> I have a question:
>does shout support closing parenthesis behavior?
> 
> 
> 
> I wonder the same. I don't see the difference between this and shout smart 
> characters.

so may be we could remove this and keep smart characters.
Now that there is a setting we could try and see.



> 
>  
> Stef
> 
> On Oct 16, 2010, at 10:27 PM, Pavel Krivanek wrote:
> 
> > Can we add a setting for it? (issue
> > http://code.google.com/p/pharo/issues/detail?id=3113)
> >
> > Cheers,
> > -- Pavel
> >
> > On Tue, Oct 12, 2010 at 8:58 AM, Stéphane Ducasse
> >  wrote:
> >> thanks!
> >>
> >>
> >> On Oct 11, 2010, at 9:37 AM, Fernando olivero wrote:
> >>
> >>> Hi , it was a enhancement i did starting from a Chris Muller enhancement 
> >>> for Squeak.
> >>>
> >>> ISSUE 2653.
> >>> http://code.google.com/p/pharo/issues/detail?id=2653&can=1&q=auto&colspec=ID%20Type%20Status%20Summary%20Milestone%20Difficulty
> >>>
> >>> I did a test, maybe a good start would be to see if its failing now.
> >>>
> >>> Fernando
> >>>
> >>> On Oct 9, 2010, at 2:18 PM, Juan Vuletich wrote:
> >>>
>  Hi Folks,
> 
>  Cuis doesn't include #autoEnclose, so I don't know how it should behave.
> 
>  Cheers,
>  Juan Vuletich
> 
>  Mariano Martinez Peck wrote:
> > Guille, if I remember correctly (not sure), these new classes like
> > TextEditor and Smalltalk editor came from Cuis. Juan (Cuis author) i
> > think he is in the mailing list but not read it so frequently. So, for
> > this issues maybe you can cc'ed him.
> >
> > Cheers
> >
> > Mariano
> >
> > 2010/10/9 Guillermo Polito  > >
> >
> >Here is the piece of code that's behaving weird
> >
> >TextEditor>>dispatchOn:
> >
> >...
> >...
> >char := aKeyboardEvent keyCharacter.
> > openers := '([{'.
> >closers := ')]}'.
> >   ( closers includes: char) ifTrue: [ self blinkPrevParen:
> >char ].
> >   result := self normalCharacter: aKeyboardEvent.
> >   (self class autoEnclose and: [ openers includes: char ])
> >not ifTrue: [ ^ result  ].
> >suffix := closers at: (openers indexOf: char).
> >paragraph text append: suffix asString.
> >  self moveCursor: [ : position | position  ] forward: true
> >specialBlock: [ : pos | "no special behavior" ] event:
> >aKeyboardEvent .
> >self userHasEdited.
> >
> >-
> >
> >So, if I evaluate "TextEditor autoEnclose: false", it is stops
> >behaving like that :)
> >
> >What should be the desired behavior?  Having it configurable as it
> >is today but fix the strange bracket adding? remove this behavior?
> >I can't find now how ParagraphEditor did this.
> >
> >Guille
> >
> >
> >On Wed, Oct 6, 2010 at 10:34 PM, Guillermo Polito
> >mailto:guillermopol...@gmail.com>> wrote:
> >
> >Yes, the issue can be reduced to:
> >
> >open parenthesis (or brackets), then something else (anywhere
> >in the editor).
> >
> >2010/10/6 Mariano Martinez Peck  >>
> >
> >I detected a similar problem:
> >
> >once you type an opening parenthesis, and then something
> >else, it adds a new one at the END of the code
> >
> >check http://code.google.com/p/pharo/issues/detail?id=2939
> >
> >2010/10/6 Guillermo Polito  >>
> >
> >http://code.google.com/p/pharo/issues/detail?id=3069
> >
> >if you type:
> >
> >[] -> []]
> >
> >() -> ())
> >
> >{} -> {}}
> >
> >
> >
> >
> >Bye!
> >
> >___
> >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] Speeding up Pharo 1.1

2010-10-18 Thread Stéphane Ducasse

On Oct 18, 2010, at 9:22 AM, Bart Veenstra wrote:

> After MCMethodDefinition shutDown it looks like it is reacting a bit
> faster to keyboard input. I often experience sluggishness in
> autocompletion method. When I type in a name of a class in a
> workspace, the autocomplete suggests 3 options. I want to choose the
> middle, so I press down and after 3 seconds (or sometimes nothging
> happens) it selects the class. The longer I have my image open, the
> longer this will take :S

Argh we should fix that.
I will start to integrate enh of levente related to hasBinding but I'm not 
sure it will help.

Stef
> 
> 
> 
> 
> 2010/10/17 Igor Stasenko :
>> Bart,
>> can you try doing:
>> 
>> MCMethodDefinition shutDown
>> 
>> in your image?
>> 
>> On 16 October 2010 14:48, Bart Veenstra  wrote:
>>> Hi list,
>>> 
>>> I have been working with Pharo for almost a month now, and I suspect
>>> that the performance is degrading fast. UI tasks takes several seconds
>>> to react to my keyboard.
>>> 
>>> At work we use VAST and I have experience with VW as well and those
>>> smalltaks react to my keyboard and mouse actions instantly. But Pharo
>>> works very sluggish.
>>> 
>>> My image is about 130MB because I have loaded all dutch postcode in
>>> memory, but that should not affect the performance of general
>>> operations like typing with the keyboard. I am not a fast typer, but
>>> sometimes it takes seconds to show my keyboard input. I can't use the
>>> down key to select the right method from suggestions, because it seems
>>> to lockup completely.
>>> 
>>> Are there ways to speedup Pharo? I would love to use cogVM but I
>>> haven't got gemtools working on it...
>>> 
>>> Will upgrading to 1.1.1 fix these issues?
>>> 
>>> Is my OS (Windows 7-64bit) causing these issues?
>>> 
>>> Regards,
>>> 
>>> Bart
>>> 
>>> ___
>>> 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


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


Re: [Pharo-project] A Lazy Inspector?

2010-10-18 Thread Stéphane Ducasse

On Oct 18, 2010, at 4:40 AM, Oscar E A Callau wrote:

> Hello all,
> 
> I was wondering what actually the inspector does in the following case:
> 
> When you explore (or inspect) the expression: Class environment
> you get all classes in the system dictionary. If you navigate inside a class, 
> for example AColorSelectorMorph, you can see all its properties and one of 
> them is environment, if you go inside it, you get again all classes in the 
> system dictionary. So, you can repeat this infinitely (or until you get run 
> out of memory, I guess)
> 
> Is it the behavior of a lazy inspector? If true, why I cannot inspect a 
> mutually-recursive class definition,

I do not understand what you mean by that.
Normally if you define the two classes then you can browse navigate them 
without problem with the inspector.


> like this:
> 
> Object subclass: #Foo
>   instanceVariableNames: 'bar'
>   classVariableNames: ''
>   poolDictionaries: ''
>   category: ''
> 
> Foo>>initialize
>   bar:= Bar new
> 
> Object subclass: #Bar
>   instanceVariableNames: 'foo'
>   classVariableNames: ''
>   poolDictionaries: ''
>   category: ''
> 
> Foo>>initialize
>   bar:= Foo new
> 
> Thanks in advance.
> 
> P.S.: How can I stop my execution in the pharo image when it is in a infinite 
> loop? I can't remember what the shortcut was.
> 
> 
> ___
> 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] Missing Close in About Dialog

2010-10-18 Thread Stéphane Ducasse
thanks Bernhard :)
Welcome too :)

Stef (busy running).

On Oct 17, 2010, at 4:30 PM, Bernhard Pieber wrote:

> Ah, interesting! I just tested it again more thoroughly and I found out that 
> it has to do with the size of the Pharo window. If I maximize it on my 30" 
> display the dialog truncated so that the OK button is not visible. If I make 
> the window is much smaller it appears. See 
> http://dl.dropbox.com/u/6204244/Pharo%20About%20Dialog.png.
> 
> Thanks for the fast response!
> 
> Cheers,
> Bernhard
> 
> Am 17.10.2010 um 16:08 schrieb Schwab,Wilhelm K:
> 
>> Are you sure?  I see an OK button at the bottom right of About in an image 
>> that identifies itself the same way.
>> 
>> 
>> 
>> 
>> From: pharo-project-boun...@lists.gforge.inria.fr 
>> [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bernhard Pieber 
>> [bernh...@pieber.com]
>> Sent: Sunday, October 17, 2010 10:05 AM
>> To: Pharo-project@lists.gforge.inria.fr
>> Subject: [Pharo-project] Missing Close in About Dialog
>> 
>> Dear Pharo Folks,
>> 
>> It is a very minor thing but I wanted to let you know that the About Dialog 
>> (World Menu > System > About…) in the latest stable Pharo Dev image 
>> (Pharo-1.1.1-dev10.09.1) has not got any Close button.
>> 
>> Cheers,
>> Bernhard
>> ___
>> 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] Fwd: [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Schwab,Wilhelm K
I don't know if it's better (or even as good), but when the dust settles, it 
would be nice to have something _called_ SharedQueue that does what's expected 
of it and delegates to the improved classes.  Another option would be to go 
through a deprecation period with SharedQueue.



From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Stéphane Ducasse 
[stephane.duca...@inria.fr]
Sent: Monday, October 18, 2010 9:26 AM
To: Pharo Development
Subject: [Pharo-project] Fwd: [squeak-dev] SharedQueue does scale (was: Re: 
SharedQueue doesn't scale)

>>>
>>>
>>
>> Thanks, Levente for giving a feedback.
>> Please, feel free to shape my classes in more complete from (such as
>> proper naming),
>> to make them ready for inclusion in both Squeak's and Pharo cores.
>> I propose the following names:
>> AtomicQueue (base class) -> AtomicCollection
>> FIFOQueue -> AtomicQueue
>> LIFOQueue -> AtomicStack
>> If you, or anyone else having better suggestions, speak now :)
>
>
> Sounds like good names.
>
>
>> In any case, i'm am open to discuss further details and possible
>> caveats of using new classes
>> to anyone interested in using them.
>>
>> P.S. As a side note, i now can explain (to myself at first place), why
>> i intuitively choosed to used atomic swap
>> instead of CAS.
>> Because it fits better fits with smalltalk language semantics:
>>
>> A swap operation in smalltalk implemented as two assignments:
>> x := y. y := z.
>> An assignments is basic operation, which have nothing to do with
>> late-bound nature of language.
>> Unless we going to introduce a meta-object protocol(s), which could
>> turn a simple assignment
>> into some message sends under the hood, it will remain a basic,
>> early-bound operation.
>> And even if we do, it is highly unlikely, that even then we will throw
>> away the old,
>> simple assignment, which identifies an assignment source & target at
>> compile time.
>>
>> In contrast, a CAS operation , if written in smalltalk looks like:
>>
>> (a == b ) ifTrue: [ a := c ]
>>
>> so, it having two message sends (#== , #ifTrue:), and from strict,
>> pure language perspective,
>> this using a late-bound semantics (a message sends),
>> and as any message send, the message result and behavior cannot be
>> predicted at compile time
>> and therefore its wrong to assume that such statement could be an
>> atomic operation.
>>
>> Unless, of course, we introduce a new language syntax which will
>> denote a CAS operation explicitly.
>>
>>>
>>> Levente
>>>
>>>
>>> snip
>>>
>>
>>
>> --
>> 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] [SPAM] Re: Speeding up Pharo 1.1

2010-10-18 Thread Schwab,Wilhelm K
I doubt you will have trouble loading with SIXX, but ask if you do :)





From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bart Veenstra 
[bart.veens...@gmail.com]
Sent: Monday, October 18, 2010 7:54 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1

I haven't put my mind yet to loading the data, but I guess I will get
this running pretty soon. For loading packages I will create a
metacello configuratoin with all packages so I only need to load this
once. (including seaside and other 3rd party tools)

Regards,

Bart

2010/10/18 Schwab,Wilhelm K :
> I am not clear on upgrades, but I strongly urge establishing a process for 
> saving and loading packages and data, otherwise you can end up trapped in a 
> very old image.  SIXX has done well for me so far with data.  What don't you 
> understand about loading?
>
> For saving and loading packages, I use a homegrown tool called Migrate; see 
> the in box (and expect to ask some questions here) if you are interested.
>
>
>
> 
> From: pharo-project-boun...@lists.gforge.inria.fr 
> [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bart Veenstra 
> [bart.veens...@gmail.com]
> Sent: Monday, October 18, 2010 3:48 AM
> To: Pharo-project@lists.gforge.inria.fr
> Subject: Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1
>
> I would love to use a new image and reload all my apps, but I have
> some important data in the image persisted, and I guess I would loose
> these with a new image. I installed SIXX already for exporting. this
> works. Now the importing part.
>
> Is there a way I can upgrade to 1.1.1 from 1.1? The software update
> option doesn't do much.
>
> Regards,
>
>
> Bart
>
> 2010/10/18 Sven Van Caekenberghe :
>>
>> On 18 Oct 2010, at 09:21, Bart Veenstra wrote:
>>
>>> After MCMethodDefinition shutDown it looks like it is reacting a bit
>>> faster to keyboard input. I often experience sluggishness in
>>> autocompletion method. When I type in a name of a class in a
>>> workspace, the autocomplete suggests 3 options. I want to choose the
>>> middle, so I press down and after 3 seconds (or sometimes nothging
>>> happens) it selects the class. The longer I have my image open, the
>>> longer this will take :S
>>
>> That is what I had before, see my earlier answer...
>>
>> Sven
>>
>>
>> ___
>> 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

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


[Pharo-project] Fwd: [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Stéphane Ducasse
>>> 
>>> 
>> 
>> Thanks, Levente for giving a feedback.
>> Please, feel free to shape my classes in more complete from (such as
>> proper naming),
>> to make them ready for inclusion in both Squeak's and Pharo cores.
>> I propose the following names:
>> AtomicQueue (base class) -> AtomicCollection
>> FIFOQueue -> AtomicQueue
>> LIFOQueue -> AtomicStack
>> If you, or anyone else having better suggestions, speak now :)
> 
> 
> Sounds like good names.
> 
> 
>> In any case, i'm am open to discuss further details and possible
>> caveats of using new classes
>> to anyone interested in using them.
>> 
>> P.S. As a side note, i now can explain (to myself at first place), why
>> i intuitively choosed to used atomic swap
>> instead of CAS.
>> Because it fits better fits with smalltalk language semantics:
>> 
>> A swap operation in smalltalk implemented as two assignments:
>> x := y. y := z.
>> An assignments is basic operation, which have nothing to do with
>> late-bound nature of language.
>> Unless we going to introduce a meta-object protocol(s), which could
>> turn a simple assignment
>> into some message sends under the hood, it will remain a basic,
>> early-bound operation.
>> And even if we do, it is highly unlikely, that even then we will throw
>> away the old,
>> simple assignment, which identifies an assignment source & target at
>> compile time.
>> 
>> In contrast, a CAS operation , if written in smalltalk looks like:
>> 
>> (a == b ) ifTrue: [ a := c ]
>> 
>> so, it having two message sends (#== , #ifTrue:), and from strict,
>> pure language perspective,
>> this using a late-bound semantics (a message sends),
>> and as any message send, the message result and behavior cannot be
>> predicted at compile time
>> and therefore its wrong to assume that such statement could be an
>> atomic operation.
>> 
>> Unless, of course, we introduce a new language syntax which will
>> denote a CAS operation explicitly.
>> 
>>> 
>>> Levente
>>> 
>>> 
>>> snip
>>> 
>> 
>> 
>> -- 
>> 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] [update 1.2] #12196

2010-10-18 Thread Stéphane Ducasse

12196
-

- Issue 3121:   LongTest API improvement. 
- Issue 3120:   MultiByteFileStream class>>lineEndDefault.
- Issue 3119:   rounded and truncated for DateAndTime.
- Issue 3126:   Cleans do: symbol usage

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


Re: [Pharo-project] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread Igor Stasenko
On 18 October 2010 14:55, nullPointer  wrote:
>
> Now works :|
>

yes, but probably you found a Cog issue.

>
> pvtStartProcess
>
>        internalProcess := [ self pvtCallProcess: self] fork.
>
>
>
> pvtGetNewProcessBlock
>
>        ^[:timer || intervalDelay |
>
>                [timer enabled] whileTrue:[
>
>                        (Delay forMilliseconds: timer interval) wait.
>
>                        timer enabled ifTrue:[
>
>                                timer raiseOnElapsedTimeForProcessThread: 
> (timer getProcess).
>
>                                WorldState addDeferredUIMessage:[
>                                        timer raiseOnElapsedTimeForUIThread: 
> (timer getProcess)
>                                ].
>                        ]
>                ].
>        ].
>
>
>
> pvtCallProcess: oneParam
>
>        | processBlock |
>
>        processBlock := self pvtGetNewProcessBlock.
>        processBlock value: oneParam.
>
>
> Anyway I understand than the other way must be go. Something I did bad.
>
> Many thanks for the help
>
>
> --
> View this message in context: 
> http://forum.world.st/Implementing-a-Timer-newProcessWith-anArray-fails-tp2999831p383.html
> Sent from the Pharo Smalltalk mailing list archive at Nabble.com.
>
> ___
> 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] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread nullPointer

Now works :|


pvtStartProcess

internalProcess := [ self pvtCallProcess: self] fork.



pvtGetNewProcessBlock

^[:timer || intervalDelay |

[timer enabled] whileTrue:[

(Delay forMilliseconds: timer interval) wait. 

timer enabled ifTrue:[

timer raiseOnElapsedTimeForProcessThread: 
(timer getProcess).

WorldState addDeferredUIMessage:[ 
timer raiseOnElapsedTimeForUIThread: 
(timer getProcess) 
].
]
].
].



pvtCallProcess: oneParam

| processBlock |

processBlock := self pvtGetNewProcessBlock.
processBlock value: oneParam.


Anyway I understand than the other way must be go. Something I did bad.

Many thanks for the help


-- 
View this message in context: 
http://forum.world.st/Implementing-a-Timer-newProcessWith-anArray-fails-tp2999831p383.html
Sent from the Pharo Smalltalk mailing list archive at Nabble.com.

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


Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1

2010-10-18 Thread Bart Veenstra
I haven't put my mind yet to loading the data, but I guess I will get
this running pretty soon. For loading packages I will create a
metacello configuratoin with all packages so I only need to load this
once. (including seaside and other 3rd party tools)

Regards,

Bart

2010/10/18 Schwab,Wilhelm K :
> I am not clear on upgrades, but I strongly urge establishing a process for 
> saving and loading packages and data, otherwise you can end up trapped in a 
> very old image.  SIXX has done well for me so far with data.  What don't you 
> understand about loading?
>
> For saving and loading packages, I use a homegrown tool called Migrate; see 
> the in box (and expect to ask some questions here) if you are interested.
>
>
>
> 
> From: pharo-project-boun...@lists.gforge.inria.fr 
> [pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bart Veenstra 
> [bart.veens...@gmail.com]
> Sent: Monday, October 18, 2010 3:48 AM
> To: Pharo-project@lists.gforge.inria.fr
> Subject: Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1
>
> I would love to use a new image and reload all my apps, but I have
> some important data in the image persisted, and I guess I would loose
> these with a new image. I installed SIXX already for exporting. this
> works. Now the importing part.
>
> Is there a way I can upgrade to 1.1.1 from 1.1? The software update
> option doesn't do much.
>
> Regards,
>
>
> Bart
>
> 2010/10/18 Sven Van Caekenberghe :
>>
>> On 18 Oct 2010, at 09:21, Bart Veenstra wrote:
>>
>>> After MCMethodDefinition shutDown it looks like it is reacting a bit
>>> faster to keyboard input. I often experience sluggishness in
>>> autocompletion method. When I type in a name of a class in a
>>> workspace, the autocomplete suggests 3 options. I want to choose the
>>> middle, so I press down and after 3 seconds (or sometimes nothging
>>> happens) it selects the class. The longer I have my image open, the
>>> longer this will take :S
>>
>> That is what I had before, see my earlier answer...
>>
>> Sven
>>
>>
>> ___
>> 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] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread nullPointer

The assert works good.

   processBlock numArgs. "returns 1 too"

I´m thinking perhaps the problem is Cog VM... it´s possible?
If I debug:

block := [ :int1 | | int2 | int2 := 2.  int1 + int2 ].
block newProcessWith: { 2 }.

I get an SimulationGuardException exception...
-- 
View this message in context: 
http://forum.world.st/Implementing-a-Timer-newProcessWith-anArray-fails-tp2999831p357.html
Sent from the Pharo Smalltalk mailing list archive at Nabble.com.

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

Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1

2010-10-18 Thread Schwab,Wilhelm K
I am not clear on upgrades, but I strongly urge establishing a process for 
saving and loading packages and data, otherwise you can end up trapped in a 
very old image.  SIXX has done well for me so far with data.  What don't you 
understand about loading?

For saving and loading packages, I use a homegrown tool called Migrate; see the 
in box (and expect to ask some questions here) if you are interested.  




From: pharo-project-boun...@lists.gforge.inria.fr 
[pharo-project-boun...@lists.gforge.inria.fr] On Behalf Of Bart Veenstra 
[bart.veens...@gmail.com]
Sent: Monday, October 18, 2010 3:48 AM
To: Pharo-project@lists.gforge.inria.fr
Subject: Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1

I would love to use a new image and reload all my apps, but I have
some important data in the image persisted, and I guess I would loose
these with a new image. I installed SIXX already for exporting. this
works. Now the importing part.

Is there a way I can upgrade to 1.1.1 from 1.1? The software update
option doesn't do much.

Regards,


Bart

2010/10/18 Sven Van Caekenberghe :
>
> On 18 Oct 2010, at 09:21, Bart Veenstra wrote:
>
>> After MCMethodDefinition shutDown it looks like it is reacting a bit
>> faster to keyboard input. I often experience sluggishness in
>> autocompletion method. When I type in a name of a class in a
>> workspace, the autocomplete suggests 3 options. I want to choose the
>> middle, so I press down and after 3 seconds (or sometimes nothging
>> happens) it selects the class. The longer I have my image open, the
>> longer this will take :S
>
> That is what I had before, see my earlier answer...
>
> Sven
>
>
> ___
> 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] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread Igor Stasenko
It works for me:

([:foo | foo + 1 ] newProcessWith: #(10)) resume

and

([:foo | foo + 1 ] newProcessWith: {10}) resume

works as well.

Try put

self assert: processBlock argumentCount == 1

in pvtStartProcess.


-- 
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] Speeding up Pharo 1.1

2010-10-18 Thread Igor Stasenko
2010/10/18 Mariano Martinez Peck :
>
>
> On Mon, Oct 18, 2010 at 9:21 AM, Bart Veenstra 
> wrote:
>>
>> After MCMethodDefinition shutDown
>
> Does this have some kind of bad side effect or I can do it also?
>

it clears the MC cache. Absolutely safe.
See http://code.google.com/p/pharo/issues/detail?id=3048..
and there are also a recent discussion about it on pharo-dev about
removing MC cache from
weak-dependents list, (but i'm too lazy to search and give a link to it  :) ).

> Cheers
>
> Mariano
>
>>
>> it looks like it is reacting a bit
>> faster to keyboard input. I often experience sluggishness in
>> autocompletion method. When I type in a name of a class in a
>> workspace, the autocomplete suggests 3 options. I want to choose the
>> middle, so I press down and after 3 seconds (or sometimes nothging
>> happens) it selects the class. The longer I have my image open, the
>> longer this will take :S
>>
>>
>>
>>
>> 2010/10/17 Igor Stasenko :
>> > Bart,
>> > can you try doing:
>> >
>> > MCMethodDefinition shutDown
>> >
>> > in your image?
>> >
>> > On 16 October 2010 14:48, Bart Veenstra  wrote:
>> >> Hi list,
>> >>
>> >> I have been working with Pharo for almost a month now, and I suspect
>> >> that the performance is degrading fast. UI tasks takes several seconds
>> >> to react to my keyboard.
>> >>
>> >> At work we use VAST and I have experience with VW as well and those
>> >> smalltaks react to my keyboard and mouse actions instantly. But Pharo
>> >> works very sluggish.
>> >>
>> >> My image is about 130MB because I have loaded all dutch postcode in
>> >> memory, but that should not affect the performance of general
>> >> operations like typing with the keyboard. I am not a fast typer, but
>> >> sometimes it takes seconds to show my keyboard input. I can't use the
>> >> down key to select the right method from suggestions, because it seems
>> >> to lockup completely.
>> >>
>> >> Are there ways to speedup Pharo? I would love to use cogVM but I
>> >> haven't got gemtools working on it...
>> >>
>> >> Will upgrading to 1.1.1 fix these issues?
>> >>
>> >> Is my OS (Windows 7-64bit) causing these issues?
>> >>
>> >> Regards,
>> >>
>> >> Bart
>> >>
>> >> ___
>> >> 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
>
>
> ___
> 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] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Igor Stasenko
On 18 October 2010 07:00, Levente Uzonyi  wrote:
> On Sun, 17 Oct 2010, Levente Uzonyi wrote:
>
> snip
>
>> SharedQueue's code for "growing" (#makeRoomAtEnd) is crap IMHO. Because of
>> that it takes O(n) time to add or remove and element to or from the queue.
>> SharedQueue2 is a lot better approach, because it doesn't try to
>> reimplement a dynamic array, but uses OrderedCollection instead.
>
> I uploaded a new version of that method to the Trunk. I don't think it's
> really useful, because I'm pretty sure we will get rid of both SharedQueue
> and SharedQueue2 in the near future.
> Anyway I did some benchmarks using Cog, and SharedQueue became surprisingly
> good, though it's still not even close to Igor's new FIFOQueue or
> AtomicSharedQueue.
>
> Benchmark #1: Make a large queue
>
> { SharedQueue. SharedQueue2. FIFOQueue. AtomicSharedQueue } collect: [
> :queueClass |
>        | queue |
>        queue := queueClass new.
>        queueClass -> (
>                (1 to: 5) collect: [ :run |
>                        Smalltalk garbageCollect.
>                        {
>                               [ 1 to: 100 do: [ :each | queue nextPut:
> each ] ] timeToRun.
>                               [ 1 to: 100 do: [ :each | queue next ] ]
> timeToRun } ]) ].
>
> SharedQueue->#(#(1028 1615) #(945 1557) #(976 2322) #(492 459) #(489 476)).
> SharedQueue2->#(#(1976 2284) #(1318 8298) #(982 692) #(1005 675) #(1002
> 665)).
> FIFOQueue->#(#(180 67) #(184 67) #(182 69) #(181 66) #(177 67)).
> AtomicSharedQueue->#(#(208 66) #(207 67) #(209 66) #(213 68) #(209 65)).
>
> This benchmark is similar to what Igor used, but it doesn't create a new
> queue between runs. It simply adds 1,000,000 elements then removes them
> which is a pretty unrealistic scenario for a shared queue. The effect of GC
> is pretty high on this benchmark, probably that's responsible for the high
> spikes.
>
> Benchmark #2: Sequential throughput test
>
> { SharedQueue. SharedQueue2. FIFOQueue. AtomicSharedQueue } collect: [
> :queueClass |
>        | queue |
>        queue := queueClass new.
>        queueClass -> (
>                (1 to: 5) collect: [ :run |
>                        | results |
>                        Smalltalk garbageCollect.
>                        results := #(0 0).
>                        1 to: 1000 do: [ :round |
>                                results := results + {
>                                        [ 1 to: 1000 do: [ :each | queue
> nextPut: each ] ] timeToRun.
>                                        [ 1 to: 1000 do: [ :each | queue next
> ] ] timeToRun } ].
>                        results ]) ].
>
> SharedQueue->#(#(464 452) #(472 436) #(466 437) #(463 449) #(462 452)).
> SharedQueue2->#(#(949 692) #(980 663) #(984 670) #(992 670) #(958 677)).
> FIFOQueue->#(#(125 67) #(263 62) #(250 76) #(262 63) #(247 81)).
> AtomicSharedQueue->#(#(154 70) #(264 77) #(273 62) #(275 63) #(265 71)).
>
> This is similar to benchmark #1, but instead of adding and removing
> 1,000,000 at once it's chunked up to 1,000 equal parts. It's more realistic
> than benchmark #1. It's interesting that both FIFOQueue and
> AtomicSharedQueue performed better in the previous benchmark, unlike the
> other two queues, which are better here.
>
> Benchmark #3: Concurrent throughput test
>
> { SharedQueue. SharedQueue2. FIFOQueue. AtomicSharedQueue } collect: [
> :queueClass |
>        | queue semaphore |
>        queue := queueClass new.
>        semaphore := Semaphore new.
>        queueClass -> (
>                (1 to: 5) collect: [ :run |
>                        | producers consumers |
>                        Smalltalk garbageCollect.
>                        producers := (1 to: 100) collect: [ :each |
>                                [ 1 to: 1 do: [ :index | queue nextPut:
> each ] ] newProcess ].
>                        consumers := (1 to: 100) collect: [ :each |
>                                [
>                                        1 to: 1 do: [ :index | queue next
> ].
>                                        semaphore signal ] newProcess ].
>                        [
>                                consumers do: [ :each | each priority: 39;
> resume ].
>                                producers do: [ :each | each priority: 39;
> resume ].
>                                100 timesRepeat: [ semaphore wait ] ]
> timeToRun ]) ].
>
> SharedQueue->#(3143 2977 3034 2949 3021).
> SharedQueue2->#(4280 4384 4179 4160 4181).
> FIFOQueue->#(245 311 252 254 255).
> AtomicSharedQueue->#(277 274 277 280 274)
>
> This benchmark is the real concurrent stress test. 100 processes are adding
> 10,000 elements to the queue while another 100 are reading from it. It
> clearly shows that Igor's queues are an order of magnitude faster. Also 200
> concurrent processes cause much less slowdown compared to the sequential
> tests for them.
>
> So, even though SharedQueue is now faster than SharedQueue2, both will have
> to go IMHO. :)
>

Than

Re: [Pharo-project] Fwd: pharo sprint / moose dojo - october 23-24, bern

2010-10-18 Thread Laval Jannik
Hi,

I created an entry at: http://code.google.com/p/pharo/wiki/PharoSprints
We will join you by internet :)

Cheers,
Jannik

On Oct 18, 2010, at 11:01 , Tudor Girba wrote:

> Hi,
> 
> This is just a reminder that the next Pharo sprint will take place during 
> October 23-24 in Bern (see below). If you want to attend, please let me know.
> 
> Cheers,
> Doru
> 
> 
> Begin forwarded message:
> 
>> We will organize a joint Pharo sprint / Moose dojo during October 23-24, in 
>> Bern (at the Software Composition Group, University of Bern). 
>> 
>> Some action points are mentioned on the dedicated page (of course, other 
>> ideas and interests are welcome as well):
>> http://www.moosetechnology.org/events/2010-10-22-dojo
>> 
>> For planning purposes, please let me know if you will attend. ESUG will 
>> kindly offer support for food and drinks.
>> 
>> Cheers,
>> Doru 
>> 
>> p.s. In case it is of interest, on October 22, we also have CHOOSE Forum 
>> 2010 in Bern, an event on the topic of Domain-Specific Engineering where, 
>> among others we'll learn about the role of Smalltalk :)
>> http://choose.s-i.ch/events/forum2010
> 
> --
> www.tudorgirba.com
> 
> "Obvious things are difficult to teach."
> 
> 
> 
> 
> ___
> Pharo-project mailing list
> Pharo-project@lists.gforge.inria.fr
> http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

---
Jannik Laval

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

[Pharo-project] Fwd: pharo sprint / moose dojo - october 23-24, bern

2010-10-18 Thread Tudor Girba
Hi,

This is just a reminder that the next Pharo sprint will take place during 
October 23-24 in Bern (see below). If you want to attend, please let me know.

Cheers,
Doru


Begin forwarded message:

> We will organize a joint Pharo sprint / Moose dojo during October 23-24, in 
> Bern (at the Software Composition Group, University of Bern). 
> 
> Some action points are mentioned on the dedicated page (of course, other 
> ideas and interests are welcome as well):
> http://www.moosetechnology.org/events/2010-10-22-dojo
> 
> For planning purposes, please let me know if you will attend. ESUG will 
> kindly offer support for food and drinks.
> 
> Cheers,
> Doru 
> 
> p.s. In case it is of interest, on October 22, we also have CHOOSE Forum 2010 
> in Bern, an event on the topic of Domain-Specific Engineering where, among 
> others we'll learn about the role of Smalltalk :)
> http://choose.s-i.ch/events/forum2010

--
www.tudorgirba.com

"Obvious things are difficult to teach."




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


[Pharo-project] Implementing a Timer: "newProcessWith: anArray" fails

2010-10-18 Thread nullPointer

Hi

I do implementing a easy Timer class. The purpose of timer is launch events
for UI thread and the process thread too when a interval of time is elapsed.

My problem is throwned when I call the message #newProcessWith: from
BlockClosure. I pass an array with a parameter, the instance of CLTimer
class, which is used in the Closure process for launc the events. A error of
not is valid the number of arguments is launched:

 'This block accepts 1 argument, but was called with 0
arguments.'

I don´t understand very good the problem. I have pass an array with one
element, and the Closure receives one parameter too...

Basically the code:

pvtGetNewProcessBlock

^[:timer || intervalDelay |

[timer enabled] whileTrue:[

(Delay forMilliseconds: timer interval) wait. 

timer enabled ifTrue:[

timer raiseOnElapsedTimeForProcessThread: 
(timer getProcess).

WorldState addDeferredUIMessage:[ 
timer raiseOnElapsedTimeForUIThread: 
(timer getProcess) 
].
]
].
].


pvtStartProcess

| processBlock |

processBlock := self pvtGetNewProcessBlock.

internalProcess := processBlock newProcessWith:{self}.
internalProcess resume.



PD. Exists some complete doc with the way for work with threads in
Pharo/Squeak? I did see time ago a doc of Smalltalk processes, in french
language, but I don´t see in Google :(


http://forum.world.st/file/n2999831/CLTimer.st CLTimer.st 
-- 
View this message in context: 
http://forum.world.st/Implementing-a-Timer-newProcessWith-anArray-fails-tp2999831p2999831.html
Sent from the Pharo Smalltalk mailing list archive at Nabble.com.

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

Re: [Pharo-project] Speeding up Pharo 1.1

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 9:21 AM, Bart Veenstra wrote:

> After MCMethodDefinition shutDown


Does this have some kind of bad side effect or I can do it also?

Cheers

Mariano


> it looks like it is reacting a bit
> faster to keyboard input. I often experience sluggishness in
> autocompletion method. When I type in a name of a class in a
> workspace, the autocomplete suggests 3 options. I want to choose the
> middle, so I press down and after 3 seconds (or sometimes nothging
> happens) it selects the class. The longer I have my image open, the
> longer this will take :S
>
>
>
>
> 2010/10/17 Igor Stasenko :
> > Bart,
> > can you try doing:
> >
> > MCMethodDefinition shutDown
> >
> > in your image?
> >
> > On 16 October 2010 14:48, Bart Veenstra  wrote:
> >> Hi list,
> >>
> >> I have been working with Pharo for almost a month now, and I suspect
> >> that the performance is degrading fast. UI tasks takes several seconds
> >> to react to my keyboard.
> >>
> >> At work we use VAST and I have experience with VW as well and those
> >> smalltaks react to my keyboard and mouse actions instantly. But Pharo
> >> works very sluggish.
> >>
> >> My image is about 130MB because I have loaded all dutch postcode in
> >> memory, but that should not affect the performance of general
> >> operations like typing with the keyboard. I am not a fast typer, but
> >> sometimes it takes seconds to show my keyboard input. I can't use the
> >> down key to select the right method from suggestions, because it seems
> >> to lockup completely.
> >>
> >> Are there ways to speedup Pharo? I would love to use cogVM but I
> >> haven't got gemtools working on it...
> >>
> >> Will upgrading to 1.1.1 fix these issues?
> >>
> >> Is my OS (Windows 7-64bit) causing these issues?
> >>
> >> Regards,
> >>
> >> Bart
> >>
> >> ___
> >> 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
>
___
Pharo-project mailing list
Pharo-project@lists.gforge.inria.fr
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project

Re: [Pharo-project] [SPAM] Re: Speeding up Pharo 1.1

2010-10-18 Thread Bart Veenstra
I would love to use a new image and reload all my apps, but I have
some important data in the image persisted, and I guess I would loose
these with a new image. I installed SIXX already for exporting. this
works. Now the importing part.

Is there a way I can upgrade to 1.1.1 from 1.1? The software update
option doesn't do much.

Regards,


Bart

2010/10/18 Sven Van Caekenberghe :
>
> On 18 Oct 2010, at 09:21, Bart Veenstra wrote:
>
>> After MCMethodDefinition shutDown it looks like it is reacting a bit
>> faster to keyboard input. I often experience sluggishness in
>> autocompletion method. When I type in a name of a class in a
>> workspace, the autocomplete suggests 3 options. I want to choose the
>> middle, so I press down and after 3 seconds (or sometimes nothging
>> happens) it selects the class. The longer I have my image open, the
>> longer this will take :S
>
> That is what I had before, see my earlier answer...
>
> Sven
>
>
> ___
> 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] A Lazy Inspector?

2010-10-18 Thread Mariano Martinez Peck
On Mon, Oct 18, 2010 at 4:40 AM, Oscar E A Callau wrote:

> Hello all,
>
> I was wondering what actually the inspector does in the following case:
>
> When you explore (or inspect) the expression: Class environment
> you get all classes in the system dictionary. If you navigate inside a
> class, for example AColorSelectorMorph, you can see all its properties and
> one of them is environment, if you go inside it, you get again all classes
> in the system dictionary. So, you can repeat this infinitely (or until you
> get run out of memory, I guess)
>
> Is it the behavior of a lazy inspector? If true, why I cannot inspect a
> mutually-recursive class definition, like this:
>
> Object subclass: #Foo
>instanceVariableNames: 'bar'
>classVariableNames: ''
>poolDictionaries: ''
>category: ''
>
> Foo>>initialize
>bar:= Bar new
>
> Object subclass: #Bar
>instanceVariableNames: 'foo'
>classVariableNames: ''
>poolDictionaries: ''
>category: ''
>
> Foo>>initialize
>bar:= Foo new
>
> Thanks in advance.
>
>
That's a good question. I have no idea how it is hanlder.


> P.S.: How can I stop my execution in the pharo image when it is in a
> infinite loop? I can't remember what the shortcut was.
>
>
http://book.pharo-project.org/book/TipsAndTricks/InterruptKey/



>
> ___
> 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] [SPAM] Re: Speeding up Pharo 1.1

2010-10-18 Thread Sven Van Caekenberghe

On 18 Oct 2010, at 09:21, Bart Veenstra wrote:

> After MCMethodDefinition shutDown it looks like it is reacting a bit
> faster to keyboard input. I often experience sluggishness in
> autocompletion method. When I type in a name of a class in a
> workspace, the autocomplete suggests 3 options. I want to choose the
> middle, so I press down and after 3 seconds (or sometimes nothging
> happens) it selects the class. The longer I have my image open, the
> longer this will take :S

That is what I had before, see my earlier answer...

Sven


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


Re: [Pharo-project] Speeding up Pharo 1.1

2010-10-18 Thread Bart Veenstra
VM Statistics:

uptime  45h21m14s
memory  125,787,076 bytes
old 122,936,884 bytes (97.7%)
young   288,944 bytes (0.2%)
used123,225,828 bytes (98.0%)
free2,561,248 bytes (2.0%)
GCs 211,214 (773ms between GCs)
full26 totalling 9,392ms (0.0% uptime), avg 361.2ms
incr211188 totalling 6,751ms (0.0% uptime), avg 0.0ms
tenures 176 (avg 1199 GCs/tenure)
Since last view 198,425 (0ms between GCs)
uptime  -29.4s
full5 totalling 6,910ms (-23.5% uptime), avg 
1382.0ms
incr198420 totalling 4,258ms (-14.5% uptime), avg 0.0ms
tenures 100 (avg 1984 GCs/tenure)


2010/10/18 Bart Veenstra :
> After MCMethodDefinition shutDown it looks like it is reacting a bit
> faster to keyboard input. I often experience sluggishness in
> autocompletion method. When I type in a name of a class in a
> workspace, the autocomplete suggests 3 options. I want to choose the
> middle, so I press down and after 3 seconds (or sometimes nothging
> happens) it selects the class. The longer I have my image open, the
> longer this will take :S
>
>
>
>
> 2010/10/17 Igor Stasenko :
>> Bart,
>> can you try doing:
>>
>> MCMethodDefinition shutDown
>>
>> in your image?
>>
>> On 16 October 2010 14:48, Bart Veenstra  wrote:
>>> Hi list,
>>>
>>> I have been working with Pharo for almost a month now, and I suspect
>>> that the performance is degrading fast. UI tasks takes several seconds
>>> to react to my keyboard.
>>>
>>> At work we use VAST and I have experience with VW as well and those
>>> smalltaks react to my keyboard and mouse actions instantly. But Pharo
>>> works very sluggish.
>>>
>>> My image is about 130MB because I have loaded all dutch postcode in
>>> memory, but that should not affect the performance of general
>>> operations like typing with the keyboard. I am not a fast typer, but
>>> sometimes it takes seconds to show my keyboard input. I can't use the
>>> down key to select the right method from suggestions, because it seems
>>> to lockup completely.
>>>
>>> Are there ways to speedup Pharo? I would love to use cogVM but I
>>> haven't got gemtools working on it...
>>>
>>> Will upgrading to 1.1.1 fix these issues?
>>>
>>> Is my OS (Windows 7-64bit) causing these issues?
>>>
>>> Regards,
>>>
>>> Bart
>>>
>>> ___
>>> 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] Speeding up Pharo 1.1

2010-10-18 Thread Bart Veenstra
After MCMethodDefinition shutDown it looks like it is reacting a bit
faster to keyboard input. I often experience sluggishness in
autocompletion method. When I type in a name of a class in a
workspace, the autocomplete suggests 3 options. I want to choose the
middle, so I press down and after 3 seconds (or sometimes nothging
happens) it selects the class. The longer I have my image open, the
longer this will take :S




2010/10/17 Igor Stasenko :
> Bart,
> can you try doing:
>
> MCMethodDefinition shutDown
>
> in your image?
>
> On 16 October 2010 14:48, Bart Veenstra  wrote:
>> Hi list,
>>
>> I have been working with Pharo for almost a month now, and I suspect
>> that the performance is degrading fast. UI tasks takes several seconds
>> to react to my keyboard.
>>
>> At work we use VAST and I have experience with VW as well and those
>> smalltaks react to my keyboard and mouse actions instantly. But Pharo
>> works very sluggish.
>>
>> My image is about 130MB because I have loaded all dutch postcode in
>> memory, but that should not affect the performance of general
>> operations like typing with the keyboard. I am not a fast typer, but
>> sometimes it takes seconds to show my keyboard input. I can't use the
>> down key to select the right method from suggestions, because it seems
>> to lockup completely.
>>
>> Are there ways to speedup Pharo? I would love to use cogVM but I
>> haven't got gemtools working on it...
>>
>> Will upgrading to 1.1.1 fix these issues?
>>
>> Is my OS (Windows 7-64bit) causing these issues?
>>
>> Regards,
>>
>> Bart
>>
>> ___
>> 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] [squeak-dev] SharedQueue does scale (was: Re: SharedQueue doesn't scale)

2010-10-18 Thread Stéphane Ducasse
> 
> This benchmark is the real concurrent stress test. 100 processes are adding 
> 10,000 elements to the queue while another 100 are reading from it. It 
> clearly shows that Igor's queues are an order of magnitude faster. Also 200 
> concurrent processes cause much less slowdown compared to the sequential 
> tests for them.
> 
> So, even though SharedQueue is now faster than SharedQueue2, both will have 
> to go IMHO. :)

Hi Levente

Naively why?
and replace by what?

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