[squeak-dev] The Trunk: MorphicTests-ct.88.mcz

commits at source.squeak.org commits at source.squeak.org
Sat Jul 9 17:31:41 UTC 2022


Christoph Thiede uploaded a new version of MorphicTests to project The Trunk:
http://source.squeak.org/trunk/MorphicTests-ct.88.mcz

==================== Summary ====================

Name: MorphicTests-ct.88
Author: ct
Time: 9 July 2022, 7:31:39.249611 pm
UUID: 84ddbf6c-cab7-7546-9339-6140fe321128
Ancestors: MorphicTests-mt.87

Complements ToolBuilder-Morphic-ct.320 (tests for file dialogs).

=============== Diff against MorphicTests-mt.87 ===============

Item was added:
+ FileAbstractSelectionDialogTest subclass: #DirectoryChooserDialogTest
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicTests-ToolBuilder'!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>expectedFailures (in category 'failures') -----
+ expectedFailures
+ 
+ 	self flag: #todo. "Can only be debugged, but not run - this raises an InvalidDirectoryError which's defaultAction handles the exception silently. Should this class be a Notification instead?"
+ 	^ #(testChooseAbsentDirectory testTypeAndChooseAbsentDirectory)!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testChooseAbsentDirectory (in category 'tests - interface') -----
+ testChooseAbsentDirectory
+ 
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: (self pathForFile: 'nurp').
+ 	
+ 	self assert: nil equals: result.!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testChooseDefault (in category 'tests - interactions') -----
+ testChooseDefault
+ 
+ 	self openDialog.
+ 	
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: mockDirectory equals: result.!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testChooseDirectory (in category 'tests - interface') -----
+ testChooseDirectory
+ 
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: mockChildDirectory fullName.
+ 	
+ 	self assert: mockChildDirectory equals: result.!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testNewDirectory (in category 'tests - interface') -----
+ testNewDirectory
+ 
+ 	self openDialog.
+ 	
+ 	[dialog newDirectoryName] valueSupplyingAnswer: #('*name*' 'nurp').
+ 	self assert: (mockDirectory directoryExists: 'nurp').
+ 	self assert: mockDirectory / 'nurp' equals: dialog directory.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: mockDirectory / 'nurp' equals: result.!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testSelectAndChooseDirectory (in category 'tests - interactions') -----
+ testSelectAndChooseDirectory
+ 
+ 	self openDialog.
+ 	
+ 	dialog setDirectoryTo: (dialog subDirectoriesOf: mockDirectory) first.
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: mockChildDirectory equals: result.!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testTypeAndChooseAbsentDirectory (in category 'tests - interactions') -----
+ testTypeAndChooseAbsentDirectory
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: (self pathForDirectory: mockDirectory file: 'twin').
+ 	self deny: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: nil equals: result.!

Item was added:
+ ----- Method: DirectoryChooserDialogTest>>testTypeAndChooseDirectory (in category 'tests - interactions') -----
+ testTypeAndChooseDirectory
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: mockChildDirectory fullName.
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: mockChildDirectory equals: result.!

