Delegate GraphicsContext objects
authorStefan Vogel <sv@exept.de>
Tue, 19 Jul 2016 21:45:55 +0200
changeset 3709 ae76cdc6787a
parent 3707 baba86518fd9
child 3710 5054e19472b6
Delegate GraphicsContext objects
PrinterContext.st
WinPrinterContext.st
--- a/PrinterContext.st	Mon Jul 18 14:14:06 2016 +0200
+++ b/PrinterContext.st	Tue Jul 19 21:45:55 2016 +0200
@@ -1,6 +1,8 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
-              All Rights Reserved
+	      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
@@ -9,9 +11,13 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+'From Smalltalk/X, Version:7.1.0.0 on 18-07-2016 at 13:47:02'                   !
+
 "{ Package: 'stx:libview2' }"
 
-GraphicsMedium subclass:#PrinterContext
+"{ NameSpace: Smalltalk }"
+
+DeviceGraphicsContext subclass:#PrinterContext
 	instanceVariableNames:'abort jobid printerInfo textAlign'
 	classVariableNames:''
 	poolDictionaries:''
@@ -23,7 +29,7 @@
 copyright
 "
  COPYRIGHT (c) 2006 by eXept Software AG
-              All Rights Reserved
+	      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
@@ -36,14 +42,14 @@
 
 documentation
 "
-    I am the mediator between the smalltalk printing protocol 
+    I am the mediator between the smalltalk printing protocol
     (which is the same as the graphics drawing protocol) and the
     windows printer.
     When youopena printer, you will typically talk to me, and I will
     forward the graphics commands to my printer.
 
     [author:]
-        Felix Madrid (fm@exept.de)
+	Felix Madrid (fm@exept.de)
 "
 ! !
 
@@ -59,12 +65,12 @@
 
 default
     "Answer the default Printer, or nil if none."
-    
+
     |defaultName|
 
-    ^ (defaultName := self defaultPrinterName) isNil 
-        ifTrue:[ nil ]
-        ifFalse:[ self named:defaultName ]
+    ^ (defaultName := self defaultPrinterName) isNil
+	ifTrue:[ nil ]
+	ifFalse:[ self named:defaultName ]
 
     "
      self default
@@ -78,7 +84,7 @@
 defaultMargins
     "Private - answer aPoint containing the default horizontal and vertical
      margins for a page (units in inches)."
-    
+
     ^ 0.5 @ 0.75
 
     "Created: / 01-08-2006 / 16:09:31 / fm"
@@ -87,7 +93,7 @@
 
 defaultPrinterName
     "Answer the name of the default printer, or nil if none."
-    
+
     |printerInfo printerName|
 
     printerInfo := OperatingSystem getDefaultPrinterName.
@@ -102,10 +108,10 @@
     "Modified: / 10-10-2006 / 17:32:45 / cg"
 !
 
-getPrinterInformation:printerNameString 
+getPrinterInformation:printerNameString
     " Answer the printer information for the printer named printerNameString.  If no name is specified,
       answer the information for the default printer."
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:56:31 / cg"
@@ -126,7 +132,7 @@
 
 printerNames
     "Answer a collection of all known printer names."
-    
+
     ^ OperatingSystem getPrintersNames
 
     "Created: / 27-07-2006 / 17:54:45 / fm"
@@ -137,7 +143,7 @@
 
 abortPrintJob
     "Abort the current print job."
-    
+
     abort := true.
     jobid := nil.
 
@@ -147,7 +153,7 @@
 
 aborted
     "Answer whether the user aborted from PrintAbortDialog."
-    
+
     ^ abort
 
     "Created: / 27-07-2006 / 10:20:10 / fm"
@@ -164,7 +170,7 @@
 getCharHeight
     "Private - answer the height of the font selected in the receiver's
      device context."
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:50:06 / cg"
@@ -179,16 +185,16 @@
 
 name
     "Answer the receiver's name from the current printerInfo."
-    
+
     ^ self printerInfo printerName
 
     "Modified: / 02-08-2006 / 16:55:03 / fm"
     "Modified: / 10-10-2006 / 18:15:33 / cg"
 !
 
-name:aName 
+name:aName
     "Set the receiver's printer name to aName."
-    
+
     self printerInfo:(self class getPrinterInformation:aName)
 
     "Modified: / 10-10-2006 / 18:15:36 / cg"
