[Pkg] The Trunk: Tools-dtl.145.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Dec 9 22:52:07 UTC 2009


David T. Lewis uploaded a new version of Tools to project The Trunk:
http://source.squeak.org/trunk/Tools-dtl.145.mcz

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

Name: Tools-dtl.145
Author: dtl
Time: 9 December 2009, 5:48:42 am
UUID: 955bc68c-2eb4-4753-98df-2b98f2e9d17a
Ancestors: Tools-ar.144

Update CodeHolder to allow registration of new code pane display modes in browsers. This change enables SlangBrowser (VMMaker package) to display translated C code in browsers.

Note: The label text on the "source" button for browsers is not properly updated when the edit pane mode is changed. This is an existing bug, not affected by these changes.


=============== Diff against Tools-ar.144 ===============

Item was changed:
  ----- Method: CodeHolder>>okayToAccept (in category 'misc') -----
  okayToAccept
  	"Answer whether it is okay to accept the receiver's input"
  
  	self showingDocumentation ifTrue:
  		[self inform: 
  'Sorry, for the moment you can
  only submit changes here when
  you are showing source.  Later, you
  will be able to edit the isolated comment
  here and save it back, but only if YOU
  implement it!!.'.
  		^ false].
  
+ 	self showingEditContentsOption ifTrue:
+ 		[self inform: 'Cannot accept ', self contentsSymbol, ' input'.
+ 		^ false].
+ 
  	self showingAnyKindOfDiffs ifFalse:
  		[^ true]. 
  	^ (UIManager default chooseFrom: {
  		'accept anyway -- I''ll take my chances'.
  		'um, let me reconsider'.
  	} title:
  'Caution!!  You are "showing diffs" here, so 
  there is a danger that some of the text in the
  code pane is contaminated by the "diff" display') = 1!

Item was added:
+ ----- Method: CodeHolder class>>addContentsSymbolQuint:afterEntry: (in category 'controls') -----
+ addContentsSymbolQuint: quint afterEntry: aSymbol 
+ 	"Register a menu selection item in the position after the entry with
+ 	selection symbol aSymbol."
+ 
+ 	"CodeHolder
+ 		addContentsSymbolQuint: #(#altSyntax #toggleAltSyntax #showingAltSyntaxString 'altSyntax' 'alternative syntax')
+ 		afterEntry: #colorPrint"
+ 
+ 	| entry |
+ 	ContentsSymbolQuints
+ 		detect: [:e | (e isKindOf: Collection) and: [e first = quint first]]
+ 		ifNone: [entry := ContentsSymbolQuints
+ 						detect: [:e | (e isKindOf: Collection) and: [e first = aSymbol]].
+ 			ContentsSymbolQuints add: quint after: entry.
+ 			^ self].
+ 	self notify: 'entry already exists for ', quint first!

Item was changed:
  StringHolder subclass: #CodeHolder
  	instanceVariableNames: 'currentCompiledMethod contentsSymbol'
+ 	classVariableNames: 'ContentsSymbolQuints EditContentsOptions'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Tools-Base'!
  
  !CodeHolder commentStamp: '<historical>' prior: 0!
  An ancestor class for all models which can show code.  Eventually, much of the code that currently resides in StringHolder which only applies to code-holding StringHolders might get moved down here.!

Item was added:
+ ----- Method: CodeHolder class>>removeContentsSymbol: (in category 'controls') -----
+ removeContentsSymbol: aSymbol 
+ 	"Unregister the menu selection item with selection symbol aSymbol."
+ 
+ 	"CodeHolder removeContentsSymbol: #altSyntax"
+ 
+ 	| entries |
+ 	entries := ContentsSymbolQuints
+ 		select: [:e | (e isKindOf: Collection) and: [e first = aSymbol]].
+ 	ContentsSymbolQuints removeAll: entries.
+ 	^ entries
+ !

Item was added:
+ ----- Method: CodeHolder class>>initialize (in category 'class initialization') -----
+ initialize
+ 
+ 	"CodeHolder initialize"
+ 
+ 	ContentsSymbolQuints := self defaultContentsSymbolQuints asOrderedCollection.
+ 	EditContentsOptions := Dictionary new.
+ 	self defaultEditContentsOptions
+ 		do: [:opt | EditContentsOptions at: opt key put: opt value]!

Item was changed:
  ----- Method: MessageSet>>contents (in category 'contents') -----
  contents
  	"Answer the contents of the receiver"
  
  	^ contents == nil
  		ifTrue: [currentCompiledMethod := nil. '']
  		ifFalse: [messageListIndex = 0 
  			ifTrue: [currentCompiledMethod := nil. contents]
+ 			ifFalse: [self editContents]]!
- 			ifFalse: [self showingByteCodes
- 				ifTrue: [self selectedBytecodes]
- 				ifFalse: [self selectedMessage]]]!

