merged ruler & vRuler (prep for spec support)
authorClaus Gittinger <cg@exept.de>
Wed, 24 Nov 1999 13:12:33 +0100
changeset 1619 fda861e265ca
parent 1618 2b4c2f143f1d
child 1620 99124a1a1342
merged ruler & vRuler (prep for spec support)
Ruler.st
VerticalRuler.st
--- a/Ruler.st	Fri Nov 19 14:27:57 1999 +0100
+++ b/Ruler.st	Wed Nov 24 13:12:33 1999 +0100
@@ -11,7 +11,7 @@
 "
 
 SimpleView subclass:#Ruler
-	instanceVariableNames:'fgColor metric paperWidth paperHeight scale showUnit'
+	instanceVariableNames:'fgColor metric paperWidth paperHeight scale showUnit orientation'
 	classVariableNames:''
 	poolDictionaries:''
 	category:'Views-Misc'
@@ -129,6 +129,26 @@
     "Modified: 29.5.1996 / 16:42:46 / cg"
 !
 
+paperHeightInch:inches
+    "set the width of the document"
+
+    paperHeight := inches.
+    shown ifTrue:[
+	self redraw
+    ]
+!
+
+paperHeightMM:millis
+    "set the width of the document"
+
+    paperHeight := UnitConverter millimeterToInch:millis.
+    shown ifTrue:[
+        self redraw
+    ]
+
+    "Modified: 31.5.1996 / 19:39:46 / cg"
+!
+
 paperWidthInch:inches
     "set the width of the document"
 
@@ -184,17 +204,21 @@
 initialize
     super initialize.
 
+    orientation isNil ifTrue:[
+        orientation := #horizontal.
+    ].
+
     viewBackground := styleSheet colorAt:#rulerBackgroundColor default:viewBackground.
     fgColor := styleSheet colorAt:#rulerForegroundColor.
     fgColor isNil ifTrue:[
-	fgColor := styleSheet colorAt:#foregroundColor.
+        fgColor := styleSheet colorAt:#foregroundColor.
     ].
     fgColor isNil ifTrue:[
-	viewBackground brightness > 0.5 ifTrue:[
-	    fgColor := Black.
-	] ifFalse:[
-	    fgColor := White
-	].
+        viewBackground brightness > 0.5 ifTrue:[
+            fgColor := Black.
+        ] ifFalse:[
+            fgColor := White
+        ].
     ].
     fgColor := fgColor on:device.
 
@@ -203,9 +227,9 @@
     self height:(font height + (2 * font descent)). 
 
     (Smalltalk language == #english) ifTrue:[
-	metric := #inch
+        metric := #inch
     ] ifFalse:[
-	metric := #mm
+        metric := #mm
     ].
     metric := styleSheet at:#rulerMetric default:metric.
 
@@ -220,9 +244,9 @@
      take a smaller font
     "
     font := (Font family:(font family)
-		    face:(font face)
-		   style:(font style)
-		    size:8) on:device.
+                    face:(font face)
+                   style:(font style)
+                    size:8) on:device.
 
     "
      Ruler new open
@@ -254,126 +278,236 @@
 redraw
     "redraw the scale"
 
-    |x pixelPerMM pixelPerInch mod pos shortLen veryShortLen longLen charY
-     top paperWidthMM paperWidthPixel xOrigin labelRight stringRight marg|
+    |x y pixelPerMM pixelPerInch mod pos shortLen veryShortLen longLen 
+     charX charY fontHeight fontAscent
+     top paperHeightMM paperWidthMM paperHeightPixel paperWidthPixel 
+     org xOrigin yOrigin labelRight labelBot stringRight marg|
 
     shown ifFalse:[^ self].
 
     self clear.
 
-    xOrigin := self viewOrigin x.
+    org := self viewOrigin.
+    xOrigin := org x.
+    yOrigin := org y.
 
     paperWidthPixel := ((self inchToPixel:paperWidth) * scale) rounded.
+    paperHeightPixel := ((self inchToPixel:paperHeight) * scale) rounded.
 
