refactorred OS-independent stuff
authorClaus Gittinger <cg@exept.de>
Mon, 16 Apr 2007 12:56:22 +0200
changeset 2300 4f9a576ecdc6
parent 2299 b0576a106d03
child 2301 135f21a3d127
refactorred OS-independent stuff
PrinterContext.st
--- a/PrinterContext.st	Mon Apr 16 12:40:02 2007 +0200
+++ b/PrinterContext.st	Mon Apr 16 12:56:22 2007 +0200
@@ -12,7 +12,7 @@
 "{ Package: 'stx:libview2' }"
 
 GraphicsMedium subclass:#PrinterContext
-	instanceVariableNames:'name abort jobid printerInfo textAlign'
+	instanceVariableNames:'abort jobid printerInfo textAlign'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Interface-Printing'
@@ -50,19 +50,9 @@
 !PrinterContext class methodsFor:'instance creation'!
 
 fromPrinterInfo: aPrinterInfo
-    | aPrinter hDC|     
+    self subclassResponsibility
 
-    hDC := aPrinterInfo createDC.
-    hDC = 0 ifTrue: [ ^self error: 'Error while opening printer.' ].
-    aPrinter := self new.
-    aPrinter printerInfo: aPrinterInfo.
-    aPrinter setDevice:(WinPrinter on: aPrinterInfo) id:nil gcId:hDC.
-    aPrinter initExtent.
-    ^aPrinter
-
-    "Created: / 03-08-2006 / 12:53:52 / fm"
-    "Modified: / 04-08-2006 / 12:55:01 / fm"
-    "Modified: / 10-10-2006 / 19:05:07 / cg"
+    "Modified: / 16-04-2007 / 12:56:56 / cg"
 ! !
 
 !PrinterContext class methodsFor:'accessing'!
@@ -98,35 +88,18 @@
 defaultPrinterName
     "Answer the name of the default printer, or nil if none."
     
-    |printerInfo printerName|
-
-    printerInfo := OperatingSystem getDefaultPrinterName.
-    printerName := (printerInfo copyFrom:1 to:(printerInfo indexOf:$,) - 1) trimBlanks.
-    ^ printerName size == 0 ifTrue:[ nil ] ifFalse:[ printerName ]
+    self subclassResponsibility
 
-    "
-     PrinterContext defaultPrinterName
-    "
-
-    "Modified: / 02-08-2006 / 17:26:09 / fm"
-    "Modified: / 10-10-2006 / 17:32:45 / cg"
+    "Modified: / 16-04-2007 / 12:56:21 / cg"
 !
 
 getPrinterInformation:printerNameString 
     " Answer the printer information for the printer named printerNameString.  If no name is specified,
       answer the information for the default printer."
     
-    |h|
+    self subclassResponsibility
 
-    h := OperatingSystem openPrinter:printerNameString.
-    ^ OperatingSystem 
-        getDocumentProperties:nil
-        hPrinter:h
-        pDeviceName:printerNameString.
-
-    "Created: / 27-07-2006 / 10:22:32 / fm"
-    "Modified: / 01-08-2006 / 16:01:44 / fm"
-    "Modified: / 10-10-2006 / 18:57:45 / cg"
+    "Modified: / 16-04-2007 / 12:56:31 / cg"
 !
 
 named: aName
@@ -151,240 +124,6 @@
     "Modified: / 10-10-2006 / 18:57:51 / cg"
 ! !
 
