Ruler.st
author claus
Wed, 13 Oct 1993 02:03:48 +0100
changeset 2 ab6002adaee1
parent 0 0fd7841626f6
child 4 e1e3fbe98999
permissions -rw-r--r--
(none)

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

View subclass:#Ruler
         instanceVariableNames:'fgColor metric paperWidth paperHeight'
         classVariableNames:''
         poolDictionaries:''
         category:'Views-Interactors'
!

Ruler comment:'

COPYRIGHT (c) 1991-93 by Claus Gittinger
              All Rights Reserved

a Ruler for page layout.

$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.2 1993-10-13 01:03:20 claus Exp $

written oct 91 by claus
'!

!Ruler methodsFor:'accessing'!

metric:aSymbol
    "set the metric"

    metric := aSymbol.
    shown ifTrue:[
        self redraw
    ]
! !

!Ruler methodsFor:'redrawing'!

redraw
    "redraw scale"

    |x pixelPerMM pixelPerInch mod pos shortLen veryShortLen longLen charY
     top paperWidthMM paperWidthPixel|

    self fill:viewBackground.

    paperWidthPixel := (self inchToPixel:paperWidth) rounded.
    (width > paperWidthPixel) ifTrue:[
        self paint:(Color darkGrey).
        self fillRectangleX:paperWidthPixel y:0
                      width:(width - paperWidthPixel) height:height.
        self paint:fgColor.
        self displayLineFromX:paperWidthPixel y:0
                          toX:paperWidthPixel y:height
    ].

    self paint:fgColor.

    top := height - font height - font ascent.
    longLen := font height.
    shortLen := longLen // 2.
    charY := top + (font ascent) + shortLen.
    mod := 1.

    (metric == #mm) ifTrue:[
        "centimeter - long blibs every centimeter; short ones every half"

        paperWidthMM := self inchToMillimeter:paperWidth.
        pixelPerMM := self millimeterToPixel:1.
        pos := 5.
        x := (pixelPerMM * pos) rounded.
        self displayString:'cm' x:3 y:charY.
        [(x < width) and:[pos <= paperWidthMM]] whileTrue:[
            (mod == 1) ifTrue:[
                self displayLineFromX:x y:top
                                  toX:x y:(top + shortLen)
            ] ifFalse:[
                self displayLineFromX:x y:top
                                  toX:x y:(top + longLen).
                self displayString:(pos // 10) asInteger printString
                                 x:(x + 3)
                                 y:charY
            ].
            mod := (mod + 1) \\ 2.
            pos := pos + 5.
            x := (pixelPerMM * pos) rounded 
        ]
    ].
    (metric == #inch) ifTrue:[
        "inches - long blibs every inch; short ones every half; very
         short ones every quarter"

        pixelPerInch := self inchToPixel:1.
        pos := 0.25.
        x := (pixelPerInch * pos) rounded.
        veryShortLen := longLen // 4.
        self displayString:'inch' x:3 y:charY.
        [(x < width) and:[pos <= paperWidth]] whileTrue:[
            (mod == 0) ifTrue:[
                self displayLineFromX:x y:top
                                  toX:x y:(top + longLen).
                self displayString:pos asInteger printString
                                 x:(x + 3)
                                 y:charY
            ] ifFalse:[
                (mod == 2) ifTrue:[
                    self displayLineFromX:x y:top
                                      toX:x y:(top + shortLen)
                ] ifFalse:[
                    self displayLineFromX:x y:top
                                      toX:x y:(top + veryShortLen)
                ]
            ].
            mod := (mod + 1) \\ 4.
            pos := pos + 0.25.
            x := (pixelPerInch * pos) rounded
        ]
    ].
    self redrawEdges
! !

!Ruler methodsFor:'initialization'!

initialize
    super initialize.

    fgColor := Black.
    self height:(font height + font descent + font descent). 
    (Language == #english) ifTrue:[
        metric := #inch
    ] ifFalse:[
        metric := #mm
    ].
    paperWidth := 8.5.
    paperHeight := 11

    "Ruler new realize"
! !

!Ruler methodsFor:'metric conversions'!

inchToMillimeter:inches
    "convert inches to mm"

    ^ inches * 25.4
!

inchToPixel:inches
    "convert inches to screen pixels"

    ^ inches * self horizontalPixelPerInch
!

inchToTwip:inches
    "convert inches to twips"

    ^ inches * 1440

!

millimeterToPixel:mm
    "convert mms to screen pixels"

    ^ mm * self horizontalPixelPerMillimeter

!

millimeterToInch:mm
    "convert mm to inches"

    ^ mm / 25.4
!

pointToTwip:points
    "convert points to twips"

    ^ points * 20
!

twipToInch:twips
    "convert twips to inches"

    ^ twips / 1440.0
!

pixelToInch:pixels
    "convert pixels to inches"

    ^ pixels / self horizontalPixelPerInch
!

twipToPixel:twips
    "convert twips to screen pixels"

    ^ (twips / 1440.0) * self horizontalPixelPerInch

!

twipToPoint:twips
    "convert twips to points"

    ^ twips / 20.0
! !