PostscriptPrinterStream.st
author Claus Gittinger <cg@exept.de>
Mon, 03 Jun 1996 15:38:16 +0200
changeset 380 fa5adc326473
parent 378 91abcf70e0c3
child 382 113b013200d3
permissions -rw-r--r--
checkin from browser

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

PrinterStream subclass:#PostscriptPrinterStream
	instanceVariableNames:'xPos yPos lineBuffer colNr lineNr fFamily fStyle pageStartAction
		pageEndAction'
	classVariableNames:'Prolog Trailer PageProlog PageTrailer FontNames FontHeight
		FontWidth LeftX TopY PageHeight LinesPerPage PhysicalPageHeight
		Italic Bold Normal BoldItalic Courier Times Helvetica TopInset
		LeftInset BottomInset'
	poolDictionaries:''
	category:'Streams-External'
!

!PostscriptPrinterStream class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1988 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 simple text output to postscript printers;
    to use it, evaluate 
        Smalltalk at:#Printer put:PostscriptPrinterStream
    (usually in some rc file).
    or change it via the launchers settings-menu.

    See examples on how to send something to the printer.

    For now, only Helvetica, Courier and Times fonts in italic, roman and bold
    are supported.

    It does not directly support graphics and other fancy features of Postscript,
    but provides a compatible interface for simple text line-printing 
    (see other subclasses of PrinterStream).

    If you already have a postscript string at hand, this can be sent to
    the printer in native mode.

    To output graphics, you need the PSGraphicsContext (and friend-) classes.
    These provide protocol similar to the one provided by display graphicContexts.
    Notice, that these postscript classes are derived from public domain code;
    there is no warranty.

    [see also:]
        PSGraphicsContext 
        EpsonFX1PrinterStream HPLjetIIPrinterStream PrinterStream

    [author:]
        Claus Gittinger
"
!