-!PrinterContext class methodsFor:'testing & examples'!
-
-print: aString font: aFont title: aTitle
-    "Open a print dialog to allow printing of the given string
-     using the given title & font."
-
-    self print: aString font: aFont title: aTitle wordWrap: false     
-
-   "
-    PrinterContext print: 'Holaaaa!! (from:  PrinterContext>>print:aString font:aFont title:aTitle)' font: nil title: 'Printing Test'
-    PrinterContext print: self printingTestString font: nil title: 'Printing Test String'
-    PrinterContext print: self printingTestString font: (Font family:'Arial' face:'medium' size:8) title: 'Printing Test String'
-   "
-
-    "Created: / 27-07-2006 / 17:52:33 / fm"
-    "Modified: / 03-08-2006 / 18:52:31 / fm"
-    "Modified: / 10-10-2006 / 17:37:49 / cg"
-!
-
-print: aString font: aFont title: aTitle wordWrap: wordWrap
-    "Open a print dialog to allow printing of the given string
-     using the given title & font."
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer
-            print: aString
-            font: aFont
-            title: aTitle 
-            wordWrap: wordWrap
-            marginsRect: nil 
-    ] forkAt: 3
-
-    "
-     PrinterContext print: 'Holaaaa!! (from:  PrinterContext>>print:aString font:aFont title:aTitle)' font: nil title: 'Printing Test' wordWrap: true
-     PrinterContext print: (PrinterContext class sourceCodeAt:#'print:font:title:wordWrap:') font:nil title:'Printing Test String' wordWrap:true
-     PrinterContext print: (PrinterContext class sourceCodeAt:#'print:font:title:wordWrap:') font: (Font family:'Arial' face:'medium' size:8) title: 'Printing Test String' wordWrap: true
-    "
-
-    "Created: / 03-08-2006 / 18:51:53 / fm"
-    "Modified: / 10-10-2006 / 17:42:06 / cg"
-!
-
-printCircles: arrayOfPointsAndRadius
-    "Opens a print dialog and prints the given circles"
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer startPrintJob: 'Circles'.
-        arrayOfPointsAndRadius
-            do:[:pointAndRadius |
-                printer displayCircle:(pointAndRadius at:1) 
-                        radius:(pointAndRadius at:2).
-            ].
-        printer endPrintJob.
-    ] forkAt: 3
-
-    "
-     PrinterContext printCircles:  
-        (Array with: (Array with: 800@800 with: 600)
-               with: (Array with: 1500@1500 with: 1000)
-               with: (Array with: 4000@2500 with: 2000))
-    "
-
-    "Created: / 07-08-2006 / 11:46:52 / fm"
-    "Modified: / 10-10-2006 / 17:36:23 / cg"
-!
-
-printCirclesIn: rectangles
-    "Opens a print dialog and prints the given circles"
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer startPrintJob: 'Circles In Rectangles'.
-        rectangles
-           do:[:rectangle |
-               printer displayCircleIn: rectangle.
-           ].
-       printer endPrintJob.
-    ] forkAt: 3
-
-    "
-     PrinterContext printCirclesIn:  
-        (Array with: (Rectangle left:20 top:20 width:400 height:600)
-               with: (Rectangle left:40 top:40 width:600 height:400)    
-        )
-    "
-
-    "Created: / 07-08-2006 / 11:48:46 / fm"
-    "Modified: / 10-10-2006 / 17:38:28 / cg"
-!
-
-printLines: pairOfPointsArray
-    "Opens a print dialog and prints the given lines"
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer startPrintJob: 'Lines'.
-        printer foreground:Color black background:Color white.
-        pairOfPointsArray
-            do:[:pairOfPoints |                 
-                 printer displayLineFrom: (pairOfPoints at:1)  to: (pairOfPoints at:2).
-            ].
-        printer endPrintJob.
-    ] forkAt: 3
-
-    "
-     PrinterContext printLines:  
-        (Array with: (Array with:10@10 with:100@10)
-               with: (Array with:10@10 with:35@200))
-    "
-
-    "Created: / 07-08-2006 / 12:09:48 / fm"
-    "Modified: / 07-08-2006 / 14:11:17 / fm"
-    "Modified: / 10-10-2006 / 17:38:44 / cg"
-!
-
-printPolygons: polygons
-    "Opens a print dialog and prints the given polygons"
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer startPrintJob: 'Polygons'.
-        printer foreground:Color black background:Color white.
-        polygons
-            do:[:aPolygon |
-                 aPolygon displayStrokedOn: printer.
-            ].
-        printer endPrintJob.
-    ] forkAt: 3
-
-    "
-     PrinterContext printPolygons:  
-        (Array with: (Polygon vertices:(
-                                Array
-                                    with:10@10
-                                    with:60@10
-                                    with:35@60)))
-    "
-
-    "Created: / 07-08-2006 / 12:09:48 / fm"
-    "Modified: / 07-08-2006 / 14:11:17 / fm"
-    "Modified: / 10-10-2006 / 17:39:23 / cg"
-!
-
-printRectangles: rectangles
-    "Opens a print dialog and prints the given rectangles"
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer startPrintJob: 'Rectangles'.
-        rectangles 
-            do:[:rectangle |
-                printer displayRectangleX: rectangle origin x 
-                        y: rectangle origin y 
-                        width: rectangle width 
-                        height: rectangle height.
-            ].
-        printer endPrintJob.
-    ] forkAt: 3
-
-    "
-     PrinterContext printRectangles:  
-        (Array with: (Rectangle left:20 top:20 width:400 height:600)
-               with: (Rectangle left:40 top:40 width:600 height:400)    
-        )
-    "
-
-    "Created: / 07-08-2006 / 11:40:48 / fm"
-    "Modified: / 10-10-2006 / 17:39:51 / cg"
-!
-
-printStrings: stringAndPositionsArray
-    "Opens a print dialog and prints the given strings"
-
-    | printerInfo printer |
-
-    printerInfo := PrintingDialog getPrinterInfo.
-    printerInfo isNil ifTrue:[^self].
-
-    printer := self fromPrinterInfo: printerInfo.
-    [ 
-        printer startPrintJob: 'Strings with Position'.
-        printer foreground:Color black background:Color white.
-        stringAndPositionsArray
-            do:[:pairOfPointsAndPosition |                 
-                 printer displayString:(pairOfPointsAndPosition at: 1) 
-                            x:(pairOfPointsAndPosition at: 2) x
-                            y:(pairOfPointsAndPosition at: 2) y
-            ].
-        printer endPrintJob.
-    ] forkAt: 3
-
-    "
-     PrinterContext printStrings:  
-        (Array with: (Array with:'Testing printing with standart method' with:10@10)
-               with: (Array with:'Another test string to print' with:80@200))
-    "
-
-    "Created: / 07-08-2006 / 12:09:48 / fm"
-    "Modified: / 07-08-2006 / 14:11:17 / fm"
-    "Modified: / 10-10-2006 / 17:40:07 / cg"
-! !
-
 !PrinterContext methodsFor:'abort handling'!
 
 abortPrintJob
