VerticalRuler.st
author Claus Gittinger <cg@exept.de>
Sat, 27 Apr 1996 20:23:13 +0200
changeset 161 5b6e284959a4
parent 86 4d7dbb5f1719
child 195 0fbaea91aa3d
permissions -rw-r--r--
examples

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

Ruler subclass:#VerticalRuler
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Views-Misc'
!

!VerticalRuler class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1994 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.
"
!

documentation
"
    like a Ruler, but vertical.
    see documentation in Ruler
"
! !

!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 := self millimeterToInch:millis.
    shown ifTrue:[
	self redraw
    ]
! !

!VerticalRuler methodsFor:'initialization'!

initialize
    super initialize.

    self width:(font widthOf:'inch').

    "
     VerticalRuler new open
    "
! !

!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 := self 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
! !

!VerticalRuler class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libwidg2/VerticalRuler.st,v 1.7 1996-04-27 18:22:04 cg Exp $'
! !