DVS fileOut truncation error

Derek Brans brans at nerdonawire.com
Wed Dec 4 19:46:21 UTC 2002


Avi,

My DVS fileOut is being truncated for some reason.  Here is a sample.  
The last line should read "self rendPackageList" but instead it says 
"self renderP"

Any idea what might be causing that?

Thank you,
Derek

Smalltalk organization addCategory: 'WebDVS'!

WATreeVisitor subclass: #WADirectoryVisitor
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WebDVS'!

WADirectoryVisitor class
	instanceVariableNames: ''!

WAComponent subclass: #WAFileList
	instanceVariableNames: 'tree '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WebDVS'!

WAFileList class
	instanceVariableNames: ''!

WATreeVisitor subclass: #WAFileNameVisitor
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WebDVS'!

WAFileNameVisitor class
	instanceVariableNames: ''!

WAComponent subclass: #WebDVS
	instanceVariableNames: 'fileList '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'WebDVS'!

WebDVS class
	instanceVariableNames: ''!

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 11/29/2002 11:39'!
addPackage
	|packageName|
	packageName_ self call: (WAInputDialog new message: 'Name of package').
	FilePackageManager named: packageName.
	! !

!WAFileList methodsFor: 'as yet unclassified' stamp: 'djb 12/4/2002 
08:30'!
buildTreeFor: aFileName
	| oc dir newTree|
	newTree_ WATree new.
	oc _ OrderedCollection new.
	dir _ FileDirectory default.
	oc addFirst: dir fullName.
	[dir pathName = '']
		whileFalse: [dir _ dir containingDirectory.
					 oc addFirst: dir fullName].
	oc do: [:ea | newTree select: ea].
	newTree childVisitor: WADirectoryVisitor new.
	newTree labelVisitor: WAFileNameVisitor new.
	^ newTree! !

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 12/4/2002 11:11'!
editDirectoryForPackage: pkg
	pkg directory: (
	FileDirectory on: (
	self call: (
	WAFileList on: (
	FileDirectory dirPathFor: pkg fileName))))! !

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 12/2/2002 22:23'!
fileList
	^fileList ifNil:[fileList_WAFileList new]! !

!WebDVS class methodsFor: 'as yet unclassified' stamp: 'djb 11/29/2002 
11:52'!
initialize
	self registerAsApplication: 'WebDVS' sessionClass: WASession ! !

!WAFileList class methodsFor: 'as yet unclassified' stamp: 'djb 
12/4/2002 08:36'!
on: aDirectory
	^self new startOn: aDirectory
! !

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 11/29/2002 14:45'!
packageListView
	^[:html |  html table: [
			PackageManager allManagers do: [ :pkg|
				html tableRow: [
					html tableData: [html text: pkg asString] fixTemps.
					html tableData:
					[html form: [
						html textInputWithValue: (FileDirectory dirPathFor: pkg fileName)
							callback: [:v | pkg directory: v] fixTemps.
						html submitButton.]].
					html tableData: [html anchorWithAction:[pkg unregister] fixTemps
						text:'delete '].
					html tableData: [html anchorWithAction:[self 
halt. pkg fileOut] fixTemps
						text: 'fileOut'].
					html tableData: [html anchorWithAction:[pkg fileIn] fixTemps
						text: 'fileIn']
				]
			]fixTemps
	]fixTemps]
				! !

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 11/29/2002 15:10'!
renderControlsForPackage: pkg on: html
	html anchorWithAction: [pkg unregister]  text: 'delete '; space.
	html anchorWithAction: [pkg fileOut]  text: 'fileOut'; space.
	^html anchorWithAction: [pkg fileIn]  text: 'fileIn'! !

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 12/4/2002 11:14'!
renderDirectoryEditorForPackage: pkg on: html
	html form:
			[html
			attributes: {'size' -> 50};
			textInputWithValue: (FileDirectory dirPathFor:pkg fileName)
			callback: [:path | pkg directory: (FileDirectory on: path)].
			html space.
			html anchorWithAction: [self editDirectoryForPackage: pkg] 
text: 'browse'.].
		
	! !

!WAFileList methodsFor: 'as yet unclassified' stamp: 'djb 12/3/2002 
09:52'!
renderOn: html
	html
		form: [html render: self tree.
			html
				submitButtonWithAction: [self select]
				text: 'select']! !

!WebDVS methodsFor: 'as yet unclassified' stamp: 'djb 12/4/2002 11:40'!
renderOn: html
	html heading: 'WebDVS'.
	html anchorWithAction:[self addPackage] text:'Add Package'.
	self renderP


Nerd on a Wire: Web and Information Solutions
Website Design - Database Systems - Site Hosting
604.874.6463
mailto:info at nerdonawire.com
For more information, visit http://nerdonawire.com




More information about the Squeak-dev mailing list