[BUG] all category of System Browser

ohshima at is.titech.ac.jp ohshima at is.titech.ac.jp
Wed May 12 17:00:21 UTC 1999


  Hi,

  I found the "-- all --" category is useful.  However, I
also found that my work was gone when I tried to save a
method with compile errors.  It happened when I selected the
category.

  Doing the following in the system browser will
reproduce the error:

  1.  select the "all" category for a class, type a
      new method definition which will cause compile error,
      and save.
  2.  select the category, select a method, then insert a compile
      error and save. 
  3.  select the category, type a method definition which
      already exists, (and enbug), and save.

  Attached is a (quite dirty) workaround for this problem.
A better fix should be presented:-)

                                             OHSHIMA Yoshiki
                Dept. of Mathematical and Computing Sciences
                               Tokyo Institute of Technology 


'From Squeak 2.4c of May 10, 1999 on 13 May 1999 at 1:53:11 am'!

!Browser methodsFor: 'accessing' stamp: 'yo 5/13/1999 01:48'!
contents: input notifying: aController 
	"The retrieved information has changed and its source must now be
	 updated. The information can be a variety of things, depending on
	 the list selections (such as templates for class or message definition,
	 methods) or the user menu commands (such as definition, comment,
	 hierarchy).  Answer the result of updating the source."
	| aString aText theClass result selectedName |
	aString _ input asString.
	aText _ input asText.
	editSelection == #editSystemCategories ifTrue: [^ self changeSystemCategories: aString].
	editSelection == #editClass | (editSelection == #newClass) ifTrue: [^ self defineClass: aString notifying: aController].
	editSelection == #editComment
		ifTrue: 
			[theClass _ self selectedClass.
			theClass
				ifNil: 
					[PopUpMenu notify: 'You must select a class
before giving it a comment.'.
					^ false].
			theClass comment: aText stamp: Utilities changeStamp.
			^ true].
	editSelection == #hierarchy ifTrue: [^ true].
	editSelection == #editMessageCategories ifTrue: [^ self changeMessageCategories: aString].
	editSelection == #editMessage | (editSelection == #newMessage)
		ifTrue: [((selectedName _ self selectedMessageCategoryName) ~= nil and: 					[selectedName asSymbol = ClassOrganizer allCategory])
				ifTrue: 
					["User tried to save a new method while the ALL category 
					         was selected"
					editSelection == #newMessage
						ifTrue: [self selectUnclassifiedCategory]
						ifFalse: [self selectOriginalCategoryForCurrentMethod].
					result _ self defineMessage: aText notifying: aController.
					self changed: #messageCategoryList.
					^ result]
				ifFalse: [
					^ self defineMessage: aText notifying: aController]].
	editSelection == #none
		ifTrue: 
			[PopUpMenu notify: 'This text cannot be accepted
in this part of the browser.'.
			^ false].
	self error: 'unacceptable accept'! !

!Browser methodsFor: 'message category list' stamp: 'yo 5/13/1999 00:28'!
selectMessageCategoryNamed: aSymbol 
	"Given aSymbol, select the category with that name.  Do nothing if 
	aSymbol doesn't exist."
	| index |
	(self messageCategoryList includes: aSymbol)
		ifFalse: [^ self].
	index _ self messageCategoryList indexOf: aSymbol.
	"self messageCategoryListIndex: index."
	messageCategoryListIndex _ index.
	messageListIndex _ 0.
	self changed: #messageCategorySelectionChanged.
	self changed: #messageCategoryListIndex.	"update my selection"
	self changed: #messageList.
	"self changed: #contents."
! !

!Browser methodsFor: 'message category list' stamp: 'yo 5/12/1999 23:57'!
selectUnclassifiedCategory
	"Select the unclassified category."

	"self messageCategoryListIndex: 0"
	messageCategoryListIndex _ 0.
	messageListIndex _ 0.
	self changed: #messageCategorySelectionChanged.
	self changed: #messageCategoryListIndex.	"update my selection"
	self changed: #messageList.
	"self changed: #contents."
! !

!Browser methodsFor: 'message list' stamp: 'yo 5/13/1999 01:50'!
selectedMessage
	"Answer a copy of the source code for the selected message selector."
	| class selector method tempNames |
	contents == nil ifFalse: [^ contents copy].
	class _ self selectedClassOrMetaClass.
	selector _ self selectedMessageName.
	selector ifNil: [^''].
	method _ class compiledMethodAt: selector.

	(Sensor controlKeyPressed
		or: [method fileIndex > 0 and: [(SourceFiles at: method fileIndex) == nil]])
		ifTrue:
		["Emergency or no source file -- decompile without temp names"
		contents _ (class decompilerClass new decompile: selector in: class method: method)
			decompileString.
		^ contents copy].

	Sensor leftShiftDown ifTrue:
		["Special request to decompile -- get temps from source file"
		tempNames _ (class compilerClass new
						parse: method getSourceFromFile asString in: class notifying: nil)
						tempNames.
		contents _ ((class decompilerClass new withTempNames: tempNames)
				decompile: selector in: class method: method) decompileString.
		contents _ contents asText makeSelectorBoldIn: class.
		^ contents copy].

	contents _ class sourceCodeAt: selector.
	Preferences browseWithPrettyPrint ifTrue:
		[contents _ class compilerClass new
			format: contents in: class notifying: nil].
	contents _ contents asText makeSelectorBoldIn: class.
	^ contents copy! !





More information about the Squeak-dev mailing list