Sending attachments to the Squeak list -- a better way!

Henrik Gedenryd Henrik.Gedenryd at lucs.lu.se
Sun Sep 3 13:32:00 UTC 2000


Duane,

this is a useful submisson. However, I would prefer if you made a couple of
changes. Could you add an extra menu item with a compress option, or 95% of
the people won't realize it is there I think. (perhaps the preference
becomes redundant too then?), and use the standard suffix .cs.gz instead of
a new, potentially confusing one? (assuming that unzipping them yields a .gz
file)

How about it? Myself I am compiling 95 submissions from this summer for
release as updates... Your phone stuff is in the pipeline!

thanks in advance,
Henrik

-------------- next part --------------
'From Squeak2.8 of 13 June 2000 [latest update: #2359] on 25 August 2000 at
5:15:00 pm'!
"Change Set:		GZipChangeSets
Date:			25 August 2000
Author:			Duane Maxwell/exobox

This change set adds the ability to file in/out change sets that are
compressed with GZip.  The output of compressed change sets is controlled
by the preference #changeSetCompressed.  The FileList and ChangeSet
browsers have been modified to directly understand the compressed change
set files, stored with the extension '.csz'.

Submitted by Duane Maxwell/exobox"!


!ChangeSet methodsFor: 'fileIn/Out' stamp: 'DSM 8/25/2000 17:11'!
fileOut
	"File out the receiver, to a file whose name is a function of the
