Skip to content

Commit

Permalink
Fix for issue 22729
Browse files Browse the repository at this point in the history
Added regression tests
  • Loading branch information
bouraqadi committed Dec 5, 2018
1 parent 4cd23cf commit 58ca1cf
Show file tree
Hide file tree
Showing 3 changed files with 87 additions and 2 deletions.
2 changes: 1 addition & 1 deletion src/Tool-ExternalBrowser/ExternalBrowser.class.st
Expand Up @@ -87,7 +87,7 @@ ExternalBrowser class >> serviceBrowseCode [
selector: #browseStream:
description: 'Open a "file-contents browser" on this file, allowing you to view and selectively load its code'
buttonLabel: 'Code')
argumentGetter: [ :file| file readOnlyStream ]
argumentGetter: [ :file| file readStream]
]

{ #category : #'System-FileRegistry' }
Expand Down
85 changes: 85 additions & 0 deletions src/Tool-ExternalBrowser/ExternalBrowserTest.class.st
@@ -0,0 +1,85 @@
Class {
#name : #ExternalBrowserTest,
#superclass : #TestCase,
#instVars : [
'initialWindows',
'file'
],
#category : #'Tool-ExternalBrowser-Test'
}

{ #category : #running }
ExternalBrowserTest >> assert: serviceProvider dropFileWithSuffix: suffix [
| allMatchingServices service |
allMatchingServices := serviceProvider fileReaderServicesForFile: file pathString suffix: suffix.
self deny: allMatchingServices isEmpty.
service := allMatchingServices anyOne.
self shouldnt: [service performServiceFor: file] raise: MessageNotUnderstood.

]

{ #category : #running }
ExternalBrowserTest >> classNameForTest [
^#MyWonderfulClass
]

{ #category : #running }
ExternalBrowserTest >> fileForTestContent [
^'''From Pharo7.0.0rc1 of 4 December 2018 [Build information: Pharo-7.0.0+rc1.build.1435.sha.4cd23cf7be1a90c7c52e9f8786860a6290b7c2a6 (64 Bit)] on 5 December 2018 at 9:30:34.922838 am''!
Object subclass: #', self classNameForTest,'
instanceVariableNames: ''some iv''
classVariableNames: ''''
poolDictionaries: ''''
category: #MyCategory!
!', self classNameForTest,' commentStamp: ''NouryBouraqadi 12/4/2018 17:19'' prior: 0!
My unique and explicit comment!
!', self classNameForTest,' methodsFor: ''protocol'' stamp: ''NouryBouraqadi 12/4/2018 17:12''!
myMethod
! !
'
]

{ #category : #running }
ExternalBrowserTest >> fileNameForTest [
^ 'fileForExternalBrowserTest'
]

{ #category : #running }
ExternalBrowserTest >> initFileWithSuffix: suffix [
file := FileSystem workingDirectory / self fileNameForTest, '.', suffix.
file
writeStreamDo: [ :stream | stream nextPutAll: self fileForTestContent ].
initialWindows := World windowsSatisfying: [: each| true ].
]

{ #category : #running }
ExternalBrowserTest >> setUp [
super setUp.
initialWindows := World windowsSatisfying: [: each| true ].
]

{ #category : #running }
ExternalBrowserTest >> tearDown [
| newWindows |
super tearDown.
file deleteIfAbsent: [ ].
Smalltalk at: self classNameForTest ifPresent: [ : cl | cl removeFromSystem ].
newWindows := World windowsSatisfying: [ : each | (initialWindows includes: each) not ].
newWindows do: #delete.
]

{ #category : #running }
ExternalBrowserTest >> testDropChangeFile [
self initFileWithSuffix: 'changes'.
self assert: ExternalChangesBrowser dropFileWithSuffix: 'changes'

]

{ #category : #running }
ExternalBrowserTest >> testDropStFile [
self initFileWithSuffix: 'st'.
self assert: ExternalBrowser dropFileWithSuffix: 'st'

]
2 changes: 1 addition & 1 deletion src/Tool-ExternalBrowser/ExternalChangesBrowser.class.st
Expand Up @@ -114,7 +114,7 @@ ExternalChangesBrowser class >> serviceBrowseCSOrSTFile [
selector: #openOnStream:
description: 'Open a changelist tool on this file'
buttonLabel: 'Changes')
argumentGetter: [ :stream | stream readOnlyStream ]
argumentGetter: [ :stream | stream readStream ]
]

{ #category : #'file service' }
Expand Down

0 comments on commit 58ca1cf

Please sign in to comment.