EnterBox.st
changeset 59 450ce95a72a4
parent 48 eabeb474d989
child 60 f3c738c24ce6
--- a/EnterBox.st	Tue Aug 30 00:54:47 1994 +0200
+++ b/EnterBox.st	Mon Oct 10 04:03:47 1994 +0100
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1990 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -12,8 +12,8 @@
 
 ModalBox subclass:#EnterBox
        instanceVariableNames:'labelField enterField buttonPanel
-                              okButton abortButton
-                              okAction abortAction'
+			      okButton abortButton
+			      okAction abortAction'
        classVariableNames:''
        poolDictionaries:''
        category:'Views-DialogBoxes'
@@ -21,9 +21,9 @@
 
 EnterBox comment:'
 COPYRIGHT (c) 1990 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libwidg/EnterBox.st,v 1.9 1994-08-23 23:36:47 claus Exp $
+$Header: /cvs/stx/stx/libwidg/EnterBox.st,v 1.10 1994-10-10 03:01:21 claus Exp $
 '!
 
 !EnterBox class methodsFor:'documentation'!
@@ -31,7 +31,7 @@
 copyright
 "
  COPYRIGHT (c) 1990 by Claus Gittinger
-              All Rights Reserved
+	      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
@@ -44,7 +44,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libwidg/EnterBox.st,v 1.9 1994-08-23 23:36:47 claus Exp $
+$Header: /cvs/stx/stx/libwidg/EnterBox.st,v 1.10 1994-10-10 03:01:21 claus Exp $
 "
 !
 
@@ -54,22 +54,22 @@
     with 2 buttons; a cancel button, and a trigger-action button.
     The boxes title can be changed using: 
 
-        aBox title:'some string'
+	aBox title:'some string'
 
     The two button-labels default to 'abort' and 'ok'; 
     they can be changed using:
 
-        aBox okText:'someString'
-        aBox abortText:'someString'
+	aBox okText:'someString'
+	aBox abortText:'someString'
 
     The initial text in the enterfield can be set using:
 
-        aBox initialText:'someString'
+	aBox initialText:'someString'
 
     when the ok-button is pressed, an action is performed, which is
     set using:
 
-        aBox action:[ ... ]
+	aBox action:[ ... ]
 
     the abort-action defaults to no-action, but can also be set.
     The box can be opened modal (i.e. the currently active view will
@@ -77,19 +77,46 @@
     is equivalent to #openModal).
 
     example:
-        |box|
+	|box|
+
+	box := EnterBox new.
+	box title:'your name please:'.
+	box action:[:arg | Transcript showCr:'entered: ' , arg printString].
+	box open
+
+	|box|
 
-        box := EnterBox new.
-        box title:'your name please:'.
-        box action:[:arg | Transcript showCr:'entered: ' , arg printString].
-        box open
+	box := EnterBox new.
+	box title:'your name please:'.
+	box action:[:arg | Transcript showCr:'entered: ' , arg printString].
+	box openModeless
+
+    If the box is needed to ask for a simple string, you can also use the
+    #request method, to bring up a box, let it ask for something and return
+    the entered string. This method will return nil, if the box was
+    closed with the 'abort' button.
+    Example:
 
-        |box|
+	|box string|
+
+	box := EnterBox new.
+	string := box request:'input some string:'.
+	string isNil ifTrue:[
+	    Transcript showCr:'no input'
+	] ifFalse:[
+	    Transcript showCr:('the enetered string was: ' , string)
+	]
 
-        box := EnterBox new.
-        box title:'your name please:'.
-        box action:[:arg | Transcript showCr:'entered: ' , arg printString].
-        box openModeless
+    of course, this can be written shorter as:
+
+	|string|
+
+	string := EnterBox new request:'input some string:'.
+	string isNil ifTrue:[
+	    Transcript showCr:'no input'
+	] ifFalse:[
+	    Transcript showCr:('the enetered string was: ' , string)
+	]
 "
 ! !
 
@@ -103,6 +130,12 @@
     ^ self defaultExtent
 ! !
 
+!EnterBox class methodsFor:'easy startup '!
+
+request:aTitle
+    ^ self new request:aTitle
+! !
+
 !EnterBox class methodsFor:'instance creation'!
 
 action:aBlock
@@ -126,8 +159,8 @@
      okText and abortText; it will evaluate aBlock when 'ok' is pressed"
 
     ^ ((self new) title:titleString 
-                 okText:okText 
-              abortText:abortText) action:aBlock
+		 okText:okText 
+	      abortText:abortText) action:aBlock
 ! !
 
 !EnterBox methodsFor:'initialization'!
@@ -151,45 +184,42 @@
     innerWidth := width - space2.
 
     labelField origin:(ViewSpacing @ ViewSpacing)
