FBrowser.st
changeset 49 6fe62433cfa3
parent 47 94f7b0e07ff5
child 52 7b48409ae088
--- a/FBrowser.st	Fri Oct 28 04:30:49 1994 +0100
+++ b/FBrowser.st	Fri Oct 28 04:31:16 1994 +0100
@@ -26,7 +26,7 @@
 COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
 
-$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.18 1994-10-10 03:33:24 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.19 1994-10-28 03:29:30 claus Exp $
 '!
 
 !FileBrowser class methodsFor:'documentation'!
@@ -47,7 +47,7 @@
 
 version
 "
-$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.18 1994-10-10 03:33:24 claus Exp $
+$Header: /cvs/stx/stx/libtool/Attic/FBrowser.st,v 1.19 1994-10-28 03:29:30 claus Exp $
 "
 !
 
@@ -221,6 +221,7 @@
 				   'copy path'
 				   '-'                               
 				   'up'
+"/                                   'back'
 				   'change to home-directory'
 				   'change directory ...'
 				  ).             
@@ -229,6 +230,7 @@
 			copyPath
 			nil
 			changeToParentDirectory
+"/                        changeToPreviousDirectory
 			changeToHomeDirectory
 			changeCurrentDirectory
 		      ).
@@ -265,7 +267,9 @@
     fileListView  notNil ifTrue:[
 	labels := resources array:#(
 					   'spawn'                   
+					   '-'                               
 					   'get contents'                    
+					   'insert contents'                    
 					   'show info'             
 					   'show full info'          
 					   'fileIn'                 
@@ -273,6 +277,7 @@
 					   'update'                 
 					   '-'                               
 					   'execute unix command ...'                
+					   'st/x tools'                
 					   '-'                               
 					   'remove'                 
 					   'rename ...'                 
@@ -287,7 +292,9 @@
 	    middleButtonMenu:(PopUpMenu 
 				    labels:labels
 				 selectors:#(fileSpawn
+					     nil
 					     fileGet
+					     fileInsert
 					     fileGetInfo
 					     fileGetLongInfo
 					     fileFileIn
@@ -295,6 +302,7 @@
 					     updateCurrentDirectory
 					     nil
 					     fileExecute
+					     stxTools
 					     nil
 					     fileRemove
 					     fileRename
@@ -305,7 +313,20 @@
 					     newDirectory
 					     newFile)
 				  receiver:self
-				       for:fileListView)
+				       for:fileListView).
+
+	fileListView middleButtonMenu
+	    subMenuAt:#stxTools put:(PopUpMenu
+					labels:#(
+						 'Changes browser'
+						 'Editor '
+						)
+					selectors:#(
+						 openChangesBrowser
+						 openEditor
+						)
+					receiver:self
+					for:fileListView)
     ]
 ! !
 
@@ -349,7 +370,7 @@
 ask:question yesButton:yesButtonText action:aBlock
     "common method to ask a yes/no question"
 
-    self ask:question yesButton:yesButtonText noButton:'abort' action:aBlock
+    self ask:question yesButton:yesButtonText noButton:'cancel' action:aBlock
 !
 
 ask:question yesButton:yesButtonText noButton:noButtonText action:aBlock
@@ -357,10 +378,10 @@
 
     |yesNoBox|
 
-    yesNoBox := YesNoBox new.
-    yesNoBox title:question withCRs.
-    yesNoBox okText:(resources at:yesButtonText).
-    yesNoBox noText:(resources at:noButtonText).
+    yesNoBox := YesNoBox 
+		    title:question withCRs
+		  yesText:(resources at:yesButtonText)
+		   noText:(resources at:noButtonText).
     yesNoBox okAction:aBlock.
     yesNoBox showAtPointer
 !
@@ -395,18 +416,15 @@
 !
 
 getInfoFile
-    "get filename of a description-file (.dir.info);
-     uncomment stuff below if you want this to also
-     automatically show contents of README files."
+    "get filename of a description-file (.dir.info, README etc.);
+     This file is automatically shown when a directory is enterred.
+     You can add more names below if you like."
 
     #( '.dir.info'
