FileSelectionBox.st
changeset 197 00927189c882
parent 174 d80a6cc3f9b2
child 235 bbd0a7433459
--- a/FileSelectionBox.st	Thu Nov 23 02:43:52 1995 +0100
+++ b/FileSelectionBox.st	Thu Nov 23 03:26:58 1995 +0100
@@ -11,10 +11,10 @@
 "
 
 ListSelectionBox subclass:#FileSelectionBox
-       instanceVariableNames:'patternField'
-       classVariableNames:''
-       poolDictionaries:''
-       category:'Views-DialogBoxes'
+	 instanceVariableNames:'patternField'
+	 classVariableNames:''
+	 poolDictionaries:''
+	 category:'Views-DialogBoxes'
 !
 
 !FileSelectionBox class methodsFor:'documentation'!
@@ -33,10 +33,6 @@
 "
 !
 
-version
-    ^ '$Header: /cvs/stx/stx/libwidg/FileSelectionBox.st,v 1.22 1995-11-11 16:20:16 cg Exp $'
-!
-
 documentation
 "
     this class implements file selection boxes. Instances show a list of
@@ -97,6 +93,10 @@
 	box matchBlock:[:name | OperatingSystem isDirectory:name].
 	box open
 "
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libwidg/FileSelectionBox.st,v 1.23 1995-11-23 02:25:26 cg Exp $'
 ! !
 
 !FileSelectionBox class methodsFor:'defaults'!
@@ -134,183 +134,38 @@
     ^ FileSelectionList
 ! !
 
-!FileSelectionBox methodsFor:'initialization'!
-
-initialize
-    |corner|
-
-    super initialize.
-
-    label := resources string:'File dialog'.
-
-    labelField extent:(0.7 @ labelField height).
-    labelField label:(resources string:'select a file:').
-    labelField adjust:#left.
+!FileSelectionBox methodsFor:'accessing'!
 
-    patternField := EditField in:self.
-    self is3D ifTrue:[
-	corner := (1.0 @ (labelField origin y+patternField heightIncludingBorder)).
-    ] ifFalse:[
-	corner := [(width - ViewSpacing - (patternField borderWidth * 2)) @ (labelField origin y+patternField height"IncludingBorder")].
-    ].
-    patternField origin:(0.7 @ labelField origin y) corner:corner.
-    patternField rightInset:ViewSpacing.
-    patternField initialText:'*'.
-    patternField leaveAction:[:reason | 
-	selectionList pattern:patternField contents. 
-	self updateList
-    ].
-    patternField hiddenOnRealize:true. "delay showing, until a pattern is defined"
+contents
+    "return the current entered value (i.e. the enterFields string).
+     redefined to return the full pathname."
+
+    |string sep|
 
