Help with MenuMorph

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

Help with MenuMorph

Stéphane Ducasse
HI guys

I'm trying to fix all the sound interface for 2.0 and I got trapped into MenuMorph. How do I schedule a menu and get its selected value?
I have to convert code like the following one.



        | aMenu sz on |
        aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
        ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].
       
        sz := aMenu popUpInWorld.
        ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
                how can I get the selected value?
               

        sz ifNil: [^ self].
        on := soundInput isRecording.
        self stop.
        fft := FFT new: sz.
        self resetDisplay.
        on ifTrue: [self start].


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
In fact I see that the problem is more into

how can I specify a menu item which returns a value that I specify without passing a symbol

                ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].
                                                                                                                                               

On Mar 11, 2013, at 1:28 PM, Stéphane Ducasse <[hidden email]> wrote:

> HI guys
>
> I'm trying to fix all the sound interface for 2.0 and I got trapped into MenuMorph. How do I schedule a menu and get its selected value?
> I have to convert code like the following one.
>
>
>
> | aMenu sz on |
> aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
> ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].
>
> sz := aMenu popUpInWorld.
> ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
> how can I get the selected value?
>
>
> sz ifNil: [^ self].
> on := soundInput isRecording.
> self stop.
> fft := FFT new: sz.
> self resetDisplay.
> on ifTrue: [self start].
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

jannik laval
Hi Stef,

I am searching to do that too.
For now, I am using something else... And I plan to create new Menu more usable.

Here is what I use, for your case, just adapt it when trying:

===
        | aMenu sz on |
on := soundInput isRecording.
        self stop.
        aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
        ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | 
aMenu add: r printString 
target: FFT
selector: #new
argument: r
].

        aMenu popUpInWorld.
        
        self resetDisplay.
        on ifTrue: [self start].
===

Jannik


2013/3/11 stephane ducasse <[hidden email]>
In fact I see that the problem is more into

how can I specify a menu item which returns a value that I specify without passing a symbol

                ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].


On Mar 11, 2013, at 1:28 PM, Stéphane Ducasse <[hidden email]> wrote:

> HI guys
>
> I'm trying to fix all the sound interface for 2.0 and I got trapped into MenuMorph. How do I schedule a menu and get its selected value?
> I have to convert code like the following one.
>
>
>
>       | aMenu sz on |
>       aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
>       ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].
>
>       sz := aMenu popUpInWorld.
>       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
>               how can I get the selected value?
>
>
>       sz ifNil: [^ self].
>       on := soundInput isRecording.
>       self stop.
>       fft := FFT new: sz.
>       self resetDisplay.
>       on ifTrue: [self start].
>
>





--

~~Dr. Jannik Laval~~
École des Mines de Douai
Enseignant-chercheur
http://www.jannik-laval.eu

Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse

On Mar 11, 2013, at 2:10 PM, jannik laval <[hidden email]> wrote:

Hi Stef,

I am searching to do that too.
For now, I am using something else... And I plan to create new Menu more usable.

Here is what I use, for your case, just adapt it when trying:

===
        | aMenu sz on |
on := soundInput isRecording.
        self stop.
        aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
        ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | 
aMenu add: r printString 
target: FFT
selector: #new
argument: r
].

        aMenu popUpInWorld.
        
        self resetDisplay.
        on ifTrue: [self start].
===

the problem is that we are missing a way to have menu that simply return a value (without resorting to a method execution and selector).

Stef

Jannik


2013/3/11 stephane ducasse <[hidden email]>
In fact I see that the problem is more into

how can I specify a menu item which returns a value that I specify without passing a symbol

                ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].


On Mar 11, 2013, at 1:28 PM, Stéphane Ducasse <[hidden email]> wrote:

> HI guys
>
> I'm trying to fix all the sound interface for 2.0 and I got trapped into MenuMorph. How do I schedule a menu and get its selected value?
> I have to convert code like the following one.
>
>
>
>       | aMenu sz on |
>       aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
>       ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].
>
>       sz := aMenu popUpInWorld.
>       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
>               how can I get the selected value?
>
>
>       sz ifNil: [^ self].
>       on := soundInput isRecording.
>       self stop.
>       fft := FFT new: sz.
>       self resetDisplay.
>       on ifTrue: [self start].
>
>





--

~~Dr. Jannik Laval~~
École des Mines de Douai
Enseignant-chercheur
http://www.jannik-laval.eu


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

jannik laval

On Mar 11, 2013, at 5:41 PM, stephane ducasse <[hidden email]> wrote:


On Mar 11, 2013, at 2:10 PM, jannik laval <[hidden email]> wrote:

Hi Stef,

I am searching to do that too.
For now, I am using something else... And I plan to create new Menu more usable.

