Nicolas Cellier uploaded a new version of System to project The Trunk:
http://source.squeak.org/trunk/System-nice.336.mcz ==================== Summary ==================== Name: System-nice.336 Author: nice Time: 11 June 2010, 10:29:30.971 pm UUID: e037fc0a-5251-0b46-93da-33e398988e7a Ancestors: System-cmm.335 Use String>>lines and Stream>>#nextLine to handle any case of in image LF leakage =============== Diff against System-cmm.335 =============== Item was changed: ----- Method: Utilities class>>instanceComparisonsBetween:and: (in category 'miscellaneous') ----- instanceComparisonsBetween: fileName1 and: fileName2 "For differential results, run printSpaceAnalysis twice with different fileNames, then run this method... Smalltalk printSpaceAnalysis: 0 on: 'STspace.text1'. --- do something that uses space here --- Smalltalk printSpaceAnalysis: 0 on: 'STspace.text2'. Smalltalk instanceComparisonsBetween: 'STspace.text1' and 'STspace.text2'" | instCountDict report f aString items className newInstCount oldInstCount newSpace oldPair oldSpace | instCountDict := Dictionary new. report := ReadWriteStream on: ''. f := FileStream readOnlyFileNamed: fileName1. [f atEnd] whileFalse: + [aString := f nextLine. - [aString := f upTo: Character cr. items := aString findTokens: ' '. (items size == 4 or: [items size == 5]) ifTrue: [instCountDict at: items first put: (Array with: items third asNumber with: items fourth asNumber)]]. f close. f := FileStream readOnlyFileNamed: fileName2. [f atEnd] whileFalse: + [aString := f nextLine. - [aString := f upTo: Character cr. items := aString findTokens: ' '. (items size == 4 or: [items size == 5]) ifTrue: [className := items first. newInstCount := items third asNumber. newSpace := items fourth asNumber. oldPair := instCountDict at: className ifAbsent: [nil]. oldInstCount := oldPair ifNil: [0] ifNotNil: [oldPair first]. oldSpace := oldPair ifNil: [0] ifNotNil: [oldPair second]. oldInstCount ~= newInstCount ifTrue: [report nextPutAll: (newInstCount - oldInstCount) printString; tab; nextPutAll: (newSpace - oldSpace) printString; tab; nextPutAll: className asString; cr]]]. f close. (StringHolder new contents: report contents) openLabel: 'Instance count differentials between ', fileName1, ' and ', fileName2! Item was changed: ----- Method: Utilities class>>offerCommonRequests (in category 'common requests') ----- offerCommonRequests "Offer up the common-requests menu. If the user chooses one, then evaluate it, and -- provided the value is a number or string -- show it in the Transcript." "Utilities offerCommonRequests" | reply result aMenu index normalItemCount strings | Smalltalk isMorphic ifTrue: [^ self offerCommonRequestsInMorphic]. (CommonRequestStrings == nil or: [CommonRequestStrings isKindOf: Array]) ifTrue: [self initializeCommonRequestStrings]. strings := CommonRequestStrings contents. normalItemCount := strings asString lineCount. aMenu := UIManager default + chooseFrom: (strings asString lines copyWith: 'edit this menu') - chooseFrom: (((strings asString, '\edit this menu' withCRs) - findTokens: Character cr) asArray) lines: (Array with: normalItemCount). index := aMenu startUp. index == 0 ifTrue: [^ self]. reply := aMenu labelString lineNumber: index. reply size == 0 ifTrue: [^ self]. index > normalItemCount ifTrue: [^ self editCommonRequestStrings]. result := self evaluate: reply in: nil to: nil. (result isNumber) | (result isString) ifTrue: [Transcript cr; nextPutAll: result printString]! Item was changed: ----- Method: ResourceManager class>>reloadCachedResources (in category 'resource caching') ----- reloadCachedResources "ResourceManager reloadCachedResources" "Reload cached resources from the disk" | fd files stream url localName storeBack archiveName | CachedResources := Dictionary new. LocalizedExternalResources := nil. fd := Project squeakletDirectory. files := fd fileNames asSet. stream := [fd readOnlyFileNamed: self resourceCacheName] on: FileDoesNotExistException do:[:ex| fd forceNewFileNamed: self resourceCacheName]. stream size < 50000 ifTrue:[stream := ReadStream on: stream contentsOfEntireFile]. storeBack := false. [stream atEnd] whileFalse:[ + url := stream nextLine. + localName := stream nextLine. - url := stream upTo: Character cr. - localName := stream upTo: Character cr. (localName beginsWith: 'zip://') ifTrue:[ archiveName := localName copyFrom: 7 to: localName size. (files includes: archiveName) ifTrue:[self addCacheLocation: localName for: url] ifFalse:[storeBack := true]. ] ifFalse:[ (files includes: localName) ifTrue:[self addCacheLocation: localName for: url] ifFalse:[storeBack := true] ]. ]. stream close. storeBack ifTrue:[ stream := fd forceNewFileNamed: self resourceCacheName. CachedResources keysAndValuesDo:[:urlString :cacheLocs| cacheLocs do:[:cacheLoc| stream nextPutAll: urlString; cr. stream nextPutAll: cacheLoc; cr]. ]. stream close. ].! Item was changed: ----- Method: Utilities class>>parseListContents: (in category 'fetching updates') ----- parseListContents: listContents | sections vers strm line fileNames | "Parse the contents of updates.list into {{vers. {fileNames*}}*}, and return it." sections := OrderedCollection new. fileNames := OrderedCollection new: 1000. vers := nil. strm := ReadStream on: listContents. [strm atEnd] whileFalse: + [line := strm nextLine. - [line := strm upTo: Character cr. line size > 0 ifTrue: [line first = $# ifTrue: [vers ifNotNil: [sections addLast: {vers. fileNames asArray}]. "Start a new section" vers := line allButFirst. fileNames resetTo: 1] ifFalse: [line first = $* ifFalse: [fileNames addLast: line]]]]. vers ifNotNil: [sections addLast: {vers. fileNames asArray}]. ^ sections asArray " TEST: | list | list := Utilities parseListContents: (FileStream oldFileNamed: 'updates.list') contentsOfEntireFile. list = (Utilities parseListContents: (String streamContents: [:s | Utilities writeList: list toStream: s])) ifFalse: [self error: 'test failed'] ifTrue: [self inform: 'test OK'] "! Item was changed: ----- Method: ChangeSet>>summaryStringDelta: (in category 'fileIn/Out') ----- summaryStringDelta: delta "Answer the string summarizing this changeSet" ^ String streamContents: [:s | | line author s2 ps intName date | intName := self name splitInteger. intName first isNumber ifTrue: [s nextPutAll: (intName first + delta) printString , intName last] ifFalse: [s nextPutAll: intName first "weird convention of splitInteger"]. (ps := self preambleString) ifNil: [s cr] ifNotNil: [s2 := ReadStream on: ps. + s2 match: 'Date:'; skipSeparators. date := s2 nextLine. + s2 match: 'Author:'; skipSeparators. author := s2 nextLine. - s2 match: 'Date:'; skipSeparators. date := s2 upTo: Character cr. - s2 match: 'Author:'; skipSeparators. author := s2 upTo: Character cr. s nextPutAll: ' -- '; nextPutAll: author; nextPutAll: ' -- '; nextPutAll: date; cr. [s2 atEnd] whileFalse: + [line := s2 nextLine. - [line := s2 upTo: Character cr. (line isEmpty or: [line = '"']) ifFalse: [s nextPutAll: line; cr]]]]. ! Item was changed: ----- Method: SmalltalkImage>>vmStatisticsShortString (in category 'vm statistics') ----- vmStatisticsShortString "Convenience item for access to recent statistics only" "StringHolderView open: (StringHolder new contents: SmalltalkImage current vmStatisticsShortString) label: 'VM Recent Statistics'" + ^ (ReadStream on: self vmStatisticsReportString) upToAll: 'Since'; nextLine; upToEnd - ^ (ReadStream on: self vmStatisticsReportString) upToAll: 'Since'; upTo: Character cr; upToEnd ! Item was changed: ----- Method: SpaceTally>>printSpaceDifferenceFrom:to: (in category 'fileOut') ----- printSpaceDifferenceFrom: fileName1 to: fileName2 "For differential results, run printSpaceAnalysis twice with different fileNames, then run this method... SpaceTally new printSpaceAnalysis: 0 on: 'STspace.text1'. --- do something that uses space here --- SpaceTally new printSpaceAnalysis: 0 on: 'STspace.text2'. SpaceTally new printSpaceDifferenceFrom: 'STspace.text1' to: 'STspace.text2' " | f coll1 coll2 item | f := FileStream readOnlyFileNamed: fileName1. coll1 := OrderedCollection new. + [f atEnd] whileFalse: [coll1 add: f nextLine]. - [f atEnd] whileFalse: [coll1 add: (f upTo: Character cr)]. f close. f := FileStream readOnlyFileNamed: fileName2. coll2 := OrderedCollection new. [f atEnd] whileFalse: + [item := f nextLine. - [item := (f upTo: Character cr). ((coll1 includes: item) and: [(item endsWith: 'percent') not]) ifTrue: [coll1 remove: item] ifFalse: [coll2 add: item]]. f close. (StringHolder new contents: (String streamContents: [:s | s nextPutAll: fileName1; cr. coll1 do: [:x | s nextPutAll: x; cr]. s cr; cr. s nextPutAll: fileName2; cr. coll2 do: [:x | s nextPutAll: x; cr]])) openLabel: 'Differential Space Analysis'. ! |
Free forum by Nabble | Edit this page |