@@ -417,26 +156,16 @@
     "Private - answer the height of the font selected in the receiver's
      device context."
     
-    |textMetrics answer|
+    self subclassResponsibility
 
-    
-    textMetrics := Win32OperatingSystem::TextMetricsStructure new.
-"/    (OperatingSystem getTextMetrics:gcId lpMetrics:textMetrics) ifFalse:[ ^ self error ].
-"/    Transcript showCR: 'CHAR HEIGHT PRIM ******* ', '   ',  (textMetrics tmHeight + textMetrics tmExternalLeading) printString.
-"/    Transcript showCR: 'CHAR HEIGHT DEVICE ***** ', '   ', (self font heightOf:'PQWEXCZ' on:self device) printString.
-    answer := (self font heightOf:'PQWEXCZ' on:self device).
-"/    answer := textMetrics tmHeight + textMetrics tmExternalLeading.
-    ^answer 
-
-    "Created: / 02-08-2006 / 17:47:20 / fm"
-    "Modified: / 03-08-2006 / 10:09:01 / fm"
-    "Modified: / 10-10-2006 / 18:15:17 / cg"
+    "Modified: / 16-04-2007 / 12:50:06 / cg"
 !
 
 horizontalPixelsPerMeter
-        "Answer horizontal pixels per meter
-        on the screen."
+    "Answer horizontal pixels per meter on the screen."
     ^self pixelsPerInchOfScreenWidth  * 39.3700787
+
+    "Modified: / 16-04-2007 / 12:55:21 / cg"
 !
 
 name
@@ -457,89 +186,70 @@
 !
 
 numberOfColorBitsPerPixel
-    ^ OperatingSystem getDeviceCaps:gcId index:12 "Bitspixel"
+    self subclassResponsibility
 
-    "Created: / 03-08-2006 / 09:58:18 / fm"
-    "Modified: / 10-10-2006 / 18:15:40 / cg"
+    "Modified: / 16-04-2007 / 12:51:15 / cg"
 !
 
 physicalOffsetX
-
-        "Papierhöhe in Pixels"
-       "Changed by K3/EEZ3-Mg, 02.03.99"
+    self subclassResponsibility
 
-    ^ OperatingSystem getDeviceCaps:gcId index:112 "PhysicalOffsetX"
-
-    "Created: / 01-08-2006 / 16:28:34 / fm"
+    "Modified: / 16-04-2007 / 12:54:23 / cg"
 !
 
 physicalOffsetY
-
-        "Papierhöhe in Pixels"
-       "Changed by K3/EEZ3-Mg, 02.03.99"
+    self subclassResponsibility
 
-    ^ OperatingSystem getDeviceCaps:gcId index:113 "PhysicalOffsetY"
-
-    "Created: / 01-08-2006 / 16:28:34 / fm"
+    "Modified: / 16-04-2007 / 12:52:17 / cg"
 !
 
 pixelsPerInchOfScreenHeight
