TextRuler.st
author claus
Wed, 13 Oct 1993 03:49:40 +0100
changeset 4 e1e3fbe98999
parent 2 ab6002adaee1
child 8 91035a03b4cf
permissions -rw-r--r--
(none)

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

Ruler subclass:#TextRuler
         instanceVariableNames:'leftMargin rightMargin tabStops tabTypes'
            classVariableNames:'leftAlignForm rightAlignForm
                                alignForm centerForm leftMarginForm
                                rightMarginForm leftTabForm rightTabForm
                                centerTabForm
                                decimalTabForm currentTabType moving'
         poolDictionaries:''
         category:'Views-Interactors'
!

TextRuler comment:'

COPYRIGHT (c) 1991 by Claus Gittinger
              All Rights Reserved

a Ruler for page layout showing tabs., margins etc.

$Header: /cvs/stx/stx/libwidg2/TextRuler.st,v 1.3 1993-10-13 02:49:40 claus Exp $
written oct 91 by claus
'!

!TextRuler class methodsFor:'defaults'!

alignForm
    "return the form displayed in the align-button"

    alignForm isNil ifTrue:[
        alignForm := Form fromFile:'align.bit' resolution:100
    ].
    ^ alignForm
!

centerForm
    "return the form displayed in the center-button"

    centerForm isNil ifTrue:[
        centerForm := Form fromFile:'center.bit' resolution:100
    ].
    ^ centerForm
!

leftAlignForm
    "return the form displayed in the leftAlign-button"

    leftAlignForm isNil ifTrue:[
        leftAlignForm := Form fromFile:'leftAlign.bit' resolution:100
    ].
    ^ leftAlignForm
!

rightAlignForm
    "return the form displayed in the rightAlign-button"

    rightAlignForm isNil ifTrue:[
        rightAlignForm :=  Form fromFile:'rightAlign.bit' resolution:100
    ].
    ^ rightAlignForm
!

rightTabForm
    "return the form displayed in the rightTab-button"

    rightTabForm isNil ifTrue:[
        rightTabForm := Form fromFile:'rightTab.bit' resolution:100
    ].
    ^ rightTabForm
!

leftTabForm
    "return the form displayed in the leftTab-button"

    leftTabForm isNil ifTrue:[
        leftTabForm := Form fromFile:'leftTab.bit' resolution:100
    ].
    ^ leftTabForm
!

centerTabForm
    "return the form displayed in the centerTab-button"

    centerTabForm isNil ifTrue:[
        centerTabForm := Form fromFile:'centerTab.bit' resolution:100
    ].
    ^ centerTabForm
!

decimalTabForm
    "return the form displayed in the decimalTab-button"

    decimalTabForm isNil ifTrue:[
        decimalTabForm := Form fromFile:'decimalTab.bit' resolution:100
    ].
    ^ decimalTabForm
!

leftMarginForm
    "return the form displayed for the left margin marker"

    leftMarginForm isNil ifTrue:[
        leftMarginForm := Form fromFile:'leftMargin.bit' resolution:100
    ].
    ^ leftMarginForm
!

rightMarginForm
    "return the form displayed for the right margin marker"

    rightMarginForm isNil ifTrue:[
        rightMarginForm := Form fromFile:'rightMarg.bit' resolution:100
    ].
    ^ rightMarginForm
! !

!TextRuler methodsFor:'initializing'!