-    enterField addDependent:self.
-
-    "
-     FileSelectionBox open
-     FileSelectionBox new show
-    "
-!
-
-createEnterField
-    "if the (optional) class FilenameEditField is present, use
-     it, since it provides filename completion. Otherwise, we have
-     to live with the dump (default) field ...
-    "
-    FilenameEditField notNil ifTrue:[
-	^ FilenameEditField new.
+    string := super contents.
+    string isNil ifTrue:[
+	^ selectionList directory pathName
     ].
-    ^ super createEnterField
-!
-
-focusSequence
-    patternField shown ifTrue:[
-	^ Array 
-	    with:patternField 
-	    with:enterField 
-	    with:selectionList 
-	    with:abortButton
-	    with:okButton 
+    sep := Filename separator.
+    (string startsWith:sep) ifTrue:[
+	^ string
     ].
-    ^ super focusSequence
+    ^ (selectionList directory pathName asFilename construct:string) asString
 !
 
-realize
-    "if some default is present in the enterField,
-     scroll to make this one visible"
-
-    |contents|
-
-    super realize.
-    (contents := enterField contents) notNil ifTrue:[
-	contents notEmpty ifTrue:[
-	    selectionList makeVisible:contents
-	]
-    ]
-! !
-
-!FileSelectionBox methodsFor:'change & update'!
-
-update:something with:argument from:changedObject
-    |commonName index s|
+directory:directoryName
+    "change the directory shown in the list."
 
-    something == #directory ifTrue:[
-	"
-	 sent by fileNameEnterField, if a filename
-	 completion was not possible due to multiple
-	 matches.
-	"
-	selectionList directory:argument.
-	s := enterField contents.
-	s notNil ifTrue:[
-	    commonName := s asFilename baseName.
-	    commonName size > 0 ifTrue:[
-		index := selectionList list findFirst:[:entry | entry startsWith:commonName].
-		index ~~ 0 ifTrue:[
-		    selectionList makeLineVisible:index
-		]
-	    ]
-	]
-    ]
-! !
-
-!FileSelectionBox methodsFor:'user actions'!
-
-okPressed
-    "called for both on ok-press and on return-key"
-
-    |dir string fname|
-
-    string := enterField contents.
-    string notNil ifTrue:[
-	string := string withoutSeparators.
-	string asFilename isAbsolute ifTrue:[
-	    fname := string asFilename
-	] ifFalse:[
-	    dir := selectionList directory pathName asFilename.
-	    fname := dir construct:string
-	].
-	fname isDirectory ifTrue:[
-	    selectionList directory:fname asString.
-	    self updateList.
-	    ^ self
-	]
-    ].
-    super okPressed
+    selectionList directory:directoryName
 !
 
-selectionChanged
-    |entry|
-
-    entry := selectionList selectionValue.
-    enterField contents:entry
-!
-
-doubleClick
-    |entry|
-
-    entry := selectionList selectionValue.
-    entry notNil ifTrue:[
-	((selectionList directory typeOf:entry) == #directory) ifFalse:[
-	    enterField contents:entry.
-	    self okPressed
-	]
-    ].
-! !
-
-!FileSelectionBox methodsFor:'private'!
-
-updateList
-    selectionList updateList
-! !
-
-!FileSelectionBox methodsFor:'queries'!
+matchBlock:aBlock
+    "set the matchBlock (in the selectionList). Only files
+     for which the block returns true are shown.
+     The matching is actually done in the fileSelectionList."
 
-preferredExtent
-    "return my preferred extent - thats the minimum size 
-     to make everything visible"
-
-    |wWanted hWanted|
-
-    wWanted := ViewSpacing + 
-	       labelField preferredExtent x + 
-	       (ViewSpacing * 2) + 
-	       patternField preferredExtent x + 
-	       ViewSpacing.
-    (wWanted < width) ifTrue:[
-	wWanted := width
-    ].
-    hWanted := ViewSpacing + labelField height +
-	       ViewSpacing + enterField height +
-	       ViewSpacing + selectionList height +
-	       ViewSpacing + buttonPanel preferredExtent y +
-	       ViewSpacing.
-
-    (hWanted < height) ifTrue:[
-	hWanted := height
-    ].
-    ^ (wWanted @ hWanted)
-! !
-
-!FileSelectionBox methodsFor:'accessing'!
+    selectionList matchBlock:aBlock 
+!
 
 openOn:aPath
     "open the box showing files in aPath.
@@ -320,12 +175,6 @@
     self showAtPointer
 !
 
-directory:directoryName
-    "change the directory shown in the list."
-
-    selectionList directory:directoryName
-!
-
 pattern:aPattern
     "set the pattern - this also enables the PatternField
      (if the pattern is non-nil) or hides it (if nil)."
@@ -361,29 +210,181 @@
     windowGroup notNil ifTrue:[
 	windowGroup focusSequence:focusSequence
     ].
+! !
+
+!FileSelectionBox methodsFor:'change & update'!
+
+update:something with:argument from:changedObject
+    |commonName index s|
+
+    something == #directory ifTrue:[
+	"
+	 sent by fileNameEnterField, if a filename
+	 completion was not possible due to multiple
+	 matches.
+	"
+	selectionList directory:argument.
+	s := enterField contents.
+	s notNil ifTrue:[
+	    commonName := s asFilename baseName.
+	    commonName size > 0 ifTrue:[
+		index := selectionList list findFirst:[:entry | entry startsWith:commonName].
+		index ~~ 0 ifTrue:[
+		    selectionList makeLineVisible:index
+		]
+	    ]
+	]
+    ]
+! !
+
+!FileSelectionBox methodsFor:'initialization'!
+
+createEnterField
+    "if the (optional) class FilenameEditField is present, use
+     it, since it provides filename completion. Otherwise, we have
+     to live with the dump (default) field ...
+    "
+    FilenameEditField notNil ifTrue:[
+	^ FilenameEditField new.
+    ].
+    ^ super createEnterField
 !
 