Item was added:
+ ----- Method: CodeHolder class>>defaultEditContentsOptions (in category 'controls') -----
+ defaultEditContentsOptions
+ 	"An array of associations of current display mode symbol to selector
+ 	that creates the edit contents for that display mode. The default selector
+ 	is #selectedMessage; this is a list of alternative to the default."
+ 
+ 	^ {
+ 		#byteCodes -> #selectedBytecodes
+ 	}!

Item was changed:
  ----- Method: Browser>>contents (in category 'accessing') -----
  contents
  	"Depending on the current selection, different information is retrieved.
  	Answer a string description of that information. This information is the
  	method of the currently selected class and message."
  
  	| comment theClass latestCompiledMethod |
  	latestCompiledMethod := currentCompiledMethod.
  	currentCompiledMethod := nil.
  
  	editSelection == #newTrait
  		ifTrue: [^Trait newTemplateIn: self selectedSystemCategoryName].
  	editSelection == #none ifTrue: [^ ''].
  	editSelection == #editSystemCategories 
  		ifTrue: [^ systemOrganizer printString].
  	editSelection == #newClass 
  		ifTrue: [^ (theClass := self selectedClass)
  			ifNil:
  				[Class template: self selectedSystemCategoryName]
  			ifNotNil:
  				[Class templateForSubclassOf: theClass category: self selectedSystemCategoryName]].
  	editSelection == #editClass 
  		ifTrue: [^self classDefinitionText].
  	editSelection == #editComment 
  		ifTrue:
  			[(theClass := self selectedClass) ifNil: [^ ''].
  			comment := theClass comment.
  			currentCompiledMethod := theClass organization commentRemoteStr.
  			^ comment size = 0
  				ifTrue: ['This class has not yet been commented.']
  				ifFalse: [comment]].
  	editSelection == #hierarchy 
  		ifTrue: [
  			self selectedClassOrMetaClass isTrait
  				ifTrue: [^'']
  				ifFalse: [^self selectedClassOrMetaClass printHierarchy]].
  	editSelection == #editMessageCategories 
  		ifTrue: [^ self classOrMetaClassOrganizer printString].
  	editSelection == #newMessage
  		ifTrue:
  			[^ (theClass := self selectedClassOrMetaClass) 
  				ifNil: ['']
  				ifNotNil: [theClass sourceCodeTemplate]].
  	editSelection == #editMessage
  		ifTrue:
+ 			[^ self editContentsWithDefault:
+ 				[currentCompiledMethod := latestCompiledMethod.
+ 				self selectedMessage]].
- 			[self showingByteCodes ifTrue: [^ self selectedBytecodes].
- 			currentCompiledMethod := latestCompiledMethod.
- 			^ self selectedMessage].
  
  	self error: 'Browser internal error: unknown edit selection.'!

Item was added:
+ ----- Method: CodeHolder class>>defaultContentsSymbolQuints (in category 'controls') -----
+ defaultContentsSymbolQuints
+ 	"Default list of quintuplets representing information on the alternative views available in the code pane
+ 		first element:	the contentsSymbol used
+ 		second element:	the selector to call when this item is chosen.
+ 		third element:	the selector to call to obtain the wording of the menu item.
+ 		fourth element:	the wording to represent this view
+ 		fifth element:	balloon help
+ 	A hypen indicates a need for a seperator line in a menu of such choices"
+ 
+ 	^ {
+ 		{#source
+ 			. #togglePlainSource 
+ 			. #showingPlainSourceString 
+ 			. 'source'
+ 			. 'the textual source code as written' translated} .
+ 		{#documentation
+ 			. #toggleShowDocumentation
+ 			. #showingDocumentationString
+ 			. 'documentation'
+ 			. 'the first comment in the method' translated} .
+ 
+ 		#- .
+ 		{#prettyPrint
+ 			. #togglePrettyPrint
+ 			. #prettyPrintString
+ 			. 'prettyPrint'
+ 			. 'the method source presented in a standard text format' translated} .
+ 
+ 		#- .
+ 		{#showDiffs
+ 			. #toggleRegularDiffing
+ 			. #showingRegularDiffsString
+ 			. 'showDiffs'
+ 			. 'the textual source diffed from its prior version' translated} .
+ 
+ 		#- .
+ 		{#decompile
+ 			. #toggleDecompile
+ 			. #showingDecompileString
+ 			. 'decompile'
+ 			. 'source code decompiled from byteCodes' translated} .
+ 		{#byteCodes
+ 			. #toggleShowingByteCodes
+ 			. #showingByteCodesString
+ 			. 'byteCodes'	
+ 			. 'the bytecodes that comprise the compiled method' translated} .
+ 
+ 		#- .
+ 		{#tiles
+ 			. #toggleShowingTiles
+ 			. #showingTilesString
+ 			. 'tiles'
+ 			. 'universal tiles representing the method' translated}
+ 	}!

