The Trunk: System-cmm.725.mcz

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

The Trunk: System-cmm.725.mcz

commits-2
Chris Muller uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-cmm.725.mcz

==================== Summary ====================

Name: System-cmm.725
Author: cmm
Time: 27 April 2015, 3:20:18.66 pm
UUID: b166e202-b3c3-4232-a17e-cd55a873fa50
Ancestors: System-mt.724

- Attempting to load preferences is blowing up, fix by restoring the old one-click behavior.
- Proper fix for browsing allStoresInto: SomeClassVar from: aClassOrMetaclass, so that all stores occurring in either the instance or class side will be revealed even if the browse was initiated from the class-side.

=============== Diff against System-mt.724 ===============

Item was changed:
  ----- Method: Preferences class>>loadPreferencesFrom: (in category 'personalization') -----
+ loadPreferencesFrom: aFileName
- loadPreferencesFrom: aFile
  | stream params dict desktopColor |
+ stream := ReferenceStream fileNamed: aFileName.
- stream := ReferenceStream on: aFile.
  params := stream next.
  self assert: (params isKindOf: IdentityDictionary).
  params removeKey: #PersonalDictionaryOfPreferences.
  dict := stream next.
  self assert: (dict isKindOf: IdentityDictionary).
  desktopColor := stream next.
  stream close.
  dict keysAndValuesDo:
  [:key :value | (self preferenceAt: key ifAbsent: [nil]) ifNotNil:
  [:pref | pref preferenceValue: value preferenceValue]].
 
  params keysAndValuesDo: [ :key :value | self setParameter: key to: value ].
 
  Smalltalk isMorphic
  ifTrue: [ World fillStyle: desktopColor ]
  ifFalse: [ self desktopColor: desktopColor. ScheduledControllers updateGray ].
  !

Item was changed:
  ----- Method: Preferences class>>preferenceAt:ifAbsent: (in category 'preference-object access') -----
  preferenceAt: aSymbol ifAbsent: aBlock
  "Answer the Preference object at the given symbol, or the value of aBlock if not present"
 
+ ^self accessDictionaryOfPreferencesIn: [ :dictionaryOfPreferences |
+ dictionaryOfPreferences at: aSymbol ifAbsent: aBlock ]!
- self accessDictionaryOfPreferencesIn: [ :dictionaryOfPreferences |
-                 dictionaryOfPreferences
-                         at: aSymbol
-                         ifPresent: [ :preference | ^preference ] ].
-         ^aBlock value!

Item was removed:
- ----- Method: Preferences class>>restorePreferencesFromDisk: (in category 'personalization') -----
- restorePreferencesFromDisk: aFile
- Cursor wait
- showWhile: [[self loadPreferencesFrom: aFile]
- on: Error
- do: [:ex | self inform: 'there was an error restoring the preferences' translated]]!

Item was changed:
  ----- Method: Preferences class>>storePreferencesToDisk (in category 'personalization') -----
  storePreferencesToDisk
+ Cursor wait showWhile: [
+ [ self storePreferencesIn: 'my.prefs' ] on: Error do: [ :ex | self inform: 'there was an error storing your preferences to disk' ]]!
- | newName |
- newName := UIManager default request: 'Please confirm name for save...' initialAnswer: 'myPreferences'.
- newName isEmpty
- ifTrue: [^ self].
- Cursor wait
- showWhile: [[self storePreferencesIn: newName , '.prefs']
- on: Error
- do: [:ex | self inform: 'there was an error storing your preferences to disk. you probably already have stored your preferences' translated]]!

Item was changed:
  ----- Method: SystemNavigation>>allStoresInto:from: (in category 'query') -----
  allStoresInto: varName from: aClass
  "Answer a sequence of MewthodReferences for all the receiver's methods
  or any methods of a subclass/superclass that assign to the instance variable name."
  "self new allStoresInto: 'contents' from: Collection."
  | result roots |
  result := OrderedCollection new.
  (aClass theNonMetaClass inheritsFrom: SharedPool) ifTrue:
  [roots := self allClasses select: [:class| class sharedPools includes: aClass theNonMetaClass].
   roots do:
  [:root|
  root withAllSubclassesDo:
  [:class|
  (class whichMethodsStoreInto: varName),
  (class class whichMethodsStoreInto: varName) do:
  [:eachMethod|
  result add: eachMethod methodReference]]]].
  aClass withAllSubAndSuperclassesDo:
  [ : class |
+ (class theNonMetaClass whichMethodsStoreInto: varName),
+ (class theMetaClass whichMethodsStoreInto: varName) do:
- (class whichMethodsStoreInto: varName),
- (class class whichMethodsStoreInto: varName) do:
  [ : eachMethod |
  result add: eachMethod methodReference ] ].
  ^result!

Item was changed:
  ----- Method: SystemNavigation>>browseAllStoresInto:from: (in category 'browse') -----
+ browseAllStoresInto: varName from: aClass
- browseAllStoresInto: varName from: aClass
  "Create and schedule a Message Set browser for all the receiver's methods
  or any methods of a subclass/superclass that refer to the instance variable name."
  "self new browseAllStoresInto: 'contents' from: Collection."
  ^ self
+ browseMessageList: (self allStoresInto: varName from: aClass)
- browseMessageList:
- (self
- allStoresInto: varName
- from: aClass) ,
- ((aClass allClassVarNames includes: varName)
- ifTrue:
- [ self
- allStoresInto: varName
- from: aClass class ]
- ifFalse: [ Array empty ])
  name: 'Stores into ' , varName
  autoSelect: varName!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Levente Uzonyi-2
On Mon, 27 Apr 2015, [hidden email] wrote:

> Chris Muller uploaded a new version of System to project The Trunk:
> http://source.squeak.org/trunk/System-cmm.725.mcz
>
> ==================== Summary ====================
>
> Name: System-cmm.725
> Author: cmm
> Time: 27 April 2015, 3:20:18.66 pm
> UUID: b166e202-b3c3-4232-a17e-cd55a873fa50
> Ancestors: System-mt.724
>
> - Attempting to load preferences is blowing up, fix by restoring the old one-click behavior.
> - Proper fix for browsing allStoresInto: SomeClassVar from: aClassOrMetaclass, so that all stores occurring in either the instance or class side will be revealed even if the browse was initiated from the class-side.
>
> =============== Diff against System-mt.724 ===============
>
> Item was changed:
>  ----- Method: Preferences class>>preferenceAt:ifAbsent: (in category 'preference-object access') -----
>  preferenceAt: aSymbol ifAbsent: aBlock
>   "Answer the Preference object at the given symbol, or the value of aBlock if not present"
>
> + ^self accessDictionaryOfPreferencesIn: [ :dictionaryOfPreferences |
> + dictionaryOfPreferences at: aSymbol ifAbsent: aBlock ]!
> - self accessDictionaryOfPreferencesIn: [ :dictionaryOfPreferences |
> -                 dictionaryOfPreferences
> -                         at: aSymbol
> -                         ifPresent: [ :preference | ^preference ] ].
> -         ^aBlock value!

The above change restores the old behavior of locking up the image, so it
should be reverted. An additional comment explaininng why aBlock must
not be evaluated inside the argument of #accessDictionaryOfPreferencesIn:
would be helpful.
It would be even better to finally get rid of DictionaryOfPreferences.


Levente

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Chris Muller-3
> The above change restores the old behavior of locking up the image, so it
> should be reverted. An additional comment explaininng why aBlock must not be
> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
> helpful.

Ahh, because aBlock might have a non-local return in it, leaving the
Mutex unsignaled (and critical unenterable), is that right?

Took me a minute to see that problem.

Okay, I'll revert that method if no one else does by my next commit..

> It would be even better to finally get rid of DictionaryOfPreferences.
>
>
> Levente
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Chris Muller-3
Wait, the newer one has a non-local return in it, but
Mutext>>#critical: has an ensure: in it anyway, so maybe I don't see
the problem..?

On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:

>> The above change restores the old behavior of locking up the image, so it
>> should be reverted. An additional comment explaininng why aBlock must not be
>> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
>> helpful.
>
> Ahh, because aBlock might have a non-local return in it, leaving the
> Mutex unsignaled (and critical unenterable), is that right?
>
> Took me a minute to see that problem.
>
> Okay, I'll revert that method if no one else does by my next commit..
>
>> It would be even better to finally get rid of DictionaryOfPreferences.
>>
>>
>> Levente
>>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Levente Uzonyi-2
If there's an error signaled from aBlock, and the default error handler is
activated (see UnhandledError >> #defaultAction), then the process will be
suspended (see Debugger class >> #morphicOpenOn:context:label:contents:fullView:)
while it's inside the AccessLock mutex's critical section.
The (new) UI process will try to display a debugger. To do that, it will
try to read the values of various preferences, but the suspended process
is holding the mutex, so it'll wait forever.
This results in an image lockup, because using Alt+. (Cmd+. on mac) will
also try to open a debugger.
This is why aBlock must be evaluated outside of the AccessLock mutex's
critical section.

To reproduce the error, just evaluate this expression (but keep in mind
that your image will not be able to respond anymore):

  Preferences preferenceAt: #'no such preference' ifAbsent: [ self error ]

Levente

On Tue, 28 Apr 2015, Chris Muller wrote:

> Wait, the newer one has a non-local return in it, but
> Mutext>>#critical: has an ensure: in it anyway, so maybe I don't see
> the problem..?
>
> On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
>>> The above change restores the old behavior of locking up the image, so it
>>> should be reverted. An additional comment explaininng why aBlock must not be
>>> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
>>> helpful.
>>
>> Ahh, because aBlock might have a non-local return in it, leaving the
>> Mutex unsignaled (and critical unenterable), is that right?
>>
>> Took me a minute to see that problem.
>>
>> Okay, I'll revert that method if no one else does by my next commit..
>>
>>> It would be even better to finally get rid of DictionaryOfPreferences.
>>>
>>>
>>> Levente
>>>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Eliot Miranda-2
In reply to this post by Chris Muller-3


On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
Wait, the newer one has a non-local return in it, but
Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
the problem..?

If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g. scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.

IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I presume it is there only for the rare case of a write to preferences, not to protect reads.

IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value shouldn't matter.  So the implementation could be as simple as

addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
"Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."

| aPreference aPrefSymbol |
aPrefSymbol := aName asSymbol.
aPreference := DictionaryOfPreferences
at: aPrefSymbol
ifAbsent:
[| newPreference |
newPreference := aPreference 
name:aPrefSymbol
defaultValue:aValue
helpString:helpString
localToProject:localBoolean
categoryList:categoryList
changeInformee:informeeSymbol
changeSelector:aChangeSelector
type: aType.
AccessLock critical:
[| newDict |
newDict := DictionaryOfPreferences copy.
newDict at: aPrefSymbol put: newPreference].
self  compileAccessMethodForPreference:aPreference.
newPreference]


On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
>> The above change restores the old behavior of locking up the image, so it
>> should be reverted. An additional comment explaininng why aBlock must not be
>> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
>> helpful.
>
> Ahh, because aBlock might have a non-local return in it, leaving the
> Mutex unsignaled (and critical unenterable), is that right?
>
> Took me a minute to see that problem.
>
> Okay, I'll revert that method if no one else does by my next commit..
>
>> It would be even better to finally get rid of DictionaryOfPreferences.
>>
>>
>> Levente
>>




--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Chris Muller-3
In reply to this post by Levente Uzonyi-2
On Tue, Apr 28, 2015 at 5:00 PM, Levente Uzonyi <[hidden email]> wrote:

> If there's an error signaled from aBlock, and the default error handler is
> activated (see UnhandledError >> #defaultAction), then the process will be
> suspended (see Debugger class >>
> #morphicOpenOn:context:label:contents:fullView:)
> while it's inside the AccessLock mutex's critical section.
> The (new) UI process will try to display a debugger. To do that, it will try
> to read the values of various preferences, but the suspended process is
> holding the mutex, so it'll wait forever.
> This results in an image lockup, because using Alt+. (Cmd+. on mac) will
> also try to open a debugger.
> This is why aBlock must be evaluated outside of the AccessLock mutex's
> critical section.

Okay, the newer one is probably safer because #at:ifPresent:
*probably* won't get an error, but theoretically it still could,
leaving the image locked for the very same reason.

So Eliots suggestion is sounding good -- why do something like
preferences need to be guarded on access?  It seems not that
important...

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Levente Uzonyi-2
In reply to this post by Eliot Miranda-2
There's no need to store preferences in a data structure at all. We
already have "pragma" preferences (since 4.1), which store the
preference values independently. Since the 4.1 release it's a "permanent"
goal to rewrite all preferences to "pragma" preferences.
We should just make it happen.

Levente

P.S.: Reverting that method will solve the concurrency issue.

On Tue, 28 Apr 2015, Eliot Miranda wrote:

>
>
> On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
>       Wait, the newer one has a non-local return in it, but
>       Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
>       the problem..?
>
>
> If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g.
> scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.
>
> IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I
> presume it is there only for the rare case of a write to preferences, not to protect reads.
>
> IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently
> while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value
> shouldn't matter.  So the implementation could be as simple as
>
> addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
> "Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."
>
> | aPreference aPrefSymbol |
> aPrefSymbol := aName asSymbol.
> aPreference := DictionaryOfPreferences
> at: aPrefSymbol
> ifAbsent:
> [| newPreference |
> newPreference := aPreference 
> name:aPrefSymbol
> defaultValue:aValue
> helpString:helpString
> localToProject:localBoolean
> categoryList:categoryList
> changeInformee:informeeSymbol
> changeSelector:aChangeSelector
> type: aType.
> AccessLock critical:
> [| newDict |
> newDict := DictionaryOfPreferences copy.
> newDict at: aPrefSymbol put: newPreference].
> self  compileAccessMethodForPreference:aPreference.
> newPreference]
>
>
>       On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
>       >> The above change restores the old behavior of locking up the image, so it
>       >> should be reverted. An additional comment explaininng why aBlock must not be
>       >> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
>       >> helpful.
>       >
>       > Ahh, because aBlock might have a non-local return in it, leaving the
>       > Mutex unsignaled (and critical unenterable), is that right?
>       >
>       > Took me a minute to see that problem.
>       >
>       > Okay, I'll revert that method if no one else does by my next commit..
>       >
>       >> It would be even better to finally get rid of DictionaryOfPreferences.
>       >>
>       >>
>       >> Levente
>       >>
>
>
>
>
> --
> best,Eliot
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Chris Muller-4
Mmm, isn't it useful for save / load?  What about "themes" -- swapping
an entire set of preferences with another?  How easily could someone
find a list of all preferences in the system all in one place?

On Tue, Apr 28, 2015 at 5:41 PM, Levente Uzonyi <[hidden email]> wrote:

> There's no need to store preferences in a data structure at all. We already
> have "pragma" preferences (since 4.1), which store the preference values
> independently. Since the 4.1 release it's a "permanent" goal to rewrite all
> preferences to "pragma" preferences.
> We should just make it happen.
>
> Levente
>
> P.S.: Reverting that method will solve the concurrency issue.
>
>
> On Tue, 28 Apr 2015, Eliot Miranda wrote:
>
>>
>>
>> On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]>
>> wrote:
>>       Wait, the newer one has a non-local return in it, but
>>       Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
>>       the problem..?
>>
>>
>> If one hits ctrl-period when the system is in the critical section then
>> the debugger can't open because it interrupts the critical section,
>> preventing the ensure block from running, attempts to access e.g.
>> scroll bar preferences when it tries to open, and the system deadlocks.
>> So preferences either need to be *not* protected by a critical section, or
>> the Debugger needs not to access preferences.
>>
>> IMO, we should try and write preferences so that they don't require a
>> lock.  Writing them as a lock-free data structure would be a really good
>> idea. First that critical section is slow and clunky.  Second, I
>> presume it is there only for the rare case of a write to preferences, not
>> to protect reads.
>>
>> IMO, a simple implementation which copied and replaced the entire
>> preferences dictionary on write would be sufficient.  Sure there's a danger
>> that some client would get a stale value if it read concurrently
>> while there was a write, but then so what?  A preference is a preference,
>> not a hard-and-fast value, and code should work accessing a preference no
>> matter its value, so momentarily getting a stale value
>> shouldn't matter.  So the implementation could be as simple as
>>
>> addPreference: aName categories: categoryList default: aValue balloonHelp:
>> helpString projectLocal: localBoolean changeInformee: informeeSymbol
>> changeSelector: aChangeSelector type: aType
>> "Add or replace a preference as indicated.  Reuses the preexisting
>> Preference object for this symbol, if there is one, so that UI artifacts
>> that interact with it will remain valid."
>>
>> | aPreference aPrefSymbol |
>> aPrefSymbol := aName asSymbol.
>> aPreference := DictionaryOfPreferences
>> at: aPrefSymbol
>> ifAbsent:
>> [| newPreference |
>> newPreference := aPreference
>> name:aPrefSymbol
>> defaultValue:aValue
>> helpString:helpString
>> localToProject:localBoolean
>> categoryList:categoryList
>> changeInformee:informeeSymbol
>> changeSelector:aChangeSelector
>> type: aType.
>> AccessLock critical:
>> [| newDict |
>> newDict := DictionaryOfPreferences copy.
>> newDict at: aPrefSymbol put: newPreference].
>> self  compileAccessMethodForPreference:aPreference.
>> newPreference]
>>
>>
>>       On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]>
>> wrote:
>>       >> The above change restores the old behavior of locking up the
>> image, so it
>>       >> should be reverted. An additional comment explaininng why aBlock
>> must not be
>>       >> evaluated inside the argument of
>> #accessDictionaryOfPreferencesIn: would be
>>       >> helpful.
>>       >
>>       > Ahh, because aBlock might have a non-local return in it, leaving
>> the
>>       > Mutex unsignaled (and critical unenterable), is that right?
>>       >
>>       > Took me a minute to see that problem.
>>       >
>>       > Okay, I'll revert that method if no one else does by my next
>> commit..
>>       >
>>       >> It would be even better to finally get rid of
>> DictionaryOfPreferences.
>>       >>
>>       >>
>>       >> Levente
>>       >>
>>
>>
>>
>>
>> --
>> best,Eliot
>>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Eliot Miranda-2
In reply to this post by Levente Uzonyi-2
Hi Levente,  Hi Chris,

On Tue, Apr 28, 2015 at 3:41 PM, Levente Uzonyi <[hidden email]> wrote:
There's no need to store preferences in a data structure at all. We already have "pragma" preferences (since 4.1), which store the preference values independently. Since the 4.1 release it's a "permanent" goal to rewrite all preferences to "pragma" preferences.
We should just make it happen.

This seems like a lot of work, and is work that can be done over time.  But right now we're suffering lock ups due to the Mutex in Preferences.  For example, the Notifier/Debugger accesses the scrollBarsOnRight preference and I've often seen lock ups caused by this.  So I propose that I fix the access to be as I described it.  There be no access lock except for adding/updating preferences.  So reading is done without synchronisation, and setting and/or adding is done by copying and assigning.  I also propose to compile preferences without creating a block, so

autoIndent
^ self
valueOfFlag: #autoIndent
ifAbsent: true

instead of

autoIndent
^ self
valueOfFlag: #autoIndent
ifAbsent: [true]

which is well-supported by both the Interpreter and the Cog VMs, given Object>>value ^self.  This to save space and time.

Levente

P.S.: Reverting that method will solve the concurrency issue.


On Tue, 28 Apr 2015, Eliot Miranda wrote:



On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
      Wait, the newer one has a non-local return in it, but
      Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
      the problem..?


If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g.
scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.

IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I
presume it is there only for the rare case of a write to preferences, not to protect reads.

IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently
while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value
shouldn't matter.  So the implementation could be as simple as

addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
"Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."

| aPreference aPrefSymbol |
aPrefSymbol := aName asSymbol.
aPreference := DictionaryOfPreferences
at: aPrefSymbol
ifAbsent:
[| newPreference |
newPreference := aPreference 
name:aPrefSymbol
defaultValue:aValue
helpString:helpString
localToProject:localBoolean
categoryList:categoryList
changeInformee:informeeSymbol
changeSelector:aChangeSelector
type: aType.
AccessLock critical:
[| newDict |
newDict := DictionaryOfPreferences copy.
newDict at: aPrefSymbol put: newPreference].
self  compileAccessMethodForPreference:aPreference.
newPreference]


      On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
      >> The above change restores the old behavior of locking up the image, so it
      >> should be reverted. An additional comment explaininng why aBlock must not be
      >> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
      >> helpful.
      >
      > Ahh, because aBlock might have a non-local return in it, leaving the
      > Mutex unsignaled (and critical unenterable), is that right?
      >
      > Took me a minute to see that problem.
      >
      > Okay, I'll revert that method if no one else does by my next commit..
      >
      >> It would be even better to finally get rid of DictionaryOfPreferences.
      >>
      >>
      >> Levente
      >>




--
best,Eliot







--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Chris Muller-3
+1

On Tue, Jun 30, 2015 at 12:46 PM, Eliot Miranda <[hidden email]> wrote:

> Hi Levente,  Hi Chris,
>
> On Tue, Apr 28, 2015 at 3:41 PM, Levente Uzonyi <[hidden email]> wrote:
>>
>> There's no need to store preferences in a data structure at all. We
>> already have "pragma" preferences (since 4.1), which store the preference
>> values independently. Since the 4.1 release it's a "permanent" goal to
>> rewrite all preferences to "pragma" preferences.
>> We should just make it happen.
>
>
> This seems like a lot of work, and is work that can be done over time.  But
> right now we're suffering lock ups due to the Mutex in Preferences.  For
> example, the Notifier/Debugger accesses the scrollBarsOnRight preference and
> I've often seen lock ups caused by this.  So I propose that I fix the access
> to be as I described it.  There be no access lock except for adding/updating
> preferences.  So reading is done without synchronisation, and setting and/or
> adding is done by copying and assigning.  I also propose to compile
> preferences without creating a block, so
>
> autoIndent
> ^ self
> valueOfFlag: #autoIndent
> ifAbsent: true
>
> instead of
>
> autoIndent
> ^ self
> valueOfFlag: #autoIndent
> ifAbsent: [true]
>
> which is well-supported by both the Interpreter and the Cog VMs, given
> Object>>value ^self.  This to save space and time.
>
>> Levente
>>
>> P.S.: Reverting that method will solve the concurrency issue.
>>
>>
>> On Tue, 28 Apr 2015, Eliot Miranda wrote:
>>
>>>
>>>
>>> On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]>
>>> wrote:
>>>       Wait, the newer one has a non-local return in it, but
>>>       Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
>>>       the problem..?
>>>
>>>
>>> If one hits ctrl-period when the system is in the critical section then
>>> the debugger can't open because it interrupts the critical section,
>>> preventing the ensure block from running, attempts to access e.g.
>>> scroll bar preferences when it tries to open, and the system deadlocks.
>>> So preferences either need to be *not* protected by a critical section, or
>>> the Debugger needs not to access preferences.
>>>
>>> IMO, we should try and write preferences so that they don't require a
>>> lock.  Writing them as a lock-free data structure would be a really good
>>> idea. First that critical section is slow and clunky.  Second, I
>>> presume it is there only for the rare case of a write to preferences, not
>>> to protect reads.
>>>
>>> IMO, a simple implementation which copied and replaced the entire
>>> preferences dictionary on write would be sufficient.  Sure there's a danger
>>> that some client would get a stale value if it read concurrently
>>> while there was a write, but then so what?  A preference is a preference,
>>> not a hard-and-fast value, and code should work accessing a preference no
>>> matter its value, so momentarily getting a stale value
>>> shouldn't matter.  So the implementation could be as simple as
>>>
>>> addPreference: aName categories: categoryList default: aValue
>>> balloonHelp: helpString projectLocal: localBoolean changeInformee:
>>> informeeSymbol changeSelector: aChangeSelector type: aType
>>> "Add or replace a preference as indicated.  Reuses the preexisting
>>> Preference object for this symbol, if there is one, so that UI artifacts
>>> that interact with it will remain valid."
>>>
>>> | aPreference aPrefSymbol |
>>> aPrefSymbol := aName asSymbol.
>>> aPreference := DictionaryOfPreferences
>>> at: aPrefSymbol
>>> ifAbsent:
>>> [| newPreference |
>>> newPreference := aPreference
>>> name:aPrefSymbol
>>> defaultValue:aValue
>>> helpString:helpString
>>> localToProject:localBoolean
>>> categoryList:categoryList
>>> changeInformee:informeeSymbol
>>> changeSelector:aChangeSelector
>>> type: aType.
>>> AccessLock critical:
>>> [| newDict |
>>> newDict := DictionaryOfPreferences copy.
>>> newDict at: aPrefSymbol put: newPreference].
>>> self  compileAccessMethodForPreference:aPreference.
>>> newPreference]
>>>
>>>
>>>       On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]>
>>> wrote:
>>>       >> The above change restores the old behavior of locking up the
>>> image, so it
>>>       >> should be reverted. An additional comment explaininng why aBlock
>>> must not be
>>>       >> evaluated inside the argument of
>>> #accessDictionaryOfPreferencesIn: would be
>>>       >> helpful.
>>>       >
>>>       > Ahh, because aBlock might have a non-local return in it, leaving
>>> the
>>>       > Mutex unsignaled (and critical unenterable), is that right?
>>>       >
>>>       > Took me a minute to see that problem.
>>>       >
>>>       > Okay, I'll revert that method if no one else does by my next
>>> commit..
>>>       >
>>>       >> It would be even better to finally get rid of
>>> DictionaryOfPreferences.
>>>       >>
>>>       >>
>>>       >> Levente
>>>       >>
>>>
>>>
>>>
>>>
>>> --
>>> best,Eliot
>>>
>>
>>
>>
>
>
>
> --
> best,
> Eliot
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Eliot Miranda-2
In reply to this post by Eliot Miranda-2
Hi All, but especially Chris,

   I just committed System-eem.745 to the inbox.  Please review.

