NonPositionableExternalStream.st
author Claus Gittinger <cg@exept.de>
Fri, 12 Feb 1999 15:55:00 +0100
changeset 3980 8f9443e37693
parent 3956 51f1a9a4d63f
child 4392 26fb48f04e1b
permissions -rw-r--r--
renamed __new() to __STX___new()

"
 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.
"

ExternalStream subclass:#NonPositionableExternalStream
	instanceVariableNames:''
	classVariableNames:'StdInStream StdOutStream StdErrorStream'
	poolDictionaries:''
	category:'Streams-External'
!

!NonPositionableExternalStream primitiveDefinitions!
%{

#include <stdio.h>
#define _STDIO_H_INCLUDED_

%}

! !

!NonPositionableExternalStream 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
"
    This class provides common protocol for all non-positionable,
    external streams. Concrete subclasses are terminal streams, pipe streams,
    PrinterStreams, Sockets etc.

    There are three special instances of this class, representing stdin,
    stdout and stderr of the smalltalk/X process (see Unix manuals, if you
    dont know what those are used for). These special streams are bound to
    to globals Stdin, Stdout and Stderr at early initialization time
    (see Smalltalk>>initializeStandardStreams).

    The name of this class is a historical leftover - it should be called
    'TTYStream' or similar.

    [author:]
	Claus Gittinger
"
! !

!NonPositionableExternalStream class methodsFor:'instance creation'!

forStderr
    "{ Pragma: +optSpace }"

    "return a NonPositionableExternalStream object for writing to
     Unixes standard error output file descriptor"

    StdErrorStream isNil ifTrue:[
	StdErrorStream := self basicNew initializeForStderr
    ].
    ^ StdErrorStream
!

forStdin
    "{ Pragma: +optSpace }"

    "return a NonPositionableExternalStream object for reading from
     Unixes standard input file descriptor"

    StdInStream isNil ifTrue:[
	StdInStream := self basicNew initializeForStdin
    ].
    ^ StdInStream
!

forStdout
    "{ Pragma: +optSpace }"

    "return a NonPositionableExternalStream object for writing to
     Unixes standard output file descriptor"

    StdOutStream isNil ifTrue:[
	StdOutStream := self basicNew initializeForStdout
    ].
    ^ StdOutStream
! !

!NonPositionableExternalStream methodsFor:'error handling'!

positionError
    "{ Pragma: +optSpace }"

    "notify that this stream has no concept of a position"

    ^ PositionErrorSignal raiseRequestWith:self in:thisContext sender
! !

!NonPositionableExternalStream methodsFor:'positioning'!

position
    "{ Pragma: +optSpace }"

    "catch position - there is none here"

    ^ self positionError
!

position:aPosition
    "{ Pragma: +optSpace }"

    "catch position - there is none here"

    ^ self positionError
!

skip:numberToSkip
    "skip count objects, return the receiver"

    "dont know how to unread ..."
    numberToSkip < 0 ifTrue:[
	^ self error:'stream is not positionable'
    ].
    numberToSkip timesRepeat:self next
!

skipThroughAll:aCollection
    "skip for and through the sequence given by the argument, aCollection;
     return nil if not found, the receiver otherwise. 
     On a successful match, the next read will return elements after aCollection;
     if no match was found, the receiver will be positioned at the end.
     Redefined to be the same as Stream>>#skipThroughAll, to undo
     the redefinition from PositionableStream"

    |buffer l first idx|

    l := aCollection size.
    first := aCollection at:1.
    [self atEnd] whileFalse:[
	buffer isNil ifTrue:[
	    buffer := self nextAvailable:l.
	].
	buffer = aCollection ifTrue:[
	    ^ self
	].
	idx := buffer indexOf:first startingAt:2.
	idx == 0 ifTrue:[
	    buffer := nil
	] ifFalse:[
	    buffer := (buffer copyFrom:idx) , (self nextAvailable:(idx - 1))
	]
    ].
    ^ nil

    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipThroughAll:'901'.
     s upToEnd                    
    "
    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipThroughAll:'1234'.
     s upToEnd                    
    "
    "
     |s|
     s := ReadStream on:'12345678901234567890'.
     s skipThroughAll:'999'.
     s atEnd                    
    "

    "Modified: / 11.1.1997 / 19:09:06 / cg"
    "Created: / 15.1.1998 / 23:33:37 / stefan"
! !

!NonPositionableExternalStream methodsFor:'printing & storing'!

printOn:aStream
    "{ Pragma: +optSpace }"

    "append a printed representation of the receiver on aStream"

    |myName|

    self == Stdin ifTrue:[
	myName := 'Stdin'.
    ] ifFalse:[
	self == Stdout ifTrue:[
	    myName := 'Stdout'.
	] ifFalse:[
	    self == Stderr ifTrue:[
		myName := 'Stderr'.
	    ]
	]
    ].

    myName notNil ifTrue:[
	aStream nextPutAll:myName.
	^ self
    ].
    super printOn:aStream
!

storeOn:aStream
    "{ Pragma: +optSpace }"

    "append a printed representation of the receiver on aStream, from
     which the receiver can be reconstructed."

    ((self == Stdin)
    or:[self == Stdout
    or:[self == Stderr]]) ifTrue:[
	^ self printOn:aStream
    ].
    super storeOn:aStream
! !

!NonPositionableExternalStream methodsFor:'private'!

initializeForStderr
    "{ Pragma: +optSpace }"

    "setup for writing to stderr"

    mode := #readwrite.
    buffered := false.
%{
    OBJ fp;

    __INST(filePointer) = fp = __MKOBJ(stderr); __STORE(self, fp);
#ifdef WIN32
    __INST(eolMode) = @symbol(crlf);
#else
# ifdef xxx__VMS__  /* XXX: to be tested */
    __INST(eolMode) = @symbol(cr);
# endif
#endif

%}
!

initializeForStdin
    "{ Pragma: +optSpace }"

    "setup for reading stdin"

    mode := #readonly.
    buffered := true.
%{
    OBJ fp;

    __INST(filePointer) = fp = __MKOBJ(stdin); __STORE(self, fp);
%}
!

initializeForStdout
    "{ Pragma: +optSpace }"

    "setup for writing to stdout"

    mode := #readwrite.
    buffered := false.
%{
    OBJ fp;

    __INST(filePointer) = fp = __MKOBJ(stdout); __STORE(self, fp);
#ifdef WIN32
    __INST(eolMode) = @symbol(crlf);
#else
# ifdef xxx__VMS__   /* XXX: to be tested */
    __INST(eolMode) = @symbol(cr);
# endif
#endif
%}
!

reOpen
    "{ Pragma: +optSpace }"

    "reopen the stream after an image restart.
     If I am one of the standard streams, reopen is easy"

    (self == StdInStream) ifTrue:[
	^ self initializeForStdin
    ].
    (self == StdOutStream) ifTrue:[
	^ self initializeForStdout
    ].
    (self == StdErrorStream) ifTrue:[
	^ self initializeForStderr
    ].
    ^ super reOpen
! !

!NonPositionableExternalStream methodsFor:'queries'!

isPositionable
    "return true, if the stream supports positioning (this one is not)"

    ^ false
! !

!NonPositionableExternalStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic/NonPositionableExternalStream.st,v 1.34 1999-02-12 14:54:55 cg Exp $'
! !