The Inbox: Morphic-phite.429.mcz

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

The Inbox: Morphic-phite.429.mcz

commits-2
A new version of Morphic was added to project The Inbox:
http://source.squeak.org/inbox/Morphic-phite.429.mcz

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

Name: Morphic-phite.429
Author: phite
Time: 26 April 2010, 10:28:16.551 am
UUID: 9b7e8e83-92c6-3742-b34d-e06b6e88450c
Ancestors: Morphic-phite.428

Refactored the DockingBar and the WorldMenu to add custom self-defined menus. (See class comment of MenuEntrySpec)

Changed Class comments of TheWorldMenu and TheWorldMainDockingBar. They now reference MenuEntrySpec to explain how new menu entries may be added.

=============== Diff against Morphic-phite.428 ===============

Item was changed:
  ----- Method: MenuMorph>>addLine (in category 'construction') -----
  addLine
  "Append a divider line to this menu. Suppress duplicate lines."
  self hasItems
  ifFalse: [^ self].
  (self lastSubmorph isKindOf: MenuLineMorph)
  ifFalse: [self addMorphBack: MenuLineMorph new] !

Item was changed:
  ----- Method: MenuEntrySpec classSide>>newFrom: (in category 'as yet unclassified') -----
  newFrom: aDict
  "Creates a new MenuEntrySpec from a Dictionary.
  Possible keys are: #contents, #help, #icon, #selectedIcon,
+ #target, #selector, #argument, #location, #position, #dockingBar, #worldMenu
- #target, #selector, #argument, #location, #position
  where #location describes where the menuEntry should be placed
