[FIX] for ZipTool problems (and request for help)

Ned Konz ned at bike-nomad.com
Wed Dec 5 19:33:22 UTC 2001


On Wednesday 05 December 2001 09:54 am, Ned Konz wrote:
> On Tuesday 04 December 2001 12:49 am, Mike Rutenberg wrote:
> > I was just trying to use the ZipTool to open the Windows VM source code
> > zip file (Squeak3.1Alpha6Src.zip) and ran into two problems.  I am
> > running on Windows 2000 using the Windows 31alpha6 VM, and the most
> > recent alpha image.
>
> I don't really have time to investigate this right now, as I have a
> deadline

Well, I did fix the two problems mentioned. See the attached CS.
I tried it on Linux and Windows, but someone needs to try on a Mac.

******* I NEED HELP HERE:

However, this problem remains:

> I did find a more serious problem when writing the same file back out: it
> seems to get stuck and/or write extra bytes to the file. Haven't looked
> into this yet.
>
> Anyone want to look at this last problem?

It seems to write a huge and damaged file.

This may have consequences for Project saving, so I'm a bit concerned that it 
be fixed.

Plus of course it's really really slow. Is this the Zlib code?

-- 
Ned Konz
currently: Stanwood, WA
email:     ned at bike-nomad.com
homepage:  http://bike-nomad.com
-------------- next part --------------
'From Squeak3.2alpha of 3 October 2001 [latest update: #4567] on 5 December 2001 at 11:14:01 am'!
"Change Set:		ZipToolFixes2-nk
Date:			5 December 2001
Author:			Ned Konz

This fixes two problems with my Zip Tool:
1. problems reading a read-only archive
2. problems on systems where the filename directory separator is not $/

It also cleans up the existence of the Zip Tool in the Tools flap and page of the Objects tool (and will also put the Refactoring Browser there if you have it installed). Note that it has to make the Objects Tool a bit longer to fit the ZipTool's thumbnail.

There remains a problem when writing out a large archive that this does not fix.

"!


!ArchiveViewer methodsFor: 'archive operations' stamp: 'nk 12/5/2001 10:12'!
extractAll
	| directory stream |

	self canExtractAll ifFalse: [^ self].
	[
		directory _ FileList2 modalFolderSelector ifNil: [^ self].
		(self extractAllPossibleInDirectory: directory) ifTrue: [
			self members do: [:ea |  | newName |
				newName _ ea fileName copyReplaceAll: '/' with: directory pathNameDelimiter asString.
				ea isDirectory ifTrue: [
					[directory createDirectory: newName allButLast]
						on: Error
						do: [:ex | 
							(PopUpMenu confirm: newName , ' cannot be created. Continue?')
								ifFalse: [^ self]
						]
				] ifFalse: [
					(stream _ directory forceNewFileNamed: newName) ifNil: [
						(PopUpMenu confirm: newName , ' cannot be created. Continue?') 
							ifFalse: [^ self]
					] ifNotNil: [
						ea extractTo: stream. stream close
					]
				]
			].
			^ self
		].
		PopUpMenu confirm: 'Try again?'
	] whileTrue! !

!ArchiveViewer methodsFor: 'initialization' stamp: 'nk 12/5/2001 09:13'!
file: aStream
	| name |
	name _ aStream name.
	archive _ ZipArchive new readFrom: aStream named: name.
	self setLabel: name.
	self memberIndex:  0.
	self changed: #memberList! !

!ArchiveViewer methodsFor: 'initialization' stamp: 'nk 12/5/2001 09:17'!
fileName: aString
	archive _ ZipArchive new readFromFileNamed: aString.
	self setLabel: aString.
	self memberIndex:  0.
	self changed: #memberList! !


!ArchiveViewer class methodsFor: 'parts bin' stamp: 'nk 12/5/2001 09:36'!
prototypicalToolWindow
	"Answer an example of myself seen in a tool window, for the benefit of parts-launching tools"

	^(self new) createWindow! !