initialize
    |leftAlignToggle alignToggle centerToggle rightAlignToggle
     leftTabButton centerTabButton rightTabButton decimalTabButton
     lineSpacingField panel1 panel2 panel3 scaleHeight h group|

    super initialize.

    scaleHeight := (font height) * 2.
    self height:(scaleHeight * 3).

    h := self class leftAlignForm height.
    panel1 := HorizontalPanelView
                        origin:(0.0 @ 0.0)
                        extent:[(width // 3) @ (h*2) "(height - scaleHeight)"]
                            in:self.
    panel1 borderWidth:0.
    panel1 layout:#left.

    panel2 := HorizontalPanelView
                        origin:[(width // 3) @ margin]
                        extent:[(width // 3) @ (h*2) "(height - scaleHeight)"]
                            in:self.
    panel2 borderWidth:0.
    panel2 layout:#center.

    panel3 := HorizontalPanelView
                        origin:[(width // 3 * 2) @ margin]
                        extent:[((width // 3)-margin) @ (h*2) "(height - scaleHeight)"]
                            in:self.
    panel3 borderWidth:0.
    panel3 layout:#right.

    leftAlignToggle := RadioButton form:(self class leftAlignForm)
                                 action:[self leftAlign]
                                     in:panel1.
    alignToggle := RadioButton form:(self class alignForm)
                             action:[self align]
                                 in:panel1.
    centerToggle := RadioButton form:(self class centerForm)
                              action:[self center]
                                  in:panel1.
    rightAlignToggle := RadioButton form:(self class rightAlignForm)
                                  action:[self rightAlign]
                                      in:panel1.
    group := RadioButtonGroup new.
    group add:leftAlignToggle.
    group add:alignToggle.
    group add:centerToggle.
    group add:rightAlignToggle.

    leftTabButton := Button form:(self class leftTabForm)
                          action:[self leftTab]
                              in:panel2.
    centerTabButton := Button form:(self class centerTabForm)
                            action:[self centerTab]
                                in:panel2.
    rightTabButton := Button form:(self class rightTabForm)
                           action:[self rightTab]
                               in:panel2.
    decimalTabButton := Button form:(self class decimalTabForm)
                             action:[self decimalTab]
                                 in:panel2.

    lineSpacingField := EditField in:panel3.


    leftMargin := 0.25.
    rightMargin := 8.25

    "TextRuler new realize"
!

initEvents
    super initEvents.
    self enableButtonEvents.
    self enableButtonMotionEvents

! !

!TextRuler methodsFor:'user interaction'!

leftAlign
    ^ self
!

rightAlign
    ^ self
!

align
    ^ self
!

center
    ^ self
!

leftTab
    ^ self
!

rightTab
    ^ self
!

centerTab
    ^ self
!

decimalTab
    ^ self
!

buttonPress:button x:x y:y
    "position a tab or start moving a ruler"

    |mpos|

    mpos := self inchToPixel:leftMargin.
    (((mpos - 4) <= x) and:[x <= (mpos + 4)]) ifTrue:[
        "start moving left margin"
        moving := #left.
        ^ self
    ].
    mpos := self inchToPixel:rightMargin.
    (((mpos - 4) <= x) and:[x <= (mpos + 4)]) ifTrue:[
        "start moving right margin"
        moving := #right.
        ^ self
    ].

    ^ self
!

buttonMotion:state x:x y:y
    "position a tab or start moving a ruler"

    |mpos|

    moving notNil ifTrue:[
        self clearMargin:moving.
        mpos := self pixelToInch:x.
        (mpos < 0) ifTrue:[
            mpos := 0
        ].
        (mpos > paperWidth) ifTrue:[
            mpos := paperWidth
        ].
        (moving == #left) ifTrue:[
            leftMargin := mpos
        ].
        (moving == #right) ifTrue:[
            rightMargin := mpos
        ].
        self drawMargin:moving
    ]
!

buttonRelease:button x:x y:y
    "position a tab or start moving a ruler"

    moving := nil
! !

!TextRuler methodsFor:'redrawing'!

clearMargin:which
    "clear margin"

    |x top form|

    self paint:viewBackground.
    self background:viewBackground.

    top := height - (font height) - (font ascent).

    (which == #left) ifTrue:[
        x := (self inchToPixel:leftMargin) rounded.
        form := self class leftMarginForm
    ].
    (which == #right) ifTrue:[
        x := (self inchToPixel:rightMargin) rounded.
        form := self class rightMarginForm
    ].

    self drawOpaqueForm:form x:(x - (form width // 2))
!

drawMargin:which
    "clear margin"

    |x top form|

    self paint:fgColor.
    self background:viewBackground.

    top := height - (font height) - (font ascent).

    (which == #left) ifTrue:[
        x := (self inchToPixel:leftMargin) rounded.
        form := self class leftMarginForm
    ].
    (which == #right) ifTrue:[
        x := (self inchToPixel:rightMargin) rounded.
        form := self class rightMarginForm
    ].

    self drawOpaqueForm:form x:(x - (form width // 2))
!

redraw
    "redraw margin & tab marks"

    |x top form tab type|

    super redraw.

    self paint:fgColor.
    self background:viewBackground.

    top := height - (font height) - (font ascent).

    x := (self inchToPixel:leftMargin) rounded.
    form := self class leftMarginForm.
    self drawOpaqueForm:form x:(x - (form width // 2))
                             y:(top - form height).
    x := (self inchToPixel:rightMargin) rounded.
    form := self class rightMarginForm.
    self drawOpaqueForm:form x:(x - (form width // 2))
                             y:(top - form height).

    tabStops notNil ifTrue:[
        1 to:tabStops size do:[:tabNr |
            tab := tabStops at:tabNr.
            type := tabTypes at:tabNr.
            x := (self inchToPixel:tab) rounded.
            (type == #left) ifTrue:[
                form := self class leftTabForm
            ] ifFalse:[
                (type == #right) ifTrue:[
                    form := self class rightTabForm
                ] ifFalse:[
                    (type == #center) ifTrue:[
                        form := self class centerTabForm
                    ] ifFalse:[
                        (type == #decimal) ifTrue:[
                            form := self class decimalTabForm
                        ]
                    ]
                ]
            ].
            self drawOpaqueForm:form x:(x - (form width // 2))
                                     y:(top - form height)
        ]
    ]
! !