SystemOrganization addCategory: #'FS-AnsiStreams'! Object subclass: #FSStream instanceVariableNames: 'handle position' classVariableNames: '' poolDictionaries: '' category: 'FS-AnsiStreams'! !FSStream commentStamp: 'cwp 11/18/2009 11:34' prior: 0! I am an abstract superclass for read- and write-streams that perform IO via a handle rather than by calling primitives directly. My subclasses' provide a cursor on a collection, so that sequences of IO messages can be position independent. handle A subclass of FSHandle. All IO goes through this object. position An integer describing the next index to be accessed.! FSStream subclass: #FSReadStream instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FS-AnsiStreams'! !FSReadStream commentStamp: 'cwp 11/18/2009 11:36' prior: 0! I implement (more or less) the ANSI protocol. I provide methods for reading data from a file. ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/29/2009 22:45'! atEnd ^ position - 1 = handle size! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/29/2009 22:58'! do: aBlock [self atEnd] whileFalse: [aBlock value: self next]! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/29/2009 22:59'! next | result | result := handle at: position. position := position + 1. ^ result! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/29/2009 23:03'! next: count | result | result := ByteArray new: count. handle at: position read: result startingAt: 1 count: count. position := position + 1. ^ result! ! !FSReadStream methodsFor: 'squeak' stamp: 'cwp 7/31/2009 00:24'! nextInto: aCollection | count | count := handle at: position read: aCollection startingAt: 1 count: aCollection size. position := position + count. ^ count < aCollection size ifTrue: [aCollection first: count] ifFalse: [aCollection]! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/29/2009 23:31'! nextLine | char | ^ ByteArray streamContents: [:out | [self atEnd or: [#(13 10) includes: (char := self next)]] whileFalse: [out nextPut: char]. (char = 13 and: [self peek = 10]) ifTrue: [position := position + 1]]. ! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/30/2009 23:03'! nextMatchFor: anObject ^ self next = anObject! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/29/2009 23:27'! peek ^ handle at: position! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/30/2009 23:06'! peekFor: anObject ^ self peek = anObject! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/30/2009 23:19'! skip: anInteger position := position + anInteger min: handle size + 1! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/30/2009 23:27'! skipTo: anObject | result | [self atEnd or: [result := (self next = anObject)]] whileFalse. ^ result! ! !FSReadStream methodsFor: 'ansi gettable' stamp: 'cwp 7/30/2009 23:37'! upTo: anObject | byte | ^ ByteArray streamContents: [:out | [self atEnd or: [(byte := self next) = anObject]] whileFalse: [out nextPut: byte]] ! ! !FSStream classSide methodsFor: 'instance creation' stamp: 'cwp 7/29/2009 22:30'! onHandle: aHandle ^ self new setHandle: aHandle ! ! !FSStream methodsFor: 'public' stamp: 'cwp 7/29/2009 22:29'! close handle close! ! !FSStream methodsFor: 'public' stamp: 'cwp 7/29/2009 22:29'! contents | size contents | size := handle size. contents := ByteArray new: size. handle at: 1 read: contents startingAt: 1 count: size. ^ contents! ! !FSStream methodsFor: 'public' stamp: 'cwp 10/29/2009 09:47'! isOpen ^ handle isOpen! ! !FSStream methodsFor: 'public' stamp: 'cwp 2/5/2011 22:54'! isStream ^ true! ! !FSStream methodsFor: 'public' stamp: 'cwp 10/29/2009 09:47'! open handle open! ! !FSStream methodsFor: 'public' stamp: 'cwp 7/29/2009 22:32'! position ^ position! ! !FSStream methodsFor: 'public' stamp: 'cwp 7/29/2009 22:32'! position: anInteger position := anInteger! ! !FSStream methodsFor: 'initialize-release' stamp: 'cwp 7/29/2009 22:30'! setHandle: aHandle handle := aHandle. position := 1! ! FSStream subclass: #FSWriteStream instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'FS-AnsiStreams'! !FSWriteStream commentStamp: 'cwp 11/18/2009 11:36' prior: 0! I implement (more or less) the ANSI protocol. I provide methods for writing data to a file.! !FSWriteStream methodsFor: 'ansi puttable' stamp: 'cwp 7/28/2009 22:25'! cr self nextPut: 13! ! !FSWriteStream methodsFor: 'ansi puttable' stamp: 'cwp 7/28/2009 22:22'! flush handle flush! ! !FSWriteStream methodsFor: 'ansi puttable' stamp: 'cwp 7/23/2009 17:03'! nextPut: anObject handle at: position put: anObject. position := position + 1. ^ anObject! ! !FSWriteStream methodsFor: 'ansi puttable' stamp: 'cwp 7/23/2009 22:51'! nextPutAll: aCollection handle at: position write: aCollection startingAt: 1 count: aCollection size. position := position + aCollection size. ^ aCollection! ! !FSWriteStream methodsFor: 'ansi puttable' stamp: 'cwp 7/28/2009 22:26'! space self nextPut: 32! ! !FSWriteStream methodsFor: 'ansi puttable' stamp: 'cwp 7/28/2009 22:28'! tab self nextPut: 9! ! !FSWriteStream methodsFor: 'file' stamp: 'cwp 10/15/2009 22:05'! truncate handle truncateTo: position - 1! ! !FSWriteStream methodsFor: 'file' stamp: 'cwp 10/15/2009 21:49'! truncateTo: anInteger handle truncateTo: anInteger! !