PrinterStream.st
author Claus Gittinger <cg@exept.de>
Fri, 31 May 1996 22:58:37 +0200
changeset 368 423cf3f4e522
parent 367 647af479888f
child 370 705453f00711
permissions -rw-r--r--
added query if printer supports pages at all (only PS does)

"
 COPYRIGHT (c) 1990 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.
"

PipeStream subclass:#PrinterStream
	instanceVariableNames:'native pageFormat'
	classVariableNames:'PrintCommand LeftMargin DefaultCommands PageFormat
		DefaultPageFormats Landscape'
	poolDictionaries:''
	category:'Streams-External'
!

!PrinterStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1990 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
"
    a stream for printing; this (concrete or abstract) class can handle only
    very dumb printers. 
    No attributes (italic, bold etc) and no multiple fonts are supported 
    - just plain single font text printing.

    More intelligence is added by subclasses (see PostscriptPrinterStream among others.)

    These classes do not support graphics printing - they are only for
    text; although some limited font functionality (such as bold or italic printing)
    may be supported by some subclasses.


    [usage:]

    The concrete printer class is bound to the global variable Printer,
    which is either set to PrinterStream (for dumb printers) or to one of
    the subclasses (PostscriptPrinterStream etc.).

    To print:

        |p|

        p := Printer new.
        p notNil ifTrue:[
            p nextPutAll:'hello world'; cr.
            p nextPutAll:' ...'; cr.
            p close
        ].

    See users of the Printer global variable for more examples.

    [class variables:]
        PrintCommand    <String>        the operatingSystem command for printing.
                                        Usually something like 'lp' or 'lpr'

        LeftMargin      <Integer>       optional default left margin.
                                        Defaults to 0.


    [author:]
        Claus Gittinger
"
! !

!PrinterStream class methodsFor:'initialization'!

initialize
    "this is usually redefined by the startup-file"

    PrintCommand isNil ifTrue:[
        OperatingSystem isBSDlike ifTrue:[
            PrintCommand := 'lpr'
        ] ifFalse:[
            PrintCommand := 'lp'
        ]
    ].
    LeftMargin isNil ifTrue:[
        LeftMargin := 0
    ].

    DefaultPageFormats isNil ifTrue:[
    "/ UnitConverter must support all of them.
        self defaultPageFormats:#(
                                    'letter'
                                    'a4'
                                    'a5'
                                    'a6'
                               ).
    ].

    Landscape isNil ifTrue:[
        Landscape := false
    ].

    PageFormat isNil ifTrue:[
        Language == #us ifTrue:[
            PageFormat := #letter
        ] ifFalse:[
            PageFormat := #a4
        ]
    ]

    "
     PrinterStream initialize
    "
! !

!PrinterStream class methodsFor:'instance creation'!

new
    "return a new stream for printing"

    ^ self basicNew initialize startPrint
!

newNative
    "return a new stream for untranslated printing
     (i.e. text should be sent via nextPutUntranslated in the printers
      native format)"

    ^ self basicNew initialize setNative; writingTo:(self printCommand)
! !

!PrinterStream class methodsFor:'accessing - defaults'!

defaultCommands
    "return a list presented as possible commands for printed
     (in the launchers printer configuration).
     This list can be set from the startup script with:
        PrinterStream defaultCommands:#( ... )"

    ^ DefaultCommands

    "Created: 23.4.1996 / 18:25:18 / cg"
!

defaultCommands:collectionOfCommandStrings
    "set the list which will be presented as possible commands for printing.
     (shown in in the launchers printer configuration).
     This can be done from the startup script with:
        PrinterStream defaultCommands:#( ... )"

    DefaultCommands := collectionOfCommandStrings

    "Created: 23.4.1996 / 18:26:06 / cg"
!

defaultPageFormats
    "return a list of supported pae formats.
     This list can be set from the startup script with:
        PrinterStream defaultPageFormats:#..."

    ^ DefaultPageFormats

    "Created: 23.4.1996 / 18:25:18 / cg"
!