As I say in the commit comment, this is step 1.  If the code looks OK, the next step is a version which moves the preferences dictionary into a class inst var, so that ServicePreferences sits happily below Preferences.  But for that I'll need advice on how to write the sequence of loads.  I *think* it's one configuration map and one package load.  The commit/configuration adds the class inst var and copies the DictionaryOfPreferences into it.  A subsequent commit replaces all methods that acess DictionaryOfPreferences and ServiceDictionaryOfPreferences with accesses to the class inst var


Rewrite Preferences to eliminate the AccessProtect.
Use a copy, update copy, assign scheme to update
the preferences dictionary atomically.

Change Preferences access method compilation to
use Object>>#value to eliminate a block creation.

Change Preference initialization to eliminate the
isKindOf: Symbol.

This is step 1.  Given SystemPreferences it is clear
that the preferences dictionary should be stored in
a class inst var, so that SystemPreferences and
Preferences can share methods but access different
dictionaries.  The dictionaryOfProferences[:] accessors
are dubious as they break encapsulatiopn.  For example,
the reportPreferences: method, which is the only external
access, could insateaqd be moved into Preferences class.

On Tue, Jun 30, 2015 at 10:46 AM, Eliot Miranda <[hidden email]> wrote:
Hi Levente,  Hi Chris,