@@ -237,13 +243,13 @@
     "Modified: / 16-04-2007 / 12:52:36 / cg"
 !
 
-printerInfo:aPrinterInfo 
+printerInfo:aPrinterInfo
     printerInfo := aPrinterInfo
 
     "Modified: / 16-04-2007 / 12:54:07 / cg"
 !
 
-printerInfoWithName:aName 
+printerInfoWithName:aName
     self printerInfo:(self class getPrinterInformation:aName).
 
     "Modified: / 16-04-2007 / 12:54:04 / cg"
@@ -263,7 +269,7 @@
 
 printerUserFriendlyName
     "Answer the receiver's name from the current printerInfo."
-    
+
     ^ self printerInfo userFriendlyName
 
     "Created: / 03-08-2006 / 12:55:57 / fm"
@@ -276,7 +282,7 @@
     "Modified: / 16-04-2007 / 12:53:51 / cg"
 !
 
-setPrinterFont:aFont 
+setPrinterFont:aFont
 
     self font: aFont
 
@@ -307,10 +313,10 @@
 
 buildPrinter
     "Private - create all the operating system resources needed."
-    
+
     self
-        createDC;
-        initExtent
+	createDC;
+	initExtent
 
     "Created: / 27-07-2006 / 10:20:36 / fm"
     "Modified: / 01-08-2006 / 15:57:49 / fm"
@@ -319,7 +325,7 @@
 
 createDC
     "Private - Create a device context for the receiver"
-    
+
     self subclassResponsibility
 
     "Created: / 27-07-2006 / 10:21:05 / fm"
@@ -330,19 +336,17 @@
 initExtent
     "Private - init the width and height of GraphicsTool for the receiver."
 
-    width := self printerWidthArea.
-    height := self printerHeightArea.
     self graphicsDevice
-        width:width;
-        height:height.
-    
+        width:self printerWidthArea;
+        height:self printerHeightArea.
+
 
     "Modified: / 01-08-2006 / 16:14:49 / fm"
 !
 
 releaseDC
     "Private - Closes the device context of the receiver"
-    
+
     self subclassResponsibility
 
     "Created: / 27-07-2006 / 10:21:05 / fm"
@@ -352,7 +356,7 @@
 
 !PrinterContext methodsFor:'printing'!
 
-print:aString font:aFont title:aTitle wordWrap:wordWrapBoolean marginsRect:aMarginsRect 
+print:aString font:aFont title:aTitle wordWrap:wordWrapBoolean marginsRect:aMarginsRect
     "Answer the receiver.  Output the receiver string to
      the printer using aFont.  A Print abort dialog box will be opened
      with aTitle.  If collateBoolean is true, collate output, otherwise
@@ -360,50 +364,50 @@
      wordWrapBoolean is true, word wrap the lines, otherwise do not.
      Left, top, right & bottom margins are specified in inches in
      aMarginsRect."
-    
+
     |lines linesPerPage totalPage marginsRect firstPage abortDialog|
 
     jobid isNil ifTrue:[
-        self startPrintJob:aTitle
+	self startPrintJob:aTitle
     ].
     abortDialog := PrintAbortDialog new open:aTitle printer:self.
     self font:aFont.
     marginsRect := self marginsRectangleFor:aMarginsRect.
-    lines := self 
-                asArrayOfStringLines:aString
-                in:marginsRect
-                wordWrap:wordWrapBoolean.
+    lines := self
+		asArrayOfStringLines:aString
+		in:marginsRect
+		wordWrap:wordWrapBoolean.
     linesPerPage := self linesPerPageFor: marginsRect.
     totalPage := (lines size + linesPerPage - 1) // linesPerPage.
     firstPage := true.
-    
+
 "/    collateBoolean
 "/        ifTrue: [
 "/            copiesInteger timesRepeat: [