Here is what I use, for your case, just adapt it when trying:

===
        | aMenu sz on |
on := soundInput isRecording.
        self stop.
        aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
        ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | 
aMenu add: r printString 
target: FFT
selector: #new
argument: r
].

        aMenu popUpInWorld.
        
        self resetDisplay.
        on ifTrue: [self start].
===

the problem is that we are missing a way to have menu that simply return a value (without resorting to a method execution and selector).

Yes, I know :)
Try this small class. I named it MenuMorphNG.
You can use it like that:

===
menu := MenuMorphNG new defaultTarget: menu.
menu add: 'test1' value: #testForPharo.
menu addLine.
menu add: 'test2' value: 2.0.
menu localize; invokeModal.
menu selectedValue
===

Jannik



Stef

Jannik


2013/3/11 stephane ducasse <[hidden email]>
In fact I see that the problem is more into

how can I specify a menu item which returns a value that I specify without passing a symbol

                ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].


On Mar 11, 2013, at 1:28 PM, Stéphane Ducasse <[hidden email]> wrote:

> HI guys
>
> I'm trying to fix all the sound interface for 2.0 and I got trapped into MenuMorph. How do I schedule a menu and get its selected value?
> I have to convert code like the following one.
>
>
>
>       | aMenu sz on |
>       aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
>       ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [:r | aMenu add: r printString action: r].
>
>       sz := aMenu popUpInWorld.
>       ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
>               how can I get the selected value?
>
>
>       sz ifNil: [^ self].
>       on := soundInput isRecording.
>       self stop.
>       fft := FFT new: sz.
>       self resetDisplay.
>       on ifTrue: [self start].
>
>





--

~~Dr. Jannik Laval~~
École des Mines de Douai
Enseignant-chercheur
http://www.jannik-laval.eu




MenuMorphNG.st (891 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
Thanks Jannik.
I was thinking that
        - we could have a different MenuItem class: ValuedMenuItem
        - that a add:value: in MenuMorph could create an instance of this ValuedMenuItem

Like that we can integrate both nicely.

What do you think?

Stef

On Mar 11, 2013, at 9:33 PM, jannik.laval <[hidden email]> wrote:

> <MenuMorphNG.st>


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
Jannik

I'm doing it because this is exactly done like that in menuMorph:
everything falls down to


addToggle: aString target: anObject selector: aSymbol getStateSelector: stateSymbol enablementSelector: enableSymbol argumentList: argList
        "Append a menu item with the given label. If the item is selected, it will send the given selector to the target object."

        |item|
        item := ToggleMenuItemMorph new
                contents: aString;
                target: anObject;
                selector: aSymbol;
                arguments: argList;
                getStateSelector: stateSymbol;
                enablementSelector: enableSymbol.
        ^ self addMenuItem: item.


:)




On Mar 11, 2013, at 9:36 PM, stephane ducasse <[hidden email]> wrote:

> Thanks Jannik.
> I was thinking that
> - we could have a different MenuItem class: ValuedMenuItem
> - that a add:value: in MenuMorph could create an instance of this ValuedMenuItem
>
> Like that we can integrate both nicely.
>
> What do you think?
>
> Stef
>
> On Mar 11, 2013, at 9:33 PM, jannik.laval <[hidden email]> wrote:
>
>> <MenuMorphNG.st>
>
>


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
Jannik

It works :)
I will produce a cs because this is a nice extension :)

Stef

Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

jannik laval
Ok, I did it too :))

I created a ValuedMenuItemMorph as you propose.

Jannik

On Mar 11, 2013, at 9:53 PM, stephane ducasse <[hidden email]> wrote:

> Jannik
>
> It works :)
> I will produce a cs because this is a nice extension :)
>
> Stef
>


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
Now I have the problem that I do not know how to get the value from the menu and not the menu item morph


setFFTSize
        "Set the size of the FFT used for frequency analysis."

        | aMenu sz on |
        aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
        ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [ :r | aMenu add: r printString value: r].
        sz := aMenu xxxxxxx
                                               
        sz ifNil: [^ self].
        on := soundInput isRecording.
        self stop.
        fft := FFT new: sz.
        self resetDisplay.
        on ifTrue: [self start].


do you have an idea?

Stef
Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
I should probably redefine