-               extent:(innerWidth @ labelField height).
+	       extent:(innerWidth @ labelField height).
 
     self createEnterField.
     enterField origin:(ViewSpacing @ (space2 + labelField height))
-               extent:((width - space2 - (enterField borderWidth * 2) - margin) @ enterField height).
+	       extent:((width - space2 - (enterField borderWidth * 2) - margin) @ enterField height).
     enterField origin:[ViewSpacing @ (space2 + labelField height)]
-               extent:[(width - space2 - (enterField borderWidth * 2) - margin) @ enterField height].
+	       extent:[(width - space2 - (enterField borderWidth * 2) - margin) @ enterField height].
     enterField leaveAction:[:key | self okPressed].
-    enterField addDependent:self. "to get preferredExtent-changes"
+    enterField addDependent:self. "to get preferedExtent-changes"
 
     buttonPanel := HorizontalPanelView in:self.
     buttonPanel origin:(ViewSpacing @ (height - (font height * 2) - ViewSpacing - (borderWidth * 2)))
-                extent:((width - space2 - (ViewSpacing // 2) - (buttonPanel borderWidth * 2)) 
-                       @ ((font height * 2) + (borderWidth * 2))).
+		extent:((width - space2 - (ViewSpacing // 2) - (buttonPanel borderWidth * 2)) 
+		       @ ((font height * 2) + (borderWidth * 2))).
     buttonPanel origin:[ViewSpacing @ (height - (font height * 2) - ViewSpacing - (borderWidth * 2))]
-                extent:[(width - space2 - (ViewSpacing // 2) - (buttonPanel borderWidth * 2)) 
-                       @ ((font height * 2) + (borderWidth * 2))].
+		extent:[(width - space2 - (ViewSpacing // 2) - (buttonPanel borderWidth * 2)) 
+		       @ ((font height * 2) + (borderWidth * 2))].
 
     buttonPanel layout:"#spread2" #right.
     buttonPanel borderWidth:0.
 
-    abortButton := Button label:(resources at:'abort')
-                         action:[
-                                    abortButton turnOffWithoutRedraw.
-                                    self abortPressed
-                                ]
-                             in:buttonPanel.
+    abortButton := Button abortButtonIn:buttonPanel.
+    abortButton action:[
+			   abortButton turnOffWithoutRedraw.
+			   self abortPressed
+		       ].
 
-    okButton := Button label:(resources at:'ok')
-                      action:[
-                                okButton turnOffWithoutRedraw.
-                                self okPressed
-                             ]
-                          in:buttonPanel.
-    okButton isReturnButton:true.
+    okButton := Button okButtonIn:buttonPanel.
+    okButton action:[
+		       okButton turnOffWithoutRedraw.
+		       self okPressed
+		    ].
 
-    okButton cursor:(Cursor thumbsUp).
-    abortButton cursor:(Cursor thumbsDown).
-
+    "
+     forward keyboard input to the enterfield
+    "
     self keyboardHandler:enterField
 !
 
@@ -223,38 +253,53 @@
     ^ (okButton originRelativeTo:self) + (okButton extent // 2)
 ! !
 
+!EnterBox methodsFor:'startup'!
+
+request
+    "open the box and return the entered string or nil, if
+     abort was pressed"
+
+    self action:[:string | ^ string].
+    self open.
+    ^ nil
+!
+
+request:title
+    "set the title, open the box and return the entered string or nil, if
+     abort was pressed"
+
+    self title:title.
+    ^ self request
+! !
+
 !EnterBox methodsFor:'private'!
 
+preferedExtent 
+    |wWanted hWanted wPanel vs2 nx ny min|
+
+    vs2 := ViewSpacing * 2.
+    wWanted := (labelField widthIncludingBorder max:enterField preferedExtent x) + vs2.
+    wPanel := buttonPanel preferedExtent x + vs2.
+    wPanel > wWanted ifTrue:[
+	wWanted := wPanel
+    ].
+    hWanted := vs2 + labelField height + enterField height +
+	       (ViewSpacing * 6) + buttonPanel height + ViewSpacing.
+
+    min := self class minExtent.
+    wWanted <  min x ifTrue:[
+	wWanted :=  min x
+    ].
+    hWanted <  min y ifTrue:[
+	hWanted :=  min y
+    ].
+    ^ wWanted @ hWanted
+!
+
 resize
     "resize myself to make everything visible"
 
-    |wWanted hWanted wPanel vs2 nx ny min|
-
-    vs2 := ViewSpacing * 2.
-    wWanted := (labelField widthIncludingBorder max:enterField preferredExtent x) + vs2.
-    wPanel := buttonPanel preferedExtent x + vs2.
-    wPanel > wWanted ifTrue:[
-        wWanted := wPanel
-    ].
-    hWanted := vs2 + labelField height + enterField height +
-               (ViewSpacing * 6) + buttonPanel height + ViewSpacing.
-
-    min := self class minExtent.
-    wWanted <  min x ifTrue:[
-        wWanted :=  min x
-    ].
-    hWanted <  min y ifTrue:[
-        hWanted :=  min y
-    ].
-    ((wWanted ~= width) or:[hWanted ~= height]) ifTrue:[
-        "
-         make sure, that we are fully visible
-         (by moving origin if nescessary)
-        "
-        nx := self origin x min:(device width - wWanted).
-        ny := self origin y min:(device height - hWanted).
-        self origin:nx@ny extent:(wWanted @ hWanted)
-    ]
+    self extent:(self preferedExtent)
 ! !
 
 !EnterBox methodsFor:'accessing'!
@@ -265,13 +310,13 @@
     |oldSize|
 
     aString ~= labelField label ifTrue:[
-        oldSize := labelField extent.
-        labelField label:aString.
-        labelField resize.
+	oldSize := labelField extent.
+	labelField label:aString.
+	labelField resize.
 
-        labelField extent ~= oldSize ifTrue:[
-            self resize
-        ]
+	labelField extent ~= oldSize ifTrue:[
+	    self resize
+	]
     ]
 !
 
@@ -281,13 +326,13 @@
     (titleString ~= labelField label 
      or:[okString ~= okButton label
      or:[abortString ~= abortButton label]]) ifTrue:[
-        okButton label:okString.
-        okButton resize.
-        abortButton label:abortString.
-        abortButton resize.
-        labelField label:titleString.
-        labelField resize.
-        self resize.
+	okButton label:okString.
+	okButton resize.
+	abortButton label:abortString.
+	abortButton resize.
+	labelField label:titleString.
+	labelField resize.
+	self resize.
     ]
 !
 
@@ -295,11 +340,11 @@
     "set title and text in okbutton"
 
     (titleString ~= labelField label or:[okString ~= okButton label]) ifTrue:[
-        okButton label:okString.
-        okButton resize.
-        labelField label:titleString.
-        labelField resize.
-        self resize.
+	okButton label:okString.
+	okButton resize.
+	labelField label:titleString.
+	labelField resize.
+	self resize.
     ]
 !
 
@@ -309,12 +354,12 @@
     |oldSize|
 
     aString ~= okButton label ifTrue:[
-        oldSize := okButton extent.
-        okButton label:aString.
-        okButton resize.
-        okButton extent ~= oldSize ifTrue:[
-            self resize
-        ]
+	oldSize := okButton extent.
+	okButton label:aString.
+	okButton resize.
+	okButton extent ~= oldSize ifTrue:[
+	    self resize
+	]
     ]
 !
 
@@ -324,12 +369,12 @@
     |oldSize|
 
     aString ~= abortButton label ifTrue:[
-        oldSize := abortButton extent.
-        abortButton label:aString.
-        abortButton resize.
-        abortButton extent ~= oldSize ifTrue:[
-            self resize
-        ]
+	oldSize := abortButton extent.
+	abortButton label:aString.
+	abortButton resize.
+	abortButton extent ~= oldSize ifTrue:[
+	    self resize
+	]
     ]
 !
 
@@ -338,11 +383,11 @@
 
     (abortString ~= abortButton label 
     or:[okString ~= okButton label]) ifTrue:[
-        okButton label:okString.
-        abortButton label:abortString.
-        okButton resize.
-        abortButton resize.
-        self resize
+	okButton label:okString.
+	abortButton label:abortString.
+	okButton resize.
+	abortButton resize.
+	self resize
     ]
 !
 
@@ -387,15 +432,15 @@
 
 !EnterBox methodsFor:'dependencies'!
 
-update:something with:someArgument
+update:something with:someArgument from:changedObject
     "sent if my enterbox thinks it needs more real-estate ..."
 
     |ext|
 
-    something == enterField ifTrue:[
-        someArgument == #preferredExtent ifTrue:[
-            self resize
-        ]
+    changedObject == enterField ifTrue:[
+	something == #preferedExtent ifTrue:[
+	    self resize
+	]
     ]
 ! !
 
@@ -409,13 +454,13 @@
 
     self hide.
     aBlock notNil ifTrue:[
-        string := self contents.
-        string isNil ifTrue:[
-            string := ''
-        ] ifFalse:[
-            string := string withoutSeparators
-        ].
-        aBlock value:string
+	string := self contents.
+	string isNil ifTrue:[
+	    string := ''
+	] ifFalse:[
+	    string := string withoutSeparators
+	].
+	aBlock value:string
     ]
 !