ModalBox.st
changeset 270 f80e2a67de1e
parent 269 ea536bb319a6
child 296 655507429feb
--- a/ModalBox.st	Mon Nov 27 23:31:52 1995 +0100
+++ b/ModalBox.st	Mon Nov 27 23:42:20 1995 +0100
@@ -11,10 +11,10 @@
 "
 
 StandardSystemView subclass:#ModalBox
-	 instanceVariableNames:'shadowView exclusiveKeyboard'
-	 classVariableNames:'UseTransientViews'
-	 poolDictionaries:''
-	 category:'Views-Basic'
+       instanceVariableNames:'shadowView exclusiveKeyboard '
+       classVariableNames:'UseTransientViews'
+       poolDictionaries:''
+       category:'Views-Basic'
 !
 
 !ModalBox class methodsFor:'documentation'!
@@ -33,6 +33,10 @@
 "
 !
 
+version
+    ^ '$Header: /cvs/stx/stx/libview/ModalBox.st,v 1.31 1995-11-27 22:42:20 cg Exp $'
+!
+
 documentation
 "
     this class implements modal boxes; ModalBoxes are different from
@@ -78,138 +82,8 @@
     "
 ! !
 
-!ModalBox methodsFor:'accessing'!
-
-exclusiveKeyboard:aBoolean
-    "set/clear exclusive locking of the keyboard;
-     If set, the box will take total control over the
-     keyboard, not allowing input to other views/boxes
-     while active.
-     Danger: only use this for very very urgent boxes, since
-     no interaction with any view on the screen is possible then."
-
-    exclusiveKeyboard := aBoolean
-! !
-
-!ModalBox methodsFor:'event handling'!
-
-coveredBy:aView
-    "the receiver has been covered by another view.
-     If the other view is a non-modal one, raise"
-
-    |mainGroup topViews|
-
-    "
-     if the other view is not a modal- (or shadow-, or popup-) -view,
-     bring myself to the front again.
-    "
-    aView isPopUpView ifFalse:[
-	"
-	 if I have a mainGroup,
-	 only raise if its one of my maingroup-views
-	"
-	windowGroup notNil ifTrue:[
-	    mainGroup := windowGroup mainGroup.
-	    mainGroup notNil ifTrue:[
-		topViews := mainGroup topViews.
-		topViews notNil ifTrue:[
-		    topViews do:[:aTopView |
-			aView == aTopView ifTrue:[
-			    self raise.     
-			    ^ self
-			]
-		    ]
-		].
-		^ self
-	    ]
-	].
-	self raise
-    ]
-!
-
-pointerEnter:state x:x y:y
-    "mhmh: this seems to be a special X kludge;
-     without the following, we will not regain input focus after
-     pointer is reentered."
-
-    self getKeyboardFocus.
-    super pointerEnter:state x:x y:y
-!
-
-terminate
-    "this is the close from a windowmanager
-     (only if UseTransientViews == true)"
-
-    "
-     if I am a dialog, make the receiver invisible and leave control.
-     But, do not destroy the underlying view resources, to allow for
-     another open/show to occur later.
-     if I have been opened modeLess, perform the normal destroy operation.
-    "
-    (windowGroup isNil or:[windowGroup isModal]) ifTrue:[
-	self hide
-    ] ifFalse:[
-	super terminate
-    ]
-!
-
-visibilityChange:how
-    "raise when covered - this should not be needed, since we
-     have been created as override-redirect window (which should
-     stay on top - but some window managers (fvwm) seem to ignore
-     this ..."
-
-    "the code below is not good, since it will lead to
-     oscillating raises when two modalBoxes are going to cover
-     each other - see coveredBy:-handling ..."
-
-"/    how ~~ #fullyVisible ifTrue:[
-"/        self raise
-"/    ]
-! !
-
 !ModalBox methodsFor:'initialize / release'!
 
-addToCurrentProject
-    "ignored here"
-
-    ^ self
-!
-
-create
-    super create.
-    shadowView notNil ifTrue:[
-	self saveUnder:true
-    ]
-!
-
-destroy
-    shadowView notNil ifTrue:[
-	shadowView destroy.
-	shadowView := nil
-    ].
-    self leaveControl. "just to make sure"
-    super destroy.
-!
-
-initEvents
-    super initEvents.
-    self enableEvent:#visibilityChange
-!
-
-initStyle
-    |style|
-
-    super initStyle.
-    style := styleSheet name.
-    ((style ~~ #normal) and:[style ~~ #mswindows]) ifTrue:[
-	borderWidth := 0.
-	UseTransientViews ifFalse:[
-	    self level:2
-	]
-    ]
-!
-
 initialize
     |form resizeButton moveButton|
 
@@ -275,8 +149,22 @@
 
 !
 
-isPopUpView
-    ^ UseTransientViews not
+initEvents
+    super initEvents.
+    self enableEvent:#visibilityChange
+!
+
+initStyle
+    |style|
+
+    super initStyle.
+    style := styleSheet name.
+    ((style ~~ #normal) and:[style ~~ #mswindows]) ifTrue:[
+	borderWidth := 0.
+	UseTransientViews ifFalse:[
+	    self level:2
+	]
+    ]
 !
 
 reinitialize
@@ -284,6 +172,32 @@
    self unrealize.
 !
 
+addToCurrentProject
+    "ignored here"
+
+    ^ self
+!
+
+destroy
+    shadowView notNil ifTrue:[
+	shadowView destroy.
+	shadowView := nil
+    ].
+    self leaveControl. "just to make sure"
+    super destroy.
+!
+
+create
+    super create.
+    shadowView notNil ifTrue:[
+	self saveUnder:true
+    ]
+!
+
+isPopUpView
+    ^ UseTransientViews not
+!
+
 resize
     "resize myself to make everything visible"
 
@@ -338,48 +252,6 @@
     "Modified: 6.9.1995 / 15:31:21 / claus"
 ! !
 
-!ModalBox methodsFor:'move & resize'!
-
-doMove
-    "the move button was pressed"
-
-    |r|
-
-    r := device rectangleFromUser:(self origin corner:self corner).
-    shadowView notNil ifTrue:[
-	shadowView unrealize
-    ].
-    self origin:r origin extent:(r extent max:(100@100)).
-    shadowView notNil ifTrue:[
-	shadowView realize.
-	self raise
-    ].
-!
-
-doResize
-    "the resize button was pressed"
-
-    |r|
-
-    r := device rectangleFromUser:(self origin corner:self corner).
-    shadowView notNil ifTrue:[
-	shadowView unrealize
-    ].
-    self origin:r origin extent:(r extent max:(100@100)).
-    shadowView notNil ifTrue:[
-	shadowView realize.
-	self raise
-    ].
-! !
-
-!ModalBox methodsFor:'private'!
-
-leaveControl
-    exclusiveKeyboard ifTrue:[
-	device ungrabKeyboard
-    ]
-! !
-
 !ModalBox methodsFor:'queries'!
 
 preferredExtent
@@ -390,76 +262,20 @@
     ^ self class defaultExtent
 ! !
 
-!ModalBox methodsFor:'show / hide'!
-
-autoHideAfter:seconds with:anAction
-    "install a background process, which hides the box
-     after some time. Also, if non-nil, anAction will be
-     evaluated then. The action will not be evaluated if
-     the box is closed by the user pressing a button."
-
-    "the implementation is simple: just fork of a process
-     to hide me."
-    [
-	(Delay forSeconds:seconds) wait.
-	self shown ifTrue:[
-	    self hide. 
-	    anAction notNil ifTrue:[anAction value]
-	]
-    ] forkAt:4.
-
-    "
-     |b|
-
-     b := InfoBox title:'hello there'.
-     b autoHideAfter:5 with:[].
-     b showAtCenter.
-    "
-!
-
-fixPosition:aPoint
-    "set origin to aPoint, but make sure, that the box is fully visible 
-     by shifting it into the visible screen area if nescessary.
-     This prevents invisible modalBoxes (which you could never close)."
+!ModalBox methodsFor:'accessing'!
 
-    self origin:aPoint.
-    self makeFullyVisible
-!
-
-fixSize
-    "this is sent right before the modalBox is made visible;
-     If the size is not fixed, adjust my size."
-
-    sizeFixed == true ifFalse:[
-	self resize.
-    ].
-    super fixSize.
-!
-
-hide
-    "make the receiver invisible and leave control"
-
-    |p|
+exclusiveKeyboard:aBoolean
+    "set/clear exclusive locking of the keyboard;
+     If set, the box will take total control over the
+     keyboard, not allowing input to other views/boxes
+     while active.
+     Danger: only use this for very very urgent boxes, since
+     no interaction with any view on the screen is possible then."
 
-    shadowView notNil ifTrue:[shadowView unrealize].
-    windowGroup notNil ifTrue:[windowGroup focusView:nil].
-    self leaveControl.
-    self unrealize.
-    device flush. 
+    exclusiveKeyboard := aBoolean
+! !
 
-    (windowGroup notNil and:[(p := windowGroup previousGroup) notNil]) ifTrue:[
-	"
-	 this is a kludge for IRIS which does not provide backingstore:
-	 when we hide a modalbox (such as a searchbox) which covered
-	 a scrollbar, the scrollbars bitblt-method will copy from the
-	 not-yet redrawn area - effectively clearing the scroller.
-	 We need a short delay here, since at this time, the expose event has
-	 not yet arrived.
-	"
-	(Delay forSeconds:0.1) wait.
-	p processExposeEvents   
-    ].
-!
+!ModalBox methodsFor:'show / hide'!
 
 mapped
     "wait till visible for grabbing"
@@ -487,6 +303,34 @@
 "/    ]
 !
 
+fixPosition:aPoint
+    "set origin to aPoint, but make sure, that the box is fully visible 
+     by shifting it into the visible screen area if nescessary.
+     This prevents invisible modalBoxes (which you could never close)."
+
+    self origin:aPoint.
+    self makeFullyVisible
+!
+
+fixSize
+    "this is sent right before the modalBox is made visible;
+     If the size is not fixed, adjust my size."
+
+    sizeFixed == true ifFalse:[
+	self resize.
+    ].
+    super fixSize.
+!
+
+positionOffset
+    "return the delta, by which the box should be
+     displaced from the mouse pointer. 
+     Usually redefined in subclasses to have the most convenient
+     ok-button appear under the pointer."
+
+    ^ (width // 2) @ (height // 2)
+!
+
 open
     "default for modalboxes is to come up modal at the pointer position"
 
@@ -559,15 +403,6 @@
 "/    ].
 !
 
-positionOffset
-    "return the delta, by which the box should be
-     displaced from the mouse pointer. 
-     Usually redefined in subclasses to have the most convenient
-     ok-button appear under the pointer."
-
-    ^ (width // 2) @ (height // 2)
-!
-
 show
     "make myself visible (at the last or default position) and take control"
 
@@ -659,6 +494,23 @@
     "
 !
 
+showCenteredIn:aView
+    "make myself visible at the screen center."
+
+    |top|
+
+    top := aView topView.
+    top raise.
+    self showAt:(top center + (aView originRelativeTo:top)) center:true
+
+    "
+     |b|
+
+     b := InfoBox title:'hello'.
+     b showCenteredIn:Transcript.
+    "
+!
+
 showAtPointer
     "make myself visible at mouse pointer shifted to have
      convenient button under cursor. self positionOffset should
@@ -704,4 +556,184 @@
 	    intersects: (aView origin corner: aView corner)) 
 	ifTrue:[
 	    "
-	     try to t
\ No newline at end of file
+	     try to the left of the untouchable view
+	    "
+	    newX := aView origin x - width.
+	    "
+	     should look for vertical possibilities too ...
+	    "
+	    pos x:newX.
+	]
+
+    ].
+    self showAt:pos
+!
+
+hide
+    "make the receiver invisible and leave control"
+
+    |p|
+
+    shadowView notNil ifTrue:[shadowView unrealize].
+    windowGroup notNil ifTrue:[windowGroup focusView:nil].
+    self leaveControl.
+    self unrealize.
+    device flush. 
+
+    (windowGroup notNil and:[(p := windowGroup previousGroup) notNil]) ifTrue:[
+	"
+	 this is a kludge for IRIS which does not provide backingstore:
+	 when we hide a modalbox (such as a searchbox) which covered
+	 a scrollbar, the scrollbars bitblt-method will copy from the
+	 not-yet redrawn area - effectively clearing the scroller.
+	 We need a short delay here, since at this time, the expose event has
+	 not yet arrived.
+	"
+	(Delay forSeconds:0.1) wait.
+	p processExposeEvents   
+    ].
+!
+
+autoHideAfter:seconds with:anAction
+    "install a background process, which hides the box
+     after some time. Also, if non-nil, anAction will be
+     evaluated then. The action will not be evaluated if
+     the box is closed by the user pressing a button."
+
+    "the implementation is simple: just fork of a process
+     to hide me."
+    [
+	(Delay forSeconds:seconds) wait.
+	self shown ifTrue:[
+	    self hide. 
+	    anAction notNil ifTrue:[anAction value]
+	]
+    ] forkAt:4.
+
+    "
+     |b|
+
+     b := InfoBox title:'hello there'.
+     b autoHideAfter:5 with:[].
+     b showAtCenter.
+    "
+! !
+
+!ModalBox methodsFor:'move & resize'!
+
+doMove
+    "the move button was pressed"
+
+    |r|
+
+    r := device rectangleFromUser:(self origin corner:self corner).
+    shadowView notNil ifTrue:[
+	shadowView unrealize
+    ].
+    self origin:r origin extent:(r extent max:(100@100)).
+    shadowView notNil ifTrue:[
+	shadowView realize.
+	self raise
+    ].
+!
+
+doResize
+    "the resize button was pressed"
+
+    |r|
+
+    r := device rectangleFromUser:(self origin corner:self corner).
+    shadowView notNil ifTrue:[
+	shadowView unrealize
+    ].
+    self origin:r origin extent:(r extent max:(100@100)).
+    shadowView notNil ifTrue:[
+	shadowView realize.
+	self raise
+    ].
+! !
+
+!ModalBox methodsFor:'event handling'!
+
+terminate
+    "this is the close from a windowmanager
+     (only if UseTransientViews == true)"
+
+    "
+     if I am a dialog, make the receiver invisible and leave control.
+     But, do not destroy the underlying view resources, to allow for
+     another open/show to occur later.
+     if I have been opened modeLess, perform the normal destroy operation.
+    "
+    (windowGroup isNil or:[windowGroup isModal]) ifTrue:[
+	self hide
+    ] ifFalse:[
+	super terminate
+    ]
+!
+
+visibilityChange:how
+    "raise when covered - this should not be needed, since we
+     have been created as override-redirect window (which should
+     stay on top - but some window managers (fvwm) seem to ignore
+     this ..."
+
+    "the code below is not good, since it will lead to
+     oscillating raises when two modalBoxes are going to cover
+     each other - see coveredBy:-handling ..."
+
+"/    how ~~ #fullyVisible ifTrue:[
+"/        self raise
+"/    ]
+!
+
+coveredBy:aView
+    "the receiver has been covered by another view.
+     If the other view is a non-modal one, raise"
+
+    |mainGroup topViews|
+
+    "
+     if the other view is not a modal- (or shadow-, or popup-) -view,
+     bring myself to the front again.
+    "
+    aView isPopUpView ifFalse:[
+	"
+	 if I have a mainGroup,
+	 only raise if its one of my maingroup-views
+	"
+	windowGroup notNil ifTrue:[
+	    mainGroup := windowGroup mainGroup.
+	    mainGroup notNil ifTrue:[
+		topViews := mainGroup topViews.
+		topViews notNil ifTrue:[
+		    topViews do:[:aTopView |
+			aView == aTopView ifTrue:[
+			    self raise.     
+			    ^ self
+			]
+		    ]
+		].
+		^ self
+	    ]
+	].
+	self raise
+    ]
+!
+
+pointerEnter:state x:x y:y
+    "mhmh: this seems to be a special X kludge;
+     without the following, we will not regain input focus after
+     pointer is reentered."
+
+    self getKeyboardFocus.
+    super pointerEnter:state x:x y:y
+! !
+
+!ModalBox methodsFor:'private'!
+
+leaveControl
+    exclusiveKeyboard ifTrue:[
+	device ungrabKeyboard
+    ]
+! !