[net.lang.st80] Filename expansion goodie -- makes "file lists" useful

rentsch@unc.UUCP (Tim Rentsch) (02/12/86)

Here is a Smalltalk goodie ("hack" might be a better word) to do
filename expansion.   (Ever been frustrated by not being able to
type a general file spec into a file list?  Well, in the interpreter
we have here it doesn't work.)  Note: although this code is kind of
crocky, it does have the pleasant attribute that it makes "file
lists" accept file specifications rather than just names.

============================CUT HERE====================================
'From Smalltalk-80,
	version 2,
	of April 1, 1983 on 12 January 1986 at 10:26:33 pm'!


!String reorganize!
('comparing' < <= > >= hash hashMappedBy: match: sameAs: spellAgainst:)
('accessing' at: at:put: basicAt: basicAt:put: findString:startingAt: replaceFrom:to:with:startingAt: replaceFrom:to:withByteArray:startingAt: size string)
('enumerating' lexemesDo:)
('copying' copyUpTo: deepCopy)
('printing' isLiteral printOn: storeOn:)
('converting' asDisplayText asFileName asLowercase asNumber asParagraph asString asSymbol asText asUnixCommand asUppercase contractTo: oldRunDecodeOn: oldRunEncoded withCRs)
('displaying' displayAt: displayOn:at:)
('private' compare: primReplaceFrom:to:with:startingAt: stringhash)
('primitive' system)
!



!String methodsFor: 'enumerating'!

lexemesDo: aBlock
	"do aBlock for each lexeme I contain.
		Preliminary version -- 'lexemes' are between blanks.
		Done January 12, 1986  by Tim Rentsch"

	| sz bl pos nextBlank |
	sz _ self size.
	bl _ $ .
	pos _ 1.
	[ pos < sz  &  ( ( self at: pos ) = bl ) ] whileTrue:
		[ pos _ pos + 1 ].

	[ pos < sz ] whileTrue: [
		nextBlank _ self findString: ' ' startingAt: pos.
		nextBlank = 0 ifTrue: [ nextBlank _ sz + 1 ].
		aBlock value: ( self copyFrom: pos to: nextBlank - 1 ).
		pos _ nextBlank.
		[ pos < sz  &  ( ( self at: pos ) = bl ) ] whileTrue:
			[ pos _ pos + 1 ].

	].! !


!UnixFileDirectory methodsFor: 'file accessing'!

filesMatching: pattern 
	"Answer an Array of the names of files that match the string, pattern.
		Needs de-crocking.  
		January 12, 1986  by Tim Rentsch"
	| names name namesString dirPre |
	names _ WriteStream on: (Array new: 10).
	dirPre _ directoryName = '.'
		ifTrue: [ '' ]
		ifFalse: [ directoryName , '/' ].
	namesString _ ( 'echo ' , dirPre , pattern ) asUnixCommand unixIt.
	namesString = 'echo: No match. ' ifFalse: [
		namesString lexemesDo: [ :word | names nextPut: word ]
	].
	^names contents! !