Item was added:
+ ClassTestCase subclass: #FileAbstractSelectionDialogTest
+ 	instanceVariableNames: 'mockDirectory mockFile1 mockFile2 mockFile3 mockChildDirectory mockChildFile dialog morph result'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicTests-ToolBuilder'!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest class>>isAbstract (in category 'testing ') -----
+ isAbstract
+ 
+ 	^ self = FileAbstractSelectionDialogTest!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>createChildFile: (in category 'support') -----
+ createChildFile: fileName
+ 
+ 	FileStream
+ 		fileNamed: (self pathForChildFile: fileName)
+ 		do: [:stream | stream nextPutAll: thisContext longPrintString].!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>createFile: (in category 'support') -----
+ createFile: fileName
+ 
+ 	FileStream
+ 		fileNamed: (self pathForFile: fileName)
+ 		do: [:stream | stream nextPutAll: thisContext longPrintString].!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>dialogClass (in category 'accessing') -----
+ dialogClass
+ 
+ 	^ self classToBeTested!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>openDialog (in category 'support') -----
+ openDialog
+ 
+ 	^ morph := self toolBuilder build: dialog!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>pathForChildFile: (in category 'support') -----
+ pathForChildFile: fileName
+ 
+ 	^ self pathForDirectory: mockChildDirectory file: fileName!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>pathForDirectory:file: (in category 'support') -----
+ pathForDirectory: directory file: fileName
+ 
+ 	^ directory fullName, directory class slash, fileName!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>pathForFile: (in category 'support') -----
+ pathForFile: fileName
+ 
+ 	^ self pathForDirectory: mockDirectory file: fileName!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>setUp (in category 'running') -----
+ setUp
+ 
+ 	super setUp.
+ 	
+ 	self setUpDirectory.
+ 	self setUpDialog.!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>setUpDialog (in category 'running') -----
+ setUpDialog
+ 
+ 	dialog := self dialogClass new.
+ 	dialog addDependent: self.
+ 	dialog directory: mockDirectory.!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>setUpDirectory (in category 'running') -----
+ setUpDirectory
+ 
+ 	mockDirectory := FileDirectory default / self class asString / UUID new asString.
+ 	mockDirectory assureExistence.
+ 	
+ 	{mockFile1 := 'plonk1.txt'.
+ 	mockFile2 := 'plonk2.st'.
+ 	mockFile3 := 'plonk3.cs'}
+ 		do: [:file | self createFile: file].
+ 	
+ 	mockChildDirectory := mockDirectory / 'child'.
+ 	mockChildDirectory assureExistence.
+ 	
+ 	mockChildFile := 'griffle.gif'.
+ 	self createChildFile: mockChildFile.!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>tearDown (in category 'running') -----
+ tearDown
+ 
+ 	[mockDirectory ifNotNil: [mockDirectory assureAbsence].
+ 	(FileDirectory default / self class asString) assureAbsence]
+ 		ensure: [super tearDown].!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>testCancel (in category 'tests - interface') -----
+ testCancel
+ 
+ 	self openDialog.
+ 	
+ 	dialog cancelFileChooser.
+ 	
+ 	self assert: nil equals: result.!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>testDirectoryTree (in category 'tests - interface') -----
+ testDirectoryTree
+ 
+ 	| node index |
+ 	self openDialog.
+ 	
+ 	node := dialog rootDirectoryList
+ 		detect: [:root | (dialog directoryNameOf: root) = mockDirectory pathParts first]
+ 		ifNone: [].
+ 	self assert: node notNil.
+ 	
+ 	index := 2.
+ 	[self assert: (dialog hasMoreDirectories: node).
+ 	(dialog subDirectoriesOf: node)
+ 		detect: [:child | (dialog directoryNameOf: child) = (mockDirectory pathParts at: index)]
+ 		ifFound: [:child | node := child. index := index + 1]
+ 		ifNone: [self fail]]
+ 			doWhileFalse: [(dialog directoryNameOf: node) = mockDirectory localName].
+ 	self assert: mockDirectory equals: dialog directory.
+ 	
+ 	self deny: (dialog hasMoreDirectories: mockChildDirectory).!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>toolBuilder (in category 'accessing') -----
+ toolBuilder
+ 
+ 	^ self toolBuilderClass new!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>toolBuilderClass (in category 'accessing') -----
+ toolBuilderClass
+ 
+ 	^ MorphicToolBuilder!

Item was added:
+ ----- Method: FileAbstractSelectionDialogTest>>update: (in category 'updating') -----
+ update: aspect
+ 
+ 	aspect = #close ifTrue:
+ 		[result := dialog finalChoice].!

Item was added:
+ FileDialogTest subclass: #FileChooserDialogTest
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicTests-ToolBuilder'!

Item was added:
+ ----- Method: FileChooserDialogTest>>testTypeToSelect (in category 'tests - interactions') -----
+ testTypeToSelect
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: mockFile2 allButLast.
+ 	self assert: mockFile2 equals: (dialog fileList at: dialog fileListIndex).
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForFile: mockFile2) equals: result.!

Item was added:
+ FileAbstractSelectionDialogTest subclass: #FileDialogTest
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicTests-ToolBuilder'!

Item was added:
+ ----- Method: FileDialogTest class>>isAbstract (in category 'testing ') -----
+ isAbstract
+ 
+ 	^ self = FileDialogTest!

Item was added:
+ ----- Method: FileDialogTest>>testChooseAbsentFile (in category 'tests - interface') -----
+ testChooseAbsentFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: mockFile2 , '.absent'.
+ 	
+ 	self assert: nil equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testChooseFile (in category 'tests - interface') -----
+ testChooseFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: mockFile2.
+ 	
+ 	self assert: (self pathForFile: mockFile2) equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testChooseNothing (in category 'tests - interactions') -----
+ testChooseNothing
+ 
+ 	self openDialog.
+ 	
+ 	self deny: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: nil equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testFileList (in category 'tests - interface') -----
+ testFileList
+ 
+ 	self openDialog.
+ 	
+ 	self assert: {mockFile1. mockFile2. mockFile3} equals: dialog fileList.!

Item was added:
+ ----- Method: FileDialogTest>>testFileListWithPattern (in category 'tests - interface') -----
+ testFileListWithPattern
+ 
+ 	dialog pattern: '*2*'.
+ 	self openDialog.
+ 	
+ 	self assert: {mockFile2} equals: dialog fileList.!

Item was added:
+ ----- Method: FileDialogTest>>testFileListWithSuffixList (in category 'tests - interface') -----
+ testFileListWithSuffixList
+ 
+ 	dialog suffixList: #('cs' 'st').
+ 	self openDialog.
+ 	
+ 	self assert: {mockFile2. mockFile3} equals: dialog fileList.!

