FileBrowser.st
changeset 132 9bf0c15113f2
parent 126 fca75dda31db
child 133 fa9a37e36a07
--- a/FileBrowser.st	Thu Aug 31 15:26:53 1995 +0200
+++ b/FileBrowser.st	Thu Sep 07 14:53:52 1995 +0200
@@ -17,8 +17,9 @@
 		fileList checkBlock checkDelta timeOfLastCheck showLongList
 		showVeryLongList showDotFiles myName killButton compressTabs
 		lockUpdate previousDirectory currentFileName timeOfFileRead
-		tabSpec'
-	 classVariableNames:'DirectoryHistory DirectoryHistoryWhere HistorySize DefaultIcon'
+		tabSpec commandView commandIndex'
+	 classVariableNames:'DirectoryHistory DirectoryHistoryWhere HistorySize DefaultIcon
+			     CommandHistory CommandHistorySize'
 	 poolDictionaries:''
 	 category:'Interface-Browsers'
 !
@@ -27,7 +28,7 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.47 1995-08-29 23:46:46 claus Exp $
+$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.48 1995-09-07 12:53:25 claus Exp $
 '!
 
 !FileBrowser class methodsFor:'documentation'!
@@ -48,7 +49,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.47 1995-08-29 23:46:46 claus Exp $
+$Header: /cvs/stx/stx/libtool/FileBrowser.st,v 1.48 1995-09-07 12:53:25 claus Exp $
 "
 !
 
@@ -161,11 +162,16 @@
 
     lockUpdate := false.
 
+    CommandHistory isNil ifTrue:[
+	CommandHistory := OrderedCollection new.
+	CommandHistorySize := 50
+    ].
     DirectoryHistory isNil ifTrue:[
 	DirectoryHistory := OrderedCollection new.
 	DirectoryHistoryWhere := OrderedCollection new.
 	HistorySize := 15.
     ].
+    commandIndex := 0.
 
     myName := (resources string:self class name).
     self label:myName.
@@ -212,14 +218,22 @@
 	       extent:(killButton width @ filterField height).
     killButton hiddenOnRealize:true.
 
-    frame := VariableVerticalPanel
-		 origin:[frame borderWidth negated 
-			 @ 
-			 labelFrame height
-			 "/ (labelView height + labelView origin y + spacing)
-			]
-		 corner:(1.0 @ 1.0)
-		     in:self.
+    self initializeCommandViewIn:self.
+
+"/    frame := VariableVerticalPanel
+"/                 origin:[frame borderWidth negated 
+"/                         @ 
+"/                         labelFrame height
+"/                         "/ (labelView height + labelView origin y + spacing)
+"/                        ]
+"/                 corner:(1.0 @ 1.0)
+"/                     in:self.
+
+    frame := VariableVerticalPanel origin:0.0@0.0 corner:1.0@1.0 in:self.
+    frame topInset:labelFrame height.
+    commandView notNil ifTrue:[
+	frame bottomInset:(commandView height + spacing)
+    ].
 
     topFrame := ScrollableView for:SelectionInListView in:frame.
     topFrame origin:(0.0 @ 0.0) corner:(1.0 @ 0.3).
@@ -232,6 +246,7 @@
     fileListView menuHolder:self; menuPerformer:self; menuMessage:#fileListMenu.
 
     v := self initializeSubViewIn:frame.
+
     v origin:(0.0 @ 0.3) corner:(1.0 @ 1.0).
     subView := v scrolledView.
     (subView respondsTo:#directoryForFileDialog:) ifTrue:[
@@ -239,6 +254,8 @@
     ].
 
     ObjectMemory addDependent:self.
+
+    "Modified: 6.9.1995 / 20:26:06 / claus"
 !
 
 initializeFilterPattern
@@ -259,6 +276,77 @@
     ^ HVScrollableView for:CodeView miniScrollerH:true miniScrollerV:false in:frame.
 !
 
+initializeCommandViewIn:frame
+    "set up the command view - can be redefined in subclasses as empty,
+     if no commandView is wanted"
+
+
+    commandView := EditField origin:0.0@1.0 corner:1.0@1.0 in:frame.
+    commandView topInset:(commandView preferredExtent y negated - ViewSpacing).
+    commandView bottomInset:ViewSpacing.
+    commandView horizontalInset:ViewSpacing.
+
+    commandView contents:'** no commands which require input here **'.
+
+    commandView entryCompletionBlock:[
+	FilenameEditField filenameCompletionBlock 
+		value:commandView
+		value:currentDirectory pathName asFilename
+		value:false
+		value:false
+    ].
+    commandView leaveAction:[:key | 
+	|cmd nCmd empty|
+
+	(key == #CursorDown 
+	or:[key == #CursorUp]) ifTrue:[
+            nCmd := CommandHistory size.
+            nCmd == 0 ifTrue:[
+                empty := true
+            ] ifFalse:[
+                key == #CursorUp ifTrue:[
+                    commandIndex == nCmd ifTrue:[
+                        commandView flash.
+                    ].
+                    commandIndex := (commandIndex + 1) min:nCmd
+                ] ifFalse:[
+                    commandIndex == 1 ifTrue:[
+                        commandView flash.
+                        empty := true.
+                    ].
+                    commandIndex := (commandIndex - 1) max:1.
+                ].
+            ].
+            empty == true ifTrue:[
+                commandView contents:nil
+            ] ifFalse:[
+                commandView contents:(CommandHistory at:commandIndex).
+            ]        
+	].
+	key == #Return ifTrue:[
+	    cmd := commandView contents.
+
+	    subView insertStringAtCursor:'>> '.
+	    subView insertStringAtCursor:cmd.
+	    subView insertCharAtCursor:(Character cr).
+
+	    (cmd notNil and:[cmd notEmpty]) ifTrue:[
+		CommandHistory notNil ifTrue:[
+		    CommandHistory addFirst:cmd.
+		    CommandHistory size > CommandHistorySize ifTrue:[
+			CommandHistory removeLast
+		    ]
+		].
+		self doExecuteCommand:cmd replace:false.
+		commandView contents:nil.
+		commandIndex := 0
+	    ]
+	]
+    ].
+
+    "Modified: 7.9.1995 / 11:43:55 / claus"
+!
+
 currentDirectory:aDirectoryPath
     "set the directory to be browsed"
 