-    
-    1 to:totalPage do:[:page | 
-        abort ifTrue:[ ^ self ].
-        firstPage ifFalse:[
-            self formFeed
-        ].
-        abortDialog 
-            updatePrintingPageInfo:(self class classResources
-                                    string:'Page %1/%2'
-                                    with:page printString
-                                    with:totalPage printString).
-        
+
+    1 to:totalPage do:[:page |
+	abort ifTrue:[ ^ self ].
+	firstPage ifFalse:[
+	    self formFeed
+	].
+	abortDialog
+	    updatePrintingPageInfo:(self class classResources
+				    string:'Page %1/%2'
+				    with:page printString
+				    with:totalPage printString).
+
 "/      self device font: printerFont.
-        
-        self font:aFont.
-        self 
-            printPage:page
-            in:marginsRect
-            lines:lines
-            linesPerPage:linesPerPage.
-        firstPage := false
+
+	self font:aFont.
+	self
+	    printPage:page
+	    in:marginsRect
+	    lines:lines
+	    linesPerPage:linesPerPage.
+	firstPage := false
     ].
-    
-"/            ] 
+
+"/            ]
 "/        ] ifFalse: [
 "/            1 to: totalPage do: [ :page |
 "/                copiesInteger timesRepeat: [
@@ -411,14 +415,14 @@
 "/                    firstPage ifFalse: [ self formFeed ].
 "/                    self device font: printerFont.
 "/                    self printPage: page in: marginsRect lines: lines linesPerPage: linesPerPage.
-"/                    firstPage := false 
-"/                 ] 
-"/            ]   
+"/                    firstPage := false
+"/                 ]
+"/            ]
 "/        ].
-    
+
     jobid notNil ifTrue:[
-        self endPrintJob.
-        abortDialog close.
+	self endPrintJob.
+	abortDialog close.
     ].
 
     "/    abort ifFalse: [ abortDialog close ]
@@ -438,14 +442,14 @@
     wordWrap: wordWrapBoolean
     marginsRect: aMarginsRect
 
-        "Private - Answer the receiver.  Output the receiver string to
-        the printer using aFont.  A Print abort dialog box will be opened
-        with aTitle.  If collateBoolean is true, collate output, otherwise
-        do not.  Print copiesInteger copies of the specified string.  If
-        wordWrapBoolean is true, word wrap the lines, otherwise do not.
-        Left, top, right & bottom margins are specified in inches in
-        aMarginsRect.
-        Mg: Erweitert um pageHeader"
+	"Private - Answer the receiver.  Output the receiver string to
+	the printer using aFont.  A Print abort dialog box will be opened
+	with aTitle.  If collateBoolean is true, collate output, otherwise
+	do not.  Print copiesInteger copies of the specified string.  If
+	wordWrapBoolean is true, word wrap the lines, otherwise do not.
+	Left, top, right & bottom margins are specified in inches in
+	aMarginsRect.
+	Mg: Erweitert um pageHeader"
        "Changed by K3/EES5-Mg, 08.01.96"
 
     | lines linesPerPage totalPage marginsRect firstPage charHeight  printerFont headerLines|
@@ -458,11 +462,11 @@
     linesPerPage := marginsRect bottom - marginsRect top // charHeight.
 
     linesPerPage > headerLines size
-        ifFalse:
-          [Dialog information: 'Der Dokumentenkopf ist zu groß; wird ignoriert!!'.
-           headerLines := #().
-          ]
-        ifTrue: [linesPerPage := linesPerPage - headerLines size].
+	ifFalse:
+	  [Dialog information: 'Der Dokumentenkopf ist zu groß; wird ignoriert!!'.
+	   headerLines := #().
+	  ]
+	ifTrue: [linesPerPage := linesPerPage - headerLines size].
     totalPage := lines size + linesPerPage - 1 // linesPerPage.
     firstPage := true.
 
@@ -470,14 +474,14 @@
 "/        ifTrue: [
 "/            copiesInteger timesRepeat: [
 
-                1 to: totalPage do: [ :page |
-                    abort ifTrue: [ ^self endPrintJob ].
-                    firstPage ifFalse: [ self formFeed ].
-                    self "pen" font: aFont "printerFont".
-                    self printPage: page in: marginsRect lines: lines headerLines: headerLines linesPerPage: linesPerPage.
-                    firstPage := false ] 
+		1 to: totalPage do: [ :page |
+		    abort ifTrue: [ ^self endPrintJob ].
+		    firstPage ifFalse: [ self formFeed ].
+		    self "pen" font: aFont "printerFont".
+		    self printPage: page in: marginsRect lines: lines headerLines: headerLines linesPerPage: linesPerPage.
+		    firstPage := false ]
 
-"/              ] 
+"/              ]
 "/          ]
 "/        ifFalse: [
 "/            1 to: totalPage do: [ :page |
@@ -491,7 +495,7 @@
     "Created: / 30-11-2006 / 13:19:06 / User"
 !
 
-print:aString pageHeader:aString2 font:aFont title:aTitle wordWrap:wordWrapBoolean marginsRect:aMarginsRect 
+print:aString pageHeader:aString2 font:aFont title:aTitle wordWrap:wordWrapBoolean marginsRect:aMarginsRect
     "Private - Answer the receiver.  Output the receiver string to
      the printer using aFont.  A Print abort dialog box will be opened
      with aTitle.  If collateBoolean is true, collate output, otherwise
@@ -499,51 +503,51 @@
      wordWrapBoolean is true, word wrap the lines, otherwise do not.
      Left, top, right & bottom margins are specified in inches in
      aMarginsRect."
-    
+
     |lines linesPerPage totalPage marginsRect firstPage charHeight printerFont headerLines|
 
     self font:aFont.
     charHeight := self getCharHeight.
     marginsRect := self marginsRectangleFor:aMarginsRect.
-    lines := self 
-                asArrayOfStringLines:aString
-                in:marginsRect
-                wordWrap:wordWrapBoolean.
-    headerLines := self 
-                asArrayOfStringLines:aString2
-                in:marginsRect
-                wordWrap:wordWrapBoolean.
+    lines := self
+		asArrayOfStringLines:aString
+		in:marginsRect
+		wordWrap:wordWrapBoolean.
+    headerLines := self
+		asArrayOfStringLines:aString2
+		in:marginsRect
+		wordWrap:wordWrapBoolean.
     linesPerPage := (marginsRect bottom - marginsRect top) // charHeight.
     linesPerPage > headerLines size ifFalse:[
-        Dialog information:(self class classResources 
-                                string:'The header is too large - ignored!!').
-        headerLines := #().
+	Dialog information:(self class classResources
+				string:'The header is too large - ignored!!').
+	headerLines := #().
     ] ifTrue:[
-        linesPerPage := linesPerPage - headerLines size
+	linesPerPage := linesPerPage - headerLines size
     ].
     totalPage := (lines size + linesPerPage - 1) // linesPerPage.
     firstPage := true.
-    
+
 "/    collateBoolean
 "/        ifTrue: [
 "/            copiesInteger timesRepeat: [
-    
-    1 to:totalPage do:[:page | 
-        abort ifTrue:[ ^ self ].
-        firstPage ifFalse:[
-            self formFeed
-        ].
-        self font:printerFont.
-        self 
-            printPage:page
-            in:marginsRect
-            lines:lines
-            headerLines:headerLines
-            linesPerPage:linesPerPage.
-        firstPage := false
+
+    1 to:totalPage do:[:page |
+	abort ifTrue:[ ^ self ].
+	firstPage ifFalse:[
+	    self formFeed
+	].
+	self font:printerFont.
+	self
+	    printPage:page
+	    in:marginsRect
+	    lines:lines
+	    headerLines:headerLines
+	    linesPerPage:linesPerPage.
+	firstPage := false
     ]
 
-    "/            ] 
+    "/            ]
     "/        ] ifFalse: [
     "/            1 to: totalPage do: [ :page |
     "/                copiesInteger timesRepeat: [
@@ -551,9 +555,9 @@
     "/                    firstPage ifFalse: [ self formFeed ].
     "/                    self device font: printerFont.
     "/                    self printPage: page in: marginsRect lines: lines headerLines: headerLines linesPerPage: linesPerPage.
-    "/                    firstPage := false 
-    "/                ] 
-    "/            ] 
+    "/                    firstPage := false
+    "/                ]
+    "/            ]
     "/        ].
 
     "Created: / 03-08-2006 / 16:14:10 / fm"
@@ -564,7 +568,7 @@
 
 endPage
     "Informs device that we are finished writing to a page."
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:47:31 / cg"
@@ -585,7 +589,7 @@
     "End the print job.  Everything drawn between startPrintJob
      and endPrintJob will become one entry in the print queue.
      Won't close the DC "
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:47:28 / cg"
@@ -593,10 +597,10 @@
 
 formFeed
     "Send a form feed to the printer."
-    
+
     self
-        endPage;
-        startPage
+	endPage;
+	startPage
 
     "Created: / 27-07-2006 / 18:25:40 / fm"
     "Modified: / 10-10-2006 / 18:15:07 / cg"
@@ -604,7 +608,7 @@
 
 startPage
     "Starts a page."
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:47:13 / cg"
@@ -613,29 +617,29 @@
 startPrintJob
     "Start a print job.  Everything drawn between startPrintJob
      and endPrintJob will become one entry in the print queue."
-    
+
     self startPrintJob:nil
 
     "Created: / 27-07-2006 / 18:18:52 / fm"
     "Modified: / 10-10-2006 / 18:19:05 / cg"
 !
 
-startPrintJob:aString 
+startPrintJob:aString
     "Start a print job, using aString as the job title; everything
      drawn between startPrintJob and endPrintJob will become
      one entry in the print queue."
-    
+
     ^ self startPrintJob:aString fileName:nil
 
     "Created: / 27-07-2006 / 18:19:09 / fm"
     "Modified: / 10-10-2006 / 18:19:12 / cg"
 !
 
-startPrintJob:aString fileName:aFileName 
+startPrintJob:aString fileName:aFileName
     "Start a print job, using aString as the job title; everything
      drawn between startPrintJob and endPrintJob will become
      one entry in the print queue."
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:46:58 / cg"
@@ -664,50 +668,50 @@
 
 !PrinterContext methodsFor:'text printing'!
 
-asArrayOfStringLines:aString in:aRectangle wordWrap:wordWrapBoolean 
+asArrayOfStringLines:aString in:aRectangle wordWrap:wordWrapBoolean
     "Private - convert aString into an array of lines; if wordWrapBoolean
      is true, also perform word wrapping on the lines, within aRectangle."
-    
+
     |line lines stream x0 x1 partialLine leftMargin rightMargin partialLineWidth index|
 
     stream := ReadStream on:aString.
     lines := OrderedCollection new.
     wordWrapBoolean ifTrue:[
-        leftMargin := aRectangle left.
-        rightMargin := aRectangle right
+	leftMargin := aRectangle left.
+	rightMargin := aRectangle right
     ].
     [ stream atEnd ] whileFalse:[
-        line := stream nextLine.
-        wordWrapBoolean ifFalse:[
-            lines add:line
-        ] ifTrue:[
-            x0 := x1 := 1.
-            1 to:line size do:[:i | 
-                ((line at:i) = Character space "32" 
-                    and:[ (partialLine := line copyFrom:x0 to:i) trimBlanks notEmpty ]) 
-                        ifTrue:[
-                            partialLineWidth := self stringWidthOf:partialLine.
-                            (leftMargin + partialLineWidth) > rightMargin ifTrue:[
-                                partialLine := line copyFrom:x0 to:x1.
-                                lines add:partialLine.
-                                x0 := x1 + 1
-                            ] ifFalse:[ x1 := i ]
-                        ].
-                index := i
-            ].
-            line isEmpty ifTrue:[
-                lines add:line
-            ] ifFalse:[
-                partialLine := line copyFrom:x0 to:index.
-                partialLineWidth := self stringWidthOf:partialLine.
-                (leftMargin + partialLineWidth) > rightMargin ifTrue:[
-                    partialLine := line copyFrom:x0 to:x1.
-                    lines add:partialLine.
-                    partialLine := line copyFrom:x1 + 1 to:index
-                ].
-                lines add:partialLine
-            ]
-        ]
+	line := stream nextLine.
+	wordWrapBoolean ifFalse:[
+	    lines add:line
+	] ifTrue:[
+	    x0 := x1 := 1.
+	    1 to:line size do:[:i |
+		((line at:i) = Character space "32"
+		    and:[ (partialLine := line copyFrom:x0 to:i) trimBlanks notEmpty ])
+			ifTrue:[
+			    partialLineWidth := self stringWidthOf:partialLine.
+			    (leftMargin + partialLineWidth) > rightMargin ifTrue:[
+				partialLine := line copyFrom:x0 to:x1.
+				lines add:partialLine.
+				x0 := x1 + 1
+			    ] ifFalse:[ x1 := i ]
+			].
+		index := i
+	    ].
+	    line isEmpty ifTrue:[
+		lines add:line
+	    ] ifFalse:[
+		partialLine := line copyFrom:x0 to:index.
+		partialLineWidth := self stringWidthOf:partialLine.
+		(leftMargin + partialLineWidth) > rightMargin ifTrue:[
+		    partialLine := line copyFrom:x0 to:x1.
+		    lines add:partialLine.
+		    partialLine := line copyFrom:x1 + 1 to:index
+		].
+		lines add:partialLine
+	    ]
+	]
     ].
     ^ lines asArray
 
@@ -721,22 +725,22 @@
     x := aPoint x.
     y := aPoint y.
     (textAlign isNil or:[textAlign == 0 ]) ifTrue:[
-        self displayString:aString at:aPoint.
-        ^ self
+	self displayString:aString at:aPoint.
+	^ self
     ].
     (textAlign == 8 "TaBottom") ifTrue:[
-        y := aPoint y - (self container font ascent) "container font ascent".
+	y := aPoint y - (self container font ascent) "container font ascent".
     ] ifFalse:[ (textAlign == 6 "TaCenter") ifTrue:[
 "/        x := aRect left + ((aRect width-(container font widthOf:aString))//2).
     ] ifFalse:[ (textAlign == 2 "TaRight") ifTrue:[
-        x := aRect right - (self "container font widthof:" stringWidthOf:aString).
+	x := aRect right - (self "container font widthof:" stringWidthOf:aString).
 "/        y := self "container font ascent" getCharHeight + aPoint y .
     ] ifFalse:[ (textAlign == 14 "TaCenterBottom") ifTrue:[
-        y := aRect bottom - self getCharHeight "container font ascent".
-        x := aRect left + ((aRect width-(self "container font widthOf:" stringWidthOf:aString))//2).
+	y := aRect bottom - self getCharHeight "container font ascent".
+	x := aRect left + ((aRect width-(self "container font widthOf:" stringWidthOf:aString))//2).
     ] ifFalse:[ (textAlign == 10) ifTrue:[
-        x := aRect right - (self "container font widthof:" stringWidthOf:aString).
-        y := aPoint y - (self container font ascent)"aRect bottom - self getCharHeight".
+	x := aRect right - (self "container font widthof:" stringWidthOf:aString).
+	y := aPoint y - (self container font ascent)"aRect bottom - self getCharHeight".
     ]]]]].
 
 "/aString = '3' ifTrue:[
@@ -753,28 +757,28 @@
     "Modified: / 14-12-2006 / 12:29:13 / User"
 !
 
-displayStringLines:anIndexedCollection from:startIndex to:endIndex in:aRectangle 
+displayStringLines:anIndexedCollection from:startIndex to:endIndex in:aRectangle
     "Private - display Strings in anIndexedCollection starting at startIndex and
      ending at endIndex, clipped within the bounds of aRectangle."
-    
+
     |charHeight ascent|
 
     charHeight := self getCharHeight.
     ascent := self font ascentOn:self device.
-    startIndex to:endIndex do:[:i | 
-        |lineToPrint|
+    startIndex to:endIndex do:[:i |
+	|lineToPrint|
 
-        lineToPrint := (anIndexedCollection at:i).
-        self graphicsDevice 
-            displayString:lineToPrint
-            from:1
-            to:lineToPrint size
-            x:aRectangle left
-            y:(aRectangle top + ((i - startIndex) * charHeight))
-            in:nil
-            with:self gcId
-            opaque:false
-            fontAscent:ascent.
+	lineToPrint := (anIndexedCollection at:i).
+	self graphicsDevice
+	    displayString:lineToPrint
+	    from:1
+	    to:lineToPrint size
+	    x:aRectangle left
+	    y:(aRectangle top + ((i - startIndex) * charHeight))
+	    in:nil
+	    with:self gcId
+	    opaque:false
+	    fontAscent:ascent.
     ].
 
     "/    region := self setClipRect: aRectangle.
@@ -792,15 +796,15 @@
     "Modified: / 10-10-2006 / 18:14:36 / cg"
 !
 
-displayStringLines:anIndexedCollection in:aRectangle 
+displayStringLines:anIndexedCollection in:aRectangle
     "Private - display anIndexedCollection of Strings clipped within
      the bounds of aRectangle."
-    
-    self 
-        displayStringLines:anIndexedCollection
-        from:1
-        to:anIndexedCollection size
-        in:aRectangle
+
+    self
+	displayStringLines:anIndexedCollection
+	from:1
+	to:anIndexedCollection size
+	in:aRectangle
 
     "Created: / 03-08-2006 / 16:03:07 / fm"
     "Modified: / 10-10-2006 / 18:14:40 / cg"
@@ -815,22 +819,22 @@
 linesPerPageFor: aRectangle
     |marginsRect charHeight|
 
-    marginsRect := aRectangle isNil 
-        ifTrue:[self marginsRectangleFor: nil]
-        ifFalse:[aRectangle].
+    marginsRect := aRectangle isNil
+	ifTrue:[self marginsRectangleFor: nil]
+	ifFalse:[aRectangle].
 
-    charHeight := self getCharHeight.                   
+    charHeight := self getCharHeight.
     ^(marginsRect bottom - marginsRect top) // charHeight
 
     "Created: / 12-10-2006 / 11:52:57 / User"
     "Modified: / 16-04-2007 / 12:44:56 / cg"
 !
 
-marginsRectangleFor:aRectangle 
+marginsRectangleFor:aRectangle
     "Private - Answer a Rectangle defining margins based on aRectangle.
      Units for aRectangle are in inches, returned margins rectangle is
      in device units (pixels)."
-    
+
     |left top right bottom pixelsPerInchX pixelsPerInchY horzRes vertRes inset rectangle|
 
     pixelsPerInchX := self pixelsPerInchOfScreenWidth.
@@ -839,18 +843,18 @@
     pixelsPerInchY == 0 ifTrue:[self halt:'invalid definitions for screen resolution'].
 
     aRectangle isNil ifTrue:[
-        horzRes := self printerWidthArea.
-        vertRes := self printerHeightArea.
-        inset := self class defaultMargins.
-        left := (inset x * pixelsPerInchX) asInteger.
-        top := (inset y * pixelsPerInchY) asInteger.
-        right := horzRes - (inset x * pixelsPerInchX) asInteger.
-        bottom := vertRes - (inset y * pixelsPerInchY) asInteger
+	horzRes := self printerWidthArea.
+	vertRes := self printerHeightArea.
+	inset := self class defaultMargins.
+	left := (inset x * pixelsPerInchX) asInteger.
+	top := (inset y * pixelsPerInchY) asInteger.
+	right := horzRes - (inset x * pixelsPerInchX) asInteger.
+	bottom := vertRes - (inset y * pixelsPerInchY) asInteger
     ] ifFalse:[
-        left := (aRectangle left * pixelsPerInchX) asInteger.
-        top := (aRectangle top * pixelsPerInchY) asInteger.
-        right := (aRectangle right * pixelsPerInchX) asInteger.
-        bottom := (aRectangle bottom * pixelsPerInchY) asInteger
+	left := (aRectangle left * pixelsPerInchX) asInteger.
+	top := (aRectangle top * pixelsPerInchY) asInteger.
+	right := (aRectangle right * pixelsPerInchX) asInteger.
+	bottom := (aRectangle bottom * pixelsPerInchY) asInteger
     ].
     rectangle := left @ top corner:right @ bottom.
     ^ rectangle
@@ -860,10 +864,10 @@
     "Modified: / 16-04-2007 / 11:57:21 / cg"
 !
 
-printPage:pageIndex in:aRectangle lines:lines headerLines:headerLines linesPerPage:linesPerPage 
+printPage:pageIndex in:aRectangle lines:lines headerLines:headerLines linesPerPage:linesPerPage
     "Private - print page # pageIndex from lines, assuming
      the given number of linesPerPage."
-    
+
     |firstLine lastLine l indexString p cHeight rect hLines|
 
     firstLine := (pageIndex - 1) * linesPerPage + 1.
@@ -871,22 +875,22 @@
     rect := aRectangle deepCopy.
     hLines := headerLines deepCopy.
     headerLines size > 0 ifTrue:[
-        l := hLines first.
-        p := l indexOfSubCollection: "indexOfString:"'#P'.
-        p = 0 ifFalse:[
-            indexString := pageIndex printString , ' '.
-            l := (l copyFrom:1 to:p - 1) , indexString , (l copyFrom:p + 2 to:l size).
-            hLines at:1 put:l.
-        ].
-        cHeight := self getCharHeight.
-        rect top:rect top + (hLines size * cHeight).
+	l := hLines first.
+	p := l indexOfSubCollection: "indexOfString:"'#P'.
+	p = 0 ifFalse:[
+	    indexString := pageIndex printString , ' '.
+	    l := (l copyFrom:1 to:p - 1) , indexString , (l copyFrom:p + 2 to:l size).
+	    hLines at:1 put:l.
+	].
+	cHeight := self getCharHeight.
+	rect top:rect top + (hLines size * cHeight).
     ].
     self displayStringLines:hLines in:aRectangle.
-    self 
-        displayStringLines:lines
-        from:firstLine
-        to:lastLine
-        in:rect.
+    self
+	displayStringLines:lines
+	from:firstLine
+	to:lastLine
+	in:rect.
 
     "Created: / 27-07-2006 / 18:28:00 / fm"
     "Modified: / 03-08-2006 / 16:03:15 / fm"
@@ -894,40 +898,40 @@
     "Modified: / 30-11-2006 / 13:34:44 / User"
 !
 
-printPage:pageIndex in:aRectangle lines:lines linesPerPage:linesPerPage 
+printPage:pageIndex in:aRectangle lines:lines linesPerPage:linesPerPage
     "Private - print page # pageIndex from lines, assuming
      the given number of linesPerPage."
-    
+
     |firstLine lastLine|
 
     firstLine := (pageIndex - 1) * linesPerPage + 1.
     lastLine := (firstLine + linesPerPage - 1) min:lines size.
-    self 
-        displayStringLines:lines
-        from:firstLine
-        to:lastLine
-        in:aRectangle
+    self
+	displayStringLines:lines
+	from:firstLine
+	to:lastLine
+	in:aRectangle
 
     "Created: / 27-07-2006 / 18:24:59 / fm"
     "Modified: / 03-08-2006 / 12:47:24 / fm"
     "Modified: / 10-10-2006 / 18:18:22 / cg"
 !
 
-stringWidthOf:aString 
+stringWidthOf:aString
     "Return the width of aString
      when written using the current font."
-    
+
     ^ self stringWidthOf:aString at:aString size.
 
     "Modified: / 03-08-2006 / 10:18:23 / fm"
     "Modified: / 10-10-2006 / 18:20:08 / cg"
 !
 
-stringWidthOf:aString at:index 
+stringWidthOf:aString at:index
     "Return the width of aString up to index
      when written using the current font; expand tabs out
      to 4 spaces for calculations"
-    
+
     self subclassResponsibility
 
     "Modified: / 16-04-2007 / 12:45:42 / cg"
@@ -954,6 +958,6 @@
 !PrinterContext class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/PrinterContext.st,v 1.21 2014-03-19 10:04:20 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/WinPrinterContext.st	Mon Jul 18 14:14:06 2016 +0200
+++ b/WinPrinterContext.st	Tue Jul 19 21:45:55 2016 +0200
@@ -9,6 +9,8 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+'From Smalltalk/X, Version:7.1.0.0 on 18-07-2016 at 13:47:02'                   !
+
 "{ Package: 'stx:libview2' }"
 
 "{ NameSpace: Smalltalk }"
@@ -22,7 +24,7 @@
 
 WinPrinterContext subclass:#WinPrinterGraphicContext
 	instanceVariableNames:'fontScale printPageNumbers pageNumberFormat pageCounter
-		needsEndOfPage titleFont'
+		needsEndOfPage titleFont width height'
 	classVariableNames:''
 	poolDictionaries:''
 	privateIn:WinPrinterContext
@@ -294,7 +296,7 @@
     gc := WinPrinterGraphicContext fromPrinterInfo:printerInfo.
 
     gc notNil ifTrue:[
-        gc startPrintJob:jobName
+	gc startPrintJob:jobName
     ].
     ^ gc
 ! !
@@ -5689,6 +5691,14 @@
     ^ 50
 !
 
+extent
+    ^ width @ height
+!
+
+height
+    ^ height
+!
+
 leftMargin
     "return the papers left margin measured in pixels"
 
@@ -5705,6 +5715,10 @@
     "return the papers top margin measured in pixels"
 
     ^ 50
+!
+
+width
+    ^ width
 ! !
 
 !WinPrinterContext::WinPrinterGraphicContext methodsFor:'accessing-hooks'!