[squeak-dev] The Trunk: Collections-ar.375.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Sep 2 05:50:36 UTC 2010


Andreas Raab uploaded a new version of Collections to project The Trunk:
http://source.squeak.org/trunk/Collections-ar.375.mcz

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

Name: Collections-ar.375
Author: ar
Time: 1 September 2010, 10:49:41.755 pm
UUID: 87e30eab-a65f-e746-a0af-71bd5cf8f859
Ancestors: Collections-ul.374

Reclassify methods to fix various package dependencies.

=============== Diff against Collections-ul.374 ===============

Item was removed:
- ----- Method: String>>asAlphaNumeric:extraChars:mergeUID: (in category 'converting') -----
- asAlphaNumeric: totalSize extraChars: additionallyAllowed mergeUID: minimalSizeOfRandomPart
- 	"Generates a String with unique identifier ( UID ) qualities, the difference to a
- 	 UUID is that its beginning is derived from the receiver, so that it has a meaning
- 	 for a human reader.
- 
- 	 Answers a String of totalSize, which consists of 3 parts
- 	 1.part: the beginning of the receiver only consisting of
- 		a-z, A-Z, 0-9 and extraChars in Collection additionallyAllowed ( which can be nil )
- 	 2.part: a single _
- 	 3.part: a ( random ) UID of size >= minimalSizeOfRandomPart consisting of
- 		a-z, A-Z, 0-9
- 
- 	 Starting letters are capitalized. 
- 	 TotalSize must be at least 1.
- 	 Exactly 1 occurrence of $_ is guaranteed ( unless additionallyAllowed includes $_ ).
- 	 The random part has even for small sizes good UID qualitites for many practical purposes.
- 	 If only lower- or uppercase letters are demanded, simply convert the answer with
- 	 say #asLowercase. The probability of a duplicate will rise only moderately ( see below ).
- 
- 	 Example: 
- 		size of random part = 10
- 		in n generated UIDs the chance p of having non-unique UIDs is
- 			n = 10000 ->  p < 1e-10		if answer is reduced to lowerCase: p < 1.4 e-8
- 			n = 100000 -> p < 1e-8
- 		at the bottom is a snippet for your own calculations  
- 		Note: the calculated propabilites are theoretical,
- 			for the actually used random generator they may be much worse"
- 
- 	| stream out sizeOfFirstPart index ascii ch skip array random |
- 	totalSize > minimalSizeOfRandomPart 
- 		ifFalse: [ self errorOutOfBounds ].
- 	stream := ReadStream on: self.
- 	out := WriteStream on: ( String new: totalSize ).
- 	index := 0.
- 	skip := true.
- 	sizeOfFirstPart := totalSize - minimalSizeOfRandomPart - 1.
- 	[ stream atEnd or: [ index >= sizeOfFirstPart ]]
- 	whileFalse: [
- 		((( ascii := ( ch := stream next ) asciiValue ) >= 65 and: [ ascii <= 90 ]) or: [
- 			( ascii >= 97 and: [ ascii <= 122 ]) or: [			 
- 			ch isDigit or: [
- 			additionallyAllowed notNil and: [ additionallyAllowed includes: ch ]]]])
- 		ifTrue: [
- 			skip
- 				ifTrue: [ out nextPut: ch asUppercase ]
- 				ifFalse: [ out nextPut: ch ].
- 			index := index + 1.
- 			skip := false ]
- 		ifFalse: [ skip := true ]].
- 	out nextPut: $_.
- 	array := Array new: 62.
- 	1 to: 26 do: [ :i |
- 		array at: i put: ( i + 64 ) asCharacter.
- 		array at: i + 26 put: ( i + 96 ) asCharacter ].
- 	53 to: 62 do: [ :i |
- 		array at: i put: ( i - 5 ) asCharacter ].
- 	random := UUIDGenerator default randomGenerator. 
- 	totalSize - index - 1 timesRepeat: [
- 		out nextPut: ( array atRandom: random )].
- 	^out contents
- 
- 	"	calculation of probability p for failure of uniqueness in n UIDs
- 		Note: if answer will be converted to upper or lower case replace 62 with 36
- 	| n i p all |
- 	all := 62 raisedTo: sizeOfRandomPart.
- 	i := 1.
- 	p := 0.0 .
- 	n := 10000.
- 	[ i <= n ]
- 	whileTrue: [
- 		p := p + (( i - 1 ) / all ).
- 		i := i + 1 ].
- 	p   
- 
- 	approximation formula: n squared / ( 62.0 raisedTo: sizeOfRandomPart ) / 2 
- 	" 
- 
- 	"'Crop SketchMorphs and Grab Screen Rect to JPG' 
- 			asAlphaNumeric: 31 extraChars: nil mergeUID: 10  
- 	 			'CropSketchMorphsAndG_iOw94jquN6'
- 	 'Monticello' 
- 			asAlphaNumeric: 31 extraChars: nil mergeUID: 10    
- 				'Monticello_kp6aV2l0IZK9uBULGOeG' 
- 	 'version-', ( '1.1.2' replaceAll: $. with: $- )
- 			asAlphaNumeric: 31 extraChars: #( $- ) mergeUID: 10    
- 				'Version-1-1-2_kuz2tMg2xX9iRLDVR'"
- 		!

Item was removed:
- ----- Method: TranscriptStream class>>windowColorSpecification (in category 'window color') -----
- windowColorSpecification
- 	"Answer a WindowColorSpec object that declares my preference"
- 
- 	^ WindowColorSpec classSymbol: self name wording: 'Transcript' brightColor: #lightOrange pastelColor: #paleOrange helpMessage: 'The system transcript'!