@@ -276,7 +364,17 @@
 focusSequence
     "return the sequence in which ALT-CursorRight steps focus"
 
-    ^ Array with:filterField with:fileListView with:subView
+    |fs|
+
+    fs := Array 
+	with:filterField 
+	with:fileListView 
+	with:subView.
+
+    commandView notNil ifTrue:[
+	fs := fs copyWith:commandView
+    ].
+    ^fs
 ! !
 
 !FileBrowser methodsFor:'events'!
@@ -320,6 +418,9 @@
     aComponent == labelView ifTrue:[
 	s := 'HELP_PATHFIELD'
     ].
+    aComponent == commandView ifTrue:[
+	s := 'HELP_COMMANDVIEW'
+    ].
     s notNil ifTrue:[
 	^ resources string:s
     ].
@@ -1301,7 +1402,7 @@
 		myProcess priority:(Processor userBackgroundPriority).
 
 		[
-		    |codeView|
+		    |codeView lines|
 
 		    codeView := subView.
 
@@ -1315,7 +1416,16 @@
 			    "
 			     data available
 			    "
+			    lines := OrderedCollection new:50.
 			    line := stream nextLine.
+			    line notNil ifTrue:[lines add:line].
+
+			    [stream atEnd not
+			    and:[stream canReadWithoutBlocking
+			    and:[lines size < 50]]] whileTrue:[
+				line := stream nextLine.
+				line notNil ifTrue:[lines add:line].
+			    ].
 
 			    "
 			     need this critical section; otherwise,
@@ -1323,15 +1433,22 @@
 			     an expose event ...
 			    "
 			    access critical:[                        
-				line notNil ifTrue:[
-				    line := line withTabsExpanded.
+				lines size > 0 ifTrue:[
 				    replace ifTrue:[
-					codeView at:lnr put:line.
-					codeView cursorToBottom; cursorDown.
-					lnr := lnr + 1.
+					lines do:[:line |
+					    codeView at:lnr put:line withTabsExpanded.
+					    codeView cursorToBottom; cursorDown.
+					    lnr := lnr + 1.
+					].
 				    ] ifFalse:[
-					codeView insertStringAtCursor:line.
-					codeView insertCharAtCursor:(Character cr).
+codeView insertLines:lines before:codeView cursorLine.
+codeView cursorDown:lines size.
+"/ lines do:[:line |
+"/     codeView insertLine:line withTabsExpanded before:codeView cursorLine.
+"/     codeView cursorDown.
+"/ ]
+"/                                        codeView insertStringAtCursor:line.
+"/                                        codeView insertCharAtCursor:(Character cr).
 				    ]
 				].
 			    ].
@@ -1383,7 +1500,13 @@
 	 releases reference to thisContext earlier)
 	"
 	killButton action:nil.
+    ].
+
+    subView size > 10000 ifTrue:[
+	self warn:'text quite large now - please cut off some lines'
     ]
+
+    "Modified: 6.9.1995 / 20:56:15 / claus"
 !
 
 initialCommandFor:fileName into:aBox
@@ -1493,7 +1616,10 @@
     fileName notNil ifTrue:[
 	self initialCommandFor:fileName into:box.
     ].
+    box directory:currentDirectory pathName asFilename.
     box showAtPointer
+
+    "Modified: 7.9.1995 / 10:31:54 / claus"
 !
 
 selectedFilesDo:aBlock
@@ -1964,7 +2090,7 @@
 fileFileInLazy:lazy
     "fileIn the selected file(s)"
 
-    |aStream upd here oldPath wasLazy|
+    |aStream here oldPath wasLazy|
 
     self selectedFilesDo:[:fileName |
 	((currentDirectory typeOf:fileName) == #regular) ifTrue:[
@@ -1979,16 +2105,16 @@
 	    ] ifFalse:[
 		aStream := FileStream readonlyFileNamed:fileName in:currentDirectory.
 		aStream isNil ifFalse:[
-		    upd := Class updateChanges:false.
 		    [
-			oldPath := Smalltalk systemPath.
-			Smalltalk systemPath:(oldPath copy addFirst:here; yourself).
-			wasLazy := Compiler compileLazy:lazy.
-			aStream fileIn.
+			Class withoutUpdatingChangesDo:[
+			    oldPath := Smalltalk systemPath.
+			    Smalltalk systemPath:(oldPath copy addFirst:here; yourself).
+			    wasLazy := Compiler compileLazy:lazy.
+			    aStream fileIn.
+			]
 		    ] valueNowOrOnUnwindDo:[
 			Compiler compileLazy:wasLazy.
 			Smalltalk systemPath:oldPath.
-			Class updateChanges:upd.
 			aStream close
 		    ]
 		]