-matchBlock:aBlock
-    "set the matchBlock (in the selectionList). Only files
-     for which the block returns true are shown.
-     The matching is actually done in the fileSelectionList."
+focusSequence
+    patternField shown ifTrue:[
+	^ Array 
+	    with:patternField 
+	    with:enterField 
+	    with:selectionList 
+	    with:abortButton
+	    with:okButton 
+    ].
+    ^ super focusSequence
+!
+
+initialize
+    |corner|
+
+    super initialize.
+
+    label := resources string:'File dialog'.
 
-    selectionList matchBlock:aBlock 
+    labelField extent:(0.7 @ labelField height).
+    labelField label:(resources string:'select a file:').
+    labelField adjust:#left.
+
+    patternField := EditField in:self.
+    self is3D ifTrue:[
+	corner := (1.0 @ (labelField origin y+patternField heightIncludingBorder)).
+    ] ifFalse:[
+	corner := [(width - ViewSpacing - (patternField borderWidth * 2)) @ (labelField origin y+patternField height"IncludingBorder")].
+    ].
+    patternField origin:(0.7 @ labelField origin y) corner:corner.
+    patternField rightInset:ViewSpacing.
+    patternField initialText:'*'.
+    patternField leaveAction:[:reason | 
+	selectionList pattern:patternField contents. 
+	self updateList
+    ].
+    patternField hiddenOnRealize:true. "delay showing, until a pattern is defined"
+
+    enterField addDependent:self.
+
+    "
+     FileSelectionBox open
+     FileSelectionBox new show
+    "
 !
 
-contents
-    "return the current entered value (i.e. the enterFields string).
-     redefined to return the full pathname."
+realize
+    "if some default is present in the enterField,
+     scroll to make this one visible"
+
+    |contents|
+
+    super realize.
+    (contents := enterField contents) notNil ifTrue:[
+	contents notEmpty ifTrue:[
+	    selectionList makeVisible:contents
+	]
+    ]
+! !
+
+!FileSelectionBox methodsFor:'private'!
+
+updateList
+    selectionList updateList
+! !
 
-    |string sep|
+!FileSelectionBox methodsFor:'queries'!
+
+preferredExtent
+    "return my preferred extent - thats the minimum size 
+     to make everything visible"
+
+    |wWanted hWanted|
+
+    wWanted := ViewSpacing + 
+	       labelField preferredExtent x + 
+	       (ViewSpacing * 2) + 
+	       patternField preferredExtent x + 
+	       ViewSpacing.
+    (wWanted < width) ifTrue:[
+	wWanted := width
+    ].
+    hWanted := ViewSpacing + labelField height +
+	       ViewSpacing + enterField height +
+	       ViewSpacing + selectionList height +
+	       ViewSpacing + buttonPanel preferredExtent y +
+	       ViewSpacing.
 
-    string := super contents.
-    string isNil ifTrue:[
-	^ selectionList directory pathName
+    (hWanted < height) ifTrue:[
+	hWanted := height
+    ].
+    ^ (wWanted @ hWanted)
+! !
+
+!FileSelectionBox methodsFor:'user actions'!
+
+doubleClick
+    |entry|
+
+    entry := selectionList selectionValue.
+    entry notNil ifTrue:[
+	((selectionList directory typeOf:entry) == #directory) ifFalse:[
+	    enterField contents:entry.
+	    self okPressed
+	]
     ].
-    sep := Filename separator.
-    (string startsWith:sep) ifTrue:[
-	^ string
+!
+
+okPressed
+    "called for both on ok-press and on return-key"
+
+    |dir string fname|
+
+    string := enterField contents.
+    string notNil ifTrue:[
+	string := string withoutSeparators.
+	string asFilename isAbsolute ifTrue:[
+	    fname := string asFilename
+	] ifFalse:[
+	    dir := selectionList directory pathName asFilename.
+	    fname := dir construct:string
+	].
+	fname isDirectory ifTrue:[
+	    selectionList directory:fname asString.
+	    self updateList.
+	    ^ self
+	]
     ].
-    ^ (selectionList directory pathName asFilename construct:string) asString
+    super okPressed
+!
+
+selectionChanged
+    |entry|
+
+    entry := selectionList selectionValue.
+    enterField contents:entry
 ! !
+