Ruler.st
author claus
Sat, 18 Mar 1995 06:17:38 +0100
changeset 42 3f8d31db2b1c
parent 36 160b8f0dfd7d
child 49 4dd0f5c3353e
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 scale showUnit'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Misc'
!

Ruler comment:'
COPYRIGHT (c) 1991 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.14 1995-03-18 05:17:25 claus Exp $
'!

!Ruler class methodsFor:'documentation'!

copyright
"
 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.
"
!

version
"
$Header: /cvs/stx/stx/libwidg2/Ruler.st,v 1.14 1995-03-18 05:17:25 claus Exp $
"
!

documentation
"
    a shows some unit scale; See example use in DrawTool.

    instance variables:

	fgColor         <Color>         color to draw text and marks with
	metric          <Symbol>        inch or mm
	paperWidth      <Number>        width of paper
	paperHeight     <Number>        height of paper
	scale           <Number>        scale factor for zoom
	showUnit        <Boolean>       if true, a unit string is displayed
"
!

examples
"
    |top ruler|

    top := StandardSystemView new.
    ruler := Ruler origin:0.0@0.0 corner:1.0@30 in:top.
    top open


  defining paperWidth:

    |top ruler|

    top := StandardSystemView new.
    ruler := Ruler origin:0.0@0.0 corner:1.0@30 in:top.
    ruler paperWidthInch:5.   
    top open


  hide unit string:

    |top ruler|

    top := StandardSystemView new.
    ruler := Ruler origin:0.0@0.0 corner:1.0@30 in:top.
    ruler showUnit:false.
    top open


  both horizontal and vertical rulers (as in DrawTool):

    |top hRuler vRuler|

    top := StandardSystemView new.
    hRuler := Ruler origin:30@0.0 corner:1.0@30 in:top.
    vRuler := VerticalRuler origin:0.0@30 corner:30@1.0 in:top.
    vRuler showUnit:false.
    top open


  with some 3D effects:

    |top hRuler vRuler|

    top := StandardSystemView new.
    hRuler := Ruler origin:30@0.0 corner:1.0@30 in:top.
    vRuler := VerticalRuler origin:0.0@30 corner:30@1.0 in:top.
    vRuler showUnit:false.
    hRuler level:1.
    vRuler level:1.
    top open

  see the DrawTool, for how to make it scroll in sync with some
  other view. 
"
! !

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

scale:aFactor
    "set the scale factor. 1 is identity."

    aFactor ~= scale ifTrue:[
	scale := aFactor.
	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
    ]
!

showUnit:aBoolean
    "set/clear the showUnit flag. If false, the unit string
     (i.e. 'inch' or 'mm') is not schown. Default is true."

    showUnit := aBoolean.
!

viewOrigin:origin
    origin = self viewOrigin ifTrue:[^ self].
    super setViewOrigin:origin.
    self redraw
!

widthOfContents
    ^ (device horizontalPixelPerInch * paperWidth) rounded
!

heightOfContents
    ^ (device verticalPixelPerInch * paperHeight) rounded
! !

!Ruler methodsFor:'redrawing'!

redraw
    "redraw the scale"

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

    shown ifFalse:[^ self].

    self clear.

    xOrigin := self viewOrigin x.

    paperWidthPixel := ((self inchToPixel:paperWidth) * 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
    ].

    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) * scale.
	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
		].
	    ].
	    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 displayString:'cm ' x:marg+xOrigin y:charY.
    ].
    (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.
	showUnit ifTrue:[
	    labelRight := marg + (font widthOf:'inch') + 3 + xOrigin.
	] ifFalse:[
	    labelRight := xOrigin
	].

	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
	].
	self displayString:'inch ' x:marg+xOrigin y:charY.
    ].
    self redrawEdges
! !

!Ruler methodsFor:'initialization'!

initialize
    super initialize.

    viewBackground := StyleSheet colorAt:#rulerBackgroundColor default:viewBackground.
    fgColor := StyleSheet colorAt:#rulerForegroundColor.
    fgColor isNil ifTrue:[
	fgColor := StyleSheet colorAt:#foregroundColor.
    ].
    fgColor isNil ifTrue:[
	viewBackground brightness > 0.5 ifTrue:[
	    fgColor := Black.
	] ifFalse:[
	    fgColor := White
	].
    ].
    fgColor := fgColor on:device.

    bitGravity := #NorthWest.

    self height:(font height + (2 * font descent)). 

    (Smalltalk language == #english) ifTrue:[
	metric := #inch
    ] ifFalse:[
	metric := #mm
    ].
    metric := StyleSheet at:#rulerMetric default:metric.

    showUnit := true.

    scale := 1.

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