defaultPageFormats:aList
    "set the list of supported pae formats.
     (shown in in the launchers printer configuration).
     This list can be set from the startup script with:
        PrinterStream defaultPageFormats:#..."

    DefaultPageFormats := aList.

    "/ validate the list
    aList do:[:name |
        |unit ok|

        ok := true.
        #('W' 'H' 'lW' 'lH') do:[:what |
            unit := (name , what) asSymbolIfInterned.
            (unit isNil 
            or:[(UnitConverter convert:1 from:unit to:#millimeter) isNil]) ifTrue:[
                ok := false
            ]
        ].
        ok ifFalse:[
            ('PRINTER: UnitConverter has no size-info for ''' , name , '''-format') errorPrintCR
        ]
    ].

    "
     PrinterStream
        defaultPageFormats:#(
                                'letter'
                                'a4'
                                'a5'
                                'a6'
                            )
    "

    "Created: 23.4.1996 / 18:25:18 / cg"
!

landscape
    "return the landscape setting"

    ^ Landscape
!

landscape:aBoolean
    "set/clear landscape printing"

    Landscape := aBoolean
!

leftMargin
    "return the number of blanks for the left margin"

    ^ LeftMargin
!

leftMargin:aNumber
    "set the number of blanks for the left margin"

    LeftMargin := aNumber
!

pageFormat
    "return a symbol describing the default page format.
     This list can be set from the startup script with:
        PrinterStream defaultPageFormat:#...
     or via the launchers settings menu."

    ^ PageFormat

    "Created: 23.4.1996 / 18:25:18 / cg"
!

pageFormat:aSymbol
    "set the the default page format to be aSymbol.
     Valid symbols are #letter, #a4, #a5 etc.
     The UnitConverter must contain width/height information on
     that symbol, in order for printing to be correct.

     This list can be set from the startup script with:
        PrinterStream defaultPageFormat:#...
     or via the launchers settings menu."

    PageFormat := aSymbol

    "Created: 23.4.1996 / 18:25:18 / cg"
!

printCommand
    "return the command used for printing (usually 'lp' or 'lpr').
     This is either set from the startup file, or via the launchers
     settings menu."

    ^ PrintCommand

    "Modified: 18.5.1996 / 09:12:35 / cg"
!

printCommand:aString
    "set the command for printing (usually 'lp' or 'lpr').
     This is either set from the startup file, or via the launchers
     settings menu."

    PrintCommand := aString

    "
     PrinterStream printCommand:'lpr'
     PrinterStream printCommand:'lpr -h'
     PrinterStream printCommand:'rsh ibm lpr -h'
     PrinterStream printCommand:'gs -sDEVICE=djet500 -sOutputFile=/tmp/stx.ps -sPAPERSIZE=a4 -q -; cat /tmp/stx.ps | rsh ibm lpr -h'
    "

    "Modified: 18.5.1996 / 09:12:48 / cg"
! !

!PrinterStream class methodsFor:'queries'!

printerTypeName
    "return a descriptive name"

    ^ 'dumb printer'

    "Modified: 18.4.1996 / 20:04:12 / cg"
!

supportsPageSizes
    "return true if this printer supports different page sizes"

    ^ false

    "Created: 31.5.1996 / 22:35:26 / cg"
!

supportsPostscript
    "return true if this is a postscript printer"

    ^ false

    "Created: 10.2.1996 / 16:23:07 / cg"
! !

!PrinterStream methodsFor:'access writing'!

cr
    "send a carriage-return to the printer"

    super nextPut:(Character cr).
    self spaces:LeftMargin
!

next:count put:aCharacter
    "send some character multiple times to the printer - translate as needed.
     Redefined to allow individual character translation in subclasses"

    count timesRepeat:[
        self nextPut:aCharacter
    ]

    "Created: 10.4.1996 / 13:08:13 / cg"
    "Modified: 10.4.1996 / 13:09:06 / cg"
!

nextPut:aCharacter
    "send some characters to the printer - translate as needed"

    (aCharacter == Character cr) ifTrue:[
	super nextPut:(Character cr).
	self spaces:LeftMargin
    ] ifFalse:[
	super nextPut:aCharacter
    ]
!

nextPutAll:aCollection
    "send some characters to the printer - translate as needed.
     The argument, aCollection can be a Text (i.e. include emphasis)"

    aCollection hasChangeOfEmphasis ifTrue:[
        aCollection keysAndValuesDo:[:idx :aChar |
            self emphasis:(aCollection emphasisAt:idx).
            self nextPut:aChar.
        ].
        self normal.
    ] ifFalse:[
        aCollection do:[:aChar |
            self nextPut:aChar
        ]
    ]

    "Modified: 18.5.1996 / 09:43:45 / cg"
!

nextPutAllUntranslated:aCollection
    "send some raw characters to the printer - even if not in native mode"

    super nextPutAll:aCollection

    "Modified: 10.4.1996 / 13:08:35 / cg"
!

nextPutUntranslated:aCharacter
    "send a raw character to the printer - even if not in native mode"

    super nextPut:aCharacter

    "Modified: 10.4.1996 / 13:08:28 / cg"
! !

!PrinterStream methodsFor:'emphasis change'!

bold
    "set emphasis to bold
     - ignore here, since this class does not know anything about the printer"

    ^ self

    "Modified: 18.5.1996 / 08:55:10 / cg"
!

boldItalic
    "set emphasis to boldItalic
     - ignore here, since this class does not know anything about the printer"

    ^ self

    "Created: 14.5.1996 / 18:53:43 / cg"
    "Modified: 18.5.1996 / 08:55:14 / cg"
!

emphasis:anEmphasis
    "change the emphasis"

    anEmphasis isNil ifTrue:[
        ^ self normal
    ].
    anEmphasis == #bold ifTrue:[
        ^ self bold
    ].
    anEmphasis == #italic ifTrue:[
        ^ self italic
    ].
    (anEmphasis = #(bold italic)
    or:[anEmphasis = #(italic bold)]) ifTrue:[
        ^ self boldItalic
    ].
    anEmphasis == #underline ifTrue:[
        ^ self underline
    ].
    anEmphasis == #strikeout ifTrue:[
        ^ self strikeout
    ].

    "Created: 14.5.1996 / 18:53:54 / cg"
    "Modified: 18.5.1996 / 09:42:49 / cg"
!

italic
    "set emphasis to italic
     - ignore here, since this class does not know anything about the printer"

    ^ self

    "Modified: 18.5.1996 / 08:55:18 / cg"
!

normal
    "set emphasis to normal (non-bold, non-italic)
     - ignore here, since this class does not know anything about the printer"

    ^ self

    "Modified: 18.5.1996 / 08:55:21 / cg"
!

strikeout
    "set emphasis to strikeout
     - ignore here, since this class does not know anything about the printer"

    ^ self

    "Modified: 18.5.1996 / 08:55:10 / cg"
    "Created: 18.5.1996 / 08:56:13 / cg"
!

underline
    "set emphasis to underline
     - ignore here, since this class does not know anything about the printer"

    ^ self

    "Modified: 18.5.1996 / 08:55:10 / cg"
    "Created: 18.5.1996 / 08:56:24 / cg"
! !

!PrinterStream methodsFor:'font change'!

courier
    "set font to courier 
     - ignore here, since this class does not know anything about the printer"

    ^ self
!

helvetica
    "set font to helvetic
     - ignore here, since this class does not know anything about the printer"

    ^ self
!

times
    "set font to times 
     - ignore here, since this class does not know anything about the printer"

    ^ self
! !

!PrinterStream methodsFor:'helpers writing'!

escape:aCharacter
    "since its so common, this method sends escape followed by aCharacter"

    super nextPut:(Character escape); nextPut:aCharacter
!

escapeAll:aString
    "since its so common, this method sends escape followed by aString"

    super nextPut:(Character escape); nextPutAll:aString
! !

!PrinterStream methodsFor:'initialization'!

initialize
    pageFormat := DefaultPageFormat

    "Created: 31.5.1996 / 20:14:36 / cg"
! !

!PrinterStream methodsFor:'open/close'!

basicClose
    super close
!

close
    self endPrint.
    super close
!

endPrint
    ^ self
!

setNative
    native := true

    "Created: 10.4.1996 / 13:05:01 / cg"
!

setNative:aBoolean
    native := aBoolean

    "Created: 30.5.1996 / 17:49:09 / cg"
!

startPrint
    super writingTo:PrintCommand.
    self spaces:LeftMargin
! !

!PrinterStream methodsFor:'queries'!

lineLength
    "the printer pages width (in characters)"

    ^ 80
! !

!PrinterStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/PrinterStream.st,v 1.27 1996-05-31 20:58:26 cg Exp $'
! !
PrinterStream initialize!