The Trunk: Files-ul.90.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
2 messages Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: Files-ul.90.mcz

commits-2
Levente Uzonyi uploaded a new version of Files to project The Trunk:
http://source.squeak.org/trunk/Files-ul.90.mcz

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

Name: Files-ul.90
Author: ul
Time: 27 September 2010, 3:56:36.551 am
UUID: aff6ed6c-5823-6342-b175-65f0f4e8f403
Ancestors: Files-ul.89

- Integrated Eliot's stdio changes with a minor fix/optimization

=============== Diff against Files-ul.89 ===============

Item was added:
+ ----- Method: CrLfFileStream class>>newForStdio (in category 'instance creation') -----
+ newForStdio
+ "Circumvent CrLfFileStream new's retuning an instance of MultiBteFileStream"
+ ^super new!

Item was added:
+ ----- Method: CrLfFileStream>>openOnHandle:name:forWrite: (in category 'open/close') -----
+ openOnHandle: aFileID name: streamName forWrite: writeMode
+ "Initialize the file with the given handle. If writeMode is true then
+ allow writing, otherwise put the file in read-only mode."
+ super openOnHandle: aFileID name: streamName forWrite: writeMode.
+ lineEndConvention := LineEndDefault!

Item was changed:
  ----- Method: DirectoryEntry>>fullName (in category 'access') -----
  fullName
+ "The fully-qualified name.
+ Since this method falls into the equality test, make it safe when directory is nil."
+ ^ directory
+ ifNotNil: [ directory fullNameFor: self name ]
+ ifNil: [ self name ]!
- "The fully-qualified name."
- ^ directory fullNameFor: self name!