Item was removed:
- ----- Method: TextSqkPageLink>>actOnClickFor: (in category 'as yet unclassified') -----
- actOnClickFor: textMorph
- 	"I represent a link to either a SqueakPage in a BookMorph, or a regular url"
- 
- 	| book |
- 	((url endsWith: '.bo') or: [url endsWith: '.sp']) ifFalse: [
- 		^ super actOnClickFor: textMorph].
- 	book := textMorph ownerThatIsA: BookMorph.
- 	book ifNotNil: [book goToPageUrl: url].
- 	"later handle case of page being in another book, not this one"
- 	^ true!

Item was removed:
- ----- Method: SequenceableCollection>>asPointArray (in category 'converting') -----
- asPointArray
- 	"Answer an PointArray whose elements are the elements of the receiver, in 
- 	the same order."
- 
- 	| pointArray |
- 	pointArray := PointArray new: self size.
- 	1 to: self size do:[:i| pointArray at: i put: (self at: i)].
- 	^pointArray!

Item was removed:
- ----- Method: String>>asUrl (in category 'converting') -----
- asUrl
- 	"convert to a Url"
- 	"'http://www.cc.gatech.edu/' asUrl"
- 	"msw://chaos.resnet.gatech.edu:9000/' asUrl"
- 	^Url absoluteFromText: self!

Item was removed:
- ----- Method: TranscriptStream class>>openMorphicTranscript (in category 'as yet unclassified') -----
- openMorphicTranscript
- 	"Have the current project's transcript open up as a morph"
- 
- 	^ToolBuilder open: self!

Item was removed:
- ----- Method: TextURL>>actOnClickFor: (in category 'as yet unclassified') -----
- actOnClickFor: anObject
- 	"Do what you can with this URL.  Later a web browser."
- 
- 	| response m |
- 
- 	(url beginsWith: 'sqPr://') ifTrue: [
- 		ProjectLoading thumbnailFromUrl: (url copyFrom: 8 to: url size).
- 		^self		"should not get here, but what the heck"
- 	].
- 	"if it's a web browser, tell it to jump"
- 	anObject isWebBrowser
- 		ifTrue: [anObject jumpToUrl: url. ^ true]
- 		ifFalse: [((anObject respondsTo: #model) and: [anObject model isWebBrowser])
- 				ifTrue: [anObject model jumpToUrl: url. ^ true]].
- 
- 		"if it's a morph, see if it is contained in a web browser"
- 		(anObject isKindOf: Morph) ifTrue: [
- 			m := anObject.
- 			[ m ~= nil ] whileTrue: [
- 				(m isWebBrowser) ifTrue: [
- 					m  jumpToUrl: url.
- 					^true ].
- 				(m hasProperty: #webBrowserView) ifTrue: [
- 					m model jumpToUrl: url.
- 					^true ].
- 				m := m owner. ]
- 		].
- 
- 	"no browser in sight.  ask if we should start a new browser"
- 	((self confirm: 'open a browser to view this URL?' translated) and: [WebBrowser default notNil]) ifTrue: [
- 		WebBrowser default openOnUrl: url.
- 		^ true ].
- 
- 	"couldn't display in a browser.  Offer to put up just the source"
- 
- 	response := (UIManager default 
- 				chooseFrom: (Array with: 'View web page as source' translated
- 									with: 'Cancel' translated)
- 				title:  'Couldn''t find a web browser. View\page as source?' withCRs translated).
- 	response = 1 ifTrue: [HTTPSocket httpShowPage: url].
- 	^ true!

Item was removed:
- ----- Method: TranscriptStream>>buildWith: (in category 'toolbuilder') -----
- buildWith: builder
- 	| windowSpec textSpec |
- 	windowSpec := builder pluggableWindowSpec new.
- 	windowSpec model: self.
- 	windowSpec label: 'Transcript'.
- 	windowSpec children: OrderedCollection new.
- 
- 	textSpec := builder pluggableTextSpec new.
- 	textSpec 
- 		model: self;
- 		menu: #codePaneMenu:shifted:;
- 		frame: (0 at 0corner: 1 at 1).
- 	windowSpec children add: textSpec.
- 
- 	^builder build: windowSpec!

Item was removed:
- ----- Method: TranscriptStream class>>buildWith: (in category 'toolbuilder') -----
- buildWith: aBuilder
- 	^(Smalltalk at: #Transcript) buildWith: aBuilder!

Item was removed:
- ----- Method: TranscriptStream>>openLabel: (in category 'initialization') -----
- openLabel: aString 
- 	"Open a window on this transcriptStream"
- 	^ToolBuilder open: self label: aString!

Item was removed:
- ----- Method: TranscriptStream>>open (in category 'initialization') -----
- open
- 	| openCount |
- 	openCount := self countOpenTranscripts.
- 	openCount = 0
- 		ifTrue: [self openLabel: 'Transcript']
- 		ifFalse: [self openLabel: 'Transcript #' , (openCount+1) printString]!

Item was removed:
- ----- Method: TranscriptStream>>codePaneMenu:shifted: (in category 'model protocol') -----
- codePaneMenu: aMenu shifted: shifted
- 	"Note that unless we override perform:orSendTo:, PluggableTextController will respond to all menu items"
- 	^ StringHolder basicNew codePaneMenu: aMenu shifted: shifted
- !

Item was removed:
- ----- Method: String>>asUrlRelativeTo: (in category 'converting') -----
- asUrlRelativeTo: aUrl
- 	^aUrl newFromRelativeText: self!




More information about the Squeak-dev mailing list