-"you can add these if you like ..."
-"
        'README'
        'ReadMe'
        'Readme'
        'readme' 
-"
     ) do:[:f |
 	(currentDirectory isReadable:f) ifTrue:[^ f].
     ].
@@ -460,13 +478,7 @@
     type := info at:#type.
     (longInfo and:[type == #regular]) ifTrue:[
 	fullPath := currentDirectory pathName , '/' , fileName.
-	stream := PipeStream readingFrom:('file ' , fullPath).
-	stream notNil ifTrue:[
-	    fileOutput := stream contents asString.
-	    stream close.
-	    fileOutput := fileOutput copyFrom:(fileOutput indexOf:$:) + 1.
-	    fileOutput := fileOutput withoutSeparators
-	]
+	fileOutput := fullPath asFilename fileType.
     ].
 
     s := (resources at:'type:   ').
@@ -621,6 +633,20 @@
      prevUid prevGid nameString groupString matchPattern
      tabSpec|
 
+    "the code below may look somewhat complex -
+     it reads the directory first for the names,
+     then (in a second sweep over the files) gets the
+     files type and info. This makes the Filebrowsers
+     list update seem faster, since the fileInfo (i.e. stat-calls)
+     may take long - especially on NFS-mounted directories.
+     The file reading is done at lower priority, to let user continue
+     his work in other views. However, to be fair to other fileBrowser,
+     which may also read directories at low prio, give up the processor
+     after every entry. This shares the cpu among all fileBrowsers, so
+     that browsers reading short directories will finish first.
+     ST/X users love this behavior ;-)
+    "
+
     self withCursor:(Cursor read) do:[
 	Processor removeTimedBlock:checkBlock.
 
@@ -645,6 +671,7 @@
 	    ^ self
 	].
 	files := self withoutHiddenFiles:files.
