" Module: AKG-FILESTREAM.ST Author: A. Grant Date: 28-Oct-1990 Version: 2.00-00 Modified: 3-Nov-1990 Index: nextLine Answer a String consisting of the characters of the receiver up to the next line delimiter. vmsFileName: aString Answer a String which is a valid VMS filename which is made up of the best guess from aString. " " | Change Log | ============================================================================ | Author Date Change | ALISTAIR 19 Nov 90 Version 2.00 | Added vmsFileName: selector. | " !FileStream class methodsFor: 'File Names'! vmsFileName: aString | name type pos | "Break the file name up into its name and type components." pos := aString indexOf: $.. (pos = 0) ifTrue: "Whole string is the name" [ name := aString. type := String new: 0. ] ifFalse: [ name := aString copyFrom: 1 to: (pos - 1). type := aString copyFrom: (pos + 1) to: (aString size). ]. "Scan the file name for invalid characters." pos := 1. name do: [ :char | (FileStream validVMSChar: char) ifFalse: [ name at: pos put: $_. ]. pos := pos + 1. ]. "First character of a filename may not be a -" ((name at: 1) = $-) ifTrue: [name at: 1 put: $_]. "Scan the file type for invalid characters." pos := 1. type do: [ :char | (FileStream validVMSChar: char) ifFalse: [ type at: pos put: $_. ]. pos := pos + 1. ]. "The last character of the file type may not be a -" pos := type size. (pos > 0) ifTrue: [ ((type at: pos) = $-) ifTrue: [type at: pos put: $_] ]. "Return the resulting file name" ^(name, '.', type) ! validVMSChar: aCharacter "Return true if aCharacter is a valid file name character" (aCharacter isDigit) ifTrue: [^true]. (aCharacter isLetter) ifTrue: [^true]. (#($_ $- $$) includes: aCharacter) ifTrue: [^true]. ^false !! !FileStream methodsFor: 'basic'! nextLine "Read characters until an end of line is reached." | lineString thisChar | lineString _ ''. [(((thisChar _ self next) asciiValue) = 10) or: [self atEnd]] whileFalse: [lineString := lineString copyWith: thisChar]. ^lineString !!