Item was added:
+ ----- Method: CodeHolder class>>addContentsSymbolQuint:afterPosition: (in category 'controls') -----
+ addContentsSymbolQuint: quint afterPosition: index
+ 	"Register a menu selection item in the position after index."
+ 
+ 	"CodeHolder
+ 		addContentsSymbolQuint: #(#altSyntax #toggleAltSyntax #showingAltSyntaxString 'altSyntax' 'alternative syntax')
+ 		afterPosition: 1"
+ 
+ 	| entry |
+ 	entry := ContentsSymbolQuints at: index.
+ 	self contentsSymbolQuints add: quint after: entry!

Item was added:
+ ----- Method: CodeHolder>>editContents (in category 'contents') -----
+ editContents
+ 
+ 	^ self editContentsWithDefault: [self selectedMessage]
+ !

Item was added:
+ ----- Method: CodeHolder>>showingEditContentsOption (in category 'what to show') -----
+ showingEditContentsOption
+ 	"True if any of the optional EditContentsOptions modes is in effect. This
+ 	includes bytecode display and possibly other display modes."
+ 
+ 	^ EditContentsOptions includesKey: self contentsSymbol
+ !

Item was added:
+ ----- Method: CodeHolder class>>addEditContentsOption: (in category 'controls') -----
+ addEditContentsOption: anAssociation
+ 
+ 	"CodeHolder addEditContentsOption: #translateToC -> #selectedTranslateToC"
+ 
+ 	EditContentsOptions add: anAssociation!

Item was added:
+ ----- Method: CodeHolder>>editContentsWithDefault: (in category 'contents') -----
+ editContentsWithDefault: aBlock
+ 
+ 	| selector |
+ 	selector := EditContentsOptions
+ 		at: self contentsSymbol
+ 		ifAbsent: [^ aBlock value].
+ 	^ self perform: selector
+ !

Item was changed:
  ----- Method: CodeHolder>>contentsSymbolQuints (in category 'controls') -----
  contentsSymbolQuints
  	"Answer a list of quintuplets representing information on the alternative views available in the code pane
  		first element:	the contentsSymbol used
  		second element:	the selector to call when this item is chosen.
  		third element:	the selector to call to obtain the wording of the menu item.
  		fourth element:	the wording to represent this view
  		fifth element:	balloon help
  	A hypen indicates a need for a seperator line in a menu of such choices"
  
+ 	^ ContentsSymbolQuints!
- 	^ #(
- (source			togglePlainSource 			showingPlainSourceString	'source'		'the textual source code as written')
- (documentation	toggleShowDocumentation	showingDocumentationString	'documentation'		'the first comment in the method')
- -
- (prettyPrint		togglePrettyPrint 			prettyPrintString			'prettyPrint'			'the method source presented in a standard text format')
- -
- (showDiffs		toggleRegularDiffing		showingRegularDiffsString	'showDiffs'				'the textual source diffed from its prior version')
- (prettyDiffs		togglePrettyDiffing			showingPrettyDiffsString	'prettyDiffs'		'formatted textual source diffed from formatted form of prior version')
- -
- (decompile		toggleDecompile				showingDecompileString		'decompile'			'source code decompiled from byteCodes')
- (byteCodes		toggleShowingByteCodes		showingByteCodesString		'byteCodes'			'the bytecodes that comprise the compiled method')
- -
- (tiles			toggleShowingTiles 			showingTilesString			'tiles'				'universal tiles representing the method'))!



More information about the Packages mailing list