[BUG][FIX] FillInTheBlank usage

Steve Elkins sgelkins at bellsouth.net
Sun Feb 13 08:40:32 UTC 2000


More than one, but now isn't the time to deviate from mail subject norms.

The change set included below avoids walkbacks arising from
choosing 'cancel' in a FillInTheBlank dialog.  I put this together
by looking for obvious problems in the (140) methods that use
the class in my 2.8alpha image.  Didn't fix everything.  The
preamble has a few notes about my quick pass through the list.

--------8<-------->8--------

'From Squeak2.8alpha of 13 January 2000 [latest update: #1851] on 13 February 2000 at 8:21:18 am'!
"Change Set:		FillInTheBlankUsageFixes
Date:			13 February 2000
Author:			Steve Elkins

Avoids various difficulties (usually walkbacks) that occur when the user chooses 'cancel' after causing a FillInTheBlank dialog to appear.  Some of the changes might fall into a 'user cosmetics' category.
Notes:
1. BookMorph.goToPage is changed because it relied on the fact that sending #asNumber to an empty string answers 0 and this didn't appear deliberate.
2. DictionaryInspector.addEntry allows a nil key.  Left it alone.
3. EnvelopeEditorMorph.chooseFrom:durationItem: allows the user to set duration to 0 because sending #asNumber to an empty string answers 0.  Left it alone.
4. MorphicModel.addPartNameLike:withValue: and (MorphicModel class).chooseNewName may have problems.  How to test?
5. PasteUpMorph.saveAsWorld may have a problem, but has no senders.
6. ScriptEditorMorph.typeInFrequency appears to rely deliberately on the fact that sending #asNumber to an empty string answers 0.
7. ThreeDSParser.parseStream: may have a problem.  How to test?"!


!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'sge 2/13/2000 05:20'!
fileInSoundLibrary
	"Prompt the user for a file name and the file in the sound library with that name."
	"AbstractSound fileInSoundLibrary"

	| fileName |
	fileName _ FillInTheBlank request: 'Sound library file name?'.
	fileName isEmptyOrNil ifTrue: [^ self].
	(fileName endsWith: '.sounds') ifFalse: [fileName _ fileName, '.sounds'].
	self fileInSoundLibraryNamed: fileName.
! !

!AbstractSound class methodsFor: 'sound library-file in/out' stamp: 'sge 2/13/2000 05:22'!
fileOutSoundLibrary: aDictionary
	"File out the given dictionary, which is assumed to contain sound and instrument objects keyed by their names."
	"Note: This method is separated out so that one can file out edited sound libraries, as well as the system sound library. To make such a collection, you can inspect AbstractSound sounds and remove the items you don't want. Then do: 'AbstractSound fileOutSoundLibrary: self' from the Dictionary inspector."

	| fileName refStream |
	(aDictionary isKindOf: Dictionary)
		ifFalse: [self error: 'arg should be a dictionary of sounds'].
	fileName _ FillInTheBlank request: 'Sound library file name?'.
	fileName isEmptyOrNil ifTrue: [^ self].
	refStream _ SmartRefStream fileNamed: fileName, '.sounds'.
	refStream nextPut: aDictionary.
	refStream close.
! !


!FileList methodsFor: 'file list menu' stamp: 'sge 2/13/2000 04:36'!
renameFile
	"Rename the currently selected file"
	| newName response |
	listIndex = 0 ifTrue: [^ self].
	self okToChange ifFalse: [^ self].
	(response _ FillInTheBlank request: 'NewFileName?'
 					initialAnswer: fileName)
		isEmpty ifTrue: [^ self].
	newName _ response asFileName.
	newName = fileName ifTrue: [^ self].
	directory rename: fileName toBe: newName.
	self updateFileList.
	listIndex _ list findFirst: [:item | (self fileNameFromFormattedItem: item) = newName].
	listIndex > 0 ifTrue: [fileName _ newName].
	self changed: #fileListIndex.
! !


!Morph methodsFor: 'e-toy support' stamp: 'sge 2/13/2000 07:20'!
makeGraphPaper
	| smallGrid backColor lineColor |
	smallGrid _ Compiler evaluate: (FillInTheBlank request: 'Enter grid size' initialAnswer: '16').
	smallGrid ifNil: [^ self].
	Utilities informUser: 'Choose a background color' during: [backColor _ Color fromUser].
	Utilities informUser: 'Choose a line color' during: [lineColor _ Color fromUser].
	self makeGraphPaperGrid: smallGrid background: backColor line: lineColor.! !


!BookMorph methodsFor: 'menu' stamp: 'sge 2/13/2000 05:33'!
goToPage
	| pageNum |
	pageNum _ FillInTheBlank request: 'Page?' initialAnswer: '0'.
	pageNum isEmptyOrNil ifTrue: [^true].
	self goToPage: pageNum asNumber.
! !


!Socket class methodsFor: 'tests' stamp: 'sge 2/13/2000 07:56'!
sendTest
	"Send data to the 'discard' socket of the given host. Tests the speed of one-way data transfers across the network to the given host. Note that many host hosts do not run a discard server."
	"Socket sendTest"

	| sock bytesToSend sendBuf bytesSent t serverName serverAddr |
	Transcript cr; show: 'starting send test'; cr.
	Socket initializeNetwork.
	serverName _ FillInTheBlank
		request: 'What is the destination server?'
		initialAnswer: 'create.ucsb.edu'.
	serverName isEmpty ifTrue: [^ Transcript show: 'never mind'; cr].
	serverAddr _ NetNameResolver addressForName: serverName timeout: 10.
	serverAddr = nil ifTrue: [^ self inform: 'Could not find an address for ', serverName].

	sock _ Socket new.
	Transcript show: '---------- Connecting ----------'; cr.
	sock connectTo: serverAddr port: 9.
	sock waitForConnectionUntil: self standardDeadline.
	(sock isConnected) ifFalse: [
		sock destroy.
		^ self inform: 'could not connect'].
	Transcript show: 'connection established; sending data'; cr.

	bytesToSend _ 100000.
	sendBuf _ String new: 5000 withAll: $x.
	bytesSent _ 0.
	t _ Time millisecondsToRun: [
		[bytesSent < bytesToSend] whileTrue: [
			sock sendDone ifTrue: [
				bytesSent _ bytesSent + (sock sendSomeData: sendBuf)]]].
	sock destroy.
	Transcript show: '---------- Connection Closed ----------'; cr.
	Transcript show: 'send test done; time = ', t printString; cr.
	Transcript show: ((bytesToSend asFloat / t) roundTo: 0.01) printString, ' kBytes/sec'; cr.
	Transcript endEntry.