invokeWithEvent: evt
        "Perform the action associated with the given menu item."

        | w |
        self isEnabled ifFalse: [^ self].
        target class == HandMorph ifTrue: [(self notObsolete) ifFalse: [^ self]].
        owner ifNotNil:[self isStayUpItem ifFalse:[
                self flag: #workAround. "The tile system invokes menus straightforwardly so the menu might not be in the world."
                (w := self world) ifNotNil:[
                        owner deleteIfPopUp: evt.
                        "Repair damage before invoking the action for better feedback"
                        w displayWorldSafely]]].
        selector ifNil:[^self].
        Cursor normal showWhile: [ | selArgCount |  "show cursor in case item opens a new MVC window"
                (selArgCount := selector numArgs) = 0
                        ifTrue:
                                [target perform: selector]
                        ifFalse:
                                [selArgCount = arguments size
                                        ifTrue: [target perform: selector withArguments: arguments]
                                        ifFalse: [target perform: selector withArguments: (arguments copyWith: evt)]].
                self changed].



On Mar 11, 2013, at 10:06 PM, stephane ducasse <[hidden email]> wrote:

> Now I have the problem that I do not know how to get the value from the menu and not the menu item morph
>
>
> setFFTSize
> "Set the size of the FFT used for frequency analysis."
>
> | aMenu sz on |
> aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
> ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [ :r | aMenu add: r printString value: r].
> sz := aMenu xxxxxxx
>
> sz ifNil: [^ self].
> on := soundInput isRecording.
> self stop.
> fft := FFT new: sz.
> self resetDisplay.
> on ifTrue: [self start].
>
>
> do you have an idea?
>
> Stef


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

jannik laval
Here is what I did (2 classes)
Then, you can do:

===
menu := MenuMorphNG new.
menu add: 'test1' value: #testForPharo.
menu addLine.
menu add: 'test2' value: 2.0.
menu localize; invokeModal.
menu selectedValue
===

Jannik



On Mar 11, 2013, at 10:09 PM, stephane ducasse <[hidden email]> wrote:

> I should probably redefine
>
> invokeWithEvent: evt
> "Perform the action associated with the given menu item."
>
> | w |
> self isEnabled ifFalse: [^ self].
> target class == HandMorph ifTrue: [(self notObsolete) ifFalse: [^ self]].
> owner ifNotNil:[self isStayUpItem ifFalse:[
> self flag: #workAround. "The tile system invokes menus straightforwardly so the menu might not be in the world."
> (w := self world) ifNotNil:[
> owner deleteIfPopUp: evt.
> "Repair damage before invoking the action for better feedback"
> w displayWorldSafely]]].
> selector ifNil:[^self].
> Cursor normal showWhile: [ | selArgCount |  "show cursor in case item opens a new MVC window"
> (selArgCount := selector numArgs) = 0
> ifTrue:
> [target perform: selector]
> ifFalse:
> [selArgCount = arguments size
> ifTrue: [target perform: selector withArguments: arguments]
> ifFalse: [target perform: selector withArguments: (arguments copyWith: evt)]].
> self changed].
>
>
>
> On Mar 11, 2013, at 10:06 PM, stephane ducasse <[hidden email]> wrote:
>
>> Now I have the problem that I do not know how to get the value from the menu and not the menu item morph
>>
>>
>> setFFTSize
>> "Set the size of the FFT used for frequency analysis."
>>
>> | aMenu sz on |
>> aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
>> ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [ :r | aMenu add: r printString value: r].
>> sz := aMenu xxxxxxx
>>
>> sz ifNil: [^ self].
>> on := soundInput isRecording.
>> self stop.
>> fft := FFT new: sz.
>> self resetDisplay.
>> on ifTrue: [self start].
>>
>>
>> do you have an idea?
>>
>> Stef
>
>


MenuMorphNG.st (790 bytes) Download Attachment
ValuedMenuItemMorph.st (662 bytes) Download Attachment
Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
In reply to this post by stephane ducasse
The problem is that selectedValue will not work on other menuItem :)
So I'm playing with something like that.

setFFTSize
        "Set the size of the FFT used for frequency analysis."

        | aMenu sz on |
        aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
        ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [ :r | aMenu add: r printString value: r].
        sz := (aMenu invokeAt: World activeHand position in: World allowKeyboard: true) selectedValue.
       
        sz ifNil: [^ self].
        on := soundInput isRecording.
        self stop.
        fft := FFT new: sz.
        self resetDisplay.
        on ifTrue: [self start].


it means that probably we should rethink the protocol between the menu and the menuItem.

I do not like my code. Especially that line above.
Now going to sleep in this freezing time.
Stef
Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
jannik

what guillermo did in the past was to use

        MenuMorph
                chooseFrom: choices values: choices lines: #() title:  ('display type (currently {1})' translated format:{displayType}).

I will study this implementation to see how it fits with what I did.

Stef

On Mar 11, 2013, at 10:25 PM, stephane ducasse <[hidden email]> wrote:

> The problem is that selectedValue will not work on other menuItem :)
> So I'm playing with something like that.
>
> setFFTSize
> "Set the size of the FFT used for frequency analysis."
>
> | aMenu sz on |
> aMenu := MenuMorph new title: ('FFT size (currently {1})' translated format:{fft n}).
> ((7 to: 10) collect: [:n | 2 raisedTo: n]) do: [ :r | aMenu add: r printString value: r].
> sz := (aMenu invokeAt: World activeHand position in: World allowKeyboard: true) selectedValue.
>
> sz ifNil: [^ self].
> on := soundInput isRecording.
> self stop.
> fft := FFT new: sz.
> self resetDisplay.
> on ifTrue: [self start].
>
>
> it means that probably we should rethink the protocol between the menu and the menuItem.
>
> I do not like my code. Especially that line above.
> Now going to sleep in this freezing time.
> Stef


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
Jannik

I'm studying right now choose…
So I think that I will add a method add: value: to the instance side to see how it look like.

Stef


chooseFrom: aList lines: linesArray title: queryString
        "Choose an item from the given list. Answer the index of the selected item."
        "MenuMorph
                chooseFrom: #('Hello' 'Pharoers' 'Here' 'We' 'Go')
                lines: #(2 4)
                title: 'What''s up?'"
               
        | menu result |
        (ProvideAnswerNotification signal: queryString) ifNotNil:[:answer |
                1 to: aList size do:[:i| (aList at: i) = answer ifTrue:[^i]].
                ^0].
        result := 0.
        menu := self new.
        menu addTitle: queryString.
        1 to: aList size do:[:i|
                menu add: (aList at: i) asString target: [:v| result := v] selector: #value: argument: i.
                (linesArray includes: i) ifTrue: [menu addLine]].
       
        menu invokeAt: ActiveHand position in: ActiveWorld allowKeyboard: true.
        ^result
Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

jannik laval
Ok, I like the way you use it.
Now, I hope to have in future a better menu tool.

Jannik

On Mar 12, 2013, at 4:23 PM, stephane ducasse <[hidden email]> wrote:

> Jannik
>
> I'm studying right now choose…
> So I think that I will add a method add: value: to the instance side to see how it look like.
>
> Stef
>
>
> chooseFrom: aList lines: linesArray title: queryString
> "Choose an item from the given list. Answer the index of the selected item."
> "MenuMorph
> chooseFrom: #('Hello' 'Pharoers' 'Here' 'We' 'Go')
> lines: #(2 4)
> title: 'What''s up?'"
>
> | menu result |
> (ProvideAnswerNotification signal: queryString) ifNotNil:[:answer |
> 1 to: aList size do:[:i| (aList at: i) = answer ifTrue:[^i]].
> ^0].
> result := 0.
> menu := self new.
> menu addTitle: queryString.
> 1 to: aList size do:[:i|
> menu add: (aList at: i) asString target: [:v| result := v] selector: #value: argument: i.
> (linesArray includes: i) ifTrue: [menu addLine]].
>
> menu invokeAt: ActiveHand position in: ActiveWorld allowKeyboard: true.
> ^result


Reply | Threaded
Open this post in threaded view
|

Re: Help with MenuMorph

stephane ducasse
In reply to this post by stephane ducasse
In fact I did not add an instance method because we always have to invoke the
        menu invokeAt: ActiveHand position in: ActiveWorld allowKeyboard: true.
So in that case I prefer to use chooseFrom:
But indeed this is a good experience and probably we should rebuild menu and menuItem
one of these days. I think that cleaning again a bit more is needed. I added some entries in fogbugz for that.

Stef
 
On Mar 12, 2013, at 4:23 PM, stephane ducasse <[hidden email]> wrote:

> Jannik
>
> I'm studying right now choose…
> So I think that I will add a method add: value: to the instance side to see how it look like.
>
> Stef
>
>
> chooseFrom: aList lines: linesArray title: queryString
> "Choose an item from the given list. Answer the index of the selected item."
> "MenuMorph
> chooseFrom: #('Hello' 'Pharoers' 'Here' 'We' 'Go')
> lines: #(2 4)
> title: 'What''s up?'"
>
> | menu result |
> (ProvideAnswerNotification signal: queryString) ifNotNil:[:answer |
> 1 to: aList size do:[:i| (aList at: i) = answer ifTrue:[^i]].
> ^0].
> result := 0.
> menu := self new.
> menu addTitle: queryString.
> 1 to: aList size do:[:i|
> menu add: (aList at: i) asString target: [:v| result := v] selector: #value: argument: i.
> (linesArray includes: i) ifTrue: [menu addLine]].
>
> menu invokeAt: ActiveHand position in: ActiveWorld allowKeyboard: true.
> ^result