Ok, I think the fix is below, someone can field test it?
I did write an Sunit
The idea is that we want to change (x) to /X which means it's cmd key x
But also handle the case of ( ) and (() which are aren't allowed by
the api we are using.
Also we change ';' '^' '!' '<' '/' to ' ' and if '(' doesn't follow
the proper patter of (*) then it becomes a space too.
testCharacterChanging
| testString item shouldBe resultingString where |
#(';' '^' '!' '<' '/' '(' )
do: [:c | #('*' '* ' '* ' '**' '** ' '** '
')' '*)' '* )' '* )' '**)' '** )' '** )'
')' '*)' '*X)' '*XX)' '**)' '**X)' '**XX)'
'))' '*))' '*X))' '*XX))' '**))' '**X))' '**XX))'
'(' '*(' '*X(' '*XX(' '**)' '**X(' '**XX('
'((' '*((' '*X((' '*XX((' '**((' '**X((' '**XX(('
)
do: [:template |
testString := template copyReplaceAll:
'*' with: c.
testString
permutationsDo: [:mixedUp |
item := mixedUp copy.
shouldBe := self
calculateShouldBeFrom: item using: c.
resultingString := self
modifySqueakMenu: item copy.
self should: [shouldBe
= resultingString].
(where := resultingString
indexOf: $/) > 0
ifTrue: [self
should: [(mixedUp at: where) = $(].
self should: [(mixedUp at: where+2) = $)].
self should: [(mixedUp at: where+1) asUppercase =
(resultingString at: where+1)]]]]]
where calculateShouldBeFrom: using: runs off and guess at the proper
string with a different algorithm,
an exercise for the user...
Fix is below.
modifySqueakMenu: aString
| results fixIndex middleCharacter |
results := aString.
results replaceAll: $; with: Character space.
results replaceAll: $^ with: Character space.
results replaceAll: $! with: Character space.
results replaceAll: $< with: Character space.
results replaceAll: $/ with: Character space.
fixIndex := results indexOf: $(.
[fixIndex > 0]
whileTrue: [
[(results at: fixIndex + 2) = $)
ifTrue: [middleCharacter := results at:
fixIndex + 1.
(middleCharacter = Character
space or: [middleCharacter = $(])
ifTrue: [results at:
fixIndex put: Character space]
ifFalse: [results at:
fixIndex put: $/.].
results at: fixIndex + 1 put:
middleCharacter asUppercase.
results at: fixIndex + 2 put:
Character space]
ifFalse: [results at: fixIndex put: Character
space]]
ifError: [results at: fixIndex put:
Character space].
fixIndex := results indexOf: $(].
^ results
On 19-Nov-08, at 1:45 AM, John M McIntosh wrote:
Ya it's my bug, however it's way too late tonight for me to tackle it.
The problem is that if the menu contains (x) and we attempt to
convert that into a macintosh menu the older os-9 menu logic
has specialized meanings for character strings of the form (x) so we
attempt to fix it.
http://developer.apple.com/documentation/mac/Toolbox/Toolbox-144.html
I think in this case the morphic menus use (x) to mean x is a
command key, but that would disable the menu on the macintosh.
So I was fixing up usages of (x)
Obviously not correctly since it fails on strings of the form (x1...)
--
=
=
=
========================================================================
John M. McIntosh <[EMAIL PROTECTED]>
Corporate Smalltalk Consulting Ltd. http://www.smalltalkconsulting.com
=
=
=
========================================================================
_______________________________________________
Pharo-project mailing list
[email protected]
http://lists.gforge.inria.fr/cgi-bin/mailman/listinfo/pharo-project