-    (xOrigin + width > paperWidthPixel) ifTrue:[
-        self paint:(Color darkGrey).
-        self fillRectangleX:paperWidthPixel y:0
-                      width:(xOrigin + width - paperWidthPixel) 
-                      height:height.
-        self paint:fgColor.
-        self displayLineFromX:paperWidthPixel y:0
-                          toX:paperWidthPixel y:height
-    ].
+    paperWidthMM := UnitConverter inchToMillimeter:paperWidth.
+    paperHeightMM := UnitConverter inchToMillimeter:paperHeight.
+    pixelPerMM := (self millimeterToPixel:1) * scale.
 
-    self paint:fgColor.
+    fontHeight := font height.
+    fontAscent := font ascent.
 
-    top := height - font height - font ascent.
-    longLen := font height.
-    shortLen := longLen // 2.
-    charY := top + (font ascent) + shortLen.
-    mod := 1.
-    marg := 3. "character shift"
-
-    (metric == #mm) ifTrue:[
-        "centimeter - long blibs every centimeter; short ones every half"
-
-        paperWidthMM := UnitConverter inchToMillimeter:paperWidth.
-        pixelPerMM := (self millimeterToPixel:1) * scale.
-        pos := 5.
-        showUnit ifTrue:[
-            labelRight := stringRight := marg + (font widthOf:'cm') + 3 + xOrigin.
-        ] ifFalse:[
-            labelRight := stringRight := xOrigin.
+    orientation == #horizontal ifTrue:[
+        (xOrigin + width > paperWidthPixel) ifTrue:[
+            self paint:(Color darkGrey).
+            self 
+                fillRectangleX:paperWidthPixel y:0
+                width:(xOrigin + width - paperWidthPixel) height:height.
+            self paint:fgColor.
+            self 
+                displayLineFromX:paperWidthPixel y:0
+                toX:paperWidthPixel y:height
         ].
 
-        x := (pixelPerMM * pos) rounded.
-        [(x < (width+xOrigin)) and:[pos <= paperWidthMM]] whileTrue:[
-            |l|
+        self paint:fgColor.
+
+        top := height - fontHeight - fontAscent.
+        longLen := fontHeight.
+        shortLen := longLen // 2.
+        charY := top + fontAscent + shortLen.
+        mod := 1.
+        marg := 3. "character shift"
+
+        (metric == #mm) ifTrue:[
+            "centimeter - long blibs every centimeter; short ones every half"
+
+            pos := 5.
+            showUnit ifTrue:[
+                labelRight := stringRight := marg + (font widthOf:'cm') + 3 + xOrigin.
+            ] ifFalse:[
+                labelRight := stringRight := xOrigin.
+            ].
+
+            x := (pixelPerMM * pos) rounded.
+            [(x < (width+xOrigin)) and:[pos <= paperWidthMM]] whileTrue:[
+                |l|
 
-            l := shortLen.
-            (mod ~~ 1) ifTrue:[
-                x < stringRight ifFalse:[
-                    l := longLen
+                l := shortLen.
+                (mod ~~ 1) ifTrue:[
+                    x < stringRight ifFalse:[
+                        l := longLen
+                    ].
                 ].
+                self displayLineFromX:x y:top
+                                  toX:x y:(top + l).
+
+                ((x < stringRight) or:[mod == 1]) ifFalse:[
+                    self displayString:(pos // 10) printString
+                                     x:(x + marg)
+                                     y:charY.
+                    stringRight := x + marg 
+                                    + (font widthOf:(pos // 10) printString)
+                ].
+                mod := (mod + 1) \\ 2.
+                pos := pos + 5.
+                x := (pixelPerMM * pos) rounded 
             ].
-            self displayLineFromX:x y:top
-                              toX:x y:(top + l).
+            showUnit ifTrue:[
+                self displayString:'cm ' x:marg+xOrigin y:charY.
+            ]
+        ].
+        (metric == #inch) ifTrue:[
+            "inches - long blibs every inch; short ones every half; very
+             short ones every quarter"
 
-            ((x < stringRight) or:[mod == 1]) ifFalse:[
-                self displayString:(pos // 10) printString
-                                 x:(x + marg)
-                                 y:charY.
-                stringRight := x + marg 
-                                + (font widthOf:(pos // 10) printString)
+            pixelPerInch := (self inchToPixel:1) * scale.
+            pos := 0.25.
+            showUnit ifTrue:[
+                labelRight := marg + (font widthOf:'inch') + 3 + xOrigin.
+            ] ifFalse:[
+                labelRight := xOrigin
             ].
-            mod := (mod + 1) \\ 2.
-            pos := pos + 5.
-            x := (pixelPerMM * pos) rounded 
+
+            x := (pixelPerInch * pos) rounded.
+            veryShortLen := longLen // 4.
+            [(x < (xOrigin+width)) and:[pos <= paperWidth]] whileTrue:[
+                |l|
+
+                l := shortLen.    
+                (mod == 0) ifTrue:[
+                    x < labelRight ifFalse:[
+                        l := longLen
+                    ]
+                ] ifFalse:[
+                    (mod == 2) ifFalse:[
+                        l := veryShortLen
+                    ]
+                ].
+                self displayLineFromX:x y:top
+                                  toX:x y:(top + l).
+
+                (mod == 0 and:[x >= labelRight]) ifTrue:[
+                    self displayString:pos asInteger printString
+                                     x:(x + marg)
+                                     y:charY
+                ].
+                mod := (mod + 1) \\ 4.
+                pos := pos + 0.25.
+                x := (pixelPerInch * pos) rounded
+            ].
+            showUnit ifTrue:[
+                self displayString:'inch ' x:marg+xOrigin y:charY.
+            ]
         ].
-        showUnit ifTrue:[
-            self displayString:'cm ' x:marg+xOrigin y:charY.
-        ]
-    ].
-    (metric == #inch) ifTrue:[
-        "inches - long blibs every inch; short ones every half; very
-         short ones every quarter"
+    ] ifFalse:[
+        "/ orientation == #vertical ...
 
-        pixelPerInch := (self inchToPixel:1) * scale.
-        pos := 0.25.
-        showUnit ifTrue:[
-            labelRight := marg + (font widthOf:'inch') + 3 + xOrigin.
-        ] ifFalse:[
-            labelRight := xOrigin
+        (yOrigin + height > paperHeightPixel) ifTrue:[
+            self paint:(Color darkGrey).
+            self fillRectangleX:0 y:paperHeightPixel
+                          width:width
+                          height:(yOrigin + height - paperHeightPixel).
+            self paint:fgColor.
+            self displayLineFromX:0 y:paperHeightPixel
+                              toX:width y:paperHeightPixel
         ].
 
-        x := (pixelPerInch * pos) rounded.
-        veryShortLen := longLen // 4.
-        [(x < (xOrigin+width)) and:[pos <= paperWidth]] whileTrue:[
-            |l|
+        self paint:fgColor.
+
+        left := 0. "width - (font widthOf:'WW')"
+        longLen := font widthOf:'WW'.
+        shortLen := longLen // 2.
+        charX := left + shortLen.
+        mod := 1.
+        marg := 3. "character shift"
+
+        showUnit ifTrue:[
+            labelBot := marg + fontHeight + fontAscent + yOrigin.
+        ] ifFalse:[
+            labelBot := yOrigin
+        ].
+
+        (metric == #mm) ifTrue:[
+            "centimeter - long blibs every centimeter; short ones every half"
 
-            l := shortLen.    
-            (mod == 0) ifTrue:[
-                x < labelRight ifFalse:[
-                    l := longLen
-                ]
-            ] ifFalse:[
-                (mod == 2) ifFalse:[
-                    l := veryShortLen
-                ]
+            pos := 5.
+            y := (pixelPerMM * pos) rounded.
+            [(y < (height+yOrigin)) and:[pos <= paperHeightMM]] whileTrue:[
+                |l|
+
+                l := shortLen.
+                (mod ~~ 1) ifTrue:[
+                    y < labelBot ifFalse:[
+                        l := longLen
+                    ]
+                ].
+                self displayLineFromX:left y:y toX:(left + l) y:y.
+
+                (mod ~~ 1 and:[y >= labelBot]) ifTrue:[
+                    self displayString:(pos // 10) printString
+                                     x:charX
+                                     y:(y + marg + fontHeight)
+                ].
+                mod := (mod + 1) \\ 2.
+                pos := pos + 5.
+                y := (pixelPerMM * pos) rounded 
             ].
-            self displayLineFromX:x y:top
-                              toX:x y:(top + l).
+            showUnit ifTrue:[
+                self displayString:'cm ' x:charX y:marg + fontHeight + yOrigin.
+            ]
+        ].
+        (metric == #inch) ifTrue:[
+            "inches - long blibs every inch; short ones every half; very
+             short ones every quarter"
+
+            pixelPerInch := (self inchToPixel:1) * scale.
+            pos := 0.25.
+
+            y := (pixelPerInch * pos) rounded.
+            veryShortLen := longLen // 4.
+            [(y < (yOrigin + height)) and:[pos <= paperHeight]] whileTrue:[
+                |l|
 
-            (mod == 0 and:[x >= labelRight]) ifTrue:[
-                self displayString:pos asInteger printString
-                                 x:(x + marg)
-                                 y:charY
+                l := shortLen.
+                (mod == 0) ifTrue:[
+                    y < labelBot ifFalse:[
+                        l := longLen.
+                    ]
+                ] ifFalse:[
+                    (mod == 2) ifFalse:[
+                        l := veryShortLen
+                    ]
+                ].
+                self displayLineFromX:left y:y toX:(left + l) y:y.
+
+                (mod == 0) ifTrue:[
+                    y < labelBot ifFalse:[
+                        self displayString:pos asInteger printString
+                                         x:charX
+                                         y:(y + marg + fontHeight)
+                    ]
+                ].
+                mod := (mod + 1) \\ 4.
+                pos := pos + 0.25.
+                y := (pixelPerInch * pos) rounded
             ].
-            mod := (mod + 1) \\ 4.
-            pos := pos + 0.25.
-            x := (pixelPerInch * pos) rounded
+            showUnit ifTrue:[
+                self displayString:'inch ' x:charX y:marg + fontHeight + yOrigin.
+            ]
         ].
-        showUnit ifTrue:[
-            self displayString:'inch ' x:marg+xOrigin y:charY.
-        ]
     ].
+
     self redrawEdges
 
-    "Modified: 4.6.1996 / 22:21:19 / cg"
+
 ! !
 
 !Ruler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.26 1996-06-04 20:22:04 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.27 1999-11-24 12:12:19 cg Exp $'
 ! !
--- a/VerticalRuler.st	Fri Nov 19 14:27:57 1999 +0100
+++ b/VerticalRuler.st	Wed Nov 24 13:12:33 1999 +0100
@@ -40,33 +40,12 @@
 "
 ! !
 
-!VerticalRuler methodsFor:'accessing'!
-
-paperHeightInch:inches
-    "set the width of the document"
-
-    paperHeight := inches.
-    shown ifTrue:[
-	self redraw
-    ]
-!
-
-paperHeightMM:millis
-    "set the width of the document"
-
-    paperHeight := UnitConverter millimeterToInch:millis.
-    shown ifTrue:[
-        self redraw
-    ]
-
-    "Modified: 31.5.1996 / 19:39:46 / cg"
-! !
-
 !VerticalRuler methodsFor:'initialization'!
 
 initialize
+    orientation := #vertical.
+
     super initialize.
-
     self width:(font widthOf:'inch').
 
     "
@@ -74,125 +53,8 @@
     "
 ! !
 
-!VerticalRuler methodsFor:'redrawing'!
-
-redraw
-    "redraw the scale"
-
-    |y pixelPerMM pixelPerInch mod pos shortLen veryShortLen longLen charX
-     left paperHeightMM paperHeightPixel yOrigin labelBot marg fontHeight|
-
-    shown ifFalse:[^ self].
-
-    self clear.
-
-    yOrigin := self viewOrigin y.
-
-    paperHeightPixel := ((self inchToPixel:paperHeight) * scale) rounded.
-
-    (yOrigin + height > paperHeightPixel) ifTrue:[
-        self paint:(Color darkGrey).
-        self fillRectangleX:0 y:paperHeightPixel
-                      width:width
-                      height:(yOrigin + height - paperHeightPixel).
-        self paint:fgColor.
-        self displayLineFromX:0 y:paperHeightPixel
-                          toX:width y:paperHeightPixel
-    ].
-
-    self paint:fgColor.
-
-    left := 0. "width - (font widthOf:'WW')"
-    longLen := font widthOf:'WW'.
-    shortLen := longLen // 2.
-    charX := left + shortLen.
-    mod := 1.
-    marg := 3. "character shift"
-    fontHeight := font height.
-
-    showUnit ifTrue:[
-        labelBot := marg + font height + font ascent + yOrigin.
-    ] ifFalse:[
-        labelBot := yOrigin
-    ].
-
-    (metric == #mm) ifTrue:[
-        "centimeter - long blibs every centimeter; short ones every half"
-
-        paperHeightMM := UnitConverter inchToMillimeter:paperHeight.
-        pixelPerMM := (self millimeterToPixel:1) * scale.
-        pos := 5.
-        y := (pixelPerMM * pos) rounded.
-        [(y < (height+yOrigin)) and:[pos <= paperHeightMM]] whileTrue:[
-            |l|
-
-            l := shortLen.
-            (mod ~~ 1) ifTrue:[
-                y < labelBot ifFalse:[
-                    l := longLen
-                ]
-            ].
-            self displayLineFromX:left y:y toX:(left + l) y:y.
-
-            (mod ~~ 1 and:[y >= labelBot]) ifTrue:[
-                self displayString:(pos // 10) printString
-                                 x:charX
-                                 y:(y + marg + fontHeight)
-            ].
-            mod := (mod + 1) \\ 2.
-            pos := pos + 5.
-            y := (pixelPerMM * pos) rounded 
-        ].
-        showUnit ifTrue:[
-            self displayString:'cm ' x:charX y:marg + fontHeight + yOrigin.
-        ]
-    ].
-    (metric == #inch) ifTrue:[
-        "inches - long blibs every inch; short ones every half; very
-         short ones every quarter"
-
-        pixelPerInch := (self inchToPixel:1) * scale.
-        pos := 0.25.
-
-        y := (pixelPerInch * pos) rounded.
-        veryShortLen := longLen // 4.
-        [(y < (yOrigin + height)) and:[pos <= paperHeight]] whileTrue:[
-            |l|
-
-            l := shortLen.
-            (mod == 0) ifTrue:[
-                y < labelBot ifFalse:[
-                    l := longLen.
-                ]
-            ] ifFalse:[
-                (mod == 2) ifFalse:[
-                    l := veryShortLen
-                ]
-            ].
-            self displayLineFromX:left y:y toX:(left + l) y:y.
-
-            (mod == 0) ifTrue:[
-                y < labelBot ifFalse:[
-                    self displayString:pos asInteger printString
-                                     x:charX
-                                     y:(y + marg + fontHeight)
-                ]
-            ].
-            mod := (mod + 1) \\ 4.
-            pos := pos + 0.25.
-            y := (pixelPerInch * pos) rounded
-        ].
-        showUnit ifTrue:[
-            self displayString:'inch ' x:charX y:marg + fontHeight + yOrigin.
-        ]
-    ].
-    self redrawEdges
-
-    "Modified: 31.5.1996 / 18:06:59 / cg"
-! !
-
 !VerticalRuler class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libwidg2/VerticalRuler.st,v 1.9 1996-05-31 18:08:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libwidg2/VerticalRuler.st,v 1.10 1999-11-24 12:12:33 cg Exp $'
 ! !