-    ^ OperatingSystem getDeviceCaps:gcId index:90 "Logpixelsy"
+    self subclassResponsibility
 
-    "Created: / 01-08-2006 / 16:29:16 / fm"
+    "Modified: / 16-04-2007 / 12:54:17 / cg"
 !
 
 pixelsPerInchOfScreenWidth
-    ^ OperatingSystem getDeviceCaps:gcId index:88 "Logpixelsx"
+    self subclassResponsibility
 
-    "Created: / 01-08-2006 / 16:28:34 / fm"
+    "Modified: / 16-04-2007 / 12:54:15 / cg"
 !
 
 printerHeightArea
-    ^ (OperatingSystem getDeviceCaps:gcId index:10)
+    self subclassResponsibility
 
-    "Modified: / 10-10-2006 / 18:18:31 / cg"
+    "Modified: / 16-04-2007 / 12:52:28 / cg"
 !
 
 printerInfo
-    "Answer the receiver's name from the current printerInfo."
-    
     ^ printerInfo
 
     "Created: / 02-08-2006 / 16:55:17 / fm"
-    "Modified: / 10-10-2006 / 18:18:34 / cg"
+    "Modified: / 16-04-2007 / 12:52:36 / cg"
 !
 
 printerInfo:aPrinterInfo 
-    "Sets the receiver's printerInfo."
-    
     printerInfo := aPrinterInfo
 
-    "Created: / 02-08-2006 / 16:55:34 / fm"
-    "Modified: / 03-08-2006 / 13:11:19 / fm"
-    "Modified: / 10-10-2006 / 18:18:37 / cg"
+    "Modified: / 16-04-2007 / 12:54:07 / cg"
 !
 
 printerInfoWithName:aName 
-    "Set the receiver's printer name to aName."
-    
     self printerInfo:(self class getPrinterInformation:aName).
-    ^ self
 
-    "Created: / 02-08-2006 / 16:55:52 / fm"
-    "Modified: / 10-10-2006 / 18:18:41 / cg"
+    "Modified: / 16-04-2007 / 12:54:04 / cg"
 !
 
 printerPhysicalHeight
-    ^ OperatingSystem getDeviceCaps:gcId "deviceContext" index:111 "PhysicalHeight"
+    self subclassResponsibility
 
-    "Created: / 01-08-2006 / 16:14:08 / fm"
+    "Modified: / 16-04-2007 / 12:54:00 / cg"
 !
 
 printerPhysicalWidth
-    ^ OperatingSystem getDeviceCaps:gcId "deviceContext" index:110 "PhysicalWidth"
+    self subclassResponsibility
 
-    "Created: / 01-08-2006 / 16:14:08 / fm"
+    "Modified: / 16-04-2007 / 12:53:56 / cg"
 !
 
 printerUserFriendlyName
@@ -552,9 +262,9 @@
 !
 
 printerWidthArea
-    ^ OperatingSystem getDeviceCaps:gcId "deviceContext" index:8 "Horzres"
+    self subclassResponsibility
 
-    "Created: / 01-08-2006 / 16:14:08 / fm"
+    "Modified: / 16-04-2007 / 12:53:51 / cg"
 !
 
 setPrinterFont:aFont 
@@ -565,27 +275,23 @@
 !
 
 setTextAlign:aNumber
+    textAlign :=aNumber.
 
-"/    OperatingSystem setTextAlign: aNumber to: gcId.
-    textAlign :=aNumber.
+    "Modified: / 16-04-2007 / 12:53:26 / cg"
 !
 
 setViewportOrg: aPoint
+    self subclassResponsibility
 
-    ^ OperatingSystem 
-            setViewportOrg: gcId "deviceContext"
-            x: aPoint x
-            y: aPoint y
-            oldOrigin: nil 
-
-    "Created: / 01-08-2006 / 16:14:08 / fm"
+    "Modified: / 16-04-2007 / 12:53:44 / cg"
 !
 
 verticalPixelsPerMeter
-        "Answer vertical pixels per inch
-        on the screen."
+    "Answer vertical pixels per meter on the screen."
 
     ^self pixelsPerInchOfScreenHeight * 39.3700787
+
+    "Modified: / 16-04-2007 / 12:54:43 / cg"
 ! !
 
 !PrinterContext methodsFor:'initialization & release'!
@@ -605,11 +311,11 @@
 createDC
     "Private - Create a device context for the receiver"
     