examples
"
    For text printing, use:
                                                                        [exBegin]
        |s|

        s := Printer new.
        s nextPutAll:'hello'; cr.
        s bold.
        s nextPutAll:'this is bold'; cr.
        s normal.
        s italic.
        s nextPutAll:'this is italic'; cr.
        s boldItalic.
        s nextPutAll:'this is boldItalic'; cr.
        s normal.
        s nextPutAll:'normal again'; cr.
        s helvetica.
        s nextPutAll:'helvetica'; cr.
        s times.
        s nextPutAll:'times'; cr.
        s courier.
        s nextPutAll:'courier'; cr.
        s close
                                                                        [exEnd]
    or, if you already have emphasized text at hand:
                                                                        [exBegin]
        |s|

        s := Printer new.
        s nextPutAll:'hello'; cr.
        s nextPutAll:'this is '; 
          nextPutAll:(Text string:'bold' emphasis:#bold); 
          cr;
          nextPutAll:'this is '; 
          nextPutAll:(Text string:'italic' emphasis:#italic); 
          cr;
          nextPutAll:'this is ';
          nextPutAll:(Text string:'boldItalic' emphasis:#(bold italic)); 
          cr;
          nextPutAll:'normal again'; 
          cr;
          helvetica;
          nextPutAll:'helvetica';
          cr;
          times;
          nextPutAll:'times'; 
          cr;
          courier;
          nextPutAll:'courier';
          cr.
        s close
                                                                        [exEnd]

    placing a page-hook, to add a page number:
    (page hooks require that you understand some postscript ...
     ... and have a look at how this class generates its postscript code)
                                                                        [exBegin]
        |s hook pageNr|

        s := Printer new.

        pageNr := 0.
        hook := [ 

                    pageNr := pageNr + 1.
                    s placeString:('page ' , pageNr printString) at:(5500 @ 400).
                ].

        s pageEndAction:hook.
        (1 to:200) do:[:lineNr |
            s nextPutAll:'line ' , lineNr printString.
            s cr.
        ].
        s close.
                                                                        [exEnd]


    placing a page-hook, to add a custom frame, logo or company letter-head:
    (page hooks require that you understand some postscript ...
     ... and have a look at how this class generates its postscript code.
     ... and notice that the code below is a q&d demo, working with letter-sized
     pages only; a real program should ask the printerStream about the actual 
     pageHeight/pageWidth.)
                                                                        [exBegin]
        |s hook pageNr|

        s := Printer new.

        pageNr := 0.
        hook := [ 

                    pageNr := pageNr + 1.
                    s placeString:('page ' , pageNr printString) at:(5500 @ 400).
                    s placeString:('Document revision:') at:(900 @ 1200).
                    s placeString:('Revieved by:')       at:(900 @ 900).

                    s setNative:true.
                    s nextPutAll:'0 setlinewidth'; cr.
                    s nextPutAll:'800 800 moveto'; cr.
                    s nextPutAll:'11000 800 lineto'; cr.
                    s nextPutAll:'11000 15500 lineto'; cr.
                    s nextPutAll:'800 15500 lineto'; cr.
                    s nextPutAll:'800 800 lineto'; cr.
                    s nextPutAll:'stroke'; cr.

                    s nextPutAll:'800 1100 moveto'; cr.
                    s nextPutAll:'11000 1100 lineto'; cr.
                    s nextPutAll:'stroke'; cr.

                    s nextPutAll:'800 1400 moveto'; cr.
                    s nextPutAll:'11000 1400 lineto'; cr.
                    s nextPutAll:'stroke'; cr.

                    s setNative:false.
                ].

        s pageEndAction:hook.
        (1 to:200) do:[:lineNr |
            s nextPutAll:'line ' , lineNr printString.
            s cr.
        ].
        s close.
                                                                        [exEnd]


    If you already have a postscript string at hand, this can be sent to
    the printer in native mode:
                                                                        [exBegin]
        |s|

        s := Printer newNative.
        s nextPutAll:<your postscript string>.
                                                                        [exEnd]
        s close

    To output graphics, you need the PSGraphicsContext (and friend-) classes.
    These provide protocol similar to the one provided by display graphicContexts.
    Notice, that these postscript classes are derived from public domain code;
    there is no warranty.

    Usage:
                                                                        [exBegin]
        |drawable s|

        s := Printer newNative.
        drawable := PSGraphicsContext on:s.

        drawable displayLineFrom:(0@0) to:(100@100).
        drawable displayLineFrom:(100@0) to:(0@100).
        drawable displayCircle:(150@150) radius:50.
        (Image fromFile:'bitmaps/SBrowser.xbm') displayOn:drawable at:(50@30).

        drawable close.
                                                                        [exEnd]

      the same in a view:
                                                                        [exBegin]
        |drawable|

        drawable := (View extent:200@200) openAndWait.

        drawable displayLineFrom:(0@0) to:(100@100).
        drawable displayLineFrom:(100@0) to:(0@100).
        drawable displayCircle:(150@150) radius:50.
        (Image fromFile:'bitmaps/SBrowser.xbm') displayOn:drawable at:(50@30).
                                                                        [exEnd]
"
! !

!PostscriptPrinterStream class methodsFor:'initialization'!

initCharacterSize
    "setup the character parameters"

    FontHeight := 200.   "/ used to scale fonts - corresponds to a 10 point font size
    FontWidth := 120.    "/ used to compute width of tabs

    "Created: 23.4.1996 / 19:53:34 / cg"
    "Modified: 23.4.1996 / 20:05:17 / cg"
    "Modified: 30.5.1996 / 17:24:05 / ca"
!

initFonts
    "setup the font names.
     initProlog uses those parameters."

    Italic := 0.     "/ offset from base-font# to italic version
    Bold := 1.       "/ offset from base-font# to bold version
    BoldItalic := 2. "/ offset from base-font# to boldItalic version
    Normal := 3.     "/ offset from base-font# to normal version

    Helvetica := 0.  "/ # of helvetica base font
    Times := 4.      "/ # of times base font
    Courier := 8.    "/ # of courier base font

    FontNames := #( 
                    '/Helvetica-Oblique'
                    '/Helvetica-Bold'
                    '/Helvetica-BoldOblique'
                    '/Helvetica'
                    '/Times-Italic'
                    '/Times-Bold'
                    '/Times-BoldItalic'
                    '/Times'
                    '/Courier-Oblique'
                    '/Courier-Bold'
                    '/Courier-BoldOblique'
                    '/Courier' 
                  )

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

initPage
    "setup the page parameters.
     All coordinates are scaled by 20 w.r.t the PS coordinates (i.e. in twips)."

    PageFormat isNil ifTrue:[
        PageFormat := #letter
    ].

    TopInset isNil ifTrue:[
        TopInset := 0.652778.  "/ inches
    ].
    BottomInset isNil ifTrue:[
        BottomInset := 1.18056 "/ inches
    ].
    LeftInset isNil ifTrue:[
        LeftInset := 0.625.     "/ inches
    ].

    "/     +-----------------------------------------------+  PageHeight
    "/     |                                               |
    "/     | LeftX +---------------------------------------|  TopY
    "/     |       |1st printed line                       |
    "/     |       |                                       |
    "/     |       |                                       |
    "/     |       |                                       |
    "/     |       |                                       |
    "/     |       |last line (linesPerPage)               |
    "/     |       +---------------------------------------|
    "/     |                                               |
    "/     (0/0)-------------------------------------------+  0

    LeftX := (UnitConverter convert:LeftInset from:#inch to:#twip) rounded.

    PhysicalPageHeight := (UnitConverter convert:1 from:(PageFormat , 'H') to:#twip) rounded.
    Landscape ifTrue:[
        PageHeight := (UnitConverter convert:1 from:(PageFormat , 'lH') to:#twip) rounded.
    ] ifFalse:[
        PageHeight := (UnitConverter convert:1 from:(PageFormat , 'H') to:#twip) rounded.
    ].

    TopY := PageHeight - (UnitConverter convert:TopInset from:#inch to:#twip) rounded.
    LinesPerPage := TopY - (UnitConverter convert:BottomInset from:#inch to:#twip) rounded // 200.

    "Modified: 30.5.1996 / 17:24:55 / ca"
    "Modified: 3.6.1996 / 10:45:34 / cg"
!

initPageProlog
    "define the page prolog"

    PageProlog :=
'StartPage
'.

    "Created: 23.4.1996 / 19:56:16 / cg"
!

initPageTrailer
    "define the page epilog"

    PageTrailer :=
'EndPage
'.

    "Modified: 23.4.1996 / 19:55:50 / cg"
    "Created: 23.4.1996 / 19:56:30 / cg"
!

initProlog
    "define the documents prolog"

    |tmpString t fontNr|

    tmpString :=
'%!!PS-Adobe-1.0
%%Creator: Smalltalk/X
%%DocumentFonts: Courier-Oblique Courier-Bold Courier Times-Italic Times-Bold Times
save/SmalltalkJob exch def
/OriginalState gstate def
/StartSmalltalkDoc{$smalltalk begin}def
/$smalltalk 50 dict def $smalltalk begin
/EndSmalltalkDoc{end}def
/S/show load def
/X{exch 0 rmoveto S}def
/Y{exch 0 exch rmoveto S}def
/B{3 1 roll moveto S}def
/F{$fd exch get setfont}def
/StartPage{/svpg save def .05 dup scale}def
/EndPage{svpg restore showpage}def
/DoPreFeed{/statusdict where{pop
 statusdict/prefeed known{statusdict exch/prefeed exch put 0}if}if pop}def
/Landscape{90 rotate 0 -' , PageHeight printString "15840", ' translate}def
/ISOrecode {findfont dup length dict begin
 {1 index /FID ne {def} {pop pop} ifelse} forall
 /Encoding ISOLatin1Encoding def
 currentdict end definefont pop} def
/SetUpFonts
 {dup/$fd exch array def{findfont exch scalefont $fd 3 1 roll put}repeat}def
/InitGaudy{/TwoColumn exch def /BarLength exch def
/ftD /ISO-Times-Bold findfont 12 UP scalefont def
/ftF /ISO-Times-Roman findfont 14 UP scalefont def
/ftP /ISO-Helvetica-Bold findfont 30 UP scalefont def}def
/U{1440 mul}def
/UP{U 72 div}def
/LB{/pts exch UP def /charcolor exch def /boxcolor exch def /font exch def
 /label exch def /dy exch def /dx exch def /lly exch def /llx exch def
 gsave boxcolor setgray
 llx lly moveto dx 0 rlineto 0 dy rlineto dx neg 0 rlineto closepath fill
 /lines label length def
 /yp lly dy add dy lines pts mul sub 2 div sub pts .85 mul sub def
 font setfont charcolor setgray
 label {dup stringwidth pop 2 div llx dx 2 div add exch sub yp moveto show
   /yp yp pts sub def}forall grestore}def
/Gaudy{/Page exch def /Date exch def /File exch def /Comment exch def
 .25 U 10.2 U BarLength .1 sub U .25 U [File] ftF .97 0 14 LB
 .25 U 10.45 U BarLength .1 sub U .25 U [Comment] ftF 1 0 14 LB
 .25 U 10.2 U 1 U .5 U Date ftD .7 0 12 LB
 BarLength .75 sub U 10.2 U 1 U .5 U [Page] ftP .7 1 30 LB
 TwoColumn{BarLength 2 div .19 add U 10.2 U moveto 0 -10 U rlineto stroke}if
}def
end
StartSmalltalkDoc 
% end of fixed prolog
'.

    t := ''.
    FontNames do:[:aName |
        t := t , '/ISO-' , aName , ' ' , aName , ' ISOrecode
'.
    ].
    t := t , '
'.
    tmpString := tmpString , t.

    t := ''.
    fontNr := 0.
    FontNames do:[:aName |
        t := t , (fontNr printString) , ' ' 
               , (FontHeight printString) , ' '
               , aName , (Character nl) asString.
        fontNr := fontNr + 1
    ].
    tmpString := tmpString , t.
    tmpString := tmpString , fontNr printString , ' SetUpFonts

% end of prolog
'.
    Prolog := tmpString.

    "
     PostscriptPrinterStream initProlog
    "

    "Created: 23.4.1996 / 19:40:44 / cg"
    "Modified: 1.6.1996 / 00:46:20 / cg"
!

initTrailer
    "define the documents epilog"

        Trailer :=
'EndSmalltalkDoc
SmalltalkJob restore
'

    "Created: 23.4.1996 / 19:55:24 / cg"
    "Modified: 23.4.1996 / 19:55:38 / cg"
!

initialize
    Normal isNil ifTrue:[
        self initFonts.
        self initPage.
        self initCharacterSize.

        self initProlog.
        self initTrailer.

        self initPageProlog.
        self initPageTrailer
    ]

    "
     Normal := nil.
     self initialize
    "

    "Modified: 18.5.1996 / 09:46:15 / cg"
!

reInitPage
    self initPage.
    self initProlog.

    "Created: 31.5.1996 / 23:35:18 / cg"
! !

!PostscriptPrinterStream class methodsFor:'accessing - defaults'!

bottomInset
    "return the bottom margin (in inches)"

    ^ BottomInset

    "Created: 1.6.1996 / 13:07:43 / cg"
    "Modified: 3.6.1996 / 10:44:44 / cg"
!

bottomInset:inches
    "set the bottom margin (in inches)"

    BottomInset := inches.
    self reInitPage.

    "Created: 3.6.1996 / 10:46:25 / cg"
    "Modified: 3.6.1996 / 10:47:16 / cg"
!

leftInset
    "return the left margin (in inches)"

    ^ LeftInset

    "Created: 1.6.1996 / 13:07:12 / cg"
    "Modified: 3.6.1996 / 10:45:11 / cg"
!

leftInset:inches
    "set the left margin (in inches)"

    LeftInset := inches.
    self reInitPage.

    "Created: 3.6.1996 / 10:46:33 / cg"
    "Modified: 3.6.1996 / 10:47:21 / cg"
!

topInset
    "return the top margin (in inches)"

    ^ TopInset

    "Created: 1.6.1996 / 13:07:20 / cg"
    "Modified: 3.6.1996 / 10:45:17 / cg"
!

topInset:inches
    "set the top margin (in inches)"

    TopInset := inches.
    self reInitPage.

    "Created: 3.6.1996 / 10:46:41 / cg"
    "Modified: 3.6.1996 / 10:47:26 / cg"
! !

!PostscriptPrinterStream class methodsFor:'queries'!

printerTypeName
    "return a descriptive name"

    ^ 'postscript printer'
!

supportsMargins
    "return true if this printer supports margins"

    ^ true

    "Created: 3.6.1996 / 10:48:04 / cg"
!

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

    ^ true

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

supportsPostscript
    "return true if this is a postscript printer"

    ^ true

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

!PostscriptPrinterStream methodsFor:'access writing'!

cr
    "send line termination"

    self flushLine.
    native == true ifTrue:[^ super cr].

    xPos := LeftX.
    colNr := 0.
    yPos := yPos - FontHeight.

    lineNr := lineNr + 1.
    lineNr > LinesPerPage ifTrue:[
        self nextPage
    ]

    "Modified: 1.6.1996 / 13:09:30 / cg"
!

nextPut:aCharacter
    |code|

    (aCharacter == Character cr) ifTrue:[
        ^ self cr
    ].

    native == true ifTrue:[
        self flushLine.
        ^ super nextPut:aCharacter
    ].

    (aCharacter == $( ) ifTrue:[
        lineBuffer := lineBuffer , '\(' .
        ^ self
    ].
    (aCharacter == $) ) ifTrue:[
        lineBuffer := lineBuffer , '\)' .
        ^ self
    ].
    (aCharacter == $\ ) ifTrue:[
        lineBuffer := lineBuffer , '\\' .
        ^ self
    ].

    (aCharacter == Character tab ) ifTrue:[
        self flushLine.
        colNr := ((colNr + 8) // 8) * 8. 
        xPos := LeftX + (colNr * FontWidth).
        ^ self
    ].

    (code := aCharacter asciiValue) > 16r7F ifTrue:[
        lineBuffer := lineBuffer , '\' , (code printStringRadix:8)
    ] ifFalse:[
        lineBuffer := lineBuffer copyWith:aCharacter
    ].

    "Modified: 23.4.1996 / 20:05:59 / cg"
! !

!PostscriptPrinterStream methodsFor:'accessing'!

pageEndAction:something
    "set pageEndAction - if non-nil, that will be called before
     and EndPage is emmitted. 
     An example use is a private block,
     which draws a company frame around the page ..."

    pageEndAction := something.

    "Modified: 30.5.1996 / 16:45:09 / ca"
!

pageStartAction:something
    "set pageStartAction - if nonNil, that is evaluated prior to every page."

    pageStartAction := something.

    "Modified: 30.5.1996 / 16:44:20 / ca"
! !

!PostscriptPrinterStream methodsFor:'emphasis change'!

bold
    "further printing is in bold"

    fStyle ~~ Bold ifTrue:[
        self flushLine.
        fStyle := Bold.
        self setFont
    ]

    "Modified: 3.6.1996 / 15:31:29 / cg"
!

boldItalic
    "further printing is in boldItalic"

    fStyle ~~ BoldItalic ifTrue:[
        self flushLine.
        fStyle := BoldItalic.
        self setFont
    ]

    "Created: 18.5.1996 / 09:36:36 / cg"
    "Modified: 3.6.1996 / 15:31:37 / cg"
!

italic
    "further printing is in italic"

    fStyle ~~ Italic ifTrue:[
        self flushLine.
        fStyle := Italic.
        self setFont
    ]

    "Modified: 3.6.1996 / 15:31:46 / cg"
!

normal
    "further printing is in normal style (i.e. non-bold/non-italic)"

    fStyle ~~ Normal ifTrue:[
        self flushLine.
        fStyle := Normal.
        self setFont
    ].

    "Modified: 3.6.1996 / 15:31:19 / cg"
! !

!PostscriptPrinterStream methodsFor:'font change'!

courier
    "further printing is in the courier font"

    self flushLine.
    fFamily := Courier.
    self setFont

    "Modified: 10.4.1996 / 13:34:49 / cg"
!

helvetica
    "further printing is in the helvetica font"

    self flushLine.
    fFamily := Helvetica.
    self setFont

    "Modified: 10.4.1996 / 13:34:58 / cg"
!

times
    "further printing is in the times font"

    self flushLine.
    fFamily := Times.
    self setFont

    "Modified: 10.4.1996 / 13:36:07 / cg"
! !

!PostscriptPrinterStream methodsFor:'open/close'!

endPrint
    "finish a document - finish page; then send documentTrailer.
     Send nothing if nativePrinting."

    native == true ifFalse:[
        self endPage.
        super nextPutAllUntranslated:Trailer.
    ].
    super endPrint

    "Modified: 23.4.1996 / 20:03:26 / cg"
!

startPrint
    "start a document - send documentProlog & start a page.
     Send nothing if nativePrinting."

    fFamily := Courier.
    fStyle := Normal.

    native == true ifFalse:[
        Prolog isNil ifTrue:[
            self class initialize
        ].
        super writingTo:(self class printCommand).
        super nextPutAllUntranslated:Prolog.
        self startPage
    ]

    "Modified: 1.6.1996 / 00:43:50 / cg"
! !

!PostscriptPrinterStream methodsFor:'private'!

endPage
    "end a page - flush buffered text & send pageTrailer"

    self flushLine.
    pageEndAction notNil ifTrue:[
        pageEndAction value
    ].
    super nextPutAllUntranslated:PageTrailer

    "Modified: 23.4.1996 / 20:00:01 / cg"
!

flushLine
    "flush buffered line text"

    (lineBuffer size > 0) ifTrue:[
        super nextPutAllUntranslated:(xPos printString ).
        super nextPutAllUntranslated:' '.
        super nextPutAllUntranslated:(yPos printString).
        super nextPutAllUntranslated:'('.
        super nextPutAllUntranslated:lineBuffer.
        super nextPutAllUntranslated:')B'.
        super nextPutUntranslated:(Character cr).
        xPos := xPos + (FontWidth * lineBuffer size).
        colNr := colNr + lineBuffer size
    ].
    lineBuffer := ''

    "Modified: 23.4.1996 / 20:00:13 / cg"
!

nextPage
    "new page - finish previous page & start enew.
     Should not be sent when nativePrinting."

    self endPage.
    self startPage

    "Modified: 23.4.1996 / 20:04:07 / cg"
!

placeString:aString at:pos
    "special entry: place a string at some particular position in my ps-coordinate
     system. Can be used with endPageActions to place a page-number."

    self flushLine.
    super nextPutAllUntranslated:(pos x printString ).
    super nextPutAllUntranslated:' '.
    super nextPutAllUntranslated:(pos y printString).
    super nextPutAllUntranslated:'('.
    super nextPutAllUntranslated:aString.
    super nextPutAllUntranslated:')B'.
    super nextPutUntranslated:(Character cr).

    "Created: 30.5.1996 / 17:06:36 / ca"
!

setFont
    "change the font. 
     Uses current fFamily and fStyle (which give the fonts nr)"

    |fontNumber|

    fontNumber := fFamily + fStyle.
    super nextPutAllUntranslated:fontNumber printString.
    super nextPutAllUntranslated:' F'. 
    super nextPutUntranslated:(Character cr)

    "Modified: 23.4.1996 / 20:01:28 / cg"
!

startPage
    "start a page - send pageProlog, reset x/y position and line/col."

    pageStartAction notNil ifTrue:[
        pageStartAction value
    ].
    super nextPutAllUntranslated:PageProlog.
    self class landscape ifTrue:[
        super nextPutAllUntranslated:'Landscape
'.
    ].

    self setFont.

    yPos := TopY.
    xPos := LeftX.
    lineBuffer := ''.
    lineNr := 1.
    colNr := 0

    "Modified: 1.6.1996 / 00:44:10 / cg"
! !

!PostscriptPrinterStream methodsFor:'queries'!

fontHeight
    "the used fonts height in my postscript coordinate system 
     (i.e. in twips, which is 1/20th of a point)"

    ^ FontHeight

    "Modified: 30.5.1996 / 16:47:37 / ca"
    "Modified: 1.6.1996 / 13:14:51 / cg"
!

leftX
    "the left x startPosition (i.e. leftMargin) in my postscript coordinate system.
     (i.e. in twips, which is 1/20th of a point)"

    ^ LeftX

    "Modified: 30.5.1996 / 16:48:56 / ca"
    "Modified: 1.6.1996 / 13:14:59 / cg"
!

linesPerPage
    "the number of lines per page"

    ^ LinesPerPage

    "Modified: 30.5.1996 / 16:48:20 / ca"
!

overAllPageSize
    "the overAll pageSize in my postscript coordinate system.
     (i.e. in twips, which is 1/20th of a point)"

    ^ PageHeight

    "Created: 30.5.1996 / 16:56:51 / ca"
    "Modified: 30.5.1996 / 16:58:01 / ca"
    "Modified: 1.6.1996 / 13:15:06 / cg"
!

topMargin
    "return the topMargin in my postscript coordinate system.
     (i.e. in twips, which is 1/20th of a point)"

    ^ PageHeight - TopY

    "Modified: 30.5.1996 / 16:58:01 / ca"
    "Created: 30.5.1996 / 17:02:02 / ca"
    "Modified: 1.6.1996 / 13:15:50 / cg"
!

topY
    "the top y startPosition (i.e. page-size - topMargin) in my own coordinate system
     (i.e. in twips, which is 1/20th of a point)"

    ^ TopY

    "Modified: 30.5.1996 / 16:48:48 / ca"
    "Modified: 1.6.1996 / 13:15:23 / cg"
! !

!PostscriptPrinterStream class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/PostscriptPrinterStream.st,v 1.35 1996-06-03 13:38:16 cg Exp $'
! !
PostscriptPrinterStream initialize!