+	fileList := files copy.
 
 	"
 	 this is a time consuming operation (especially, if reading an
@@ -652,28 +679,41 @@
 	 the files info ...
 	"
 	Processor activeProcess withLowerPriorityDo:[
-	    fileList := files.
-	    showLongList ifTrue:[
+
+	    "
+	     first show the names only - this is relatively fast
+	    "
+	    fileListView setList:files expandTabs:false.
 
-tabSpec := TabulatorSpecification new.
-tabSpec unit:#inch.
-tabSpec positions:#(0     2     2.3   4.3    5.3    6.0).
-"                   name  type  mode  owner  group                       "
-tabSpec align:    #(#left #left #left #right #right #decimal).
-
+	    "
+	     then walk over the files, adding more info
+	     (since we have to stat each file, this may take a while longer
+	    "
+	    showLongList ifTrue:[
+		tabSpec := TabulatorSpecification new.
+		tabSpec unit:#inch.
+"/                tabSpec positions:#(0     2     2.3   4.3    5.3    6.0      6.5).
+		tabSpec widths:     #(2     0.3   1.7     1      0.5  0.5      1"any").
+		"                   name  type  mode  owner  group  size     type"
+		tabSpec align:    #(#left #left #left #right #right #decimal #left).
 
 		text := OrderedCollection new.
-		files do:[:aFileName |
-|entry|
+		files keysAndValuesDo:[:lineIndex :aFileName |
+		    |entry col|
 
-entry := MultiColListEntry new.
-entry tabulatorSpecification:tabSpec.
+		    entry := MultiColListEntry new.
+		    entry tabulatorSpecification:tabSpec.
 
 		    "
 		     if multiple FileBrowsers are reading, let others
 		     make some progress too
 		    "
+		    windowGroup notNil ifTrue:[windowGroup processExposeEvents].
 		    Processor yield.
+		    "
+		     could be destroyed in the meanwhile ...
+		    "
+		    realized ifFalse:[^ self].
 
 		    len := aFileName size.
 		    (len < 20) ifTrue:[
@@ -682,72 +722,73 @@
 			"can happen on BSD only"
 			line := (aFileName copyTo:20) , '  '
 		    ].
-entry colAt:1 put:line.
+		    entry colAt:1 put:line.
 
 		    info := currentDirectory infoOf:aFileName.
 		    info isNil ifTrue:[
 			"not accessable - usually a symlink,
-			 which is not there/not readable
+			 to a nonexisting/nonreadable file
 			"
-			text add:line , '?  bad symbolic link'.
-entry colAt:2 put:'?'.
-entry colAt:3 put:'bad symbolic link'.
+			entry colAt:2 put:'?'.
+			entry colAt:3 put:'(bad symbolic link ?)'.
 		    ] ifFalse:[
 			typ := (info at:#type) at:1.
 			(typ == $r) ifFalse:[
-			    line := line , typ asString , '  '.
-entry colAt:2 put:typ asString.
+			    entry colAt:2 put:typ asString.
 			] ifTrue:[
-			    line := line , '   '.
-entry colAt:2 put:' '.
+			    entry colAt:2 put:' '.
 			].
 
 			modeString := self getModeString:(info at:#mode)
 						    with:#( '' $r $w $x 
 							    '  ' $r $w $x 
 							    '  ' $r $w $x ).
-entry colAt:3 put:modeString.
-			line := line , modeString , '  '.
+			entry colAt:3 put:modeString.
 
 			((info at:#uid) ~~ prevUid) ifTrue:[
 			    prevUid := (info at:#uid).
 			    nameString := OperatingSystem getUserNameFromID:prevUid.
 			    nameString := nameString , (String new:(10 - nameString size))
 			].
-entry colAt:4 put:nameString withoutSpaces.
-			line := line , nameString.
+			entry colAt:4 put:nameString withoutSpaces.
 			((info at:#gid) ~~ prevGid) ifTrue:[
 			    prevGid := (info at:#gid).
 			    groupString := OperatingSystem getGroupNameFromID:prevGid.
 			    groupString := groupString , (String new:(10 - groupString size))
 			].
-entry colAt:5 put:groupString withoutSpaces.
-			line := line , groupString.
+			entry colAt:5 put:groupString withoutSpaces.
 
 			(typ == $r) ifTrue:[
-			    line := line , (self sizePrintString:(info at:#size)) , ' '.
-entry colAt:6 put:(self sizePrintString:(info at:#size)).
+			    entry colAt:6 put:(self sizePrintString:(info at:#size)).
 			].
-text add:entry
-"/                        text add:line
+
+			entry colAt:7 put:(currentDirectory asFilename:aFileName) fileType.
+
+			text add:entry
 		    ].
+		    fileListView at:lineIndex put:entry
 		].
 	    ] ifFalse:[
-		text := files collect:[:aName |
+		files keysAndValuesDo:[:lineIndex :aName |
+		    |entry|
+
 		    "
 		     if multiple FileBrowsers are reading, let others
 		     make some progress too
 		    "
+		    windowGroup notNil ifTrue:[windowGroup processExposeEvents].
 		    Processor yield.
+		    realized ifFalse:[^ self].
+
 		    (((currentDirectory typeOf:aName) == #directory) and:[
 		    (aName ~= '..') and:[aName ~= '.']]) ifTrue:[
-			aName , ' ...'
+			entry := aName , ' ...'
 		    ] ifFalse:[
-			aName
-		    ]
+			entry := aName
+		    ].
+		    fileListView at:lineIndex put:entry
 		].
 	    ].
-	    fileListView setList:text expandTabs:false
 	].
 
 	"
@@ -761,9 +802,9 @@
     "verify argument is name of a readable & executable directory
      and if so, go there"
 
-    |msg|
+    |msg path|
 
-    self label:myName.
+    self label:myName; iconLabel:myName.
     fileName notNil ifTrue:[
 	(currentDirectory isDirectory:fileName) ifTrue:[
 	    (currentDirectory isReadable:fileName) ifTrue:[
@@ -782,15 +823,23 @@
 
 		    self setCurrentDirectory:fileName.
 
-"/ its better to do it on entry
+"/ its better to do it when directories are entered
 "/
 		    updateHistory ifTrue:[
-			(DirectoryHistory includes:(currentDirectory pathName)) ifFalse:[
-			    DirectoryHistory addFirst:currentDirectory pathName.
+			path := currentDirectory pathName.
+			(DirectoryHistory includes:path) ifFalse:[
+			    DirectoryHistory addFirst:path.
 			    DirectoryHistory size > HistorySize ifTrue:[
 				DirectoryHistory removeLast
 			    ].
 			    DirectoryHistory changed.
+			] ifTrue:[
+			    "already been there before; move the entry to
+			     the end, so it will fall out later."
+
+			    DirectoryHistory remove:path.
+			    DirectoryHistory addFirst:path.
+			    DirectoryHistory changed.
 			]
 		    ].
 		    ^ self
@@ -869,7 +918,7 @@
 
     "for very big files, give ObjectMemory a hint, to preallocate more"
     (sz := stream size) > 1000000 ifTrue:[
-	ObjectMemory moreOldSpace:sz
+	ObjectMemory moreOldSpace:(sz + (sz // 5)) "/ add 20% for tab expansion
     ].
 
     text := self readStream:stream lineDelimiter:aCharacter.
@@ -969,14 +1018,14 @@
     ]
 !
 
-showFile:fileName
-    "show contents of fileName in subView"
+showFile:fileName insert:insert
+    "show/insert contents of fileName in subView"
 
-    |buffer s n i ok convert|
+    |buffer s n i ok convert text|
 
     ((currentDirectory typeOf:fileName) == #regular) ifFalse:[
 	"clicked on something else - ignore it ..."
-	self show:(resources string:'''%1'' is not a regular file' with:fileName).
+	self warn:(resources string:'''%1'' is not a regular file' with:fileName).
 	^ self
     ].
     "
@@ -1019,15 +1068,23 @@
 	]
     ].
 
-    "release old text first - we might need the memory in case of huge files
-     (helps if you have a 4Mb file in the view, and click on another biggy)"
-    subView contents:nil.
+    insert ifFalse:[
+	"release old text first - we might need the memory in case of huge files
+	 (helps if you have a 4Mb file in the view, and click on another biggy)"
+	subView contents:nil.
+    ].
 
     convert ifTrue:[
-	self show:(self readFile:fileName lineDelimiter:(Character value:13))
+	text := self readFile:fileName lineDelimiter:(Character value:13)
     ] ifFalse:[
-	self show:(self readFile:fileName).
+	text := self readFile:fileName.
     ].
+    insert ifFalse:[
+	self show:text
+    ] ifTrue:[
+	subView insertSelectedStringAtCursor:text asString
+    ].
+
     subView acceptAction:[:theCode |
 	self writeFile:fileName text:theCode
     ]
@@ -1051,14 +1108,16 @@
 	fileName notNil ifTrue:[
 	    (currentDirectory isDirectory:fileName) ifTrue:[
 		self doChangeCurrentDirectoryTo:fileName updateHistory:true.
-		self label:myName
+		self label:myName.
+		self iconLabel:myName
 	    ] ifFalse:[
-		self showFile:fileName.
+		self showFile:fileName insert:false.
 		(currentDirectory isWritable:fileName) ifFalse:[
 		    self label:(myName , ': ' , fileName , ' (readonly)')
 		] ifTrue:[
 		    self label:(myName , ': ' , fileName)
-		]
+		].
+		self iconLabel:fileName
 	    ]
 	]
     ]
@@ -1172,7 +1231,7 @@
     ] valueNowOrOnUnwindDo:[
 	|wg|
 
-	self label:myName.
+	self label:myName; iconLabel:myName.
 	myProcess notNil ifTrue:[myProcess priority:myPriority].
 
 	"
@@ -1386,7 +1445,118 @@
     self warn:'exactly one file must be selected !!'
 ! !
 
-!FileBrowser methodsFor:'user interaction'!
+!FileBrowser methodsFor:'user interaction - misc'!
+
+terminate
+    "exit FileBrowser"
+
+    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.') withCRs
+	 yesButton:(resources at:'close')
+	 action:[self destroy]
+!
+
+destroy
+    "destroy view and boxes"
+
+    ObjectMemory removeDependent:self.
+    Processor removeTimedBlock:checkBlock.
+    checkBlock := nil.
+    DirectoryHistory removeDependent:self.
+    super destroy
+!
+
+update:what with:someArgument from:changedObject
+    (what == #aboutToExit) ifTrue:[
+	"system wants to shut down this
+	 - if text was modified, pop up, and ask user and save if requested."
+
+	(subView modified and:[subView contentsWasSaved not]) ifTrue:[
+	    shown ifFalse:[
+		self unrealize.
+		self realize
+	    ].
+	    self raise.
+	    "
+	     mhmh: I dont like this - need some way to tell windowGroup to handle
+	     all pending exposures ...
+	    "
+	    self withAllSubViewsDo:[:view | view redraw].
+
+	    self ask:(resources at:'FileBrowser:\\contents has not been saved.\\Save before exiting ?') withCRs
+		 yesButton:'save'
+		 noButton:'don''t save'
+		 action:[
+			subView acceptAction notNil ifTrue:[
+			    subView accept
+			] ifFalse:[
+			    subView save
+			]
+		    ]
+	].
+	^ self
+    ].
+    changedObject == DirectoryHistory ifTrue:[
+	self initializeLabelMiddleButtonMenu.
+	^ self
+    ].
+! !
+
+!FileBrowser methodsFor:'user interaction - pathField'!
+
+copyPath
+    "copy current path into cut & paste buffer"
+
+    Smalltalk at:#CopyBuffer put:currentDirectory pathName
+!
+
+changeDirectoryTo:aDirectoryName
+    "sent from label menu to change back to a previous directory"
+
+    self doChangeCurrentDirectoryTo:aDirectoryName updateHistory:false
+!
+
+changeCurrentDirectory
+    "if text was modified show a queryBox, 
+     otherwise change immediately to directory"
+
+    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.') withCRs
+	 yesButton:(resources at:'change')
+	 action:[self queryForDirectoryToChange]
+!
+
+changeToParentDirectory
+    "if text was modified show a queryBox, 
+     otherwise change immediately to directory"
+
+    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.') withCRs
+	 yesButton:(resources at:'change')
+	 action:[self doChangeToParentDirectory]
+!
+
+changeToHomeDirectory
+    "if text was modified show a queryBox, 
+     otherwise change immediately to directory"
+
+    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.') withCRs
+	 yesButton:(resources at:'change')
+	 action:[self doChangeToHomeDirectory]
+!
+
+queryForDirectoryToChange
+    "query for new directory"
+
+    |queryBox|
+
+    queryBox := FilenameEnterBox new.
+    queryBox initialText:''.
+    queryBox title:(resources at:'change directory to:') withCRs.
+    queryBox okText:(resources at:'change').
+    "queryBox abortText:(resources at:'abort')."
+    queryBox action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
+    queryBox showAtPointer
+! !
+
+!FileBrowser methodsFor:'user interaction - fileList'!
 
 fileSpawn
     "start another FileBrowser on the selected directory or
@@ -1406,12 +1576,6 @@
     ]
 !
 
-copyPath
-    "copy current path into cut & paste buffer"
-
-    Smalltalk at:#CopyBuffer put:(currentDirectory pathName)
-!
-
 fileExecute
     "if text was modified show a queryBox,
      otherwise pop up execute box immediately"
@@ -1436,13 +1600,43 @@
     ]
 !
 
+openChangesBrowser
+    "open a change browser on the selected file(s)"
+
+    self selectedFilesDo:[:fileName |
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    ChangesBrowser openOn:(currentDirectory pathName , '/' , fileName).
+	]
+    ].
+!
+
+openEditor
+    self selectedFilesDo:[:fileName |
+	(currentDirectory isDirectory:fileName) ifFalse:[
+	    EditTextView openOn:(currentDirectory pathName , '/' , fileName).
+	]
+    ].
+!
+
 fileSelect:lineNr
     "selected a file - do nothing here"
     ^ self
 !
 
+fileInsert
+    "insert contents of file at cursor"
+
+    |fileName|
+
+    fileName := self getSelectedFileName.
+    fileName notNil ifTrue:[
+	self showFile:fileName insert:true
+    ]
+!
+
 fileGet
-    "if text was modified show a queryBox,
+    "get contents of selected file into subView.
+     If text was modified show a queryBox,
      otherwise get it immediately"
 
     |fileName msg label|
@@ -1589,107 +1783,6 @@
     ]
 !
 
-terminate
-    "exit FileBrowser"
-
-    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when FileBrowser is closed.') withCRs
-	 yesButton:(resources at:'close')
-	 action:[self destroy]
-!
-
-destroy
-    "destroy view and boxes"
-
-    ObjectMemory removeDependent:self.
-    Processor removeTimedBlock:checkBlock.
-    checkBlock := nil.
-    DirectoryHistory removeDependent:self.
-    super destroy
-!
-
-update:what with:someArgument from:changedObject
-    (what == #aboutToExit) ifTrue:[
-	"system wants to shut down this
-	 - if text was modified, pop up, and ask user and save if requested."
-
-	(subView modified and:[subView contentsWasSaved not]) ifTrue:[
-	    shown ifFalse:[
-		self unrealize.
-		self realize
-	    ].
-	    self raise.
-	    "
-	     mhmh: I dont like this - need some way to tell windowGroup to handle
-	     all pending exposures ...
-	    "
-	    self withAllSubViewsDo:[:view | view redraw].
-
-	    self ask:(resources at:'FileBrowser:\\contents has not been saved.\\Save before exiting ?') withCRs
-		 yesButton:'save'
-		 noButton:'don''t save'
-		 action:[
-			subView acceptAction notNil ifTrue:[
-			    subView accept
-			] ifFalse:[
-			    subView save
-			]
-		    ]
-	].
-	^ self
-    ].
-    changedObject == DirectoryHistory ifTrue:[
-	self initializeLabelMiddleButtonMenu.
-	^ self
-    ].
-!
-
-changeDirectoryTo:aDirectoryName
-    "sent from label menu to change back to a previous directory"
-
-    self doChangeCurrentDirectoryTo:aDirectoryName updateHistory:false
-!
-
-changeCurrentDirectory
-    "if text was modified show a queryBox, 
-     otherwise change immediately to directory"
-
-    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.') withCRs
-	 yesButton:(resources at:'change')
-	 action:[self queryForDirectoryToChange]
-!
-
-changeToParentDirectory
-    "if text was modified show a queryBox, 
-     otherwise change immediately to directory"
-
-    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.') withCRs
-	 yesButton:(resources at:'change')
-	 action:[self doChangeToParentDirectory]
-!
-
-changeToHomeDirectory
-    "if text was modified show a queryBox, 
-     otherwise change immediately to directory"
-
-    self askIfModified:(resources at:'contents has not been saved.\\Modifications will be lost when directory is changed.') withCRs
-	 yesButton:(resources at:'change')
-	 action:[self doChangeToHomeDirectory]
-!
-
-queryForDirectoryToChange
-    "query for new directory"
-
-    |queryBox|
-
-    queryBox := FilenameEnterBox new.
-    queryBox initialText:''.
-    queryBox title:(resources at:'change directory to:') withCRs.
-    queryBox okText:(resources at:'change').
-    "queryBox abortText:(resources at:'abort')."
-    queryBox action:[:newName | self doChangeCurrentDirectoryTo:newName updateHistory:true].
-    queryBox showAtPointer
-!
-
 fileGetInfo:longInfo
     "get info on selected file - show it in a box"
 
@@ -1702,13 +1795,13 @@
 !
 
 fileGetLongInfo
-    "triggered by menu: show long stat-info"
+    "show long stat (file)-info"
 
     self fileGetInfo:true
 !
 
 fileGetInfo
-    "triggered by menu: show short stat-info"
+    "show short file (stat)-info"
 
     self fileGetInfo:false
 !