change-set name and either of the date & time or chosen to have a unique
numeric tag, depending on the preference
'sequentialChangeSetRevertableFileNames'.  The file will be compressed
depending upon the preference 'changeSetCompressed'"

	| file slips nameToUse extension compressed zip |

	compressed _ Preferences changeSetCompressed.
	extension _ compressed ifTrue: [ 'csz' ] ifFalse: [ 'cs' ].
	self checkForConversionMethods.
	nameToUse _ Preferences changeSetVersionNumbers
		ifTrue:
			[FileDirectory default nextNameFor: self name
extension: extension]
		ifFalse:
			[(self name, FileDirectory dot, Utilities
dateTimeSuffix,
				FileDirectory dot, extension) asFileName].
	Cursor write showWhile:
		[file _ FileStream newFileNamed: nameToUse.
		compressed
			ifTrue: [
				zip _ GZipWriteStream on: file.
				"dsm: Some weirdness here due to need for
Stream refactoring"
				zip nextPutAll: ((ReadWriteStream on:
String new) header; timeStamp) contents.
				self fileOutPreambleOn: zip.
				self fileOutOn: zip.
				self fileOutPostscriptOn: zip.
				zip close.
				]
			ifFalse: [
				file header; timeStamp.
				self fileOutPreambleOn: file.
				self fileOutOn: file.
				self fileOutPostscriptOn: file.
				file trailer].
		file close].

	Preferences suppressCheckForSlips ifTrue: [^ self].

	slips _ self checkForSlips.
	(slips size > 0 and: [self confirm: 'Methods in this fileOut have halts
or references to the Transcript
or other ''slips'' in them.
Would you like to browse them?'])
		ifTrue: [Smalltalk browseMessageList: slips
							name: 'Possible
slips in ', name]! !


!FileList methodsFor: 'file list menu' stamp: 'DSM 8/25/2000 17:09'!
fileAllIn
	"File in all of the currently selected file, if any."
	"wod 5/24/1998: open the file read only."
	"dsm 8/25/00: support compressed files."

	| fn ff |
	listIndex = 0 ifTrue: [^ self].
	ff _ directory readOnlyFileNamed: (fn _ self uncompressedFileName).
	((self getSuffix: fn) sameAs: 'html') ifTrue: [ff _ ff asHtml].
	((self getSuffix: fn) sameAs: 'csz') ifTrue: [
		ff _ (GZipReadStream on: ff) upToEnd.
		ff _ ReadWriteStream on: ff from: 1 to: ff size].
	ff fileIn! !

!FileList methodsFor: 'file list menu' stamp: 'DSM 8/25/2000 17:07'!
fileIntoNewChangeSet
	"File in all of the contents of the currently selected file,
	if any, into a new change set."
	"dsm 8/24/00: support compressed files."

	| fn ff |
	listIndex = 0 ifTrue: [^ self].
	ff _ directory readOnlyFileNamed: (fn _ self uncompressedFileName).
	((self getSuffix: fn) sameAs: 'html') ifTrue: [ff _ ff asHtml].
	((self getSuffix: fn) sameAs: 'csz') ifTrue: [
		ff _ (GZipReadStream on: ff) upToEnd.
		ff _ ReadWriteStream on: ff from: 1 to: ff size].
	ChangeSorter newChangesFromStream: ff named: (FileDirectory
localNameFor: fn)! !

!FileList methodsFor: 'file list menu' stamp: 'DSM 8/25/2000 14:33'!
itemsForFileEnding: suffix
	| labels lines selectors |
	labels _ OrderedCollection new.
	lines _ OrderedCollection new.
	selectors _ OrderedCollection new.
	(suffix = 'bmp') | (suffix = 'gif') | (suffix = 'jpg') | (suffix
='form') | (suffix = '*') | (suffix = 'png') ifTrue:
		[labels addAll: #('open image in a window' 'read image into
ImageImports' 'open image as background').
		selectors addAll: #(openImageInWindow importImage
openAsBackground)].
	(suffix = 'morph') | (suffix = 'morphs') | (suffix = 'sp') |
(suffix = '*') ifTrue:
		[labels add: 'load as morph'.
		selectors add: #openMorphFromFile.
		labels add: 'load as project'.
		selectors add: #openProjectFromFile].
	(suffix = 'extseg') | (suffix = 'project') | (suffix = 'pr') ifTrue:
		[labels add: 'load as project'.
		selectors add: #openProjectFromFile].
	(suffix = 'bo') | (suffix = '*') ifTrue:[
		labels add: 'load as book'.
		selectors add: #openBookFromFile].
	(suffix = 'mid') | (suffix = '*') ifTrue:
		[labels add: 'play midi file'.
		selectors add: #playMidiFile].
	(suffix = 'movie') | (suffix = '*') ifTrue:
		[labels add: 'open as movie'.
		selectors add: #openAsMovie].
	(suffix = 'st') | (suffix = 'cs') | (suffix = 'csz') | (suffix =
'*') ifTrue:
		[suffix = '*' ifTrue: [lines add: labels size].
		labels addAll: #('fileIn' 'file into new change set'
'browse changes' 'browse code' 'remove line feeds' 'broadcast as update').
		lines add: labels size - 1.
		selectors addAll: #(fileInSelection fileIntoNewChangeSet
browseChanges browseFile removeLinefeeds putUpdate)].
	(suffix = 'swf') | (suffix = '*') ifTrue:[
		labels add:'open as Flash'.
		selectors add: #openAsFlash].
	(suffix = 'ttf') | (suffix = '*') ifTrue:[
		labels add: 'open true type font'.
		selectors add: #openAsTTF].
	(suffix = 'gz') | (suffix = 'csz') | (suffix = '*') ifTrue:[
		labels addAll: #('view decompressed' 'decompress to file').
		selectors addAll: #(viewGZipContents saveGZipContents)].
	(suffix = '3ds') | (suffix = '*') ifTrue:[
		labels add: 'Open 3DS file'.
		selectors add: #open3DSFile].
	(suffix = 'tape') | (suffix = '*') ifTrue:
		[labels add: 'open for playback'.
		selectors add: #openTapeFromFile].
	(suffix = 'wrl') | (suffix = '*') ifTrue:
		[labels add: 'open in Wonderland'.
		selectors add: #openVRMLFile].
	(suffix = 'htm') | (suffix = 'html') ifTrue:
		[labels add: 'open in browser'.
		selectors add: #openInBrowser].
	(suffix = '*') ifTrue:
		[labels addAll: #('generate HTML').
		lines add: labels size - 1.
		selectors addAll: #(renderFile)].
	^ Array with: labels with: lines with: selectors! !

!FileList methodsFor: 'file list menu' stamp: 'DSM 8/25/2000 14:46'!
saveGZipContents
	"Save the contents of a gzipped file"
	| zipped buffer unzipped newName |
	newName _ fileName copyUpToLast: FileDirectory extensionDelimiter.
	(FileDirectory extensionFor: fileName) = 'csz'
		ifTrue: [ newName _ newName, FileDirectory dot, 'cs' ].
	unzipped _ directory newFileNamed: newName.
	zipped _ GZipReadStream on: (directory readOnlyFileNamed: self
fullName).
	buffer _ String new: 50000.
	'Extracting ' , self fullName
		displayProgressAt: Sensor cursorPoint
		from: 0
		to: zipped sourceStream size
		during:
			[:bar |
			[zipped atEnd]
				whileFalse:
					[bar value: zipped sourceStream
position.
					unzipped nextPutAll: (zipped
nextInto: buffer)].
			zipped close.
			unzipped close].
	self updateFileList.
	^ newName! !


!Preferences class methodsFor: 'help' stamp: 'programmatic 8/25/2000 12:23'!
helpMsgsAdditionfileoutchangeSetCompressed
	^ #((changeSetCompressed 'Change sets will be compressed if true.'
) )! !

!Preferences class methodsFor: 'standard preferences' stamp: 'DSM 8/25/2000
12:14'!
changeSetCompressed
	^ self valueOfFlag: #changeSetCompressed! !

!Preferences class methodsFor: 'initial values' stamp: 'programmatic
8/25/2000 12:23'!
initialValuesAdditionfileoutchangeSetCompressed
	^ #((changeSetCompressed false (fileout ) ) )! !

"Postscript:
We now link the new preference into the mix."

Preferences addPreference: #changeSetCompressed category: #fileout default:
false balloonHelp: 'If true, change sets will be compressed using GZip, and
have a .csz extension.'
!




More information about the Squeak-dev mailing list