!Flaps class methodsFor: 'predefined flaps' stamp: 'nk 12/5/2001 10:01'!
quadsDefiningToolsFlap
	"Answer a structure defining the default Tools flap"
	| quads |
	quads _ OrderedCollection withAll: #(
	(Browser 				prototypicalToolWindow		'Browser'			'A Browser is a tool that allows you to view all the code of all the classes in the system')
	(Transcript				openAsMorph				'Transcript'			'A Transcript is a window usable for logging and debugging; browse references to #Transcript for examples of how to write to it.')
	(Workspace				prototypicalToolWindow		'Workspace'			'A Workspace is a simple window for editing text.  You can later save the contents to a file if you desire.')
	(FileList					prototypicalToolWindow		'File List'			'A File List is a tool for browsing folders and files on disks and on ftp types.')
	(DualChangeSorter		prototypicalToolWindow		'Change Sorter'		'Shows two change sets side by side')
	(SelectorBrowser			prototypicalToolWindow		'Method Finder'		'A tool for discovering methods by providing sample values for arguments and results')
	(MessageNames			prototypicalToolWindow		'Message Names'		'A tool for finding, viewing, and editing all methods whose names contain a given character sequence.')
	(Preferences			preferencesControlPanel	'Preferences'			'Allows you to control numerous options')
	(Utilities				recentSubmissionsWindow	'Recent'				'A message browser that tracks the most recently-submitted methods')
	(ProcessBrowser			prototypicalToolWindow		'Processes'			'A Process Browser shows you all the running processes')
	(Preferences			annotationEditingWindow	'Annotations'		'Allows you to specify the annotations to be shown in the annotation panes of browsers, etc.')
	(Scamper				newOpenableMorph			'Scamper'			'A web browser')
	(Celeste					newOpenableMorph			'Celeste'				'Celeste -- an EMail reader')
	(PackagePaneBrowser	prototypicalToolWindow		'Packages'			'Package Browser:  like a System Browser, except that if has extra level of categorization in the top-left pane, such that class-categories are further organized into groups called "packages"')
	(ChangeSorter			prototypicalToolWindow		'Change Set'			'A tool that allows you to view and manipulate all the code changes in a single change set')
	(ArchiveViewer		prototypicalToolWindow		'Zip Tool'			'A tool that lets you view, create, and edit ZIP archives')
).
	(Smalltalk includesKey: #RefactoringBrowser) ifTrue: [
		quads add: #(RefactoringBrowser 				prototypicalToolWindow		'RefactoringBrowser'			'A RefactoringBrowser is a tool that allows you to view all the code of all the classes in the system and perform refactorings on the code')
	].
	^quads.! !


!ObjectsTool methodsFor: 'initialization' stamp: 'nk 12/5/2001 09:55'!
initializeToStandAlone
	"Initialize the receiver so that it can live as a stand-alone morph"

	| aPane aBin aColor |
	self basicInitialize.
	self layoutInset: 6. 
	self listCentering: #topLeft.
	self cellPositioning: #topLeft.
	self wrapCentering: #center.
	self useRoundedCorners.
	self listDirection: #topToBottom.
	self hResizing: #shrinkWrap; vResizing: #shrinkWrap.

	aPane _ self paneForTabs: self modeTabs.
	aPane addMorphFront: self dismissButton.
	aPane addMorphBack: self helpButton.

	aPane color: (aColor _ aPane color) darker.
	aPane listSpacing: #equal.
	aPane cellInset: 10 @ 10.
	aPane listCentering: #center; height: 38.
	aPane wrapDirection: nil.
	self addMorphFront: aPane.

	self addMorphBack: Morph new.  "Place holder for a tabs or text pane"

	aBin _ PartsBin newPartsBinWithOrientation: #leftToRight from: #().
	aBin listDirection: #leftToRight.
	aBin wrapDirection: #topToBottom.
	aBin hResizing: #spaceFill; vResizing: #spaceFill.
	aBin extent: (self currentWorld width) @ 300.
	aBin color: aColor lighter lighter.
	aBin setNameTo: 'parts'.
	aBin dropEnabled: false.
	self addMorphBack: aBin.
	self submorphs last width: 350; hResizing: #rigid.
	self color: (Color r: 0.0 g: 0.839 b: 0.226).
	self setProperty: #initialWidth toValue: 268.
	self setNameTo: 'Objects'.
	self showCategories.




! !


!ZipArchive methodsFor: 'archive operations' stamp: 'nk 12/5/2001 09:23'!
readFrom: aStreamOrFileName
	"Maintained for backwards compatibility"
	^aStreamOrFileName isStream
		ifTrue: [ self readFrom: aStreamOrFileName named: aStreamOrFileName name ]
		ifFalse: [ self readFromFileNamed: aStreamOrFileName ].! !

!ZipArchive methodsFor: 'archive operations' stamp: 'nk 12/5/2001 09:12'!
readFrom: aStream named: name
	| eocdPosition |
	aStream binary.
	self findEndOfCentralDirectoryFrom: aStream.
	eocdPosition _ aStream position.
	self readEndOfCentralDirectoryFrom: aStream.
	aStream position: eocdPosition - centralDirectorySize.
	self readMembersFrom: aStream named: name.
! !

!ZipArchive methodsFor: 'archive operations' stamp: 'nk 12/5/2001 09:16'!
readFromFileNamed: aFileName
	| stream |
	stream _ StandardFileStream readOnlyFileNamed: aFileName.
	self readFrom: stream named: aFileName.! !

!ZipArchive methodsFor: 'archive operations' stamp: 'nk 2/23/2001 10:29'!
writeTo: stream
	stream binary.
	members do: [ :member |
		member writeTo: stream.
		member endRead.
	].
	writeCentralDirectoryOffset _ stream position.
	self writeCentralDirectoryTo: stream.
	! !

ArchiveViewer class removeSelector: #descriptionForPartsBin!
"Postscript:
Since this also affects the Objects tool and the Tools flap,
re-initialize these."
PartsBin initialize.
PartsBin cacheAllThumbnails.
Flaps replaceToolsFlap.!



More information about the Squeak-dev mailing list