On Tue, Apr 28, 2015 at 3:41 PM, Levente Uzonyi <[hidden email]> wrote:
There's no need to store preferences in a data structure at all. We already have "pragma" preferences (since 4.1), which store the preference values independently. Since the 4.1 release it's a "permanent" goal to rewrite all preferences to "pragma" preferences.
We should just make it happen.

This seems like a lot of work, and is work that can be done over time.  But right now we're suffering lock ups due to the Mutex in Preferences.  For example, the Notifier/Debugger accesses the scrollBarsOnRight preference and I've often seen lock ups caused by this.  So I propose that I fix the access to be as I described it.  There be no access lock except for adding/updating preferences.  So reading is done without synchronisation, and setting and/or adding is done by copying and assigning.  I also propose to compile preferences without creating a block, so

autoIndent
^ self
valueOfFlag: #autoIndent
ifAbsent: true

instead of

autoIndent
^ self
valueOfFlag: #autoIndent
ifAbsent: [true]

which is well-supported by both the Interpreter and the Cog VMs, given Object>>value ^self.  This to save space and time.

Levente

P.S.: Reverting that method will solve the concurrency issue.


On Tue, 28 Apr 2015, Eliot Miranda wrote:



On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
      Wait, the newer one has a non-local return in it, but
      Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
      the problem..?


If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g.
scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.

IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I
presume it is there only for the rare case of a write to preferences, not to protect reads.

IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently
while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value
shouldn't matter.  So the implementation could be as simple as

addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
"Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."

| aPreference aPrefSymbol |
aPrefSymbol := aName asSymbol.
aPreference := DictionaryOfPreferences
at: aPrefSymbol
ifAbsent:
[| newPreference |
newPreference := aPreference 
name:aPrefSymbol
defaultValue:aValue
helpString:helpString
localToProject:localBoolean
categoryList:categoryList
changeInformee:informeeSymbol
changeSelector:aChangeSelector
type: aType.
AccessLock critical:
[| newDict |
newDict := DictionaryOfPreferences copy.
newDict at: aPrefSymbol put: newPreference].
self  compileAccessMethodForPreference:aPreference.
newPreference]


      On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
      >> The above change restores the old behavior of locking up the image, so it
      >> should be reverted. An additional comment explaininng why aBlock must not be
      >> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
      >> helpful.
      >
      > Ahh, because aBlock might have a non-local return in it, leaving the
      > Mutex unsignaled (and critical unenterable), is that right?
      >
      > Took me a minute to see that problem.
      >
      > Okay, I'll revert that method if no one else does by my next commit..
      >
      >> It would be even better to finally get rid of DictionaryOfPreferences.
      >>
      >>
      >> Levente
      >>




--
best,Eliot







--
best,
Eliot



--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Levente Uzonyi-2
Hi Eliot,

I reviewed the code and made a few changes, which you can find in the
Inbox as System-ul.748. Feel free to pick the ones you like.
The change of Preferences class >> #atomicUpdatePreferences: might seem
unnecessary, because it's so unlikely to have multiple processes
changing the preferences concurrently.

Levente

P.S.: Please note that I haven't tested the code.

On Tue, 30 Jun 2015, Eliot Miranda wrote:

> Hi All, but especially Chris,
>    I just committed System-eem.745 to the inbox.  Please review.
>
> As I say in the commit comment, this is step 1.  If the code looks OK, the next step is a version which moves the preferences dictionary into a class inst var, so that ServicePreferences sits happily below Preferences.  But for that I'll need advice on how to write the
> sequence of loads.  I *think* it's one configuration map and one package load.  The commit/configuration adds the class inst var and copies the DictionaryOfPreferences into it.  A subsequent commit replaces all methods that acess DictionaryOfPreferences and
> ServiceDictionaryOfPreferences with accesses to the class inst var
>
>
> Rewrite Preferences to eliminate the AccessProtect.
> Use a copy, update copy, assign scheme to update
> the preferences dictionary atomically.
>
> Change Preferences access method compilation to
> use Object>>#value to eliminate a block creation.
>
> Change Preference initialization to eliminate the
> isKindOf: Symbol.
>
> This is step 1.  Given SystemPreferences it is clear
> that the preferences dictionary should be stored in
> a class inst var, so that SystemPreferences and
> Preferences can share methods but access different
> dictionaries.  The dictionaryOfProferences[:] accessors
> are dubious as they break encapsulatiopn.  For example,
> the reportPreferences: method, which is the only external
> access, could insateaqd be moved into Preferences class.
>
> On Tue, Jun 30, 2015 at 10:46 AM, Eliot Miranda <[hidden email]> wrote:
>       Hi Levente,  Hi Chris,
>
>       On Tue, Apr 28, 2015 at 3:41 PM, Levente Uzonyi <[hidden email]> wrote:
>             There's no need to store preferences in a data structure at all. We already have "pragma" preferences (since 4.1), which store the preference values independently. Since the 4.1 release it's a "permanent" goal to rewrite all preferences to
>             "pragma" preferences.
>             We should just make it happen.
>
>
> This seems like a lot of work, and is work that can be done over time.  But right now we're suffering lock ups due to the Mutex in Preferences.  For example, the Notifier/Debugger accesses the scrollBarsOnRight preference and I've often seen lock ups caused by
> this.  So I propose that I fix the access to be as I described it.  There be no access lock except for adding/updating preferences.  So reading is done without synchronisation, and setting and/or adding is done by copying and assigning.  I also propose to compile
> preferences without creating a block, so
>
> autoIndent
> ^ self
> valueOfFlag: #autoIndent
> ifAbsent: true
>
> instead of
>
> autoIndent
> ^ self
> valueOfFlag: #autoIndent
> ifAbsent: [true]
>
> which is well-supported by both the Interpreter and the Cog VMs, given Object>>value ^self.  This to save space and time.
>
>       Levente
>
>       P.S.: Reverting that method will solve the concurrency issue.
>
>       On Tue, 28 Apr 2015, Eliot Miranda wrote:
>
>
>
>             On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
>                   Wait, the newer one has a non-local return in it, but
>                   Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
>                   the problem..?
>
>
>             If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g.
>             scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.
>
>             IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I
>             presume it is there only for the rare case of a write to preferences, not to protect reads.
>
>             IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently
>             while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value
>             shouldn't matter.  So the implementation could be as simple as
>
>             addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
>             "Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."
>
>             | aPreference aPrefSymbol |
>             aPrefSymbol := aName asSymbol.
>             aPreference := DictionaryOfPreferences
>             at: aPrefSymbol
>             ifAbsent:
>             [| newPreference |
>             newPreference := aPreference 
>             name:aPrefSymbol
>             defaultValue:aValue
>             helpString:helpString
>             localToProject:localBoolean
>             categoryList:categoryList
>             changeInformee:informeeSymbol
>             changeSelector:aChangeSelector
>             type: aType.
>             AccessLock critical:
>             [| newDict |
>             newDict := DictionaryOfPreferences copy.
>             newDict at: aPrefSymbol put: newPreference].
>             self  compileAccessMethodForPreference:aPreference.
>             newPreference]
>
>
>                   On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
>                   >> The above change restores the old behavior of locking up the image, so it
>                   >> should be reverted. An additional comment explaininng why aBlock must not be
>                   >> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
>                   >> helpful.
>                   >
>                   > Ahh, because aBlock might have a non-local return in it, leaving the
>                   > Mutex unsignaled (and critical unenterable), is that right?
>                   >
>                   > Took me a minute to see that problem.
>                   >
>                   > Okay, I'll revert that method if no one else does by my next commit..
>                   >
>                   >> It would be even better to finally get rid of DictionaryOfPreferences.
>                   >>
>                   >>
>                   >> Levente
>                   >>
>
>
>
>
>             --
>             best,Eliot
>
>
>
>
>
>
>
> --
> best,Eliot
>
>
>
>
> --
> best,Eliot
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Eliot Miranda-2
Hi Levente,

   yes I like the repeat in atomicUpdatePreferences:.  That's safe.  I don't care much for the method temp in refEvent: cuz I think the message keyword types anEvent item adequately.  Not sure about storePreferencesIn: not taking a copy of preferencesDictionary.  Surely it's safer to take the copy.  So let me take the change to atomicUpdatePreferences: and get this show on the road :-).  Thanks for your review!

On Wed, Jul 1, 2015 at 4:30 AM, Levente Uzonyi <[hidden email]> wrote:
Hi Eliot,

I reviewed the code and made a few changes, which you can find in the Inbox as System-ul.748. Feel free to pick the ones you like.
The change of Preferences class >> #atomicUpdatePreferences: might seem unnecessary, because it's so unlikely to have multiple processes changing the preferences concurrently.

Levente

P.S.: Please note that I haven't tested the code.


On Tue, 30 Jun 2015, Eliot Miranda wrote:

Hi All, but especially Chris,
   I just committed System-eem.745 to the inbox.  Please review.

As I say in the commit comment, this is step 1.  If the code looks OK, the next step is a version which moves the preferences dictionary into a class inst var, so that ServicePreferences sits happily below Preferences.  But for that I'll need advice on how to write the
sequence of loads.  I *think* it's one configuration map and one package load.  The commit/configuration adds the class inst var and copies the DictionaryOfPreferences into it.  A subsequent commit replaces all methods that acess DictionaryOfPreferences and
ServiceDictionaryOfPreferences with accesses to the class inst var


Rewrite Preferences to eliminate the AccessProtect.
Use a copy, update copy, assign scheme to update
the preferences dictionary atomically.

Change Preferences access method compilation to
use Object>>#value to eliminate a block creation.

Change Preference initialization to eliminate the
isKindOf: Symbol.

This is step 1.  Given SystemPreferences it is clear
that the preferences dictionary should be stored in
a class inst var, so that SystemPreferences and
Preferences can share methods but access different
dictionaries.  The dictionaryOfProferences[:] accessors
are dubious as they break encapsulatiopn.  For example,
the reportPreferences: method, which is the only external
access, could insateaqd be moved into Preferences class.