-    gcId := printerInfo createDC
+    self subclassResponsibility
 
     "Created: / 27-07-2006 / 10:21:05 / fm"
     "Modified: / 02-08-2006 / 17:30:47 / fm"
-    "Modified: / 10-10-2006 / 18:14:28 / cg"
+    "Modified: / 16-04-2007 / 12:49:22 / cg"
 !
 
 initExtent
@@ -840,31 +546,18 @@
 endPage
     "Informs device that we are finished writing to a page."
     
-    (OperatingSystem endPage:gcId) > 0 ifFalse:[
-        self error
-    ]
+    self subclassResponsibility
 
-    "Created: / 27-07-2006 / 18:20:48 / fm"
-    "Modified: / 01-08-2006 / 16:01:34 / fm"
-    "Modified: / 10-10-2006 / 18:14:44 / cg"
+    "Modified: / 16-04-2007 / 12:47:31 / cg"
 !
 
 endPrintJob
     "End the print job.  Everything drawn between startPrintJob
      and endPrintJob will become one entry in the print queue."
     
-    |result|
+    self subclassResponsibility
 
-    self endPage.
-    result := OperatingSystem endDoc:gcId.
-    device close.
-    gcId := nil.
-    jobid := nil.
-    result >= 0 ifFalse:[ self error ]
-
-    "Created: / 27-07-2006 / 18:21:04 / fm"
-    "Modified: / 01-08-2006 / 16:01:38 / fm"
-    "Modified: / 10-10-2006 / 18:50:43 / cg"
+    "Modified: / 16-04-2007 / 12:47:28 / cg"
 !
 
 formFeed
@@ -881,13 +574,9 @@
 startPage
     "Starts a page."
     
-    (OperatingSystem startPage:gcId) > 0 ifFalse:[
-        ^ self error
-    ].
+    self subclassResponsibility
 
-    "Created: / 27-07-2006 / 18:25:55 / fm"
-    "Modified: / 28-07-2006 / 18:19:04 / fm"
-    "Modified: / 10-10-2006 / 18:19:02 / cg"
+    "Modified: / 16-04-2007 / 12:47:13 / cg"
 !
 
 startPrintJob
@@ -916,70 +605,23 @@
      drawn between startPrintJob and endPrintJob will become
      one entry in the print queue."
     
-    |docInfoStruct nameAddress title fileNameAddress|
+    self subclassResponsibility
 
-    gcId isNil ifTrue:[
-        self buildPrinter
-    ].
-    abort := false.
-    title := aString ? 'Smalltalk/X'.
-    nameAddress := title asExternalBytes unprotectFromGC.
-    aFileName isNil ifFalse:[
-        fileNameAddress := aFileName pathName asExternalBytes unprotectFromGC
-    ].
-    docInfoStruct := Win32OperatingSystem::DocInfoStructure new.
-    docInfoStruct
-        cbSize:docInfoStruct sizeInBytes;
-        lpszDocName:nameAddress address.
-    fileNameAddress isNil ifFalse:[
-        docInfoStruct lpszOutput:fileNameAddress address
-    ].
-    jobid := OperatingSystem startDoc:gcId docInfo:docInfoStruct.
-    jobid > 0 ifFalse:[
-        jobid = -1 ifTrue:[
-            abort := true.
-            ^ nil
-        ].
-        ^ self error
-    ].
-    self startPage
-
-    "Created: / 27-07-2006 / 18:19:31 / fm"
-    "Modified: / 03-08-2006 / 15:11:19 / fm"
-    "Modified: / 10-10-2006 / 18:20:01 / cg"
+    "Modified: / 16-04-2007 / 12:46:58 / cg"
 ! !
 
 !PrinterContext methodsFor:'queries'!
 
 supportsColor
-
-"/    | retVal info |
-"/
-"/    info := (self class getPrinterInformation: self name) asUppercase.
-"/    (info includesSubstring: ',PSCRIPT,')
-"/    ifTrue: [
-"/        retVal := (DAPASX::DapasSystemInfo getYesNoInfoApp: 'Printer' profile: 'PostScriptBlackWhite') not.
-"/    ]
-"/    ifFalse: [
-"/        retVal := (info includesSubstring: 'PDF')
-"/            ifTrue: [true]
-"/            ifFalse: [self numberOfColorBitsPerPixel > 1].
-"/    ].
-"/
-"/    ^retVal
-
     ^ false.
 
-    "Created: / 03-08-2006 / 09:55:26 / fm"
-    "Modified: / 04-08-2006 / 13:20:40 / fm"
-    "Modified: / 10-10-2006 / 18:21:07 / cg"
+    "Modified: / 16-04-2007 / 12:44:19 / cg"
 !
 
 supportsGraphics
