FileText.st
author Claus Gittinger <cg@exept.de>
Thu, 25 Apr 1996 18:18:33 +0200
changeset 254 cccfa2590e6e
parent 131 19e548711b65
child 263 c4628d0d010d
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"

StringCollection subclass:#FileText
	instanceVariableNames:'myStream lastLineKnown lastLineOfFile cachedLines cacheLineNr'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Text'
!

!FileText class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    FileText represents the contents of a text-file;
    only the offsets of the text-lines are stored in an internal array
    to save some space. The at: method fetches the line from the file.
    Individual textlines may be replaced by strings.
    the underlying file is NOT updated in this case.

    Care should be taken, if the underlying file is rewritten -
    you have to manually update/flush the pointers.
    Never rewrite the file using the data from a FileText.
    If you keep a files contents in a FileText object and want to
    rewrite that file, you MUST write to a temporary file first.
    Otherwise, you will clobber the contents.

    It is highly recommended, to use fileText for readonly texts only.

    [author:]
        Claus Gittinger
"
! !

!FileText class methodsFor:'instance creation'!

of:aStream
    "return a new FileText object for the stream aStream"

    ^ (self new:1) of:aStream
!

ofFile:aFileName
    "return a new FileText object for the named file"

    |aStream|

    aStream := FileStream readonlyFileNamed:aFileName.
    aStream isNil ifTrue:[^ nil].
    ^ (self new:1) of:aStream
! !

!FileText methodsFor:'accessing'!

at:index
    |entry oldPosition|

    (index > lastLineKnown) ifTrue:[
	self scanUpToLine:index.
	(lastLineOfFile notNil) ifTrue:[
	    (index > lastLineOfFile) ifTrue:[
		^ self subscriptBoundsError
	    ]
	]
    ].

    entry := super at:index.
    (entry isMemberOf:String) ifTrue:[^ entry].

    cachedLines isNil ifTrue:[
	cachedLines := Array new:50.
	cacheLineNr := -9999
    ].
    ((index < cacheLineNr)
     or:[index >= (cacheLineNr + cachedLines size)]) ifTrue:[
	oldPosition := myStream position.
	myStream position:entry.
	1 to:(cachedLines size) do:[:cacheIndex|
	    cachedLines at:cacheIndex put:(myStream nextLine)
	].
	myStream position:oldPosition.
	cacheLineNr := index
    ].

    ^ cachedLines at:(index - cacheLineNr + 1)
!

of:aStream
    myStream := aStream.
    lastLineOfFile := nil.
    lastLineKnown := 0.
    cachedLines := nil
!

size
    "return the number of text-lines - have to scan file the first time"

    (lastLineOfFile isNil) ifTrue:[
	self scanUpToEnd
    ].
    ^ lastLineOfFile
! !

!FileText methodsFor:'enumerating'!

do:aBlock
    self from:1 to:(self size) do:aBlock
!

from:index1 to:index2 do:aBlock
    "must be redefined back since elements are indices into file, not the elements themselfes"

    |index "{ Class: SmallInteger }"
     stop  "{ Class: SmallInteger }" |

    index := index1.
    stop := index2.
    [index <= stop] whileTrue:[
	aBlock value:(self at:index).
	index := index + 1
    ]

! !

!FileText methodsFor:'private'!

scanUpToEnd
    "scan myStream up to the end of file"

    (lastLineOfFile notNil) ifTrue:[^ self].
    [true] whileTrue:[
	lastLineKnown := lastLineKnown + 1.
	(super size < lastLineKnown) ifTrue:[
	    super grow:(super size * 2 + 1)
	].
	super at:lastLineKnown put:(myStream position).
	myStream skipLine isNil ifTrue:[
	    lastLineOfFile := lastLineKnown.
	    ^ self
	]
    ]
!

scanUpToLine:index
    "scan myStream up to line index and save line-start-positions"

    (lastLineOfFile notNil) ifTrue:[
	(index > lastLineOfFile) ifTrue:[^ self]
    ].
    [lastLineKnown <= index] whileTrue:[
	lastLineKnown := lastLineKnown + 1.
	(super size < lastLineKnown) ifTrue:[
	    super grow:(super size * 2 + 1)
	].
	super at:lastLineKnown put:(myStream position).
	myStream skipLine isNil ifTrue:[
	    lastLineOfFile := lastLineKnown.
	    ^ self
	]
    ]
! !

!FileText class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/FileText.st,v 1.15 1996-04-25 16:17:14 cg Exp $'
! !