Ruler.st
author claus
Mon, 10 Oct 1994 04:13:51 +0100
changeset 24 6704fad5eb7d
parent 11 793044d4bc90
child 26 ff148983c183
permissions -rw-r--r--
*** empty log message ***

"
 COPYRIGHT (c) 1991 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 by Claus Gittinger
	      All Rights Reserved

a Ruler for page layout.

$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.7 1994-10-10 03:13:35 claus Exp $

written oct 91 by claus
'!

!Ruler methodsFor:'accessing'!

metric:aSymbol
    "set the metric. The argument may be either #inch or #mm"

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

paperWidthInch:inches
    "set the width of the document"

    paperWidth := inches.
    shown ifTrue:[
	self redraw
    ]
!

paperWidthMM:millis
    "set the width of the document"

    paperWidth := self millimeterToInch:millis.
    shown ifTrue:[
	self redraw
    ]
! !

!Ruler methodsFor:'redrawing'!

redraw
    "redraw scale"

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

    shown ifFalse:[^ self].

"/    self fill:viewBackground.
    self clear.

    xOrigin := viewOrigin x.

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

    self paint:fgColor.

    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 := self inchToMillimeter:paperWidth.
	pixelPerMM := self millimeterToPixel:1.
	pos := 5.
	labelRight := marg + (font widthOf:'cm').

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

	pixelPerInch := self inchToPixel:1.
	pos := 0.25.
	labelRight := marg + (font widthOf:'inch').

	x := (pixelPerInch * pos - xOrigin) rounded.
	veryShortLen := longLen // 4.
	[(x < width) and:[pos <= paperWidth]] whileTrue:[
	    (mod == 0) ifTrue:[
		x < labelRight ifFalse:[
		    self displayLineFromX:x y:top
				      toX:x y:(top + longLen).
		    self displayString:pos asInteger printString
				     x:(x + marg)
				     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 - xOrigin) rounded
	].
	self displayString:'inch ' x:marg y:charY.
    ].
    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.

    "
     take a smaller font
    "
    font := (Font family:(font family)
		    face:(font face)
		   style:(font style)
		    size:8) on:device.

    "
     Ruler new open
    "
!

reinitialize
    super reinitialize.
    font := font on:device.
! !

!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
! !