[squeak-dev] Squeak 4.6: ST80Tools-cmm.8.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jun 5 20:19:19 UTC 2015


Chris Muller uploaded a new version of ST80Tools to project Squeak 4.6:
http://source.squeak.org/squeak46/ST80Tools-cmm.8.mcz

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

Name: ST80Tools-cmm.8
Author: cmm
Time: 21 April 2015, 4:49:40.23 pm
UUID: 1d69716a-4a2c-44e6-9bae-2613b5590947
Ancestors: ST80Tools-mt.7

Fix underscore assignment.

==================== Snapshot ====================

----- Method: ParagraphEditor>>browseChangeSetsWithSelector (in category '*ST80Tools') -----
browseChangeSetsWithSelector
	"Determine which, if any, change sets have at least one change for the selected selector, independent of class"

	| aSelector |
	self lineSelectAndEmptyCheck: [^ self].
	(aSelector := self selectedSelector) == nil ifTrue: [^ view flash].
	self terminateAndInitializeAround: [ChangeSorter browseChangeSetsWithSelector: aSelector]!

----- Method: ParagraphEditor>>browseItHere (in category '*ST80Tools') -----
browseItHere
	"Retarget the receiver's window to look at the selected class, if appropriate.  3/1/96 sw"
	| aSymbol b |
	(((b := model) isKindOf: Browser) and: [b couldBrowseAnyClass])
		ifFalse: [^ view flash].
	model okToChange ifFalse: [^ view flash].
	self selectionInterval isEmpty ifTrue: [self selectWord].
	(aSymbol := self selectedSymbol) ifNil: [^ view flash].

	self terminateAndInitializeAround:
		[| foundClass |
		foundClass := (Smalltalk at: aSymbol ifAbsent: [nil]).
			foundClass ifNil: [^ view flash].
			(foundClass isKindOf: Class)
				ifTrue:
					[model selectSystemCategory: foundClass category.
		model classListIndex: (model classList indexOf: foundClass name)]]!

