ActiveHelpView.st
author Claus Gittinger <cg@exept.de>
Mon, 29 Apr 1996 10:13:30 +0200
changeset 233 196eb68b707c
parent 221 ea942fe5dc04
child 236 89a3cda02cbb
permissions -rw-r--r--
documentation

"
 COPYRIGHT (c) 1995 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:#ActiveHelpView
	instanceVariableNames:'myView'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Help'
!

!ActiveHelpView class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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
"
    a talking view.

    Instances of myself show up either as a comics-like talking
    view, or as a simple square popup. This is configured via the
    styleSheet; the default is simple-square. 
    To get the fancy comics style, add a resource 'activeHelpStyle' with 
    a symbol-value of #cartoon.
    However, be aware that some servers have performance problems with
    these view-shapes (or do not support shapes at all).

    [author:]
        Claus Gittinger

    [See also:]
        ActiveHelp
"
! !

!ActiveHelpView class methodsFor:'instance creation'!

for:someText
    "create a talking-view for some text"

    |helpView textView|

    helpView := self new.
"/    textView := ListView new.
    textView := Label new. "/ ListView new.
    textView font:(helpView font on:textView device).
    ^ (helpView withView:textView) contents:someText

    "
     (ActiveHelpView for:'hello world\this is an ActiveHelpView' withCRs) realize
     (ActiveHelpView for:'press here\to open a new\SystemBrowser' withCRs) realize
    "

    "Modified: 27.4.1996 / 15:14:07 / cg"
!

with:aView
    "create a talking-view wrapping some other view"

    ^ self new withView:aView

    "
     (ActiveHelpView with:(TextView new)) realize
     (ActiveHelpView with:(TextView new)) open
     (ActiveHelpView with:(Button label:'ok')) open
    "

    "Modified: 27.4.1996 / 15:14:18 / cg"
! !

!ActiveHelpView methodsFor:'accessing'!

contents:someText
    "set the text"

    (myView isKindOf:Label) ifTrue:[
        myView label:someText asString.
        myView extent:(myView preferredExtent).
    ] ifFalse:[
        myView contents:someText.
    ].
    self resizeToFit

    "Modified: 27.4.1996 / 15:14:56 / cg"
!

withView:aView
    "set the component view"

    (aView isKindOf:Label) ifTrue:[
        aView viewBackground:viewBackground.
        aView backgroundColor:viewBackground.
    ].
    self addSubView:aView.
    myView := aView.
    myView borderWidth:0

    "Modified: 27.4.1996 / 15:16:46 / cg"
! !

!ActiveHelpView methodsFor:'events'!

redraw
    self fill:White
! !

!ActiveHelpView methodsFor:'initialization'!

initStyle
    super initStyle.

    viewBackground := styleSheet colorAt:'activeHelpBackgroundColor' default:viewBackground.
    borderWidth := styleSheet at:'activeHelpBorderWidth' default:1.
!

initialize
    super initialize.
    font := Font family:'helvetica' size:12.
    (styleSheet at:'activeHelpStyle' default:nil) == #cartoon ifTrue:[
	self viewBackground:White
    ]
!

realize
    self create.
    self computeShape.
    self enableMotionEvents.
    self enableButtonMotionEvents.
    super realize
! !

!ActiveHelpView methodsFor:'private'!