On Tue, Jun 30, 2015 at 10:46 AM, Eliot Miranda <[hidden email]> wrote:
      Hi Levente,  Hi Chris,

      On Tue, Apr 28, 2015 at 3:41 PM, Levente Uzonyi <[hidden email]> wrote:
            There's no need to store preferences in a data structure at all. We already have "pragma" preferences (since 4.1), which store the preference values independently. Since the 4.1 release it's a "permanent" goal to rewrite all preferences to
            "pragma" preferences.
            We should just make it happen.


This seems like a lot of work, and is work that can be done over time.  But right now we're suffering lock ups due to the Mutex in Preferences.  For example, the Notifier/Debugger accesses the scrollBarsOnRight preference and I've often seen lock ups caused by
this.  So I propose that I fix the access to be as I described it.  There be no access lock except for adding/updating preferences.  So reading is done without synchronisation, and setting and/or adding is done by copying and assigning.  I also propose to compile
preferences without creating a block, so

autoIndent
^ self
valueOfFlag: #autoIndent
ifAbsent: true

instead of

autoIndent
^ self
valueOfFlag: #autoIndent
ifAbsent: [true]

which is well-supported by both the Interpreter and the Cog VMs, given Object>>value ^self.  This to save space and time.

      Levente

      P.S.: Reverting that method will solve the concurrency issue.

      On Tue, 28 Apr 2015, Eliot Miranda wrote:



            On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
                  Wait, the newer one has a non-local return in it, but
                  Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
                  the problem..?


            If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g.
            scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.

            IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I
            presume it is there only for the rare case of a write to preferences, not to protect reads.

            IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently
            while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value
            shouldn't matter.  So the implementation could be as simple as

            addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
            "Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."

            | aPreference aPrefSymbol |
            aPrefSymbol := aName asSymbol.
            aPreference := DictionaryOfPreferences
            at: aPrefSymbol
            ifAbsent:
            [| newPreference |
            newPreference := aPreference 
            name:aPrefSymbol
            defaultValue:aValue
            helpString:helpString
            localToProject:localBoolean
            categoryList:categoryList
            changeInformee:informeeSymbol
            changeSelector:aChangeSelector
            type: aType.
            AccessLock critical:
            [| newDict |
            newDict := DictionaryOfPreferences copy.
            newDict at: aPrefSymbol put: newPreference].
            self  compileAccessMethodForPreference:aPreference.
            newPreference]


                  On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
                  >> The above change restores the old behavior of locking up the image, so it
                  >> should be reverted. An additional comment explaininng why aBlock must not be
                  >> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
                  >> helpful.
                  >
                  > Ahh, because aBlock might have a non-local return in it, leaving the
                  > Mutex unsignaled (and critical unenterable), is that right?
                  >
                  > Took me a minute to see that problem.
                  >
                  > Okay, I'll revert that method if no one else does by my next commit..
                  >
                  >> It would be even better to finally get rid of DictionaryOfPreferences.
                  >>
                  >>
                  >> Levente
                  >>




            --
            best,Eliot







--
best,Eliot




--
best,Eliot







--
best,
Eliot


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Chris Muller-4
I reviewed too, and already committed you and Levente's changes.

>    yes I like the repeat in atomicUpdatePreferences:.  That's safe.  I don't
> care much for the method temp in refEvent: cuz I think the message keyword
> types anEvent item adequately.  Not sure about storePreferencesIn: not
> taking a copy of preferencesDictionary.  Surely it's safer to take the copy.

I had similar doubts initially, until I read Levente's comment:  He
reminds us that the dictionary is NEVER updated.  Only read and
replaced whole.  A copy there is even misleading to the reader.

> So let me take the change to atomicUpdatePreferences: and get this show on
> the road :-).  Thanks for your review!

Already done.  Thanks Eliot and Levente!

Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: System-cmm.725.mcz

Levente Uzonyi-2
In reply to this post by Eliot Miranda-2
Hi Eliot,