----- Method: ParagraphEditor>>debug:receiver:in: (in category '*ST80Tools') -----
debug: aCompiledMethod receiver: anObject in: evalContext

	| guineaPig debugger debuggerWindow context |
	guineaPig :=
		[aCompiledMethod
			valueWithReceiver: anObject
			 arguments: (evalContext ifNil: [ #() ] ifNotNil: [ { evalContext } ]).
		 guineaPig := nil "spot the return from aCompiledMethod"] newProcess.
	context := guineaPig suspendedContext.
	debugger := Debugger new
		process: guineaPig
		controller: ((Smalltalk isMorphic not and: [ScheduledControllers inActiveControllerProcess]) ifTrue:
						[ScheduledControllers activeController])
		context: context.
	debuggerWindow := debugger openFullNoSuspendLabel: 'Debug it'.
	"Now step into the expression.  But if it is quick (is implemented as a primtiive, e.g. `0')
	 it will return immediately back to the block that is sent newProcess above.  Guard
	 against that with the check for home being thisContext."
	[debugger interruptedContext method == aCompiledMethod]
		whileFalse:
			[(guineaPig isNil
			  and: [debugger interruptedContext home == thisContext]) ifTrue:
				[debuggerWindow controller closeAndUnschedule.
				 UIManager default inform: 'Nothing to debug; expression is optimized'.
				 ^self].
			debugger send]!

----- Method: ParagraphEditor>>debugIt (in category '*ST80Tools') -----
debugIt

	| method receiver context |
	(model respondsTo: #doItReceiver) 
		ifTrue: 
			[receiver := model doItReceiver.
			context := model doItContext]
		ifFalse:
			[receiver := context := nil].
	self lineSelectAndEmptyCheck: [^self].
	method := self compileSelectionFor: receiver in: context.
	method notNil ifTrue:
		[self debug: method receiver: receiver in: context].!

----- Method: StringHolderView>>canHaveUnacceptedEdits (in category '*ST80Tools-multi-window support') -----
canHaveUnacceptedEdits
	"Answer if the receiver is an object that can hold unaccepted edits (such as a text editor widget)"

	^true!

----- Method: StringHolderView>>unacceptedEditState (in category '*ST80Tools-multi-window support') -----
unacceptedEditState
	^hasUnacceptedEdits ifTrue: [displayContents text]!

----- Method: StringHolderView>>unacceptedEditState: (in category '*ST80Tools-multi-window support') -----
unacceptedEditState: stateOrNil
	(hasUnacceptedEdits := stateOrNil notNil) ifTrue:
		[self editString: stateOrNil]!

----- Method: ScreenController>>browseRecentLog (in category '*ST80Tools') -----
browseRecentLog
	"Open a changelist browser on changes submitted since the last snapshot.  1/17/96 sw"

	ChangeList browseRecentLog!

----- Method: ScreenController>>chooseDirtyBrowser (in category '*ST80Tools') -----
chooseDirtyBrowser
	"Put up a list of browsers with unsubmitted edits and activate the one selected by the user, if any."
	"ScheduledControllers screenController chooseDirtyBrowser"

	ScheduledControllers findWindowSatisfying:
		[:c | (c model isKindOf: Browser) and: [c model canDiscardEdits not]].
 !

----- Method: ScreenController>>openChangeManager (in category '*ST80Tools') -----
openChangeManager
	"Open a dual change sorter.  For looking at two change sets at once."
	DualChangeSorter new open!

----- Method: ScreenController>>openFile (in category '*ST80Tools') -----
openFile
	FileList openFileDirectly!

----- Method: ScreenController>>openFileList (in category '*ST80Tools') -----
openFileList
	"Create and schedule a FileList view for specifying files to access."

	FileList openInMVC!

----- Method: ScreenController>>openPackageBrowser (in category '*ST80Tools') -----
openPackageBrowser 
	"Create and schedule a Browser view for browsing code."

	PackagePaneBrowser openBrowser!

----- Method: ScreenController>>openSelectorBrowser (in category '*ST80Tools') -----
openSelectorBrowser
	"Create and schedule a selector fragment window."

	SelectorBrowser new open!

----- Method: ScreenController>>openSimpleChangeSorter (in category '*ST80Tools') -----
openSimpleChangeSorter
	ChangeSorter new open!

----- Method: FileList class>>openInMVC (in category '*ST80Tools-instance creation') -----
openInMVC
	"Open a view of an instance of me on the default directory."

	| dir aFileList topView volListView templateView fileListView fileContentsView underPane pHeight |
	dir := FileDirectory default.
	aFileList := self new directory: dir.
	topView := StandardSystemView new.
	topView
		model: aFileList;
		label: dir pathName;
		minimumSize: 200 at 200.
	topView borderWidth: 1.

	volListView := PluggableListView on: aFileList
		list: #volumeList
		selected: #volumeListIndex
		changeSelected: #volumeListIndex:
		menu: #volumeMenu:.
	volListView autoDeselect: false.
	volListView window: (0 at 0 extent: 80 at 45).
	topView addSubView: volListView.

	templateView := PluggableTextView on: aFileList
		text: #pattern
		accept: #pattern:.
	templateView askBeforeDiscardingEdits: false.
	templateView window: (0 at 0 extent: 80 at 15).
	topView addSubView: templateView below: volListView.

	aFileList wantsOptionalButtons
		ifTrue:
			[underPane := aFileList optionalButtonViewForMVC.
			underPane isNil
				ifTrue: [pHeight := 60]
				ifFalse: [
					topView addSubView: underPane toRightOf: volListView.
					pHeight := 60 - aFileList optionalButtonHeight]]
		ifFalse:
			[underPane := nil.
			pHeight := 60].

	fileListView := PluggableListView on: aFileList
		list: #fileList
		selected: #fileListIndex
		changeSelected: #fileListIndex:
		menu: #fileListMenu:.
	fileListView window: (0 at 0 extent: 120 at pHeight).
	underPane isNil
		ifTrue: [topView addSubView: fileListView toRightOf: volListView]
		ifFalse: [topView addSubView: fileListView below: underPane].
	fileListView controller terminateDuringSelect: true.  "Pane to left may change under scrollbar"

	fileContentsView := PluggableTextView on: aFileList
		text: #contents accept: #put:
		readSelection: #contentsSelection menu: #fileContentsMenu:shifted:.
	fileContentsView window: (0 at 0 extent: 200 at 140).
	topView addSubView: fileContentsView below: templateView.

	topView controller open!

----- Method: FileList>>optionalButtonViewForMVC (in category '*ST80Tools-initialization') -----
optionalButtonViewForMVC
	"Answer a view of optional buttons"

	| aView bHeight windowWidth offset previousView aButtonView wid services sel allServices |
	aView := View new model: self.
	bHeight := self optionalButtonHeight.
	windowWidth := 120.
	aView window: (0 @ 0 extent: windowWidth @ bHeight).
	offset := 0.
	allServices := self universalButtonServices.
	services := allServices copyFrom: 1 to: (allServices size min: 5).
	previousView := nil.
	services
		do: [:service | sel := service selector.
		aButtonView := sel asString numArgs = 0
			ifTrue: [PluggableButtonView
					on: service provider
					getState: (service extraSelector == #none
							ifFalse: [service extraSelector])
					action: sel]
			ifFalse: [PluggableButtonView
					on: service provider
					getState: (service extraSelector == #none
							ifFalse: [service extraSelector])
					action: sel
					getArguments: #fullName
					from: self].
		service selector = services last selector
			ifTrue: [wid := windowWidth - offset]
			ifFalse: [aButtonView
					borderWidthLeft: 0
					right: 1
					top: 0
					bottom: 0.
				wid := windowWidth // services size - 2].
		aButtonView label: service buttonLabel asParagraph;
			window: (offset @ 0 extent: wid @ bHeight).
		offset := offset + wid.
		service selector = services first selector
			ifTrue: [aView addSubView: aButtonView]
			ifFalse: [aView addSubView: aButtonView toRightOf: previousView].
		previousView := aButtonView].
	^ aView!



More information about the Squeak-dev mailing list