Levente Uzonyi uploaded a new version of Tests to project The Trunk:
http://source.squeak.org/trunk/Tests-ul.385.mcz ==================== Summary ==================== Name: Tests-ul.385 Author: ul Time: 10 October 2017, 12:04:33.723597 am UUID: e78f8a8d-6b40-4e64-b052-a8ace225bb97 Ancestors: Tests-mt.384 - added RemoteStringTest with two tests to see if RemoteString works across different file streams - recategorized all test methods in Tests-Files to be in the tests category =============== Diff against Tests-mt.384 =============== Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryContainingDirectory (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryContainingDirectory (in category 'as yet unclassified') ----- testFileDirectoryContainingDirectory "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: fd containingDirectory pathName = ''. ! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryContainingDirectoryExistence (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryContainingDirectoryExistence (in category 'as yet unclassified') ----- testFileDirectoryContainingDirectoryExistence "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: (fd containingDirectory fileOrDirectoryExists: 'C:').! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryContainingEntry (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryContainingEntry (in category 'as yet unclassified') ----- testFileDirectoryContainingEntry "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: (fd containingDirectory entryAt: fd localName) notNil. ! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryDirectoryEntry (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryDirectoryEntry (in category 'as yet unclassified') ----- testFileDirectoryDirectoryEntry "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: fd directoryEntry notNil.! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryEntryFor (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryEntryFor (in category 'as yet unclassified') ----- testFileDirectoryEntryFor "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory root directoryEntryFor: 'C:'. self assert: (fd name sameAs: 'C:').! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryExists (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryExists (in category 'as yet unclassified') ----- testFileDirectoryExists "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. self assert: (FileDirectory root directoryExists: 'C:').! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryLocalName (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryLocalName (in category 'as yet unclassified') ----- testFileDirectoryLocalName "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory on: 'C:'. self assert: fd localName = 'C:'. ! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryNamed (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryNamed (in category 'as yet unclassified') ----- testFileDirectoryNamed "Hoping that you have 'C:' of course..." | fd | FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. fd := FileDirectory root directoryNamed: 'C:'. self assert: fd pathName = 'C:'.! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryNonExistence (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryNonExistence (in category 'as yet unclassified') ----- testFileDirectoryNonExistence | inexistentFileName | "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. inexistentFileName := DosFileDirectory default nextNameFor: 'DosFileDirectoryTest' extension: 'temp'. "This test can fail if another process creates a file with the same name as inexistentFileName (the probability of that is very very remote)" self deny: (DosFileDirectory default fileOrDirectoryExists: inexistentFileName)! Item was changed: + ----- Method: DosFileDirectoryTests>>testFileDirectoryRootExistence (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFileDirectoryRootExistence (in category 'as yet unclassified') ----- testFileDirectoryRootExistence "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. self assert: (FileDirectory root fileOrDirectoryExists: 'C:').! Item was changed: + ----- Method: DosFileDirectoryTests>>testFullNameFor (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testFullNameFor (in category 'as yet unclassified') ----- testFullNameFor "Hoping that you have 'C:' of course..." FileDirectory activeDirectoryClass == DosFileDirectory ifFalse:[^self]. self assert: (FileDirectory default fullNameFor: 'C:') = 'C:'. self assert: (FileDirectory default fullNameFor: 'C:\test') = 'C:\test'. self assert: (FileDirectory default fullNameFor: '\\share') = '\\share'. self assert: (FileDirectory default fullNameFor: '\\share\test') = '\\share\test'. self assert: (FileDirectory default fullNameFor: '\test') = (FileDirectory default pathParts first, '\test'). ! Item was changed: + ----- Method: DosFileDirectoryTests>>testIsDriveForDrive (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testIsDriveForDrive (in category 'as yet unclassified') ----- testIsDriveForDrive self assert: (DosFileDirectory isDrive: 'C:'). self deny: (DosFileDirectory isDrive: 'C:\'). self deny: (DosFileDirectory isDrive: 'C:\foo'). self deny: (DosFileDirectory isDrive: 'C:foo').! Item was changed: + ----- Method: DosFileDirectoryTests>>testIsDriveForShare (in category 'tests') ----- - ----- Method: DosFileDirectoryTests>>testIsDriveForShare (in category 'as yet unclassified') ----- testIsDriveForShare self assert: (DosFileDirectory isDrive: '\\server'). self deny: (DosFileDirectory isDrive: '\\server\'). self deny: (DosFileDirectory isDrive: '\\server\foo'). ! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testAddressRange (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testAddressRange (in category 'testing') ----- testAddressRange "Test source pointer to file position address translation across a wide address range" | sf i p a | sf := ExpandedSourceFileArray new. 16r1000000 to: 16r10000000 by: 4093 do: [:e | i := sf fileIndexFromSourcePointer: e. p := sf filePositionFromSourcePointer: e. a := sf sourcePointerFromFileIndex: i andPosition: p. self assert: a = e] ! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testChangesFileAddressRange (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testChangesFileAddressRange (in category 'testing') ----- testChangesFileAddressRange "Test file position to source pointer address translation for the changes file" | sf i p a a2 | sf := ExpandedSourceFileArray new. 0 to: 16r1FFFFFFF by: 4093 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. i := sf fileIndexFromSourcePointer: a. self assert: i = 2. p := sf filePositionFromSourcePointer: a. self assert: p = e. a2 := sf sourcePointerFromFileIndex: 2 andPosition: p. self assert: a2 = a]. 0 to: 16rFFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r2000000 and: 16r2FFFFFF)]. 16r1000000 to: 16r1FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r4000000 and: 16r4FFFFFF)]. 16r2000000 to: 16r2FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r6000000 and: 16r6FFFFFF)]. 16r3000000 to: 16r3FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r8000000 and: 16r8FFFFFF)]. 16r4000000 to: 16r4FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16rA000000 and: 16rAFFFFFF)]. 16r5000000 to: 16r5FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16rC000000 and: 16rCFFFFFF)]. 16r6000000 to: 16r6FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16rE000000 and: 16rEFFFFFF)]. 16r7000000 to: 16r7FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r10000000 and: 16r10FFFFFF)] ! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testCompatibilityWithStandardSourceFileArray (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testCompatibilityWithStandardSourceFileArray (in category 'testing') ----- testCompatibilityWithStandardSourceFileArray "Test compatibility with StandardSourceFileArray across the address range of StandardSourceFileArray, including the unused address space below 16r1000000" | ssf esf i1 i2 p1 p2 a1 a2 | ssf := StandardSourceFileArray new. esf := ExpandedSourceFileArray new. 0 to: 16rFFFFFF by: 811 do: [:e | i1 := ssf fileIndexFromSourcePointer: e. i2 := esf fileIndexFromSourcePointer: e. self assert: i1 = i2. self assert: i1 = 0. "This is unused address space" p1 := ssf filePositionFromSourcePointer: e. p2 := esf filePositionFromSourcePointer: e. self assert: p1 = p2]. 16r4FFFFFF to: 16r4FFFFFF by: 811 do: [:e | i1 := ssf fileIndexFromSourcePointer: e. i2 := esf fileIndexFromSourcePointer: e. self assert: i1 = i2. p1 := ssf filePositionFromSourcePointer: e. p2 := esf filePositionFromSourcePointer: e. self assert: p1 = p2. a1 := ssf sourcePointerFromFileIndex: i1 andPosition: p1. a2 := esf sourcePointerFromFileIndex: i2 andPosition: p2. self assert: a1 = a2. self assert: a1= e] ! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testFileIndexFromSourcePointer (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testFileIndexFromSourcePointer (in category 'testing') ----- testFileIndexFromSourcePointer "Test derivation of file index for sources or changes file from source pointers" | sf | sf := ExpandedSourceFileArray new. "sources file mapping" self assert: 1 = (sf fileIndexFromSourcePointer: 16r1000000). self assert: 1 = (sf fileIndexFromSourcePointer: 16r1000013). self assert: 1 = (sf fileIndexFromSourcePointer: 16r1FFFFFF). self assert: 1 = (sf fileIndexFromSourcePointer: 16r3000000). self assert: 1 = (sf fileIndexFromSourcePointer: 16r3000013). self assert: 1 = (sf fileIndexFromSourcePointer: 16r3FFFFFF). self assert: 1 = (sf fileIndexFromSourcePointer: 16r5000000). self assert: 1 = (sf fileIndexFromSourcePointer: 16r5000013). self assert: 1 = (sf fileIndexFromSourcePointer: 16r5FFFFFF). (16r1000000 to: 16r1FFFFFF by: 811) do: [:e | self assert: 1 = (sf fileIndexFromSourcePointer: e)]. (16r3000000 to: 16r3FFFFFF by: 811) do: [:e | self assert: 1 = (sf fileIndexFromSourcePointer: e)]. "changes file mapping" self assert: 2 = (sf fileIndexFromSourcePointer: 16r2000000). self assert: 2 = (sf fileIndexFromSourcePointer: 16r2000013). self assert: 2 = (sf fileIndexFromSourcePointer: 16r2FFFFFF). self assert: 2 = (sf fileIndexFromSourcePointer: 16r4000000). self assert: 2 = (sf fileIndexFromSourcePointer: 16r4000013). self assert: 2 = (sf fileIndexFromSourcePointer: 16r4FFFFFF). self assert: 2 = (sf fileIndexFromSourcePointer: 16r6000000). self assert: 2 = (sf fileIndexFromSourcePointer: 16r6000013). self assert: 2 = (sf fileIndexFromSourcePointer: 16r6FFFFFF). (16r2000000 to: 16r2FFFFFF by: 811) do: [:e | self assert: 2 = (sf fileIndexFromSourcePointer: e)]. (16r4000000 to: 16r4FFFFFF by: 811) do: [:e | self assert: 2 = (sf fileIndexFromSourcePointer: e)]. "the following numeric ranges are unused but currently produces results as follows" self assert: 0 = (sf fileIndexFromSourcePointer: 16r0000000). self assert: 0 = (sf fileIndexFromSourcePointer: 16r0000013). self assert: 0 = (sf fileIndexFromSourcePointer: 16r0FFFFFF) ! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testFilePositionFromSourcePointer (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testFilePositionFromSourcePointer (in category 'testing') ----- testFilePositionFromSourcePointer "Test derivation of file position for sources or changes file from source pointers" | sf | sf := ExpandedSourceFileArray new. "sources file" self assert: 0 = (sf filePositionFromSourcePointer: 16r1000000). self assert: 16r13 = (sf filePositionFromSourcePointer: 16r1000013). self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r1FFFFFF). self assert: 16r1000000 = (sf filePositionFromSourcePointer: 16r3000000). self assert: 16r1000013 = (sf filePositionFromSourcePointer: 16r3000013). self assert: 16r1FFFFFF = (sf filePositionFromSourcePointer: 16r3FFFFFF). "changes file" self assert: 0 = (sf filePositionFromSourcePointer: 16r2000000). self assert: 16r13 = (sf filePositionFromSourcePointer: 16r2000013). self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r2FFFFFF). self assert: 16r1000000 = (sf filePositionFromSourcePointer: 16r4000000). self assert: 16r1000013 = (sf filePositionFromSourcePointer: 16r4000013). self assert: 16r1FFFFFF = (sf filePositionFromSourcePointer: 16r4FFFFFF). "the following numeric ranges are unused but currently produces results as follows" self assert: 0 = (sf filePositionFromSourcePointer: 16r0000000). self assert: 16r13 = (sf filePositionFromSourcePointer: 16r0000013). self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r0FFFFFF) ! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testSourcePointerFromFileIndexAndPosition (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testSourcePointerFromFileIndexAndPosition (in category 'testing') ----- testSourcePointerFromFileIndexAndPosition "Test valid input ranges" | sf | sf := ExpandedSourceFileArray new. self should: [sf sourcePointerFromFileIndex: 0 andPosition: 0] raise: Error. self should: [sf sourcePointerFromFileIndex: 0 andPosition: 3] raise: Error. self should: [sf sourcePointerFromFileIndex: 1 andPosition: -1] raise: Error. self should: [sf sourcePointerFromFileIndex: 3 andPosition: 0] raise: Error. self should: [sf sourcePointerFromFileIndex: 4 andPosition: 0] raise: Error. self assert: 16r1000000 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 0). self assert: 16r1000013 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r13). self assert: 16r1FFFFFF equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16rFFFFFF). self assert: 16r2000000 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 0). self assert: 16r2000013 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r13). self assert: 16r2FFFFFF equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16rFFFFFF). self assert: 16r3000000 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r1000000). self assert: 16r3000013 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r1000013). self assert: 16r3FFFFFF equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r1FFFFFF). self assert: 16r4000000 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r1000000). self assert: 16r4000013 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r1000013). self assert: 16r4FFFFFF equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r1FFFFFF). self assert: 16r5000000 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r2000000).! Item was changed: + ----- Method: ExpandedSourceFileArrayTest>>testSourcesFileAddressRange (in category 'tests') ----- - ----- Method: ExpandedSourceFileArrayTest>>testSourcesFileAddressRange (in category 'testing') ----- testSourcesFileAddressRange "Test file position to source pointer address translation for the sources file" | sf i p a a2 | sf := ExpandedSourceFileArray new. 0 to: 16r1FFFFFFF by: 4093 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. i := sf fileIndexFromSourcePointer: a. self assert: i = 1. p := sf filePositionFromSourcePointer: a. self assert: p = e. a2 := sf sourcePointerFromFileIndex: 1 andPosition: p. self assert: a2 = a]. 0 to: 16rFFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r1000000 and: 16r1FFFFFF)]. 16r1000000 to: 16r1FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r3000000 and: 16r3FFFFFF)]. 16r2000000 to: 16r2FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r5000000 and: 16r5FFFFFF)]. 16r3000000 to: 16r3FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r7000000 and: 16r7FFFFFF)]. 16r4000000 to: 16r4FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r9000000 and: 16r9FFFFFF)]. 16r5000000 to: 16r5FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16rB000000 and: 16rBFFFFFF)]. 16r6000000 to: 16r6FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16rD000000 and: 16rDFFFFFF)]. 16r7000000 to: 16r7FFFFFF by: 811 do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16rF000000 and: 16rFFFFFFF)] ! Item was changed: + ----- Method: FileStreamTest>>testCachingNextChunkPut (in category 'tests') ----- - ----- Method: FileStreamTest>>testCachingNextChunkPut (in category 'as yet unclassified') ----- testCachingNextChunkPut "Ensure that nextChunkPut:/nextChunk works properly on a caching file" | file text read | [file := FileStream forceNewFileNamed: 'testCachingNextChunkPut'. text := 'this is a chunkful of text'. file nextChunkPut: text. read := [file position: 0; nextChunkText] valueWithin: 1 seconds onTimeout:['']. self assert: read = text. ] ensure:[file close. FileDirectory default deleteFileNamed: file name ifAbsent:[]].! Item was changed: + ----- Method: FileStreamTest>>testDetectFileDo (in category 'tests') ----- - ----- Method: FileStreamTest>>testDetectFileDo (in category 'as yet unclassified') ----- testDetectFileDo "Mantis #1838" | filename | filename := 'filestream.tst'. [(FileDirectory default forceNewFileNamed: filename) nextPutAll: '42'; close. FileStream detectFile: [FileDirectory default oldFileNamed: filename] do: [:file | self assert: file notNil. self deny: file closed. self assert: file contentsOfEntireFile = '42']] ensure: [FileDirectory default deleteFileNamed: filename ifAbsent: [] ]! Item was changed: + ----- Method: FileStreamTest>>testFileTruncation (in category 'tests') ----- - ----- Method: FileStreamTest>>testFileTruncation (in category 'as yet unclassified') ----- testFileTruncation "Ensure that nextChunkPut:/nextChunk works properly on a caching file" | file | file := nil. [ file := FileDirectory default forceNewFileNamed: 'TruncationTest.txt'. file nextPutAll: '1234567890'. ] ensure: [file close]. [ file := FileDirectory default oldFileNamed: 'TruncationTest.txt'. self should: [file contents = '1234567890']. file truncate: 4. ] ensure: [file close]. [ file := FileDirectory default readOnlyFileNamed: 'TruncationTest.txt'. self should: [file contents = '1234']. ] ensure: [ file close. FileDirectory default deleteFileNamed: file name ifAbsent:[] ]. ! Item was changed: + ----- Method: FileStreamTest>>testNextChunkOutOfBounds (in category 'tests') ----- - ----- Method: FileStreamTest>>testNextChunkOutOfBounds (in category 'as yet unclassified') ----- testNextChunkOutOfBounds "Ensure that nextChunkPut:/nextChunk works properly on a caching file" | file text read | [file := FileStream forceNewFileNamed: 'testNextChunkOutOfBounds'. text := 'this is a chunkful of text'. file nextChunkPut: text. read := [file position: 999999; nextChunkText] valueWithin: 1 seconds onTimeout:[nil]. self assert: read = ''. ] ensure:[file close. FileDirectory default deleteFileNamed: file name ifAbsent:[]].! Item was changed: + ----- Method: FileStreamTest>>testNextLine (in category 'tests') ----- - ----- Method: FileStreamTest>>testNextLine (in category 'as yet unclassified') ----- testNextLine | filename lines text | filename := 'filestream.tst'. lines := #('line 1' ' and line 2' '' 'fourth'). text := lines first , String cr , lines second , String crlf , lines third , String lf , lines fourth. [ | file | (StandardFileStream forceNewFileNamed: filename) nextPutAll: text; close. file := StandardFileStream readOnlyFileNamed: filename. lines do: [:e | self assert: file nextLine = e]. self assert: file nextLine = nil. file close] ensure: [FileDirectory default deleteFileNamed: filename ifAbsent: [] ]! Item was changed: + ----- Method: FileStreamTest>>testPositionPastEndIsAtEnd (in category 'tests') ----- - ----- Method: FileStreamTest>>testPositionPastEndIsAtEnd (in category 'as yet unclassified') ----- testPositionPastEndIsAtEnd "Tests that a file positioned after its end responds true to #atEnd" | filename file | filename := 'filestream.tst'. file := StandardFileStream forceNewFileNamed: filename. [ file position: 1000. self assert: file atEnd. ] ensure:[ file close. FileDirectory default deleteFileNamed: filename ifAbsent:[]. ].! Item was changed: + ----- Method: FileStreamTest>>testReadIntoStartingAtCount (in category 'tests') ----- - ----- Method: FileStreamTest>>testReadIntoStartingAtCount (in category 'as yet unclassified') ----- testReadIntoStartingAtCount | filename file | filename := 'filestream.tst'. [ | writeBuffer readBuffer bytesRead | writeBuffer := (ByteArray new: 2500) atAllPut: 1 ; yourself. (StandardFileStream forceNewFileNamed: filename) binary ; nextPutAll: writeBuffer ; close. file := StandardFileStream readOnlyFileNamed: filename. readBuffer := ByteArray new: 400. bytesRead := file readInto: readBuffer startingAt: 10 count: 100. self assert: bytesRead = 100. "quick test" self assert: (readBuffer occurrencesOf: 1) = 100. "compare test" 1 to: readBuffer size do: [ : n | self assert: (readBuffer at: n) = ((n between: 10 and: 10 + 100 - 1) ifTrue: [ writeBuffer at: n ] ifFalse: [ 0 ]) ] ] ensure: [ file ifNotNil: [ file close ]. FileDirectory default deleteFileNamed: filename ifAbsent: [ "ok" ] ]! Item was changed: + ----- Method: MacFileDirectoryTest>>testMacFileDirectory (in category 'tests') ----- - ----- Method: MacFileDirectoryTest>>testMacFileDirectory (in category 'test') ----- testMacFileDirectory "(self run: #testMacFileDirectory)" "This fails before the the fix if the Squeak directory is on the root directory like: 'HardDisk:Squeak' But should work both before and after the fix of John if there is several directories in the hieracry: HardDisk:User:Squeak" "If somebody can find a way to make the test failed all the time when the fix is not present we should replace it" self assert: (FileDirectory default fullName) = (FileDirectory default fullNameFor: (FileDirectory default fullName))! Item was changed: + ----- Method: MacFileDirectoryTest>>testMacIsAbsolute (in category 'tests') ----- - ----- Method: MacFileDirectoryTest>>testMacIsAbsolute (in category 'test') ----- testMacIsAbsolute "(self selector: #testMacIsAbsolute) run" self deny: (MacFileDirectory isAbsolute: 'Volumes'). self assert: (MacFileDirectory isAbsolute: 'Volumes:Data:Stef'). self deny: (MacFileDirectory isAbsolute: ':Desktop:test.st')! Item was changed: + ----- Method: MacFileDirectoryTest>>testMakeAbsolute (in category 'tests') ----- - ----- Method: MacFileDirectoryTest>>testMakeAbsolute (in category 'test') ----- testMakeAbsolute self assert: (MacFileDirectory isAbsolute: (MacFileDirectory makeAbsolute: 'Data')). self assert: (MacFileDirectory isAbsolute: (MacFileDirectory makeAbsolute: ':Data')). ! Item was added: + TestCase subclass: #RemoteStringTest + instanceVariableNames: '' + classVariableNames: '' + poolDictionaries: '' + category: 'Tests-Files'! Item was added: + ----- Method: RemoteStringTest>>testMultipleStringWritesAndReadUsingDifferentFiles (in category 'tests') ----- + testMultipleStringWritesAndReadUsingDifferentFiles + + | changesFileIndex sourceFile readOnlySourceFile stringsToWrite writtenRemoteStrings | + changesFileIndex := 2. + sourceFile := SourceFiles at: changesFileIndex. + "Ensure that CurrentReadOnlySourceFile is opened." + readOnlySourceFile := CurrentReadOnlySourceFiles at: changesFileIndex. + "Write a new string." + stringsToWrite := (1 to: 5) collect: [ :each | + Time utcMicrosecondClock asString, '_', each asString ]. + writtenRemoteStrings := stringsToWrite collect: [ :each | + RemoteString + newString: each + onFileNumber: changesFileIndex + toFile: sourceFile ]. + "Read the new chunk from CurrentReadOnlySourceFile." + writtenRemoteStrings size to: 1 by: -1 do: [ :index | + | writtenRemoteString readOnlyRemoteString | + writtenRemoteString := writtenRemoteStrings at: index. + readOnlyRemoteString := RemoteString + newFileNumber: changesFileIndex + position: writtenRemoteString position. + self assert: (stringsToWrite at: index) equals: readOnlyRemoteString text asString ]! Item was added: + ----- Method: RemoteStringTest>>testStringWriteAndReadUsingDifferentFiles (in category 'tests') ----- + testStringWriteAndReadUsingDifferentFiles + + | changesFileIndex sourceFile readOnlySourceFile stringToWrite writtenRemoteString readOnlyRemoteString | + changesFileIndex := 2. + sourceFile := SourceFiles at: changesFileIndex. + "Ensure that CurrentReadOnlySourceFile is opened." + readOnlySourceFile := CurrentReadOnlySourceFiles at: changesFileIndex. + "Write a new string." + stringToWrite := Time utcMicrosecondClock asString. + writtenRemoteString := RemoteString + newString: stringToWrite + onFileNumber: changesFileIndex + toFile: sourceFile. + "Read the new chunk from CurrentReadOnlySourceFile." + readOnlyRemoteString := RemoteString + newFileNumber: changesFileIndex + position: writtenRemoteString position. + self assert: stringToWrite equals: readOnlyRemoteString text asString! Item was changed: + ----- Method: StandardSourceFileArrayTest>>testAddressRange (in category 'tests') ----- - ----- Method: StandardSourceFileArrayTest>>testAddressRange (in category 'testing') ----- testAddressRange "Test source pointer to file position address translation across the full address range" | sf | sf := StandardSourceFileArray new. (16r1000000 to: 16r4FFFFFF by: 811) do: [:e | | i a p | i := sf fileIndexFromSourcePointer: e. p := sf filePositionFromSourcePointer: e. a := sf sourcePointerFromFileIndex: i andPosition: p. self assert: a = e] ! Item was changed: + ----- Method: StandardSourceFileArrayTest>>testChangesFileAddressRange (in category 'tests') ----- - ----- Method: StandardSourceFileArrayTest>>testChangesFileAddressRange (in category 'testing') ----- testChangesFileAddressRange "Test file position to source pointer address translation for the changes file" | sf a | sf := StandardSourceFileArray new. (0 to: 16r1FFFFFF by: 811) do: [:e | | a2 i p | a := sf sourcePointerFromFileIndex: 2 andPosition: e. i := sf fileIndexFromSourcePointer: a. self assert: i = 2. p := sf filePositionFromSourcePointer: a. self assert: p = e. a2 := sf sourcePointerFromFileIndex: 2 andPosition: p. self assert: a2 = a]. (0 to: 16rFFFFFF by: 811) do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r2000000 and: 16r2FFFFFF)]. (16r1000000 to: 16r1FFFFFF by: 811) do: [:e | a := sf sourcePointerFromFileIndex: 2 andPosition: e. self assert: (a between: 16r4000000 and: 16r4FFFFFF)] ! Item was changed: + ----- Method: StandardSourceFileArrayTest>>testFileIndexFromSourcePointer (in category 'tests') ----- - ----- Method: StandardSourceFileArrayTest>>testFileIndexFromSourcePointer (in category 'testing') ----- testFileIndexFromSourcePointer "Test derivation of file index for sources or changes file from source pointers" | sf | sf := StandardSourceFileArray new. "sources file mapping" self assert: 1 = (sf fileIndexFromSourcePointer: 16r1000000). self assert: 1 = (sf fileIndexFromSourcePointer: 16r1000013). self assert: 1 = (sf fileIndexFromSourcePointer: 16r1FFFFFF). self assert: 1 = (sf fileIndexFromSourcePointer: 16r3000000). self assert: 1 = (sf fileIndexFromSourcePointer: 16r3000013). self assert: 1 = (sf fileIndexFromSourcePointer: 16r3FFFFFF). (16r1000000 to: 16r1FFFFFF by: 811) do: [:e | self assert: 1 = (sf fileIndexFromSourcePointer: e)]. (16r3000000 to: 16r3FFFFFF by: 811) do: [:e | self assert: 1 = (sf fileIndexFromSourcePointer: e)]. "changes file mapping" self assert: 2 = (sf fileIndexFromSourcePointer: 16r2000000). self assert: 2 = (sf fileIndexFromSourcePointer: 16r2000013). self assert: 2 = (sf fileIndexFromSourcePointer: 16r2FFFFFF). self assert: 2 = (sf fileIndexFromSourcePointer: 16r4000000). self assert: 2 = (sf fileIndexFromSourcePointer: 16r4000013). self assert: 2 = (sf fileIndexFromSourcePointer: 16r4FFFFFF). (16r2000000 to: 16r2FFFFFF by: 811) do: [:e | self assert: 2 = (sf fileIndexFromSourcePointer: e)]. (16r4000000 to: 16r4FFFFFF by: 811) do: [:e | self assert: 2 = (sf fileIndexFromSourcePointer: e)]. "the following numeric ranges are unused but currently produces results as follows" self assert: 0 = (sf fileIndexFromSourcePointer: 16r0000000). self assert: 0 = (sf fileIndexFromSourcePointer: 16r0000013). self assert: 0 = (sf fileIndexFromSourcePointer: 16r0FFFFFF) ! Item was changed: + ----- Method: StandardSourceFileArrayTest>>testFilePositionFromSourcePointer (in category 'tests') ----- - ----- Method: StandardSourceFileArrayTest>>testFilePositionFromSourcePointer (in category 'testing') ----- testFilePositionFromSourcePointer "Test derivation of file position for sources or changes file from source pointers" | sf | sf := StandardSourceFileArray new. "sources file" self assert: 0 = (sf filePositionFromSourcePointer: 16r1000000). self assert: 16r13 = (sf filePositionFromSourcePointer: 16r1000013). self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r1FFFFFF). self assert: 16r1000000 = (sf filePositionFromSourcePointer: 16r3000000). self assert: 16r1000013 = (sf filePositionFromSourcePointer: 16r3000013). self assert: 16r1FFFFFF = (sf filePositionFromSourcePointer: 16r3FFFFFF). "changes file" self assert: 0 = (sf filePositionFromSourcePointer: 16r2000000). self assert: 16r13 = (sf filePositionFromSourcePointer: 16r2000013). self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r2FFFFFF). self assert: 16r1000000 = (sf filePositionFromSourcePointer: 16r4000000). self assert: 16r1000013 = (sf filePositionFromSourcePointer: 16r4000013). self assert: 16r1FFFFFF = (sf filePositionFromSourcePointer: 16r4FFFFFF). "the following numeric ranges are unused but currently produces results as follows" self assert: 0 = (sf filePositionFromSourcePointer: 16r0000000). self assert: 16r13 = (sf filePositionFromSourcePointer: 16r0000013). self assert: 16rFFFFFF = (sf filePositionFromSourcePointer: 16r0FFFFFF) ! Item was changed: + ----- Method: StandardSourceFileArrayTest>>testSourcePointerFromFileIndexAndPosition (in category 'tests') ----- - ----- Method: StandardSourceFileArrayTest>>testSourcePointerFromFileIndexAndPosition (in category 'testing') ----- testSourcePointerFromFileIndexAndPosition "Test valid input ranges" | sf | sf := StandardSourceFileArray new. self should: [sf sourcePointerFromFileIndex: 0 andPosition: 0] raise: Error. self should: [sf sourcePointerFromFileIndex: 0 andPosition: 3] raise: Error. self should: [sf sourcePointerFromFileIndex: 1 andPosition: -1] raise: Error. self should: [sf sourcePointerFromFileIndex: 1 andPosition: 16r2000000] raise: Error. self should: [sf sourcePointerFromFileIndex: 3 andPosition: 0] raise: Error. self should: [sf sourcePointerFromFileIndex: 4 andPosition: 0] raise: Error. self assert: 16r1000000 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 0). self assert: 16r1000013 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r13). self assert: 16r1FFFFFF equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16rFFFFFF). self assert: 16r2000000 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 0). self assert: 16r2000013 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r13). self assert: 16r2FFFFFF equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16rFFFFFF). self assert: 16r3000000 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r1000000). self assert: 16r3000013 equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r1000013). self assert: 16r3FFFFFF equals: (sf sourcePointerFromFileIndex: 1 andPosition: 16r1FFFFFF). self assert: 16r4000000 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r1000000). self assert: 16r4000013 equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r1000013). self assert: 16r4FFFFFF equals: (sf sourcePointerFromFileIndex: 2 andPosition: 16r1FFFFFF).! Item was changed: + ----- Method: StandardSourceFileArrayTest>>testSourcesFileAddressRange (in category 'tests') ----- - ----- Method: StandardSourceFileArrayTest>>testSourcesFileAddressRange (in category 'testing') ----- testSourcesFileAddressRange "Test file position to source pointer address translation for the sources file" | sf a | sf := StandardSourceFileArray new. (0 to: 16r1FFFFFF by: 811) do: [:e | | a2 p i | a := sf sourcePointerFromFileIndex: 1 andPosition: e. i := sf fileIndexFromSourcePointer: a. self assert: i = 1. p := sf filePositionFromSourcePointer: a. self assert: p = e. a2 := sf sourcePointerFromFileIndex: 1 andPosition: p. self assert: a2 = a]. (0 to: 16rFFFFFF by: 811) do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r1000000 and: 16r1FFFFFF)]. (16r1000000 to: 16r1FFFFFF by: 811) do: [:e | a := sf sourcePointerFromFileIndex: 1 andPosition: e. self assert: (a between: 16r3000000 and: 16r3FFFFFF)] ! Item was changed: + ----- Method: UnixFileDirectoryTests>>testCheckNameFixErrors (in category 'tests') ----- - ----- Method: UnixFileDirectoryTests>>testCheckNameFixErrors (in category 'testing') ----- testCheckNameFixErrors | directory bigName maxLength | "Do not use #on:, it will use the default directory class, which might be different on this platform." directory := UnixFileDirectory new setPathName: '.'. self assert: ('abc' = (directory checkName: 'abc' fixErrors: false)). self assert: ('abc' = (directory checkName: 'abc' fixErrors: true)). "These test the superclass implementation." self should: [directory checkName: '' fixErrors: false] raise: Error. self should: [directory checkName: '' fixErrors: true] raise: Error. maxLength := directory class maxFileNameLength. bigName := String streamContents: [:s | maxLength + 1 timesRepeat: [s nextPut: $1]]. self should: [directory checkName: bigName fixErrors: false] raise: Error. "#contractTo: seems a little odd, but it is what #checkName:fixErrors: uses" self assert: ((bigName contractTo: maxLength) = (directory checkName: bigName fixErrors: true)). "UnixFileDirectory specific tests" "UnixFileDirectory will turn / into #, if told to fix errors." self assert: ('a#b#c' = (directory checkName: 'a/b/c' fixErrors: true)). "And it will raise an error if it does not fix errors." self should: [(directory checkName: 'a/b/c' fixErrors: false)] raise: Error! |
Free forum by Nabble | Edit this page |