Reusable browsers was Re: About HyperCard

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

Reusable browsers was Re: About HyperCard

dcorking
Frank Shearar wrote:

> What does "reusable" mean here? If you mean that navigating to
> something doesn't spawn a whole new window, then we _sometimes_ have
> reusable browsers. For instance, in a Browser, selecting a class name
> and pressing <alt>-<shift>-b will, within the same Browser, jump to
> the new class.

Yes - I mean "don't spawn a new window". I wasn't aware of that hotkey.

Other nice features of the message list in Moshi are forward and back
buttons, a browseable history, and a 'reusable' toggle button, to make
it spawn a new message list without learning a hot key. (It is the
forward and back buttons I recognise from Newspeak and Amber.)

Thanks Herbert and Frank for explaining how to uncover the features
for class and message implementor.

Herbert wrote:
> to get this behaviour the Preference "trace messages" needs to be
> enabled. checking... Right now this only works for implementors,

I set the preference and still get a new message list for each
implementor I select (trunk 4.5  #12400) when I click the implementors
button - but the list _is_  reused on cmd-m. A win for the keyboard.
Thanks again.

Have fun! David

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Frank Shearar-3
On 28 February 2013 19:15, David Corking <[hidden email]> wrote:

> Frank Shearar wrote:
>
>> What does "reusable" mean here? If you mean that navigating to
>> something doesn't spawn a whole new window, then we _sometimes_ have
>> reusable browsers. For instance, in a Browser, selecting a class name
>> and pressing <alt>-<shift>-b will, within the same Browser, jump to
>> the new class.
>
> Yes - I mean "don't spawn a new window". I wasn't aware of that hotkey.
>
> Other nice features of the message list in Moshi are forward and back
> buttons, a browseable history, and a 'reusable' toggle button, to make
> it spawn a new message list without learning a hot key. (It is the
> forward and back buttons I recognise from Newspeak and Amber.)

It needs to be a bit more exposed, but there's also a "recently
visited" option in the Browser's leftmost pane. I'd like to extend
that list a bit so that it takes you back to the class you recently
viewed and show you the _method_ you last viewed in that class. Or
maybe just rip out the class thing entirely and store recently viewed
methods instead. Eh, but sometimes you'll have visited the class
comment, or class/metaclass definition...

frank

> Thanks Herbert and Frank for explaining how to uncover the features
> for class and message implementor.
>
> Herbert wrote:
>> to get this behaviour the Preference "trace messages" needs to be
>> enabled. checking... Right now this only works for implementors,
>
> I set the preference and still get a new message list for each
> implementor I select (trunk 4.5  #12400) when I click the implementors
> button - but the list _is_  reused on cmd-m. A win for the keyboard.
> Thanks again.
>
> Have fun! David
>

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Chris Muller-3
In reply to this post by dcorking
I'm the one that wrought the "Reuse Windows", and "traceMessages"
preferences.  They are part of a triad of preferences (the third is
"alternativeBrowseIt") that, when set, support a totally non-modal
approach to browsing and development.  Rather than navigating around 4
or 5 big PackagePane browsers, the idea is to "follow behavior" by
spawning new HierarchyBrowsers straight out of highlighted chunks of
code.  Rather than selecting classes and methods in lists so much,
windows are constantly opened and closed.

Notice when "alternativeBrowseIt" is selected, you can simply
double-click the argument of a method, such as:

  add: anException   "<---- double click to highlight 'anException'"

and press Command+B to browse the Exception class hierarchy.  If there
is already a class browser on Exception which does not have unsaved
edits, it is brought to the top rather than opening yet-another one
("Reuse Windows").  Note Reuse Windows works for most kinds of windows
including Monticello windows.

To "go back" simply position the cursor on the "prior" window
(underneath) or on the desktop and press Command+w to successively
close the top-most windows.  I actually stopped using OCompletion
because this approach was actually more productive for me.

traceMessages is along the same lines, I can hardly even work in
Smalltalk without this.

> Herbert wrote:
>> to get this behaviour the Preference "trace messages" needs to be
>> enabled. checking... Right now this only works for implementors,

It works for both.  You can press Command+S in the message-list for
senders to be outdented above.  For implementors, just highlight the
message in the code at the bottom and press Command+M.  You can even
select it "grossly" and there can even be intervening code in the
middle of a keyword message and it will still work!

Warning:  Once accustomed to the productivity of non-modal
development, it's very hard to go back!  :)




On Thu, Feb 28, 2013 at 1:15 PM, David Corking <[hidden email]> wrote:

> Frank Shearar wrote:
>
>> What does "reusable" mean here? If you mean that navigating to
>> something doesn't spawn a whole new window, then we _sometimes_ have
>> reusable browsers. For instance, in a Browser, selecting a class name
>> and pressing <alt>-<shift>-b will, within the same Browser, jump to
>> the new class.
>
> Yes - I mean "don't spawn a new window". I wasn't aware of that hotkey.
>
> Other nice features of the message list in Moshi are forward and back
> buttons, a browseable history, and a 'reusable' toggle button, to make
> it spawn a new message list without learning a hot key. (It is the
> forward and back buttons I recognise from Newspeak and Amber.)
>
> Thanks Herbert and Frank for explaining how to uncover the features
> for class and message implementor.
>



>
> I set the preference and still get a new message list for each
> implementor I select (trunk 4.5  #12400) when I click the implementors
> button - but the list _is_  reused on cmd-m. A win for the keyboard.
> Thanks again.
>
> Have fun! David
>

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Herbert König
Hey Chris,
> I'm the one that wrought the "Reuse Windows", and "traceMessages"
> preferences.  They are part of a triad of preferences (the third is
> "alternativeBrowseIt") that, when set, support a totally non-modal
> approach to browsing and development.

just forgot that I have to set the two other preferences too, I use
images for a long time. Thanks for the reminder. And for implementing it
in the first place :-))
> traceMessages is along the same lines, I can hardly even work in
> Smalltalk without this.

At least I find it much more cumbersome without.

Cheers,

Herbert

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Frank Shearar-3
In reply to this post by Chris Muller-3
On 28 February 2013 19:57, Chris Muller <[hidden email]> wrote:

> I'm the one that wrought the "Reuse Windows", and "traceMessages"
> preferences.  They are part of a triad of preferences (the third is
> "alternativeBrowseIt") that, when set, support a totally non-modal
> approach to browsing and development.  Rather than navigating around 4
> or 5 big PackagePane browsers, the idea is to "follow behavior" by
> spawning new HierarchyBrowsers straight out of highlighted chunks of
> code.  Rather than selecting classes and methods in lists so much,
> windows are constantly opened and closed.
>
> Notice when "alternativeBrowseIt" is selected, you can simply
> double-click the argument of a method, such as:
>
>   add: anException   "<---- double click to highlight 'anException'"
>
> and press Command+B to browse the Exception class hierarchy.  If there
> is already a class browser on Exception which does not have unsaved
> edits, it is brought to the top rather than opening yet-another one
> ("Reuse Windows").  Note Reuse Windows works for most kinds of windows
> including Monticello windows.
>
> To "go back" simply position the cursor on the "prior" window
> (underneath) or on the desktop and press Command+w to successively
> close the top-most windows.  I actually stopped using OCompletion
> because this approach was actually more productive for me.
>
> traceMessages is along the same lines, I can hardly even work in
> Smalltalk without this.
>
>> Herbert wrote:
>>> to get this behaviour the Preference "trace messages" needs to be
>>> enabled. checking... Right now this only works for implementors,
>
> It works for both.  You can press Command+S in the message-list for
> senders to be outdented above.  For implementors, just highlight the
> message in the code at the bottom and press Command+M.  You can even
> select it "grossly" and there can even be intervening code in the
> middle of a keyword message and it will still work!

That bit? The selecting of a bunch of text around a keyword message?
That impressed me no end. It _rocks_.

frank

> Warning:  Once accustomed to the productivity of non-modal
> development, it's very hard to go back!  :)
>
>
>
>
> On Thu, Feb 28, 2013 at 1:15 PM, David Corking <[hidden email]> wrote:
>> Frank Shearar wrote:
>>
>>> What does "reusable" mean here? If you mean that navigating to
>>> something doesn't spawn a whole new window, then we _sometimes_ have
>>> reusable browsers. For instance, in a Browser, selecting a class name
>>> and pressing <alt>-<shift>-b will, within the same Browser, jump to
>>> the new class.
>>
>> Yes - I mean "don't spawn a new window". I wasn't aware of that hotkey.
>>
>> Other nice features of the message list in Moshi are forward and back
>> buttons, a browseable history, and a 'reusable' toggle button, to make
>> it spawn a new message list without learning a hot key. (It is the
>> forward and back buttons I recognise from Newspeak and Amber.)
>>
>> Thanks Herbert and Frank for explaining how to uncover the features
>> for class and message implementor.
>>
>
>
>
>>
>> I set the preference and still get a new message list for each
>> implementor I select (trunk 4.5  #12400) when I click the implementors
>> button - but the list _is_  reused on cmd-m. A win for the keyboard.
>> Thanks again.
>>
>> Have fun! David
>>
>

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Chris Muller-3
>> It works for both.  You can press Command+S in the message-list for
>> senders to be outdented above.  For implementors, just highlight the
>> message in the code at the bottom and press Command+M.  You can even
>> select it "grossly" and there can even be intervening code in the
>> middle of a keyword message and it will still work!
>
> That bit? The selecting of a bunch of text around a keyword message?
> That impressed me no end. It _rocks_.

Oh I know, and I think Dan Ingalls is the one who originally
implemented it over a decade ago!

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Bert Freudenberg

On 2013-03-01, at 03:33, Chris Muller <[hidden email]> wrote:

>>> It works for both.  You can press Command+S in the message-list for
>>> senders to be outdented above.  For implementors, just highlight the
>>> message in the code at the bottom and press Command+M.  You can even
>>> select it "grossly" and there can even be intervening code in the
>>> middle of a keyword message and it will still work!
>>
>> That bit? The selecting of a bunch of text around a keyword message?
>> That impressed me no end. It _rocks_.
>
> Oh I know, and I think Dan Ingalls is the one who originally
> implemented it over a decade ago!

It's great indeed. Would be even more awesome if someone could make it ignore block arguments ...

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Chris Muller-3
>>> That bit? The selecting of a bunch of text around a keyword message?
>>> That impressed me no end. It _rocks_.
>>
>> Oh I know, and I think Dan Ingalls is the one who originally
>> implemented it over a decade ago!
>
> It's great indeed. Would be even more awesome if someone could make it ignore block arguments ...

The selection spanning block args is not the problem, its when it
spans a keyword selector symbol.

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Bert Freudenberg

On 2013-03-01, at 21:18, Chris Muller <[hidden email]> wrote:

>>>> That bit? The selecting of a bunch of text around a keyword message?
>>>> That impressed me no end. It _rocks_.
>>>
>>> Oh I know, and I think Dan Ingalls is the one who originally
>>> implemented it over a decade ago!
>>
>> It's great indeed. Would be even more awesome if someone could make it ignore block arguments ...
>
> The selection spanning block args is not the problem, its when it
> spans a keyword selector symbol.

Try this:

        self do: [:i | ] separatedBy: []

If you remove the ":i" it works.

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Bob Arning-2
You could just add another tweak:

findSelector
    "Dan's code for hunting down selectors with keyword parts; while this doesn't give a true parse, in most cases it does what we want, in where it doesn't, we're none the worse for it."
    | sel possibleParens |
    sel := self withBlanksTrimmed.
    (sel includes: $:) ifTrue:
        [sel := sel copyReplaceAll: ':' with: ': '.    "for the style (aa max:bb) with no space"
        sel := sel copyReplaceAll: '[:' with: '[ :'.    "for the style ([:a) with no space"    "<<<<<<<======="
        possibleParens := sel findTokens: Character separators.
        sel := self class streamContents:
            [:s | | level |
             level := 0.
            possibleParens do:
                [:token | | n |
                (level = 0 and: [token endsWith: ':'])
                    ifTrue: [s nextPutAll: token]
                    ifFalse: [(n := token occurrencesOf: $( ) > 0 ifTrue: [level := level + n].
                            (n := token occurrencesOf: $[ ) > 0 ifTrue: [level := level + n].
                            (n := token occurrencesOf: $] ) > 0 ifTrue: [level := level - n].
                            (n := token occurrencesOf: $) ) > 0 ifTrue: [level := level - n]]]]].

    sel isEmpty ifTrue: [^ nil].
    sel isOctetString ifTrue: [sel := sel asOctetString].
    Symbol hasInterned: sel ifTrue:
        [:aSymbol | ^ aSymbol].
    ^ nil

On 3/1/13 3:31 PM, Bert Freudenberg wrote:
On 2013-03-01, at 21:18, Chris Muller [hidden email] wrote:

That bit? The selecting of a bunch of text around a keyword message?
That impressed me no end. It _rocks_.
Oh I know, and I think Dan Ingalls is the one who originally
implemented it over a decade ago!
It's great indeed. Would be even more awesome if someone could make it ignore block arguments ...
The selection spanning block args is not the problem, its when it
spans a keyword selector symbol.
Try this:

	self do: [:i | ] separatedBy: []

If you remove the ":i" it works.

- Bert -







Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Chris Muller-3
In reply to this post by Bert Freudenberg
> Try this:
>
>         self do: [:i | ] separatedBy: []

Ha, ok, well, score +1 again for formatting code with more spacing in
it (total score:  3-1).  ;-)  I never noticed "block args" having the
problem since I always use more spacing (and, I guess, the code in the
system I've ever traced).

So the real issue appears to be related to when a colon follows a
non-whitespace character, as it does in your example and in
keyword-selector symbol case:

      self perform: #add: with: anObject

I just saw Bobs msg did half the work finding the method..  Hmm..

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

J. Vuletich (mail lists)
Quoting Chris Muller <[hidden email]>:

>> Try this:
>>
>>         self do: [:i | ] separatedBy: []
>
> Ha, ok, well, score +1 again for formatting code with more spacing in
> it (total score:  3-1).  ;-)  I never noticed "block args" having the
> problem since I always use more spacing (and, I guess, the code in the
> system I've ever traced).
>
> So the real issue appears to be related to when a colon follows a
> non-whitespace character, as it does in your example and in
> keyword-selector symbol case:
>
>       self perform: #add: with: anObject
>
> I just saw Bobs msg did half the work finding the method..  Hmm..

This could be fixed with:

findSelector
        "Dan's code for hunting down selectors with keyword parts; while this  
doesn't give a true parse, in most cases it does what we want, in  
where it doesn't, we're none the worse for it."
        | sel possibleParens level n keywordPos foundFirstKeyword |
        sel _ self withBlanksTrimmed.
        (sel includes: $:) ifTrue: [
                sel _ sel copyReplaceAll: ':' with: ': '. "for the style (aa max:bb)  
with no space"
                sel _ sel copyReplaceAll: '[:' with: '[ :'.    "for the style ([:a)  
with no space"
                possibleParens _ sel findTokens: Character separators.
                sel _ String streamContents: [ :s |
                        level _ 0.
                        foundFirstKeyword _ false.
                        keywordPos _ false.
                        possibleParens do: [ :token |
                                foundFirstKeyword
                                        ifFalse: [ token last = $: ifTrue: [ foundFirstKeyword _  
keywordPos _ true ]]
                                        ifTrue: [ keywordPos _  keywordPos not ].
                                (level = 0 and: [ keywordPos ])
                                        ifTrue: [s nextPutAll: token]
                                        ifFalse: [(n _ token occurrencesOf: $( ) > 0 ifTrue: [level _ level + n].
                                                        (n _ token occurrencesOf: $[ ) > 0 ifTrue: [level _ level + n].
                                                        (n _ token occurrencesOf: $] ) > 0 ifTrue: [level _ level - n].
                                                        (n _ token occurrencesOf: $) ) > 0 ifTrue: [level _ level - n]]]]].

        sel isEmpty ifTrue: [^ nil].
        Symbol hasInterned: sel ifTrue: [ :aSymbol |
                ^ aSymbol].
        ^ nil

I did it in Cuis. For Squeak, add the #isOctetString line.

Cheers,
Juan Vuletich


Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Bert Freudenberg

On 2013-03-02, at 02:57, "Juan Vuletich (mail lists)" <[hidden email]> wrote:

> Quoting Chris Muller <[hidden email]>:
>
>>> Try this:
>>>
>>>        self do: [:i | ] separatedBy: []
>>
>> Ha, ok, well, score +1 again for formatting code with more spacing in
>> it (total score:  3-1).  ;-)  I never noticed "block args" having the
>> problem since I always use more spacing (and, I guess, the code in the
>> system I've ever traced).
>>
>> So the real issue appears to be related to when a colon follows a
>> non-whitespace character, as it does in your example and in
>> keyword-selector symbol case:
>>
>>      self perform: #add: with: anObject
>>
>> I just saw Bobs msg did half the work finding the method..  Hmm..
>
> This could be fixed with:
>
> findSelector
> "Dan's code for hunting down selectors with keyword parts; while this doesn't give a true parse, in most cases it does what we want, in where it doesn't, we're none the worse for it."
> | sel possibleParens level n keywordPos foundFirstKeyword |
> sel _ self withBlanksTrimmed.
> (sel includes: $:) ifTrue: [
> sel _ sel copyReplaceAll: ':' with: ': '. "for the style (aa max:bb) with no space"
> sel _ sel copyReplaceAll: '[:' with: '[ :'.    "for the style ([:a) with no space"
> possibleParens _ sel findTokens: Character separators.
> sel _ String streamContents: [ :s |
> level _ 0.
> foundFirstKeyword _ false.
> keywordPos _ false.
> possibleParens do: [ :token |
> foundFirstKeyword
> ifFalse: [ token last = $: ifTrue: [ foundFirstKeyword _ keywordPos _ true ]]
> ifTrue: [ keywordPos _  keywordPos not ].
> (level = 0 and: [ keywordPos ])
> ifTrue: [s nextPutAll: token]
> ifFalse: [(n _ token occurrencesOf: $( ) > 0 ifTrue: [level _ level + n].
> (n _ token occurrencesOf: $[ ) > 0 ifTrue: [level _ level + n].
> (n _ token occurrencesOf: $] ) > 0 ifTrue: [level _ level - n].
> (n _ token occurrencesOf: $) ) > 0 ifTrue: [level _ level - n]]]]].
>
> sel isEmpty ifTrue: [^ nil].
> Symbol hasInterned: sel ifTrue: [ :aSymbol |
> ^ aSymbol].
> ^ nil


Not quite:
'3 perform: #between:and: with: 1 with: 5' findSelector
==> nil

I just pushed a version to trunk that has Bob's "[:" improvement, and I added "{}" handling.

The proper way to deal with the remaining cases (short of actual parsing) would be to strip all Strings/Symbols/Comments before the tokenization, I think. Takers? :)

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Bob Arning-2

On 3/2/13 7:48 AM, Bert Freudenberg wrote:
> The proper way to deal with the remaining cases (short of actual parsing) would be to strip all Strings/Symbols/Comments before the tokenization, I think. Takers?:)
Maybe this will do:

'From Squeak4.4 of 1 March 2013 [latest update: #12489] on 2 March 2013
at 12:08:27 pm'!
"Change Set:        FindSelector2
Date:            2 March 2013
Author:            Bob Arning

String>>findSelector2 uses Scanner to better ignore extraneous stuff"!


!Scanner methodsFor: 'expression types' stamp: 'raa 3/2/2013 11:55'!
scanForFindSelectorUpTo: terminator
"
Scanner findSelectorTests
"
     | s |

     s := WriteStream on: (String new: 100).
     [tokenType == terminator or: [tokenType == #doIt]] whileFalse: [
         tokenType caseOf: {
             [#leftParenthesis] -> [self scanToken;
scanForFindSelectorUpTo: #rightParenthesis].
             [#leftBracket] -> [self scanToken; scanForFindSelectorUpTo:
#rightBracket].
             [#leftBrace] -> [self scanToken; scanForFindSelectorUpTo:
#rightBrace].
             [#keyword] -> [s nextPutAll: token].
         } otherwise: [].
         self scanToken
     ].
     ^s contents! !


!Scanner class methodsFor: 'testing' stamp: 'raa 3/2/2013 12:05'!
findSelectorIn: aString

     | result |
     result _ Scanner new
         scan: (ReadStream on:  aString);
         scanForFindSelectorUpTo: #notATerminator.
     ^result! !

!Scanner class methodsFor: 'testing' stamp: 'raa 3/2/2013 12:02'!
findSelectorTests
"
Scanner findSelectorTests explore
"
     ^#(
         '3 perform: #between:and: with: 1 with: 5'
         'self do: [:i | ] separatedBy: [] '
         'self perform: #add: with: anObject'
         'self do: [:i | i do: [ :each | ] ] separatedBy: [] '
         'self x: {self y:} y: ''self new: 100'''
         'a max:b'
         'a'
     ) collect: [ :e |
         {e. self findSelectorIn: e}
     ].! !


!String methodsFor: 'converting' stamp: 'raa 3/2/2013 12:02'!
findSelector2
     "Revised to use scanner for better removal of extraneous stuff"

     | sel |

     sel := self withBlanksTrimmed.
     (sel includes: $:) ifTrue: [sel _ Scanner findSelectorIn: sel].
     sel isEmpty ifTrue: [^ nil].
     sel isOctetString ifTrue: [sel := sel asOctetString].
     Symbol hasInterned: sel ifTrue:
         [:aSymbol | ^ aSymbol].
     ^ nil! !



Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

J. Vuletich (mail lists)
Great! Thanks Bob! This will be in the Cuis update stream soon.

Quoting Bob Arning <[hidden email]>:

>
> On 3/2/13 7:48 AM, Bert Freudenberg wrote:
>> The proper way to deal with the remaining cases (short of actual  
>> parsing) would be to strip all Strings/Symbols/Comments before the  
>> tokenization, I think. Takers?:)
> Maybe this will do:
>
> 'From Squeak4.4 of 1 March 2013 [latest update: #12489] on 2 March  
> 2013 at 12:08:27 pm'!
> "Change Set:        FindSelector2
> Date:            2 March 2013
> Author:            Bob Arning
>
> String>>findSelector2 uses Scanner to better ignore extraneous stuff"!
>
>
> !Scanner methodsFor: 'expression types' stamp: 'raa 3/2/2013 11:55'!
> scanForFindSelectorUpTo: terminator
> "
> Scanner findSelectorTests
> "
>     | s |
>
>     s := WriteStream on: (String new: 100).
>     [tokenType == terminator or: [tokenType == #doIt]] whileFalse: [
>         tokenType caseOf: {
>             [#leftParenthesis] -> [self scanToken;  
> scanForFindSelectorUpTo: #rightParenthesis].
>             [#leftBracket] -> [self scanToken;  
> scanForFindSelectorUpTo: #rightBracket].
>             [#leftBrace] -> [self scanToken;  
> scanForFindSelectorUpTo: #rightBrace].
>             [#keyword] -> [s nextPutAll: token].
>         } otherwise: [].
>         self scanToken
>     ].
>     ^s contents! !
>
>
> !Scanner class methodsFor: 'testing' stamp: 'raa 3/2/2013 12:05'!
> findSelectorIn: aString
>
>     | result |
>     result _ Scanner new
>         scan: (ReadStream on:  aString);
>         scanForFindSelectorUpTo: #notATerminator.
>     ^result! !
>
> !Scanner class methodsFor: 'testing' stamp: 'raa 3/2/2013 12:02'!
> findSelectorTests
> "
> Scanner findSelectorTests explore
> "
>     ^#(
>         '3 perform: #between:and: with: 1 with: 5'
>         'self do: [:i | ] separatedBy: [] '
>         'self perform: #add: with: anObject'
>         'self do: [:i | i do: [ :each | ] ] separatedBy: [] '
>         'self x: {self y:} y: ''self new: 100'''
>         'a max:b'
>         'a'
>     ) collect: [ :e |
>         {e. self findSelectorIn: e}
>     ].! !
>
>
> !String methodsFor: 'converting' stamp: 'raa 3/2/2013 12:02'!
> findSelector2
>     "Revised to use scanner for better removal of extraneous stuff"
>
>     | sel |
>
>     sel := self withBlanksTrimmed.
>     (sel includes: $:) ifTrue: [sel _ Scanner findSelectorIn: sel].
>     sel isEmpty ifTrue: [^ nil].
>     sel isOctetString ifTrue: [sel := sel asOctetString].
>     Symbol hasInterned: sel ifTrue:
>         [:aSymbol | ^ aSymbol].
>     ^ nil! !
>
>
>
>


Cheers,
Juan Vuletich


Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Yoshiki Ohshima-3
Yay to people.  But here is one more challenge to the community ^^;

Back when we weren't using := for assignment, you even didn't have
select a line but just click on a line something like:

a _ self beep: nil.

and press Cmd-m to get the implementors for example.  I've been
missing this convenience since we adopted :=...

-- Yoshiki

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Bob Arning-2
I think you'll find that now works as you expect with the code I posted earlier (once you use the #findSelector2 instead of #findSelector).

After posting the code I started wondering about other possible odd situations, like what is expected from

self x: 1; y: 2

Right now it considers the selector to be #x:y: . Easy enough to fix, but is the right answer #x:, #y: or nothing?

Cheers,
Bob

On 3/2/13 8:57 PM, Yoshiki Ohshima wrote:
Yay to people.  But here is one more challenge to the community ^^;

Back when we weren't using := for assignment, you even didn't have
select a line but just click on a line something like:

a _ self beep: nil.

and press Cmd-m to get the implementors for example.  I've been
missing this convenience since we adopted :=...

-- Yoshiki





Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Frank Shearar-3
On 3 March 2013 02:23, Bob Arning <[hidden email]> wrote:

> I think you'll find that now works as you expect with the code I posted
> earlier (once you use the #findSelector2 instead of #findSelector).
>
> After posting the code I started wondering about other possible odd
> situations, like what is expected from
>
> self x: 1; y: 2
>
> Right now it considers the selector to be #x:y: . Easy enough to fix, but is
> the right answer #x:, #y: or nothing?

A menu that pops up asking you which one you meant?

frank

> Cheers,
> Bob
>
>
> On 3/2/13 8:57 PM, Yoshiki Ohshima wrote:
>
> Yay to people.  But here is one more challenge to the community ^^;
>
> Back when we weren't using := for assignment, you even didn't have
> select a line but just click on a line something like:
>
> a _ self beep: nil.
>
> and press Cmd-m to get the implementors for example.  I've been
> missing this convenience since we adopted :=...
>
> -- Yoshiki
>
>
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

timrowledge

On 03-03-2013, at 2:39 AM, Frank Shearar <[hidden email]> wrote:

> On 3 March 2013 02:23, Bob Arning <[hidden email]> wrote:
>> I think you'll find that now works as you expect with the code I posted
>> earlier (once you use the #findSelector2 instead of #findSelector).
>>
>> After posting the code I started wondering about other possible odd
>> situations, like what is expected from
>>
>> self x: 1; y: 2
>>
>> Right now it considers the selector to be #x:y: . Easy enough to fix, but is
>> the right answer #x:, #y: or nothing?
>
> A menu that pops up asking you which one you meant?

Better yet, modify the system to be able to deal with all three cases and display the results sensibly in a browser.
Multiple browsers might be an acceptable option, one for each possible case.

tim
--
tim Rowledge; [hidden email]; http://www.rowledge.org/tim
As far as we know, our computer has never had an undetected error.



Reply | Threaded
Open this post in threaded view
|

Re: Reusable browsers was Re: About HyperCard

Yoshiki Ohshima-3
In reply to this post by Bob Arning-2
On Sat, Mar 2, 2013 at 6:23 PM, Bob Arning <[hidden email]> wrote:
> I think you'll find that now works as you expect with the code I posted
> earlier (once you use the #findSelector2 instead of #findSelector).

Ah, I did not try that before posting my email.  Sorry.

> After posting the code I started wondering about other possible odd
> situations, like what is expected from
>
> self x: 1; y: 2
>
> Right now it considers the selector to be #x:y: . Easy enough to fix, but is
> the right answer #x:, #y: or nothing?

Hmm, that is an interesting trade-off, but I tend to favor an
understanding behavior with less special cases, so the logic would be
"look for a selector within the selection and when it is delimited,
stop searching." (And the question here was now to ignore unnecessary
parts that don't constitute the final result.  If this is how it
works, I don't mind that the result is just #x:.

There are other cases that gives you some surprises, such as getting
the implementors of #ifTrue:, which usually never be what you want...

--
-- Yoshiki