+ #location -> nil creates a new menuEntry in the Menu
- #location -> nil creates a new menuEntry in the DockingBar
  #location -> #('Tools' 'subMenu' 'subMenu2') puts the menuEntry into submenus
  and where #position describes the position of the menuEntry within a menu eg.
  #position -> #last - adds the menuEntry at the end of the menu (#first at the beginning)
  #position -> #(#before 'Help') - adds the menuEntry just before the 'Help' entry (#after adds it after the entry)"
 
  ^ self new
  contents: (aDict at: #contents ifAbsent: '');
  help: (aDict at: #help ifAbsent: nil);
  icon: (aDict at: #icon ifAbsent: nil);
  selectedIcon: (aDict at: #selectedIcon ifAbsent: nil);
  target: (aDict at: #target ifAbsent: nil);
  selector: (aDict at: #selector ifAbsent: nil);
  arguments: (aDict at: #arguments ifAbsent: nil);
  location: (aDict at: #location ifAbsent: nil);
+ position: (aDict at: #position ifAbsent: #last);
+ dockingBar: (aDict at: #dockingBar ifAbsent: true);
+ worldMenu: (aDict at: #worldMenu ifAbsent: true)!
- position: (aDict at: #position ifAbsent: #last)!

Item was changed:
  ----- Method: MenuEntrySpec>>installOn: (in category 'menu-creation') -----
+ installOn: aMenu
+ "Installs a menuEntry corresponding to this specification into the given menu"
- installOn: aDockingBar
- "Installs a menuEntry corresponding to this specification into the given DockingBar"
 
  | menu |
+ menu := self findOrCreateLocationIn: aMenu.
- menu := self findOrCreateLocationIn: aDockingBar.
  menu subMenu ifNil: [ menu addSubMenu: [:subMenu |] ].
  menu subMenu addItem: [ :item |
  item
  contents: self contents;
  help: self help;
  icon: self icon;
  target: self target;
  selector: self selector;
  arguments: self arguments.
  (item respondsTo: #selectedIcon:) ifTrue: [ item selectedIcon: self selectedIcon ].]
  at: self position.!

Item was added:
+ ----- Method: MenuEntrySpec>>worldMenu: (in category 'accessing') -----
+ worldMenu: aBoolean
+ "True/False - wether this menu entry describes a MenuEntry in the WorldMenu"
+ worldMenu := aBoolean!

Item was changed:
  ----- Method: TheWorldMenu>>buildWorldMenu (in category 'construction') -----
  buildWorldMenu
  "Build the menu that is put up when the screen-desktop is clicked on"
  | menu |
  menu := MenuMorph new defaultTarget: self.
  menu commandKeyHandler: self.
  self colorForDebugging: menu.
  menu addStayUpItem.
  self makeConvenient: menu.
  Smalltalk at: #ServiceGUI ifPresent:[:sgui|
  sgui worldMenu: menu.
  sgui onlyServices ifTrue: [^ menu].
  ].
  self addProjectEntries: menu.
  myWorld addUndoItemsTo: menu.
  self addRestoreDisplay: menu.
  self addUtilities: menu.
  self addObjectsAndTools: menu.
  self addPrintAndDebug: menu.
  self addSaveAndQuit: menu.
+ self addCustomMenus: menu.
  ^ menu!

Item was added:
+ ----- Method: MenuEntrySpec>>worldMenu (in category 'accessing') -----
+ worldMenu
+ "True/False - wether this menu entry describes a MenuEntry in the WorldMenu"
+ ^ worldMenu!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>findAllForDockingBar (in category 'as yet unclassified') -----
+ findAllForDockingBar
+ "Searches for MenuEntrySpecs which are meant do be displayed in the DockingBar."
+
+ ^ self findAll select: [ :spec | spec dockingBar ]!

Item was changed:
  ----- Method: TheWorldMainDockingBar>>customMenusOn: (in category 'construction') -----
  customMenusOn: aDockingBar
  "Searches for MenuEntrySpecs and add the corresponding menus to the docking bar."
+
+ MenuEntrySpec findAllForDockingBar do: [ :spec |
- | menuSpecs |
- menuSpecs := self searchForMenuSpecs sortBy: [ :a :b | a location size > b location size].
- menuSpecs do: [ :spec |
  spec installOn: aDockingBar].!

Item was added:
+ ----- Method: MenuMorph>>subMenu (in category 'accessing') -----
+ subMenu
+ "For convenience. As I don't have submenus, I act as the submenu."
+ ^ self!

Item was added:
+ ----- Method: MenuEntrySpec>>dockingBar (in category 'accessing') -----
+ dockingBar
+ "True/False - wether this menu entry describes a MenuEntry in the DockingBar"
+ ^ dockingBar!

Item was changed:
  ----- Method: MenuEntrySpec>>findOrCreateLocationIn: (in category 'menu-creation') -----
+ findOrCreateLocationIn: aMenu
- findOrCreateLocationIn: aDockingBar
  "find the menu my location points at - create it, if it does not exist."
 
  | currentMenu |
+ location size = 0 ifTrue: [ ^ aMenu ].
+ currentMenu := aMenu.
- location size = 0 ifTrue: [ ^ aDockingBar ].
- currentMenu := aDockingBar.
  (1 to: location size) do: [ :i |
  currentMenu := currentMenu menus detect:
  [ :m | m contents = (location at: i) ]
  ifNone: [
  currentMenu subMenu ifNil: [ currentMenu addSubMenu:[:subMenu| ]].
  currentMenu subMenu addItem: [:item|
  item contents: (location at: i)].
  currentMenu menus detect: [ :m | m contents = (location at: i) ]]].
  ^ currentMenu!

Item was changed:
  Object subclass: #TheWorldMainDockingBar
  instanceVariableNames: ''
  classVariableNames: 'Instance TS'
  poolDictionaries: ''
  category: 'Morphic-Kernel'!
+
+ !TheWorldMainDockingBar commentStamp: 'phite 4/26/2010 09:48' prior: 0!
+ TheWorldMainDockingBar serves to present a Squeak menu which is always visible whithin a World.
+
+ It is possible to add custom menu entries to the WorldMenu. Please have a look at the MenuEntrySpec comments for examples.!

Item was changed:
  ----- Method: MenuMorph>>add:action: (in category 'construction') -----
  add: aString action: aSymbolOrValuable
  "Append a menu item with the given label. If the item is selected, it will send the given selector to the default target object."
  "Details: Note that the menu item added captures the default target object at the time the item is added; the default target can later be changed before added additional items without affecting the targets of previously added entries. The model is that each entry is like a button that knows everything it needs to perform its action."
  aSymbolOrValuable isSymbol ifTrue:[
  self add: aString
  target: defaultTarget
  selector: aSymbolOrValuable
  argumentList: EmptyArray.
  ] ifFalse:[
  self add: aString
  target: aSymbolOrValuable
  selector: #value
  argumentList: EmptyArray.
  ]
  !

Item was changed:
  Object subclass: #TheWorldMenu
  instanceVariableNames: 'myProject myWorld myHand'
  classVariableNames: 'OpenMenuRegistry'
  poolDictionaries: ''
  category: 'Morphic-Kernel'!
 
+ !TheWorldMenu commentStamp: 'phite 4/26/2010 09:47' prior: 0!
- !TheWorldMenu commentStamp: 'sw 10/5/2002 00:44' prior: 0!
  Instances of TheWorldMenu serve to present the primary Squeak menu obtained by clicking on open desktop, which is variously spoken of as the "screen menu", the "desktop menu", or the "world menu".
 
  myProject is the Project I pertain to.
  myWorld is the world, a PasteUpMorph, that I pertain to.
+ myHand is the hand that invoked the menu.
+
+ It is possible to add custom menu entries to the WorldMenu. Please have a look at the MenuEntrySpec comments for examples.!
- myHand is the hand that invoked the menu.!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>findAllForWorldMenu (in category 'as yet unclassified') -----
+ findAllForWorldMenu
+ "Searches for MenuEntrySpecs which are meant do be displayed in the WorldMenu."
+
+ ^ self findAll select: [ :spec | spec worldMenu ]!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>allSpecAndSpecArrays (in category 'as yet unclassified') -----
+ allSpecAndSpecArrays
+ "Searches for MenuEntrySpecs. We scan all classes for #menuEntrySpecification methods and answer an Array of all menuSpecs found."
+
+ ^ ((self systemNavigation allClassesImplementing: #menuEntrySpecification)
+ collect: [ :aClass | aClass theNonMetaClass menuEntrySpecification])!

Item was added:
+ ----- Method: MenuEntrySpec>>dockingBar: (in category 'accessing') -----
+ dockingBar: aBoolean
+ "True/False - wether this menu entry describes a MenuEntry in the DockingBar"
+ dockingBar := aBoolean!

Item was changed:
  ----- Method: MenuMorph>>addItem:at: (in category 'construction') -----
  addItem: aBlock at: position
  | item |
  item := MenuItemMorph new.
  aBlock value: item.
  self addMenuItem: item at: position!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>newForDockingBarFrom: (in category 'as yet unclassified') -----
+ newForDockingBarFrom: aDict
+ "Creates a new MenuEntrySpec from a Dictionary.
+ Possible keys are: #contents, #help, #icon, #selectedIcon,
+ #target, #selector, #argument, #location, #position
+ where #location describes where the menuEntry should be placed
+ #location -> nil creates a new menuEntry in the DockingBar
+ #location -> #('Tools' 'subMenu' 'subMenu2') puts the menuEntry into submenus
+ and where #position describes the position of the menuEntry within a menu eg.
+ #position -> #last - adds the menuEntry at the end of the menu (#first at the beginning)
+ #position -> #(#before 'Help') - adds the menuEntry just before the 'Help' entry (#after adds it after the entry)"
+
+ ^ self new
+ contents: (aDict at: #contents ifAbsent: '');
+ help: (aDict at: #help ifAbsent: nil);
+ icon: (aDict at: #icon ifAbsent: nil);
+ selectedIcon: (aDict at: #selectedIcon ifAbsent: nil);
+ target: (aDict at: #target ifAbsent: nil);
+ selector: (aDict at: #selector ifAbsent: nil);
+ arguments: (aDict at: #arguments ifAbsent: nil);
+ location: (aDict at: #location ifAbsent: nil);
+ position: (aDict at: #position ifAbsent: #last);
+ dockingBar: true;
+ worldMenu: false.!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>newForWorldMenuFrom: (in category 'as yet unclassified') -----
+ newForWorldMenuFrom: aDict
+ "Creates a new MenuEntrySpec from a Dictionary.
+ Possible keys are: #contents, #help, #icon, #selectedIcon,
+ #target, #selector, #argument, #location, #position
+ where #location describes where the menuEntry should be placed
+ #location -> nil creates a new menuEntry in the DockingBar
+ #location -> #('Tools' 'subMenu' 'subMenu2') puts the menuEntry into submenus
+ and where #position describes the position of the menuEntry within a menu eg.
+ #position -> #last - adds the menuEntry at the end of the menu (#first at the beginning)
+ #position -> #(#before 'Help') - adds the menuEntry just before the 'Help' entry (#after adds it after the entry)"
+
+ ^ self new
+ contents: (aDict at: #contents ifAbsent: '');
+ help: (aDict at: #help ifAbsent: nil);
+ icon: (aDict at: #icon ifAbsent: nil);
+ selectedIcon: (aDict at: #selectedIcon ifAbsent: nil);
+ target: (aDict at: #target ifAbsent: nil);
+ selector: (aDict at: #selector ifAbsent: nil);
+ arguments: (aDict at: #arguments ifAbsent: nil);
+ location: (aDict at: #location ifAbsent: nil);
+ position: (aDict at: #position ifAbsent: #last);
+ dockingBar: false;
+ worldMenu: true.!

Item was added:
+ ----- Method: TheWorldMenu>>addCustomMenus: (in category 'construction') -----
+ addCustomMenus: menu
+ "Looks for menuEntries defined in other classes and adds them."
+
+ MenuEntrySpec findAllForWorldMenu do: [ :spec |
+ spec installOn: menu ].!

Item was changed:
  Object subclass: #MenuEntrySpec
+ instanceVariableNames: 'contents help icon selectedIcon target selector location arguments position dockingBar worldMenu'
- instanceVariableNames: 'contents help icon selectedIcon target selector location arguments position'
  classVariableNames: ''
  poolDictionaries: ''
+ category: 'Morphic-Menus'!
+
+ !MenuEntrySpec commentStamp: 'phite 4/26/2010 10:20' prior: 0!
+ You may define MenuEntrySpecs to add custom menus to TheWorldMainDockingBar or TheWorldMenu.
+
+ To add add custom menu entries your class needs to answer to #menuEntrySpecification.
+ #menuEntrySpecification may answer an instance of MenuEntrySpec or an array of MenuEntrySpecs for multiple menus.
+
+ Example:
+ MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
+ #contents 'Hello?'
+ #location #('Help' 'a subMenu' 'another subMenu')
+ #target MenuMorph #selector #inform: #arguments #('Hello World!!')
+ ))
+
+ The example above creates a MenuEntrySpec called 'Hello?' located in the Help-menu within some submenus. As you may see MenuEntrySpecs can be created with the help of an options dictionary. The options are explained later. Remember: You do not need to specify option you do not need.
+
+ MenuEntrySpec newForDockingBarFrom:  a Dictionary - created a menu entry for the DockingBar
+ MenuEntrySpec newForWorldMenuFrom: a Dictionary - creates a menu entry for the WorldMenu
+ MenuEntrySpec newFrom: a Dictionary - creates a menu entry for both
+
+ Possible options:
+ #contents
+ A String that is the visible label the user should click on
+ #help
+ A String that may be shown in a bubble near the menu entry for the user's help
+ #icon
+ A Form which is displayed near the label
+ #selectedIcon
+ A Form which is displayed instead of the icon when the menuEntry is selected
+ #target
+ An Object which is called when the user clicks on the menu entry
+ #selector
+ A Symol which is sent the the target
+ #argument
+ An Array of Arguments which are sent with the selector
+ #location
+ An Arrray of Strings which describes the place the menuEntry should be displayed.
+ #location -> nil or #() creates the menu entry in the top-level of the menu
+ #location -> #('Help') creates the menu entry in the Help-menu
+ #location -> #('Help' 'mySubMenu') creates the entry in a submenu of the Help-menu. If the submenu 'mySubMenu' does not exist it will be created
+ #position
+ A Symbol or Array describing the position of the menu entry within a menu.
+ #position -> #first creates the entry in the first slot of a menu
+ #position -> #last creates the entry in the last slot
+ #position -> #(#before 'Help') creates the entry just before the Help-menu
+ #position -> #(#after 'Help') creates the entry just after the Help-menu
+ If you reference a menu entry with #before or #after, be sure the menu entry exists.
+ #dockingBar
+ A Boolean that defines whether the menu entry should be displayed in the DockingBar.
+ This is always true if you use MenuEntrySpec newForDockingBarFrom:  a Dictionary
+ #worldMenu
+ A Boolean that defines whether the menu entry should be displayed in the WorldMenu.
+ This is always true if you use MenuEntrySpec newForWorldMenuFrom:  a Dictionary!
- category: 'Morphic-Menus-DockingBar'!

Item was added:
+ ----- Method: MenuEntrySpec classSide>>findAll (in category 'as yet unclassified') -----
+ findAll
+ "Searches for MenuEntrySpecs. We scan all classes for #menuEntrySpecification methods and answer an Array of all menuSpecs found."
+
+ | flattenEncoder |
+ "We may get the specs in arrays, so we need to flatten."
+ flattenEncoder := FlattenEncoder stream: (WriteStream with: #()).
+ self allSpecAndSpecArrays flattenOnStream: flattenEncoder.
+ ^ flattenEncoder contents!

Item was removed:
- ----- Method: TheWorldMainDockingBar>>searchForMenuSpecs (in category 'construction') -----
- searchForMenuSpecs
- "This is a one-time only method for creating the worlds DockingBar. Here we scann all classes for #menuEntrySpecification methods and answer an Array of all menuSpecs found."
-
- ^ ((self systemNavigation allClassesImplementing: #menuEntrySpecification)
- collect: [ :aClass | aClass theNonMetaClass menuEntrySpecification])!


Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Morphic-phite.429.mcz

Hannes Hirzel
Hello Philipp

I took a fresh 4.1 image, updated it to 10012, and loaded Morphic-phite.429.mcz.

As the comments were fine I was quickly able to write an example (code below).

Then I had to choose 'Rebuild menus'

It worked fine.
The question is now (see another thread by Bert) if we should go or
your solution (MenuSpec based) or the one by Steve Wessels (Pragma
based).

I do not feel too comfortable with pragmas yet whereas the MenuSpec is
something I easily understand. And in addition I have the gut feeling
that pragmas are meant for some more basic things (a kind of compiler
directive, see http://en.wikipedia.org/wiki/Directive_%28programming%29)

Like Bert  I would like to see some discussion **on this issue, but
not too along as I would like to start using this feature asap.

Hannes

** The thread started by Bert at
http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149563.html

-----------------------
Model subclass: #MyReallyNiceApplication
        instanceVariableNames: ''
        classVariableNames: ''
        poolDictionaries: ''
        category: 'MyMenuTests'!

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

MyReallyNiceApplication class
        instanceVariableNames: ''!

!MyReallyNiceApplication class methodsFor: 'as yet unclassified'
stamp: 'hjh 4/26/2010 08:52'!
menuEntrySpecification
        "Test to add another entyr in the Help menu"


^MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
                #contents 'Hello?'
                #location #('Help' 'a subMenu' 'another subMenu')
                #target MenuMorph #selector #inform: #arguments #('Hello World!!')
                ))
! !

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Morphic-phite.429.mcz

Levente Uzonyi-2
On Mon, 26 Apr 2010, Hannes Hirzel wrote:

> Hello Philipp
>
> I took a fresh 4.1 image, updated it to 10012, and loaded Morphic-phite.429.mcz.
>
> As the comments were fine I was quickly able to write an example (code below).
>
> Then I had to choose 'Rebuild menus'
>
> It worked fine.
> The question is now (see another thread by Bert) if we should go or
> your solution (MenuSpec based) or the one by Steve Wessels (Pragma
> based).
It's Balázs Kósi who implemented the registration method with pragmas
(http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149534.html 
).

>
> I do not feel too comfortable with pragmas yet whereas the MenuSpec is
> something I easily understand. And in addition I have the gut feeling
> that pragmas are meant for some more basic things (a kind of compiler
> directive, see http://en.wikipedia.org/wiki/Directive_%28programming%29)

Pragmas in Squeak are not directives (though they can be used as
directives) but a way to add metadata to a method. So the wikipedia page
is irrelevant. If take a look at the class comment of Pragma, you'll
feel more comfortable with them.
(I think that we should convert all preferences to pragma-style. It could
be a goal for 4.2.)

>
> Like Bert  I would like to see some discussion **on this issue, but
> not too along as I would like to start using this feature asap.

We should review both methods, consider the benefits and
drawbacks and then make a decision.


Levente

>
> Hannes
>
> ** The thread started by Bert at
> http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149563.html
>
> -----------------------
> Model subclass: #MyReallyNiceApplication
> instanceVariableNames: ''
> classVariableNames: ''
> poolDictionaries: ''
> category: 'MyMenuTests'!
>
> "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
>
> MyReallyNiceApplication class
> instanceVariableNames: ''!
>
> !MyReallyNiceApplication class methodsFor: 'as yet unclassified'
> stamp: 'hjh 4/26/2010 08:52'!
> menuEntrySpecification
> "Test to add another entyr in the Help menu"
>
>
> ^MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
> #contents 'Hello?'
> #location #('Help' 'a subMenu' 'another subMenu')
> #target MenuMorph #selector #inform: #arguments #('Hello World!!')
> ))
> ! !
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Morphic-phite.429.mcz

Hannes Hirzel
Thank you for the explanations. In particular reading the comment in
the Pragma class was helpful. I feel now much more comfortable with
the idea of using them. However I still think they are more related to
VM primitives and configuration issues. The menu is a GUI related
thing and having a MenuSpec feels somewhat more natural....

--Hannes

P.S. There are currently 854 methods which have a pragma in them.

On 4/26/10, Levente Uzonyi <[hidden email]> wrote:

> On Mon, 26 Apr 2010, Hannes Hirzel wrote:
>
>> Hello Philipp
>>
>> I took a fresh 4.1 image, updated it to 10012, and loaded
>> Morphic-phite.429.mcz.
>>
>> As the comments were fine I was quickly able to write an example (code
>> below).
>>
>> Then I had to choose 'Rebuild menus'
>>
>> It worked fine.
>> The question is now (see another thread by Bert) if we should go or
>> your solution (MenuSpec based) or the one by Steve Wessels (Pragma
>> based).
>
> It's Balázs Kósi who implemented the registration method with pragmas
> (http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149534.html
> ).
>
>>
>> I do not feel too comfortable with pragmas yet whereas the MenuSpec is
>> something I easily understand. And in addition I have the gut feeling
>> that pragmas are meant for some more basic things (a kind of compiler
>> directive, see http://en.wikipedia.org/wiki/Directive_%28programming%29)
>
> Pragmas in Squeak are not directives (though they can be used as
> directives) but a way to add metadata to a method. So the wikipedia page
> is irrelevant. If take a look at the class comment of Pragma, you'll
> feel more comfortable with them.
> (I think that we should convert all preferences to pragma-style. It could
> be a goal for 4.2.)
>
>>
>> Like Bert  I would like to see some discussion **on this issue, but
>> not too along as I would like to start using this feature asap.
>
> We should review both methods, consider the benefits and
> drawbacks and then make a decision.
>
>
> Levente
>
>>
>> Hannes
>>
>> ** The thread started by Bert at
>> http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149563.html
>>
>> -----------------------
>> Model subclass: #MyReallyNiceApplication
>> instanceVariableNames: ''
>> classVariableNames: ''
>> poolDictionaries: ''
>> category: 'MyMenuTests'!
>>
>> "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
>>
>> MyReallyNiceApplication class
>> instanceVariableNames: ''!
>>
>> !MyReallyNiceApplication class methodsFor: 'as yet unclassified'
>> stamp: 'hjh 4/26/2010 08:52'!
>> menuEntrySpecification
>> "Test to add another entyr in the Help menu"
>>
>>
>> ^MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
>> #contents 'Hello?'
>> #location #('Help' 'a subMenu' 'another subMenu')
>> #target MenuMorph #selector #inform: #arguments #('Hello World!!')
>> ))
>> ! !
>>
>>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Morphic-phite.429.mcz

Nicolas Cellier
2010/4/26 Hannes Hirzel <[hidden email]>:

> Thank you for the explanations. In particular reading the comment in
> the Pragma class was helpful. I feel now much more comfortable with
> the idea of using them. However I still think they are more related to
> VM primitives and configuration issues. The menu is a GUI related
> thing and having a MenuSpec feels somewhat more natural....
>
> --Hannes
>
> P.S. There are currently 854 methods which have a pragma in them.
>

That's why we should name them (Method) Annotation rather than Pragma...

Nicolas

> On 4/26/10, Levente Uzonyi <[hidden email]> wrote:
>> On Mon, 26 Apr 2010, Hannes Hirzel wrote:
>>
>>> Hello Philipp
>>>
>>> I took a fresh 4.1 image, updated it to 10012, and loaded
>>> Morphic-phite.429.mcz.
>>>
>>> As the comments were fine I was quickly able to write an example (code
>>> below).
>>>
>>> Then I had to choose 'Rebuild menus'
>>>
>>> It worked fine.
>>> The question is now (see another thread by Bert) if we should go or
>>> your solution (MenuSpec based) or the one by Steve Wessels (Pragma
>>> based).
>>
>> It's Balázs Kósi who implemented the registration method with pragmas
>> (http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149534.html
>> ).
>>
>>>
>>> I do not feel too comfortable with pragmas yet whereas the MenuSpec is
>>> something I easily understand. And in addition I have the gut feeling
>>> that pragmas are meant for some more basic things (a kind of compiler
>>> directive, see http://en.wikipedia.org/wiki/Directive_%28programming%29)
>>
>> Pragmas in Squeak are not directives (though they can be used as
>> directives) but a way to add metadata to a method. So the wikipedia page
>> is irrelevant. If take a look at the class comment of Pragma, you'll
>> feel more comfortable with them.
>> (I think that we should convert all preferences to pragma-style. It could
>> be a goal for 4.2.)
>>
>>>
>>> Like Bert  I would like to see some discussion **on this issue, but
>>> not too along as I would like to start using this feature asap.
>>
>> We should review both methods, consider the benefits and
>> drawbacks and then make a decision.
>>
>>
>> Levente
>>
>>>
>>> Hannes
>>>
>>> ** The thread started by Bert at
>>> http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149563.html
>>>
>>> -----------------------
>>> Model subclass: #MyReallyNiceApplication
>>>      instanceVariableNames: ''
>>>      classVariableNames: ''
>>>      poolDictionaries: ''
>>>      category: 'MyMenuTests'!
>>>
>>> "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
>>>
>>> MyReallyNiceApplication class
>>>      instanceVariableNames: ''!
>>>
>>> !MyReallyNiceApplication class methodsFor: 'as yet unclassified'
>>> stamp: 'hjh 4/26/2010 08:52'!
>>> menuEntrySpecification
>>>      "Test to add another entyr in the Help menu"
>>>
>>>
>>> ^MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
>>>              #contents 'Hello?'
>>>              #location #('Help' 'a subMenu' 'another subMenu')
>>>              #target MenuMorph #selector #inform: #arguments #('Hello World!!')
>>>              ))
>>> ! !
>>>
>>>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: The Inbox: Morphic-phite.429.mcz

Eliot Miranda-2


On Mon, Apr 26, 2010 at 5:26 AM, Nicolas Cellier <[hidden email]> wrote:
2010/4/26 Hannes Hirzel <[hidden email]>:
> Thank you for the explanations. In particular reading the comment in
> the Pragma class was helpful. I feel now much more comfortable with
> the idea of using them. However I still think they are more related to
> VM primitives and configuration issues. The menu is a GUI related
> thing and having a MenuSpec feels somewhat more natural....
>
> --Hannes
>
> P.S. There are currently 854 methods which have a pragma in them.
>

That's why we should name them (Method) Annotation rather than Pragma...

OK, so Pragma is bad; its historical from "primitive pragma".  But Annotation doesn't capture the potentially executable flavour of pragmas.  How about MethodMetaMessage?  (mmm, yum :) )  We could talk about meta-messages for short.  "Add a meta-message that does ..." etc...
 

Nicolas

> On 4/26/10, Levente Uzonyi <[hidden email]> wrote:
>> On Mon, 26 Apr 2010, Hannes Hirzel wrote:
>>
>>> Hello Philipp
>>>
>>> I took a fresh 4.1 image, updated it to 10012, and loaded
>>> Morphic-phite.429.mcz.
>>>
>>> As the comments were fine I was quickly able to write an example (code
>>> below).
>>>
>>> Then I had to choose 'Rebuild menus'
>>>
>>> It worked fine.
>>> The question is now (see another thread by Bert) if we should go or
>>> your solution (MenuSpec based) or the one by Steve Wessels (Pragma
>>> based).
>>
>> It's Balázs Kósi who implemented the registration method with pragmas
>> (http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149534.html
>> ).
>>
>>>
>>> I do not feel too comfortable with pragmas yet whereas the MenuSpec is
>>> something I easily understand. And in addition I have the gut feeling
>>> that pragmas are meant for some more basic things (a kind of compiler
>>> directive, see http://en.wikipedia.org/wiki/Directive_%28programming%29)
>>
>> Pragmas in Squeak are not directives (though they can be used as
>> directives) but a way to add metadata to a method. So the wikipedia page
>> is irrelevant. If take a look at the class comment of Pragma, you'll
>> feel more comfortable with them.
>> (I think that we should convert all preferences to pragma-style. It could
>> be a goal for 4.2.)
>>
>>>
>>> Like Bert  I would like to see some discussion **on this issue, but
>>> not too along as I would like to start using this feature asap.
>>
>> We should review both methods, consider the benefits and
>> drawbacks and then make a decision.
>>
>>
>> Levente
>>
>>>
>>> Hannes
>>>
>>> ** The thread started by Bert at
>>> http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149563.html
>>>
>>> -----------------------
>>> Model subclass: #MyReallyNiceApplication
>>>      instanceVariableNames: ''
>>>      classVariableNames: ''
>>>      poolDictionaries: ''
>>>      category: 'MyMenuTests'!
>>>
>>> "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
>>>
>>> MyReallyNiceApplication class
>>>      instanceVariableNames: ''!
>>>
>>> !MyReallyNiceApplication class methodsFor: 'as yet unclassified'
>>> stamp: 'hjh 4/26/2010 08:52'!
>>> menuEntrySpecification
>>>      "Test to add another entyr in the Help menu"
>>>
>>>
>>> ^MenuEntrySpec newForDockingBarFrom: (Dictionary newFromPairs: #(
>>>              #contents 'Hello?'
>>>              #location #('Help' 'a subMenu' 'another subMenu')
>>>              #target MenuMorph #selector #inform: #arguments #('Hello World!!')
>>>              ))
>>> ! !
>>>
>>>
>
>




Reply | Threaded
Open this post in threaded view
|

Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Andreas.Raab
On 4/26/2010 11:48 AM, Eliot Miranda wrote:
> OK, so Pragma is bad; its historical from "primitive pragma".  But
> Annotation doesn't capture the potentially executable flavour of
> pragmas.  How about MethodMetaMessage?  (mmm, yum :) )  We could talk
> about meta-messages for short. "Add a meta-message that does ..." etc...

But "primitive pragma" is every bit as wrong. A pragma is something that
gives the compiler information about the code without being code itself.
Primitives are't pragmas, primitives are *code* (if you don't believe
me, just remove all of them and see how that goes).

By definition, a "pragma" is an interface between the code and the
compiler, something where the code conveys meta-information to the
compiler. For example, this is a pragma (assuming the compiler
understands it):

foo
        <inline: true>

bar
        <tailcut: true>

The first one might instruct the compiler to generate the code for this
method inline, the second one to eliminate tail recursion.

None of these, however, are pragmas:

foo
        "Not a pragma since it's not for the compiler"
        <preference: 'Foo Preference'
          ...
        >

apiGetWindowFocus
        "Not a pragma since it's code"
        <apicall: ulong 'GetWindowFocus' (void)>

etc. I should also add that before the introduction of the so-called
"pragmas" there was only *code* used in the <> syntax (primitives and
FFI calls) and the change to allow non-code entities is something that,
although useful, still worries me because of the conceptual issues
associated with mixing code and non-code entities. We wouldn't even have
that discussion if <> just meant "code".

Cheers,
   - Andreas

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Igor Stasenko
On 26 April 2010 22:05, Andreas Raab <[hidden email]> wrote:

> On 4/26/2010 11:48 AM, Eliot Miranda wrote:
>>
>> OK, so Pragma is bad; its historical from "primitive pragma".  But
>> Annotation doesn't capture the potentially executable flavour of
>> pragmas.  How about MethodMetaMessage?  (mmm, yum :) )  We could talk
>> about meta-messages for short. "Add a meta-message that does ..." etc...
>
> But "primitive pragma" is every bit as wrong. A pragma is something that
> gives the compiler information about the code without being code itself.
> Primitives are't pragmas, primitives are *code* (if you don't believe me,
> just remove all of them and see how that goes).
>
> By definition, a "pragma" is an interface between the code and the compiler,
> something where the code conveys meta-information to the compiler. For
> example, this is a pragma (assuming the compiler understands it):
>
> foo
>        <inline: true>
>
> bar
>        <tailcut: true>
>
> The first one might instruct the compiler to generate the code for this
> method inline, the second one to eliminate tail recursion.
>
> None of these, however, are pragmas:
>
> foo
>        "Not a pragma since it's not for the compiler"
>        <preference: 'Foo Preference'
>          ...
>        >
>
> apiGetWindowFocus
>        "Not a pragma since it's code"
>        <apicall: ulong 'GetWindowFocus' (void)>
>
> etc. I should also add that before the introduction of the so-called
> "pragmas" there was only *code* used in the <> syntax (primitives and FFI
> calls) and the change to allow non-code entities is something that, although
> useful, still worries me because of the conceptual issues associated with
> mixing code and non-code entities. We wouldn't even have that discussion if
> <> just meant "code".
>

Pragmas are not code, even in old and limited forms, they simply
contain a meta-information for compiler.
If pragmas would be the code, then i expect them to look like code i.e.:
<[  | x y |  x := 5. y:= 6. x+y ] >

I treat a pragma as a message, sent to compiler/parser framework i.e.
whenever compiler sees:

< foo: a with: z bar: zork>

its can be simply interpreted as a message sent to compiler(or parser):
pragmaConsumer foo: a with: z bar: zork

where pragmaConsumer is an object which can do anything it wants for
taking this information into account, when processing the method's
source code.

Btw, it would be interesting to alter the compiler framework to
support that cleanly.
We can use a special class, PragmaProcessor , with all the messages like

PragmaProcessor >> primitive: aPrimitiveName module: aModuleName

and parser , in its #addPragma:  could simply do:


addPragma: aPragma
  properties := self properties copyWith: aPragma
"pragmaProcessor is a previously initialized PragmaProcessor instance"
(pragmaProcessor respondsTo: aPragma keyword ) ifTrue: [
  pragmaProcessor perform: aPragma keyword withArguments: aPragma arguments. ]

pragma processor then can call back the parser/compiler in case of
need (like adding a primitive literal,
setting a method's prim index etc), or do whatever extra it needs.

so, then we can keep a pragma processing code aside of parser/compiler
and extend it easily to support various stuff we may need.

> Cheers,
>  - Andreas
>

--
Best regards,
Igor Stasenko AKA sig.

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Andreas.Raab
On 4/26/2010 1:14 PM, Igor Stasenko wrote:

> On 26 April 2010 22:05, Andreas Raab<[hidden email]>  wrote:
>> On 4/26/2010 11:48 AM, Eliot Miranda wrote:
>>>
>>> OK, so Pragma is bad; its historical from "primitive pragma".  But
>>> Annotation doesn't capture the potentially executable flavour of
>>> pragmas.  How about MethodMetaMessage?  (mmm, yum :) )  We could talk
>>> about meta-messages for short. "Add a meta-message that does ..." etc...
>>
>> But "primitive pragma" is every bit as wrong. A pragma is something that
>> gives the compiler information about the code without being code itself.
>> Primitives are't pragmas, primitives are *code* (if you don't believe me,
>> just remove all of them and see how that goes).
>>
>> By definition, a "pragma" is an interface between the code and the compiler,
>> something where the code conveys meta-information to the compiler. For
>> example, this is a pragma (assuming the compiler understands it):
>>
>> foo
>>         <inline: true>
>>
>> bar
>>         <tailcut: true>
>>
>> The first one might instruct the compiler to generate the code for this
>> method inline, the second one to eliminate tail recursion.
>>
>> None of these, however, are pragmas:
>>
>> foo
>>         "Not a pragma since it's not for the compiler"
>>         <preference: 'Foo Preference'
>>           ...
>>         >
>>
>> apiGetWindowFocus
>>         "Not a pragma since it's code"
>>         <apicall: ulong 'GetWindowFocus' (void)>
>>
>> etc. I should also add that before the introduction of the so-called
>> "pragmas" there was only *code* used in the<>  syntax (primitives and FFI
>> calls) and the change to allow non-code entities is something that, although
>> useful, still worries me because of the conceptual issues associated with
>> mixing code and non-code entities. We wouldn't even have that discussion if
>> <>  just meant "code".
>>
>
> Pragmas are not code, even in old and limited forms, they simply
> contain a meta-information for compiler.

That is *precisely* what I said in the beginning: "A pragma is something
that gives the compiler information about the code without being code
itself". Here, I was referring to "<> syntax" which used to be code, and
now it no longer is. Calling it "pragma" however is just completely and
utterly wrong in whichever way you look at it.

> If pragmas would be the code, then i expect them to look like code i.e.:

I never claimed that that "pragmas are code". In fact, I said
*specifically* the opposite.

Cheers,
   - Andreas

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Bert Freudenberg
On 26.04.2010, at 22:41, Andreas Raab wrote:
>
> On 4/26/2010 1:14 PM, Igor Stasenko wrote:
>> On 26 April 2010 22:05, Andreas Raab<[hidden email]>  wrote:
>>> On 4/26/2010 11:48 AM, Eliot Miranda wrote:

I think that "method annotation" captures the meaning best of the alternatives mentioned so far.

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Igor Stasenko
In reply to this post by Andreas.Raab
On 26 April 2010 23:41, Andreas Raab <[hidden email]> wrote:

> On 4/26/2010 1:14 PM, Igor Stasenko wrote:
>>
>> On 26 April 2010 22:05, Andreas Raab<[hidden email]>  wrote:
>>>
>>> On 4/26/2010 11:48 AM, Eliot Miranda wrote:
>>>>
>>>> OK, so Pragma is bad; its historical from "primitive pragma".  But
>>>> Annotation doesn't capture the potentially executable flavour of
>>>> pragmas.  How about MethodMetaMessage?  (mmm, yum :) )  We could talk
>>>> about meta-messages for short. "Add a meta-message that does ..." etc...
>>>
>>> But "primitive pragma" is every bit as wrong. A pragma is something that
>>> gives the compiler information about the code without being code itself.
>>> Primitives are't pragmas, primitives are *code* (if you don't believe me,
>>> just remove all of them and see how that goes).
>>>
>>> By definition, a "pragma" is an interface between the code and the
>>> compiler,
>>> something where the code conveys meta-information to the compiler. For
>>> example, this is a pragma (assuming the compiler understands it):
>>>
>>> foo
>>>        <inline: true>
>>>
>>> bar
>>>        <tailcut: true>
>>>
>>> The first one might instruct the compiler to generate the code for this
>>> method inline, the second one to eliminate tail recursion.
>>>
>>> None of these, however, are pragmas:
>>>
>>> foo
>>>        "Not a pragma since it's not for the compiler"
>>>        <preference: 'Foo Preference'
>>>          ...
>>>        >
>>>
>>> apiGetWindowFocus
>>>        "Not a pragma since it's code"
>>>        <apicall: ulong 'GetWindowFocus' (void)>
>>>
>>> etc. I should also add that before the introduction of the so-called
>>> "pragmas" there was only *code* used in the<>  syntax (primitives and FFI
>>> calls) and the change to allow non-code entities is something that,
>>> although
>>> useful, still worries me because of the conceptual issues associated with
>>> mixing code and non-code entities. We wouldn't even have that discussion
>>> if
>>> <>  just meant "code".
>>>
>>
>> Pragmas are not code, even in old and limited forms, they simply
>> contain a meta-information for compiler.
>
> That is *precisely* what I said in the beginning: "A pragma is something
> that gives the compiler information about the code without being code
> itself". Here, I was referring to "<> syntax" which used to be code, and now
> it no longer is. Calling it "pragma" however is just completely and utterly
> wrong in whichever way you look at it.
>
>> If pragmas would be the code, then i expect them to look like code i.e.:
>
> I never claimed that that "pragmas are code". In fact, I said *specifically*
> the opposite.
>

Ok, then i wonder, what is the subject of discussion?
If its only about terminology, then its not interesting. We may call
it pragma, method annotation or whatever.
I think that more improtant is how we handling it and what we can do with it.

> Cheers,
>  - Andreas
>
>



--
Best regards,
Igor Stasenko AKA sig.

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Hannes Hirzel
On 4/26/10, Igor Stasenko <[hidden email]> wrote:
> Ok, then i wonder, what is the subject of discussion?
> If its only about terminology, then its not interesting. We may call
> it pragma, method annotation or whatever.
> I think that more improtant is how we handling it and what we can do with
> it.
>

The subject of the discussion is that we need a clear concept what
pragmas are and what they are not. Concepts have names. The names
invoke the concepts in people's minds. And the names have
connotations. It is about communication to get understood.

OK, this discussion diverts. The point of departure is that we need to
decide if we want the MenuRegistry to be pragma based or MenuSpec
based.

This leads me to think that for the MenuRegistry I prefer MenuSpecs
(which I actually did before).

So let's move ahead please and have somebody of the commiters put the
MenuRegistry in the trunk. Philipp Tessenow has posted his third
version** of the MenuRegistry today to the inbox. May I ask one of the
commiters to have a look at it please and if there are no strong
objections commit it to the trunk?

** http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149641.html

--Hannes

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Bert Freudenberg
On 26.04.2010, at 23:13, Hannes Hirzel wrote:

>
> On 4/26/10, Igor Stasenko <[hidden email]> wrote:
>> Ok, then i wonder, what is the subject of discussion?
>> If its only about terminology, then its not interesting. We may call
>> it pragma, method annotation or whatever.
>> I think that more improtant is how we handling it and what we can do with
>> it.
>>
>
> The subject of the discussion is that we need a clear concept what
> pragmas are and what they are not. Concepts have names. The names
> invoke the concepts in people's minds. And the names have
> connotations. It is about communication to get understood.
>
> OK, this discussion diverts. The point of departure is that we need to
> decide if we want the MenuRegistry to be pragma based or MenuSpec
> based.
>
> This leads me to think that for the MenuRegistry I prefer MenuSpecs
> (which I actually did before).
>
> So let's move ahead please and have somebody of the commiters put the
> MenuRegistry in the trunk. Philipp Tessenow has posted his third
> version** of the MenuRegistry today to the inbox. May I ask one of the
> commiters to have a look at it please and if there are no strong
> objections commit it to the trunk?
>
> ** http://lists.squeakfoundation.org/pipermail/squeak-dev/2010-April/149641.html
>
> --Hannes

This discussion is quite separate from the menu definitions, so please do not mix the two.

In the other thread I felt the general opinion was leaning towards the annotation-based variant of Balázs.

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Andreas.Raab
In reply to this post by Igor Stasenko
On 4/26/2010 1:56 PM, Igor Stasenko wrote:
>>> If pragmas would be the code, then i expect them to look like code i.e.:
>>
>> I never claimed that that "pragmas are code". In fact, I said *specifically*
>> the opposite.
>>
>
> Ok, then i wonder, what is the subject of discussion?

The subject of the post was an attempt to clarify what pragmas are and
what they aren't. Given that even Eliot is confused about it by
referring to "primitive pragmas" that seemed worthwhile all by itself.

> If its only about terminology, then its not interesting. We may call
> it pragma, method annotation or whatever.
> I think that more improtant is how we handling it and what we can do with it.

Terminology is important and the terminology we currently have is
*extremely* confusing. People refer to "pragmas" and whenever a third
party hears that they think "oh, compiler stuff, better stay away from
it" not realizing that that's not what these are. This is how this
discussion started after all.

Cheers,
   - Andreas

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Igor Stasenko
On 27 April 2010 00:23, Andreas Raab <[hidden email]> wrote:

> On 4/26/2010 1:56 PM, Igor Stasenko wrote:
>>>>
>>>> If pragmas would be the code, then i expect them to look like code i.e.:
>>>
>>> I never claimed that that "pragmas are code". In fact, I said
>>> *specifically*
>>> the opposite.
>>>
>>
>> Ok, then i wonder, what is the subject of discussion?
>
> The subject of the post was an attempt to clarify what pragmas are and what
> they aren't. Given that even Eliot is confused about it by referring to
> "primitive pragmas" that seemed worthwhile all by itself.
>
>> If its only about terminology, then its not interesting. We may call
>> it pragma, method annotation or whatever.
>> I think that more improtant is how we handling it and what we can do with
>> it.
>
> Terminology is important and the terminology we currently have is
> *extremely* confusing. People refer to "pragmas" and whenever a third party
> hears that they think "oh, compiler stuff, better stay away from it" not
> realizing that that's not what these are. This is how this discussion
> started after all.
>
Ok.
Observing a Squeak's history i seen an attempts to allow methods to
use an arbitrary objects
as literals. Or, by analogy, a method's properties can carry any
objects you may need.
I thinks this is a most generic form of what current 'pragmas' could evolve to.
So, from this point of view, pragmas is a subset of 'additional
arbitrary method state', which having a formally
defined structure 'instance of Pragma class'.

> Cheers,
>  - Andreas
>


--
Best regards,
Igor Stasenko AKA sig.

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

LawsonEnglish
In reply to this post by Andreas.Raab
Andreas Raab wrote:

> On 4/26/2010 1:56 PM, Igor Stasenko wrote:
>>>> If pragmas would be the code, then i expect them to look like code
>>>> i.e.:
>>>
>>> I never claimed that that "pragmas are code". In fact, I said
>>> *specifically*
>>> the opposite.
>>>
>>
>> Ok, then i wonder, what is the subject of discussion?
>
> The subject of the post was an attempt to clarify what pragmas are and
> what they aren't. Given that even Eliot is confused about it by
> referring to "primitive pragmas" that seemed worthwhile all by itself.
>
>> If its only about terminology, then its not interesting. We may call
>> it pragma, method annotation or whatever.
>> I think that more improtant is how we handling it and what we can do
>> with it.
>
> Terminology is important and the terminology we currently have is
> *extremely* confusing. People refer to "pragmas" and whenever a third
> party hears that they think "oh, compiler stuff, better stay away from
> it" not realizing that that's not what these are. This is how this
> discussion started after all.
>
>
Could take a page from QM and just refer to "<>" as Bra-Ket notation...

:-)

Lawson


Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Hannes Hirzel
I do not really understand this joke in particular as Andreas writes

<citation>Terminology is important and the terminology we currently
have is *extremely* confusing. People refer to "pragmas" and whenever
a third party hears that they think "oh, compiler stuff, better stay
away from it" not realizing that that's not what these are. This is
how this discussion started after all.</citation>

I agree with him. Please note the workd 'extremly'. And that is why I
am reluctant having these pragmas 'crawl' into menu definitions.

As I have seen so far
- Pragmas are used in connection with primitives
- they are used in connection with package versions.

Therefore I do not see a need to connect them to menus.

Bert, if you insist on having them for the menus then we need to add
comments explaining that once more the Smalltalk community has gone
for another idiosyncratic term.

--Hannes

On 4/26/10, Lawson English <[hidden email]> wrote:

> Andreas Raab wrote:
>> On 4/26/2010 1:56 PM, Igor Stasenko wrote:
>>>>> If pragmas would be the code, then i expect them to look like code
>>>>> i.e.:
>>>>
>>>> I never claimed that that "pragmas are code". In fact, I said
>>>> *specifically*
>>>> the opposite.
>>>>
>>>
>>> Ok, then i wonder, what is the subject of discussion?
>>
>> The subject of the post was an attempt to clarify what pragmas are and
>> what they aren't. Given that even Eliot is confused about it by
>> referring to "primitive pragmas" that seemed worthwhile all by itself.
>>
>>> If its only about terminology, then its not interesting. We may call
>>> it pragma, method annotation or whatever.
>>> I think that more improtant is how we handling it and what we can do
>>> with it.
>>
>> Terminology is important and the terminology we currently have is
>> *extremely* confusing. People refer to "pragmas" and whenever a third
>> party hears that they think "oh, compiler stuff, better stay away from
>> it" not realizing that that's not what these are. This is how this
>> discussion started after all.
>>
>>
> Could take a page from QM and just refer to "<>" as Bra-Ket notation...
>
> :-)
>
> Lawson
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Bert Freudenberg
On 27.04.2010, at 00:21, Hannes Hirzel wrote:
>
>> Terminology is important and the terminology we currently
>> have is *extremely* confusing.
>
> And that is why I am reluctant having these pragmas 'crawl' into menu definitions.

Now that's just silly, sorry. Nobody is questioning the utility of these guys, whatever we call them.

- Bert -



Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Hannes Hirzel
Bert,

To be precise, _you_ say it is silly. _I_ say it's not. You call them
"guys" because it seems that you do dare anymore to use their name....

Yes, I do not question the usefulness of pragmas for what they have
been used so far. Primitives and version control related things. I
oppose to use them in addition for menu definitions.

In your conversation so far you used the term 'method-annotations' as
a synonym for pragma.
This is interesting and might lead to a solution for this discussion.

It's about 'conceptualisation'. Overloading a concept with too many
meanings was never a good idea in system design.

And: to me the code for the menu definitions looks ugly. A kind of
assembler like, lisp-s expression thing with a lot of implied
assumptions.

The MenuSpec is a straighforward thing. And I think it is more
appealing for the younger generation.

I think I have said now enough about this issue and will not comment
on this anymore.

The practical problem we are currently facing with Squeak 4.1 is that
it cannot display pictures in the the file browser and that adding
entries to the menu is not possible in a clean way.

--Hannes

On 4/26/10, Bert Freudenberg <[hidden email]> wrote:

> On 27.04.2010, at 00:21, Hannes Hirzel wrote:
>>
>>> Terminology is important and the terminology we currently
>>> have is *extremely* confusing.
>>
>> And that is why I am reluctant having these pragmas 'crawl' into menu
>> definitions.
>
> Now that's just silly, sorry. Nobody is questioning the utility of these
> guys, whatever we call them.
>
> - Bert -
>
>
>
>

Reply | Threaded
Open this post in threaded view
|

Re: Pragmas (Re: The Inbox: Morphic-phite.429.mcz)

Andreas.Raab
In reply to this post by Bert Freudenberg
On 4/26/2010 3:29 PM, Bert Freudenberg wrote:
> On 27.04.2010, at 00:21, Hannes Hirzel wrote:
>>
>>> Terminology is important and the terminology we currently
>>> have is *extremely* confusing.
>>
>> And that is why I am reluctant having these pragmas 'crawl' into menu definitions.
>
> Now that's just silly, sorry. Nobody is questioning the utility of these guys, whatever we call them.

Indeed. Nobody is questioning the utility. Personally, I still find
"method property" to be the best name since it doesn't presume whether
the property has an impact on code or not. A primitive can be a method
property that represents code, a pragma can be a property that
represents a compiler instruction, an annotation can be a property that
is used for discovery.

Cheers,
   - Andreas

1234