Item was added:
+ ----- Method: FileDialogTest>>testSelectAndChooseFile (in category 'tests - interactions') -----
+ testSelectAndChooseFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog fileListIndex: (dialog fileList indexOf: mockFile2).
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForFile: mockFile2) equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testSelectAndChooseSubFile (in category 'tests - interactions') -----
+ testSelectAndChooseSubFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog setDirectoryTo: (dialog subDirectoriesOf: dialog directory) first.
+ 	self assert: {mockChildFile} equals: dialog fileList.
+ 	dialog fileListIndex: (dialog fileList indexOf: mockChildFile).
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForChildFile: mockChildFile) equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testTypeAndChooseAbsentFile (in category 'tests - interactions') -----
+ testTypeAndChooseAbsentFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: mockFile2 , '.absent'.
+ 	self deny: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: nil equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testTypeAndChooseFile (in category 'tests - interactions') -----
+ testTypeAndChooseFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: mockFile2.
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForFile: mockFile2) equals: result.!

Item was added:
+ ----- Method: FileDialogTest>>testTypeAndChooseFullPath (in category 'tests - interactions') -----
+ testTypeAndChooseFullPath
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: (self pathForChildFile: mockChildFile).
+ 	self assert: mockChildDirectory equals: dialog directory.
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForChildFile: mockChildFile) equals: result.!

Item was added:
+ FileDialogTest subclass: #FileSaverDialogTest
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'MorphicTests-ToolBuilder'!

Item was added:
+ ----- Method: FileSaverDialogTest>>testChooseAbsentFile (in category 'tests - interface') -----
+ testChooseAbsentFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: mockFile2 , '.absent'.
+ 	
+ 	self assert: (self pathForFile: mockFile2 , '.absent') equals: result.!

Item was added:
+ ----- Method: FileSaverDialogTest>>testChooseAbsentFileWithSuffix (in category 'tests - interface') -----
+ testChooseAbsentFileWithSuffix
+ 
+ 	dialog suffix: 'txt'.
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: mockFile2 , '.absent'.
+ 	
+ 	self assert: (self pathForFile: mockFile2 , '.absent.txt') equals: result.!

Item was added:
+ ----- Method: FileSaverDialogTest>>testChooseDirectory (in category 'tests - interface') -----
+ testChooseDirectory
+ 
+ 	self openDialog.
+ 	
+ 	dialog acceptFileName: mockChildDirectory localName.
+ 	
+ 	self deny: dialog canAccept.
+ 	self assert: result isNil.!

Item was added:
+ ----- Method: FileSaverDialogTest>>testInitialFileName (in category 'tests - interface') -----
+ testInitialFileName
+ 
+ 	dialog initialFilename: mockFile2.
+ 	self openDialog.
+ 	
+ 	self assert: mockFile2 equals: dialog inputText.
+ 	self assert: mockFile2 equals: (dialog fileList at: dialog fileListIndex).
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForFile: mockFile2) equals: result.!

Item was added:
+ ----- Method: FileSaverDialogTest>>testNewDirectory (in category 'tests - interface') -----
+ testNewDirectory
+ 
+ 	self openDialog.
+ 	
+ 	[dialog newDirectoryName] valueSupplyingAnswer: #('*name*' 'nurp').
+ 	self assert: (mockDirectory directoryExists: 'nurp').
+ 	self assert: mockDirectory / 'nurp' equals: dialog directory.
+ 	dialog acceptFileName: 'zonk'.
+ 	
+ 	self assert: (self pathForDirectory: mockDirectory / 'nurp' file: 'zonk') equals: result.!

Item was added:
+ ----- Method: FileSaverDialogTest>>testTypeAndChooseAbsentFile (in category 'tests - interactions') -----
+ testTypeAndChooseAbsentFile
+ 
+ 	self openDialog.
+ 	
+ 	dialog selectFileName: mockFile2 , '.absent'.
+ 	self assert: dialog canAccept.
+ 	dialog acceptFileName.
+ 	
+ 	self assert: (self pathForFile: mockFile2 , '.absent') equals: result.!

Item was added:
+ ----- Method: FileSaverDialogTest>>testTypeAndChooseAbsentFileWithSuffixList (in category 'tests - interactions') -----
+ testTypeAndChooseAbsentFileWithSuffixList
+ 
+ 	dialog suffixList: #('txt' 'cs').
+ 	self openDialog.
+ 	
+ 	"suffix choice is cancellable and dialog will remain open"
+ 	2 timesRepeat:
+ 		[[dialog selectFileName: mockFile2 , '.absent'.
+ 		dialog acceptFileName]
+ 			valueSupplyingAnswer: #('*type*' cancel)].
+ 	
+ 	[dialog selectFileName: mockFile2 , '.absent'.
+ 	dialog acceptFileName]
+ 		valueSupplyingAnswer: #('*type*' 'cs').
+ 	
+ 	self assert: (self pathForFile: mockFile2 , '.absent.cs') equals: result.!



More information about the Squeak-dev mailing list