-    ^(OperatingSystem getDeviceCaps: gcId "asParameter" index: 2 "Technology") ~= 4
+    ^ false
 
-    "Created: / 03-08-2006 / 10:07:43 / fm"
-    "Modified: / 10-10-2006 / 18:21:14 / cg"
+    "Modified: / 16-04-2007 / 12:44:29 / cg"
 ! !
 
 !PrinterContext methodsFor:'text printing'!
@@ -1121,13 +763,13 @@
 !
 
 displayText: aString at: aPoint
+    self displayString:aString x:aPoint x y:aPoint y
 
-self displayString:aString x:aPoint x y:aPoint y
+    "Modified: / 16-04-2007 / 12:44:43 / cg"
 !
 
 linesPerPageFor: aRectangle
-
-|marginsRect charHeight|
+    |marginsRect charHeight|
 
     marginsRect := aRectangle isNil 
         ifTrue:[self marginsRectangleFor: nil]
@@ -1137,6 +779,7 @@
     ^(marginsRect bottom - marginsRect top) // charHeight
 
     "Created: / 12-10-2006 / 11:52:57 / User"
+    "Modified: / 16-04-2007 / 12:44:56 / cg"
 !
 
 marginsRectangleFor:aRectangle 
@@ -1147,6 +790,7 @@
     |left top right bottom pixelsPerInchX pixelsPerInchY horzRes vertRes inset rectangle|
 
     pixelsPerInchX := self pixelsPerInchOfScreenWidth.
+pixelsPerInchX == 0 ifTrue:[self halt].
     pixelsPerInchY := self pixelsPerInchOfScreenHeight.
     aRectangle isNil ifTrue:[
         horzRes := self printerWidthArea.
@@ -1162,12 +806,12 @@
         right := (aRectangle right * pixelsPerInchX) asInteger.
         bottom := (aRectangle bottom * pixelsPerInchY) asInteger
     ].
-    rectangle := left @ top extent:right @ bottom.
+    rectangle := left @ top corner:right @ bottom.
     ^ rectangle
 
     "Created: / 27-07-2006 / 18:22:57 / fm"
     "Modified: / 04-08-2006 / 13:39:45 / fm"
-    "Modified: / 10-10-2006 / 18:15:26 / cg"
+    "Modified: / 16-04-2007 / 11:57:21 / cg"
 !
 
 printPage:pageIndex in:aRectangle lines:lines headerLines:headerLines linesPerPage:linesPerPage 
@@ -1238,34 +882,9 @@
      when written using the current font; expand tabs out
      to 4 spaces for calculations"
     
-    |answer str size spaceWidth|
+    self subclassResponsibility
 
-    index <= 0 ifTrue:[ ^ 0 ].
-    str := index >= aString size ifTrue:[ aString ] ifFalse:[ aString copyFrom:1 to:index ].
-    true "self font isNil" ifTrue:[
-        "if font not set yet, calculate based on default font"
-        "/            extString := str asExternalString.
-        size := Win32OperatingSystem::WinPointStructure new.
-        (OperatingSystem 
-            getTextExtentPoint:gcId
-            string:str
-            size:size) ifFalse:[ ^ self error ].
-        answer := size x.
-"/        Transcript showCR: 'FROM PRIM ******* ', str, '   ',  answer printString.
-"/        Transcript showCR: 'FROM DEVICE ***** ', str, '   ',(self font widthOf:str on:self device) printString.
-        #TODO.
-    ] ifFalse:[
-        answer := self font widthOf:str on:self device
-    ].
-    index > aString size ifTrue:[
-        spaceWidth := self font widthOf:Character space on:self device.
-        answer := answer + ((index - aString size) * spaceWidth)
-    ].
-    ^ answer.
-
-    "Created: / 03-08-2006 / 10:27:20 / fm"
-    "Modified: / 04-08-2006 / 12:27:26 / fm"
-    "Modified: / 10-10-2006 / 18:20:43 / cg"
+    "Modified: / 16-04-2007 / 12:45:42 / cg"
 !
 
 withLineStyle:aSymbol lineWidth:lw paint:paintColor do:aBlock
@@ -1289,5 +908,5 @@
 !PrinterContext class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/PrinterContext.st,v 1.12 2006-12-14 11:28:55 fm Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/PrinterContext.st,v 1.13 2007-04-16 10:56:22 cg Exp $'
 ! !