My change of #prefEvent: is not about the temporary variable. It's about
removing the loop which got duplicated. The original method looked like

  ...
  method := anEvent item.
  method pragmas do:[:pragma| | aPreference aPrefSymbol |
  ((pragma keyword == #preference:category:description:type:)
  or: [pragma keyword == #preference:categoryList:description:type:]) ifTrue:[
  aPrefSymbol := (aClass name,'>>', method selector) asSymbol.
  ...

Your version with #respondToPreferencePragmasInMethod:class: inlined would
look like

  ...
  method := anEvent item.
* method pragmas do:
  [:pragma|
* method pragmas do:
  [:pragma| | preference |
  ((pragma keyword beginsWith: #preference:)
  and: [self respondsTo: pragma keyword]) ifTrue:
  [preference := self
  perform: pragma keyword
  withArguments: pragma arguments.
  ...

One of the "method pragmas do:" loops (marked with *) is superfluous.
Since #respondToPreferencePragmasInMethod:class: contains the loop, and is
also sent by other methods, I decided to remove the loop from #prefEvent:.

The #copy in #storePreferencesIn: was added in Squeak 4.1, or 4.2, because
the dictionary could have been read and written concurrently. But this is
not the case anymore.

Levente

On Wed, 1 Jul 2015, Eliot Miranda wrote:

> Hi Levente,
>    yes I like the repeat in atomicUpdatePreferences:.  That's safe.  I don't care much for the method temp in refEvent: cuz I think the message keyword types anEvent item adequately.  Not sure about storePreferencesIn: not taking a copy of preferencesDictionary. 
> Surely it's safer to take the copy.  So let me take the change to atomicUpdatePreferences: and get this show on the road :-).  Thanks for your review!
>
> On Wed, Jul 1, 2015 at 4:30 AM, Levente Uzonyi <[hidden email]> wrote:
>       Hi Eliot,
>
>       I reviewed the code and made a few changes, which you can find in the Inbox as System-ul.748. Feel free to pick the ones you like.
>       The change of Preferences class >> #atomicUpdatePreferences: might seem unnecessary, because it's so unlikely to have multiple processes changing the preferences concurrently.
>
>       Levente
>
>       P.S.: Please note that I haven't tested the code.
>
>       On Tue, 30 Jun 2015, Eliot Miranda wrote:
>
>             Hi All, but especially Chris,
>                I just committed System-eem.745 to the inbox.  Please review.
>
>             As I say in the commit comment, this is step 1.  If the code looks OK, the next step is a version which moves the preferences dictionary into a class inst var, so that ServicePreferences sits happily below Preferences.  But for that I'll need
>             advice on how to write the
>             sequence of loads.  I *think* it's one configuration map and one package load.  The commit/configuration adds the class inst var and copies the DictionaryOfPreferences into it.  A subsequent commit replaces all methods that acess
>             DictionaryOfPreferences and
>             ServiceDictionaryOfPreferences with accesses to the class inst var
>
>
>             Rewrite Preferences to eliminate the AccessProtect.
>             Use a copy, update copy, assign scheme to update
>             the preferences dictionary atomically.
>
>             Change Preferences access method compilation to
>             use Object>>#value to eliminate a block creation.
>
>             Change Preference initialization to eliminate the
>             isKindOf: Symbol.
>
>             This is step 1.  Given SystemPreferences it is clear
>             that the preferences dictionary should be stored in
>             a class inst var, so that SystemPreferences and
>             Preferences can share methods but access different
>             dictionaries.  The dictionaryOfProferences[:] accessors
>             are dubious as they break encapsulatiopn.  For example,
>             the reportPreferences: method, which is the only external
>             access, could insateaqd be moved into Preferences class.
>
>             On Tue, Jun 30, 2015 at 10:46 AM, Eliot Miranda <[hidden email]> wrote:
>                   Hi Levente,  Hi Chris,
>
>                   On Tue, Apr 28, 2015 at 3:41 PM, Levente Uzonyi <[hidden email]> wrote:
>                         There's no need to store preferences in a data structure at all. We already have "pragma" preferences (since 4.1), which store the preference values independently. Since the 4.1 release it's a "permanent" goal to rewrite all
>             preferences to
>                         "pragma" preferences.
>                         We should just make it happen.
>
>
>             This seems like a lot of work, and is work that can be done over time.  But right now we're suffering lock ups due to the Mutex in Preferences.  For example, the Notifier/Debugger accesses the scrollBarsOnRight preference and I've often seen
>             lock ups caused by
>             this.  So I propose that I fix the access to be as I described it.  There be no access lock except for adding/updating preferences.  So reading is done without synchronisation, and setting and/or adding is done by copying and assigning.  I also
>             propose to compile
>             preferences without creating a block, so
>
>             autoIndent
>             ^ self
>             valueOfFlag: #autoIndent
>             ifAbsent: true
>
>             instead of
>
>             autoIndent
>             ^ self
>             valueOfFlag: #autoIndent
>             ifAbsent: [true]
>
>             which is well-supported by both the Interpreter and the Cog VMs, given Object>>value ^self.  This to save space and time.
>
>                   Levente
>
>                   P.S.: Reverting that method will solve the concurrency issue.
>
>                   On Tue, 28 Apr 2015, Eliot Miranda wrote:
>
>
>
>                         On Tue, Apr 28, 2015 at 12:47 PM, Chris Muller <[hidden email]> wrote:
>                               Wait, the newer one has a non-local return in it, but
>                               Mutex>>#critical: has an ensure: in it anyway, so maybe I don't see
>                               the problem..?
>
>
>                         If one hits ctrl-period when the system is in the critical section then the debugger can't open because it interrupts the critical section, preventing the ensure block from running, attempts to access e.g.
>                         scroll bar preferences when it tries to open, and the system deadlocks.  So preferences either need to be *not* protected by a critical section, or the Debugger needs not to access preferences.
>
>                         IMO, we should try and write preferences so that they don't require a lock.  Writing them as a lock-free data structure would be a really good idea. First that critical section is slow and clunky.  Second, I
>                         presume it is there only for the rare case of a write to preferences, not to protect reads.
>
>                         IMO, a simple implementation which copied and replaced the entire preferences dictionary on write would be sufficient.  Sure there's a danger that some client would get a stale value if it read concurrently
>                         while there was a write, but then so what?  A preference is a preference, not a hard-and-fast value, and code should work accessing a preference no matter its value, so momentarily getting a stale value
>                         shouldn't matter.  So the implementation could be as simple as
>
>                         addPreference: aName categories: categoryList default: aValue balloonHelp: helpString projectLocal: localBoolean changeInformee: informeeSymbol changeSelector: aChangeSelector type: aType
>                         "Add or replace a preference as indicated.  Reuses the preexisting Preference object for this symbol, if there is one, so that UI artifacts that interact with it will remain valid."
>
>                         | aPreference aPrefSymbol |
>                         aPrefSymbol := aName asSymbol.
>                         aPreference := DictionaryOfPreferences
>                         at: aPrefSymbol
>                         ifAbsent:
>                         [| newPreference |
>                         newPreference := aPreference 
>                         name:aPrefSymbol
>                         defaultValue:aValue
>                         helpString:helpString
>                         localToProject:localBoolean
>                         categoryList:categoryList
>                         changeInformee:informeeSymbol
>                         changeSelector:aChangeSelector
>                         type: aType.
>                         AccessLock critical:
>                         [| newDict |
>                         newDict := DictionaryOfPreferences copy.
>                         newDict at: aPrefSymbol put: newPreference].
>                         self  compileAccessMethodForPreference:aPreference.
>                         newPreference]
>
>
>                               On Tue, Apr 28, 2015 at 2:43 PM, Chris Muller <[hidden email]> wrote:
>                               >> The above change restores the old behavior of locking up the image, so it
>                               >> should be reverted. An additional comment explaininng why aBlock must not be
>                               >> evaluated inside the argument of #accessDictionaryOfPreferencesIn: would be
>                               >> helpful.
>                               >
>                               > Ahh, because aBlock might have a non-local return in it, leaving the
>                               > Mutex unsignaled (and critical unenterable), is that right?
>                               >
>                               > Took me a minute to see that problem.
>                               >
>                               > Okay, I'll revert that method if no one else does by my next commit..
>                               >
>                               >> It would be even better to finally get rid of DictionaryOfPreferences.
>                               >>
>                               >>
>                               >> Levente
>                               >>
>
>
>
>
>                         --
>                         best,Eliot
>
>
>
>
>
>
>
>             --
>             best,Eliot
>
>
>
>
>             --
>             best,Eliot
>
>
>
>
>
>
>
> --
> best,Eliot
>
>