Skip to content

Commit

Permalink
Merge branch 'Pharo8.0' into MCScanner_next
Browse files Browse the repository at this point in the history
  • Loading branch information
James Foster committed Aug 18, 2019
2 parents 4d27c0e + 9eefc91 commit 2ea5541
Show file tree
Hide file tree
Showing 8 changed files with 27 additions and 58 deletions.
Expand Up @@ -4,10 +4,12 @@ Extension { #name : #ClyMethodGroup }
ClyMethodGroup >> fileOut [
| internalStream class |
internalStream := (String new: 1000) writeStream.
internalStream header; timeStamp; cr.
self methods do: [:each |
each origin printMethodChunk: each selector on: internalStream ].
internalStream
header;
timeStamp;
cr.
self methods do: [ :each | each origin printMethodChunk: each selector on: internalStream ].
internalStream trailer.
class := methodQuery scope basisObjects anyOne.
^ FileStream writeSourceCodeFrom: internalStream baseName: (class name , '-' , self name) isSt: true.
^ CodeExporter writeSourceCodeFrom: internalStream baseName: class name , '-' , self name isSt: true
]
7 changes: 7 additions & 0 deletions src/DeprecatedFileStream/FileStream.class.st
Expand Up @@ -389,6 +389,13 @@ FileStream class >> oldFileOrNoneNamed: fileName [

]

{ #category : #'instance creation' }
FileStream class >> onHandle: aFileSystemHandle [
^ self concreteStream new
open: aFileSystemHandle fullName
forWrite: aFileSystemHandle isWritable
]

{ #category : #'instance creation' }
FileStream class >> readOnlyFileNamed: fileName [
^ self concreteStream readOnlyFileNamed: (self fullName: fileName)
Expand Down
8 changes: 0 additions & 8 deletions src/FileSystem-Core/FileStream.extension.st

This file was deleted.

2 changes: 1 addition & 1 deletion src/FileSystem-Core/ManifestFileSystemCore.class.st
Expand Up @@ -13,5 +13,5 @@ Class {

{ #category : #'meta-data - dependency analyser' }
ManifestFileSystemCore class >> manuallyResolvedDependencies [
^ #(#'Collections-Streams' #'System-Support' #'System-Platforms' #'Zinc-Character-Encoding-Core' #'AST-Core' #'System-Settings-Core' #'FileSystem-Disk')
^ #(#'System-Support' #'System-Platforms' #'Zinc-Character-Encoding-Core' #'AST-Core' #'System-Settings-Core' #'FileSystem-Disk')
]
17 changes: 0 additions & 17 deletions src/Graphics-Tests/PNGReadWriterTest.class.st
Expand Up @@ -637,23 +637,6 @@ PNGReadWriterTest >> testPngEncodingColors8 [
self encodeColors: self coloredFiles8 depth: 8.
]

{ #category : #'tests - bits' }
PNGReadWriterTest >> testPngSuite [
"Requires the suite from
ftp://swrinde.nde.swri.edu/pub/png/images/suite/PngSuite.zip
to be present as PngSuite.zip"
| file |
file := [ FileStream readOnlyFileNamed: 'PngSuite.zip'] on: Error do:[:ex| ex return].
file ifNil:[^self].
[ | zip entries |zip := ZipArchive new readFrom: file.
entries := zip members select:[:mbr| mbr fileName asLowercase endsWith: '.png'].
entries do:[:mbr|
(mbr fileName asLowercase first = $x)
ifTrue: [self encodeAndDecodeWithError: mbr contentStream ]
ifFalse: [self encodeAndDecodeStream: mbr contentStream ] ].
] ensure:[file close].
]

{ #category : #'tests - colors' }
PNGReadWriterTest >> testRed16 [
self encodeAndDecodeColor: Color red depth: 16
Expand Down
28 changes: 10 additions & 18 deletions src/Rubric/RubTextAreaExamples.class.st
Expand Up @@ -188,25 +188,17 @@ RubTextAreaExamples class >> profileSourcesFileViewing [
"The big test to check that a TextArea is able to compose and ''quickly'' show
a big file content "

"self profileSourcesFileViewing"

<script>
| contents |

contents := nil.

self
show: 'Wait a moment loading text, the sources file is huge' translated
while: [
contents := (FileStream readOnlyFileNamed: Smalltalk sourcesFile basename) contents
].

TimeProfiler spyAllOn: [
RubEditingArea new
beWrapped;
width: 600;
updateTextWith: contents;
openInWorld
]
"Do not profile reading of source file."
contents := Smalltalk sourcesFile contents.

TimeProfiler
spyAllOn: [ RubEditingArea new
beWrapped;
width: 600;
updateTextWith: contents;
openInWorld ]
]

{ #category : #examples }
Expand Down
7 changes: 2 additions & 5 deletions src/Rubric/RubTextEditor.class.st
Expand Up @@ -1994,11 +1994,8 @@ RubTextEditor >> saveContentsInFile [
suggestedName ifNil: [suggestedName := labelToUse , '.text'].
fileName := UIManager default request: 'File name?'
initialAnswer: suggestedName.
fileName isEmptyOrNil
ifFalse:
[(FileStream newFileNamed: fileName)
nextPutAll: stringToSave;
close]
fileName isEmptyOrNil
ifFalse: [ fileName asFileReference writeStreamDo: [ :out | out nextPutAll: stringToSave ] ]
]

{ #category : #scrolling }
Expand Down
6 changes: 1 addition & 5 deletions src/StartupPreferences/StartupPreferencesLoader.class.st
Expand Up @@ -217,12 +217,8 @@ StartupPreferencesLoader >> add: anAction [

{ #category : #private }
StartupPreferencesLoader >> addAtStartup: aCollection inDirectory: aFileReference named: fileName [

| scriptFile |
aFileReference ensureCreateDirectory.
scriptFile := aFileReference / fileName.
FileStream forceNewFileNamed: scriptFile fullName do: [ :stream | stream nextPutAll: (self buildStreamFor: aCollection) ].

aFileReference / fileName writeStreamDo: [ :stream | stream nextPutAll: (self buildStreamFor: aCollection) ]
]

{ #category : #'script generation' }
Expand Down

0 comments on commit 2ea5541

Please sign in to comment.