! !

!Socket class methodsFor: 'examples' stamp: 'sge 2/13/2000 07:57'!
timeTest
	"Socket timeTest"

	| serverName serverAddr s |
	Transcript show: 'initializing network ... '.
	Socket initializeNetworkIfFail: [^Transcript show:'failed'].
	Transcript show:'ok';cr.
	serverName _ FillInTheBlank
		request: 'What is your time server?'
		initialAnswer: 'localhost'.
	serverName isEmpty ifTrue: [^ Transcript show: 'never mind'; cr].
	serverAddr _ NetNameResolver addressForName: serverName timeout: 10.
	serverAddr = nil ifTrue: [self error: 'Could not find the address for ', serverName].

	s _ Socket new.
	Transcript show: '---------- Connecting ----------'; cr.
	s connectTo: serverAddr port: 13.  "13 is the 'daytime' port number"
	s waitForConnectionUntil: (self deadlineSecs: 1).
	Transcript show: 'the time server reports: ' , s getResponseNoLF.
	s closeAndDestroy.
	Transcript show: '---------- Connection Closed ----------'; cr.
! !

!Socket class methodsFor: 'examples' stamp: 'sge 2/13/2000 07:57'!
timeTestUDP
	"Socket timeTestUDP"

	| serverName serverAddr s |
	Transcript show: 'initializing network ... '.
	Socket initializeNetworkIfFail: [^Transcript show:'failed'].
	Transcript show:'ok';cr.
	serverName _ FillInTheBlank
		request: 'What is your time server?'
		initialAnswer: 'localhost'.
	serverName isEmpty ifTrue: [^ Transcript show: 'never mind'; cr].
	serverAddr _ NetNameResolver addressForName: serverName timeout: 10.
	serverAddr = nil ifTrue: [self error: 'Could not find the address for ', serverName].

	s _ Socket newUDP.		"a 'random' port number will be allocated by the system"
	"Send a packet to the daytime port and it will reply with the current date."
	Transcript show: '---------- Sending datagram from port ' , s port printString , ' ----------'; cr.
	s sendData: '!!' toHost: serverAddr port: 13.	"13 is the daytime service"
	Transcript show: 'the time server reports: ' , s getResponseNoLF.
	s closeAndDestroy.
	Transcript show: '---------- Socket closed ----------'; cr.
! !

!Socket class methodsFor: 'examples' stamp: 'sge 2/13/2000 07:58'!
timeTestUDP2
	"Socket timeTestUDP2"

	| serverName serverAddr s |
	Transcript show: 'initializing network ... '.
	Socket initializeNetworkIfFail: [^Transcript show:'failed'].
	Transcript show:'ok';cr.
	serverName _ FillInTheBlank
		request: 'What is your time server?'
		initialAnswer: 'localhost'.
	serverName isEmpty ifTrue: [^ Transcript show: 'never mind'; cr].
	serverAddr _ NetNameResolver addressForName: serverName timeout: 10.
	serverAddr = nil ifTrue: [self error: 'Could not find the address for ', serverName].

	s _ Socket newUDP.
	"The following associates a port with the UDP socket, but does NOT create a connectable endpoint"
	s setPort: 54321.
	"Send a packet to the daytime port and it will reply with the current date."
	Transcript show: '---------- Sending datagram from port ' , s port printString , ' ----------'; cr.
	s sendData: '!!' toHost: serverAddr port: 13.
	Transcript show: 'the time server reports: ' , s getResponseNoLF.
	s closeAndDestroy.
	Transcript show: '---------- Socket closed ----------'; cr.
! !

!Socket class methodsFor: 'examples' stamp: 'sge 2/13/2000 07:59'!
timeTestUDP3
	"Socket timeTestUDP3"

	| serverName serverAddr s |
	Transcript show: 'initializing network ... '.
	Socket initializeNetworkIfFail: [^Transcript show:'failed'].
	Transcript show:'ok';cr.
	serverName _ FillInTheBlank
		request: 'What is your time server?'
		initialAnswer: 'localhost'.
	serverName isEmpty ifTrue: [^ Transcript show: 'never mind'; cr].
	serverAddr _ NetNameResolver addressForName: serverName timeout: 10.
	serverAddr = nil ifTrue: [self error: 'Could not find the address for ', serverName].

	s _ Socket newUDP.
	"The following associates a port with the UDP socket, but does NOT create a connectable endpoint"
	s setPort: (Socket wildcardPort).		"explicitly request a default port number"
	"Send a packet to the daytime port and it will reply with the current date."
	Transcript show: '---------- Sending datagram from port ' , s port printString , ' ----------'; cr.
	s sendData: '!!' toHost: serverAddr port: 13.
	Transcript show: 'the time server reports: ' , s getResponseNoLF.
	s closeAndDestroy.
	Transcript show: '---------- Socket closed ----------'; cr.
! !





More information about the Squeak-dev mailing list