computeShape
    "compute the shape, based upon the size of my component view"

    |extent shapeForm borderForm y1 bw h w mirrorH mirrorV
     p1 p2 p3 pB1 pB2 pB3 offs|

    (styleSheet at:'activeHelpStyle' default:nil) ~~ #cartoon ifTrue:[^ self].

    extent := self extent.
    h := extent y.
    w := extent x.
    bw := 4.
    offs := 0.

    self corner x > self device width ifTrue:[
        mirrorH := true.
        self origin:((self origin x - w) @ (self origin y)).
        offs := bw * 2.
    ] ifFalse:[
        mirrorH := false
    ].
    self corner y > self device height ifTrue:[
        mirrorV := true.
        self origin:(self origin x @ (self origin y - h)).
    ] ifFalse:[
        mirrorV := false
    ].

    borderForm := Form width:w height:h.
    shapeForm := Form width:w height:h.
    borderForm fill:(Color colorId:0).
    shapeForm fill:(Color colorId:0).

    mirrorV ifTrue:[
        myView origin:(w // 7 + offs) @ (h//8)
               extent:(w // 7 * 6) @ (h // 3 * 2).
        y1 := 0.
    ] ifFalse:[
        myView origin:(w // 7 + offs) @ (h // 3)
               extent:(w // 7 * 6) @ (h // 3 * 2).
        y1 := h // 4.
    ].

    borderForm fillArcX:0 
                      y:y1 
                      w:w
                      h:(h // 3 * 2)
                   from:0
                  angle:360.

"/    shapeForm fillArcX:bw y:(h // 4) + bw 
"/                      w:(w - (bw * 2))
"/                      h:(h // 3 * 2 - (bw * 2))
"/                   from:0
"/                  angle:360.

    mirrorH ifTrue:[
        mirrorV ifTrue:[
            p1 := w @ h. 
            p2 := ((w * 7 // 8) @ (h // 2)).
            p3 := ((w // 2) @ (h // 2)).
            pB1 := (w-bw) @ (h-bw). 
            pB2 := ((w * 7 // 8 - bw) @ (h // 2 - bw)).
            pB3 := ((w // 2 + bw) @ (h // 2 - bw))
        ] ifFalse:[
            p1 := w @ 0. 
            p2 := ((w * 7 // 8) @ (h // 2)).
            p3 := ((w // 2) @ (h // 2)).
            pB1 := (w-bw) @ bw. 
            pB2 := ((w * 7 // 8 - bw) @ (h // 2 + bw)).
            pB3 := ((w // 2 + bw) @ (h // 2 + bw))
        ]
    ] ifFalse:[
        mirrorV ifTrue:[
            p1 := 0@h. 
            p2 := ((w // 8) @ (h // 2)). 
            p3 := ((w // 2) @ (h // 2)).
            pB1 := bw@(h-bw). 
            pB2 := ((w // 8 + bw) @ (h // 2 - bw)). 
            pB3 := ((w // 2 - bw) @ (h // 2 - bw)).
        ] ifFalse:[
            p1 := 0@0. 
            p2 := ((w // 8) @ (h // 2)). 
            p3 := ((w // 2) @ (h // 2)).
            pB1 := bw@bw. 
            pB2 := ((w // 8 + bw) @ (h // 2 + bw)). 
            pB3 := ((w // 2 - bw) @ (h // 2 + bw)).
        ]
    ].

    borderForm fillPolygon:(Array with:p1 with:p2 with:p3).
    shapeForm fillPolygon:(Array with:pB1 with:pB2 with:pB3).

    shapeForm lineWidth:bw.
    shapeForm paint:(Color colorId:0).
    shapeForm displayPolygon:(Array with:p3 with:p1 with:p2).

    shapeForm paint:(Color colorId:1).
    shapeForm fillArcX:bw 
                     y:y1 + bw 
                     w:(w - (bw * 2))
                     h:(h // 3 * 2 - (bw * 2))
                  from:0
                 angle:360.

    self borderShape:borderForm.
    self viewShape:shapeForm

    "Modified: 27.4.1996 / 15:16:15 / cg"
!

resizeToFit
    "resize myself to make the component view fit"

    |h w|

    (styleSheet at:'activeHelpStyle' default:nil) == #cartoon ifTrue:[
        h := myView height. "/ heightOfContents.
        w := myView width. "/ widthOfContents.
        self extent:((w * 0.85) rounded asInteger)
                     @ 
                    ((h * 2.5) rounded asInteger)
    ] ifFalse:[
        self extent:myView extent
    ]

    "Modified: 27.4.1996 / 15:16:29 / cg"
! !

!ActiveHelpView methodsFor:'queries'!

createOnTop
    "return true - I always want to popUp onTop of others"

    ^ true

    "Modified: 27.4.1996 / 15:15:13 / cg"
!

isPopUpView
    "return true - I am a popUp type of view"

    ^ true

    "Modified: 27.4.1996 / 15:15:42 / cg"
! !

!ActiveHelpView class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/ActiveHelpView.st,v 1.9 1996-04-29 08:13:30 cg Exp $'
! !