Item was added:
+ ----- Method: FileDirectory>>directoryEntryForName: (in category 'private') -----
+ directoryEntryForName: aFileName
+
+ "Return a single DirectoryEntry for the given (non-path) entry name,
+ or nil if the entry could not be found.
+ Raises InvalidDirectoryError if this directory's path does not identify a directory."
+
+ | entryArray sysPath sysName |
+
+ sysPath := pathName asVmPathName.
+ sysName := aFileName asVmPathName.
+
+ "New linear-time primitive."
+ entryArray := self primLookupEntryIn: sysPath name: sysName.
+ entryArray == #primFailed ifFalse:[
+ ^ entryArray ifNotNil: [(DirectoryEntry fromArray: entryArray directory: self) convertFromSystemName]
+ ].
+
+ "If the new primitive fails, use the old slow method.
+ (This fallback can be changed to signal InvalidDirectoryError once
+  VM's with FilePlugin #primitiveDirectoryEntry have been distributed everywhere;
+  the new primitive was introduced 6/13/2007."
+
+ ^self isCaseSensitive ifTrue: [
+ self entries detect: [:entry | entry name = aFileName ] ifNone: [ nil ]
+ ] ifFalse: [
+ self entries detect: [:entry | entry name sameAs: aFileName ] ifNone: [ nil ]
+ ]
+ !

Item was changed:
  FileStream subclass: #StandardFileStream
  instanceVariableNames: 'name fileID buffer1'
+ classVariableNames: 'Registry StdioHandles'
- classVariableNames: 'Registry'
  poolDictionaries: ''
  category: 'Files-Kernel'!
+ StandardFileStream class
+ instanceVariableNames: 'stdioFiles'!
 
  !StandardFileStream commentStamp: 'ul 12/6/2009 05:13' prior: 0!
  Provides a simple, platform-independent, interface to a file system. The instance variable rwmode, inherited from class PositionableStream, here is used to hold a Boolean -- true means opened for read-write, false means opened for read-only.  2/12/96 sw
 
  I implement a simple read buffering scheme with the variables defined in PositionableStream (which are unused in me otherwise) in the following way:
  collection <ByteString> or <ByteArray> This is the buffer.
  position <Integer> The relative position in the buffer. Greater or equal to zero.
  readLimit <Integer> The number of bytes buffered. Greater or equal to zero.
  Read buffering is enabled with #enableReadBuffering, disabled with #disableReadBuffering and it is enabled by default. The buffer is filled when a read attempt of an unbuffered absolute position is requested, or when a negative repositioning is made (with #position: with an argument < than the current absolute position) to an absolute position which is not buffered. In the first case, the buffer is positioned to the given absolute position. In the latter case the repositioning is made to the requested absolute position minus fourth of the buffer size. This means that further small negative repositionings won't result in buffer flushing. This is really useful when filing in code.
  The read buffer is flushed (#flushReadBuffer) whenever a write attempt is made.
  The buffer state is valid if and only if collection is not nil and position < readLimit.!
+ StandardFileStream class
+ instanceVariableNames: 'stdioFiles'!

Item was changed:
  ----- Method: StandardFileStream class>>fileExistsUserHandling: (in category 'error handling') -----
  fileExistsUserHandling: fullFileName
  | dir localName choice newName newFullFileName |
  dir := FileDirectory forFileName: fullFileName.
  localName := FileDirectory localNameFor: fullFileName.
+ choice := (UIManager default
+ chooseFrom: #('overwrite that file' 'append (risky!!!!)' 'choose another name' 'cancel')
+ title: localName, ' already exists.').
- choice := UIManager default chooseFrom:{
- 'overwrite that file'.
- 'choose another name'.
- 'cancel'
- } title: localName, '
- already exists.'.
 
  choice = 1 ifTrue: [
  dir deleteFileNamed: localName
  ifAbsent: [self error: 'Could not delete the old version of that file'].
  ^ self new open: fullFileName forWrite: true].
 
  choice = 2 ifTrue: [
+ ^ (self new open: fullFileName forWrite: true) setToEnd].
+
+ choice = 3 ifTrue: [
  newName := UIManager default request: 'Enter a new file name' initialAnswer: fullFileName.
  newFullFileName := self fullName: newName.
  ^ self newFileNamed: newFullFileName].
 
  self error: 'Please close this to abort file opening'!

Item was added:
+ ----- Method: StandardFileStream class>>flushAndVoidStdioFiles (in category 'class initialization') -----
+ flushAndVoidStdioFiles
+ stdioFiles ifNotNil:
+ [stdioFiles do:
+ [:f| f isReadOnly ifFalse: [[f flush] on: Error do: [:ex|"care less"]]].
+ stdioFiles := nil]!

Item was added:
+ ----- Method: StandardFileStream class>>initialize (in category 'class initialization') -----
+ initialize
+ "StandardFileStream initialize"
+ StdioHandles := Array new: 3.
+ Smalltalk
+ addToStartUpList: self after: SecurityManager; "the intent being before: AutoStart"
+ addToShutDownList: self after: SecurityManager!

Item was added:
+ ----- Method: StandardFileStream class>>newForStdio (in category 'private-file creation') -----
+ newForStdio
+ "Circumvent CrLfFileStream new's returning an instance of MultiBteFileStream"
+ ^self new!

Item was added:
+ ----- Method: StandardFileStream class>>shutDown: (in category 'class initialization') -----
+ shutDown: quitting
+ quitting ifTrue:
+ [self withAllSubclassesDo:
+ [:fileStreamClass| fileStreamClass flushAndVoidStdioFiles]]!

Item was added:
+ ----- Method: StandardFileStream class>>standardIOStreamNamed:forWrite: (in category 'private-file creation') -----
+ standardIOStreamNamed: moniker forWrite: forWrite
+
+ | index |
+ index := #(stdin stdout stderr) identityIndexOf: moniker.
+ ^((stdioFiles ifNil: [ stdioFiles := Array new: 3 ]) at: index)
+ ifNil: [
+ stdioFiles
+ at: index
+ put: (
+ (StdioHandles at: index)
+ ifNil: [ ^self error: moniker, ' is unavailable' ]
+ ifNotNil: [ :handle|
+ self newForStdio
+ openOnHandle: handle
+ name: moniker
+ forWrite: forWrite ]) ]!

Item was added:
+ ----- Method: StandardFileStream class>>startUp: (in category 'class initialization') -----
+ startUp: resuming
+ (resuming and: [self == StandardFileStream]) ifTrue:
+ [self withAllSubclassesDo:
+ [:fileStreamClass| fileStreamClass voidStdioFiles].
+ [StdioHandles := self stdioHandles]
+ on: Error
+ do: [:ex|
+ StdioHandles isArray ifFalse:
+ [StdioHandles := Array new: 3]]]!

Item was added:
+ ----- Method: StandardFileStream class>>stderr (in category 'file creation') -----
+ stderr
+ ^self standardIOStreamNamed: #stderr forWrite: true!

Item was added:
+ ----- Method: StandardFileStream class>>stdin (in category 'file creation') -----
+ stdin
+ ^self standardIOStreamNamed: #stdin forWrite: false!

Item was added:
+ ----- Method: StandardFileStream class>>stdioHandles (in category 'private-file creation') -----
+ stdioHandles
+ <primitive: 'primitiveFileStdioHandles' module: 'FilePlugin' error: ec>
+ self primitiveFailed!

Item was added:
+ ----- Method: StandardFileStream class>>stdout (in category 'file creation') -----
+ stdout
+ ^self standardIOStreamNamed: #stdout forWrite: true!

Item was added:
+ ----- Method: StandardFileStream class>>voidStdioFiles (in category 'class initialization') -----
+ voidStdioFiles
+ stdioFiles := nil!

Item was added:
+ ----- Method: StandardFileStream>>openOnHandle:name:forWrite: (in category 'open/close') -----
+ openOnHandle: aFileID name: streamName forWrite: writeMode
+ "Initialize the file with the given handle. If writeMode is true then
+ allow writing, otherwise put the file in read-only mode.
+ N.B. Do _not_ register the stream.  We do not want it to be
+ closed implicitly (e.g. on GC).  There may be multiple instances
+ accessing the same stream.  The stream is not a file."
+ fileID := aFileID.
+ name := streamName.
+ rwmode := writeMode.
+ buffer1 := String new: 1.
+ self enableReadBuffering!


Reply | Threaded
Open this post in threaded view
|

Re: The Trunk: Files-ul.90.mcz

laza
commits-2 wrote
Item was added:
+ ----- Method: StandardFileStream class>>stdioHandles (in category 'private-file creation') -----
+ stdioHandles
+ <primitive: 'primitiveFileStdioHandles' module: 'FilePlugin' error: ec>
+ self primitiveFailed!
It would be nice if the changes made to the FilePlugin could be merged from the cog svn branch back to the trunk. So the above would also work with "standard" squeak VMs.

Alex