Skip to content

Commit

Permalink
ifErrorDo: should be onErrorDo: and deprecate with transform
Browse files Browse the repository at this point in the history
1. Rename #ifErrorDo: into #onErrorDo:
2. use #onErrorDo: in deprecated methods like #ifError: and  #ifErrorDo:
     and move these to Deprecated90 package
3. have a transformation rule for the deprecations in  #ifError: and  #ifErrorDo:
4. Add a test #testOnErrorDo

Fix #6157
  • Loading branch information
astares committed Apr 8, 2020
1 parent 944aa46 commit 26ff285
Show file tree
Hide file tree
Showing 30 changed files with 78 additions and 75 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -180,7 +180,7 @@ ClyCompositeScopeTest >> testCreationOnTwoSubscopesOfDifferentObjects [
ClyCompositeScopeTest >> testEmptySubscopesAreForbidden [

[ClyCompositeScope on: #().
self assert: false description: 'empty subscopes should be forbidden'] ifErrorDo: [].
self assert: false description: 'empty subscopes should be forbidden'] onErrorDo: [].

]

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -136,7 +136,7 @@ ClyTypedQueryTestCase >> testForbidCreationOnScopeWhichNotSupportIt [

[query scope: (ClyCompositeScope in: environment).
self assert: false description: 'Query should be supported by scope'
] ifErrorDo: [].
] onErrorDo: [].

]

Expand All @@ -145,7 +145,7 @@ ClyTypedQueryTestCase >> testForbidCreationOnScopeWithoutEnvironment [
[
query scope: (ClyScopeExample ofAll: {}).
self assert: false description: 'Query should be only created on scope bound to concrete environment']
ifErrorDo: [ ]
onErrorDo: [ ]
]

{ #category : #tests }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ ClyUnionQueryTest >> testCreationWithSingleSubqueryButAnotherResult [
ClyUnionQueryTest >> testEmptySubqueriesAreForbidden [

[query subqueries: {}.
self assert: false description: 'empty subqueries should be forbidden'] ifErrorDo: [].
self assert: false description: 'empty subqueries should be forbidden'] onErrorDo: [].
]

{ #category : #tests }
Expand Down
2 changes: 1 addition & 1 deletion src/Calypso-SystemQueries/ClyQueryBrowserFilter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ ClyQueryBrowserFilter >> matchesByScript: anObject [
scriptBlock ifNil: [ self createBlockFromPattern].
badScript ifTrue: [ ^true ].

^[(scriptBlock value: anObject) ~~ false] ifErrorDo: [ false ]
^[(scriptBlock value: anObject) ~~ false] onErrorDo: [ false ]
]

{ #category : #testing }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ QueryAnnotationsFromClassTest >> testWhenAnnotationFailsCheckForForbiddenPropert

| annotations ann |
[ ClassAnnotationExampleWithFailedForbiddenCheck new isForbidden.
self assert: false description: 'should fail' ] ifErrorDo: [ ].
self assert: false description: 'should fail' ] onErrorDo: [ ].

annotations := ClassWithForbiddenAnnotationExample classAnnotations.
self assert: annotations size equals: 2. "one forbidden and one broken"
Expand Down
2 changes: 1 addition & 1 deletion src/Debugger-Model/DebugSession.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -228,7 +228,7 @@ DebugSession >> keepAlive: anObjectThatWantsToKeepMeAlive [
DebugSession >> logStackToFileIfNeeded [
self class logDebuggerStackToFile ifFalse: [ ^self ].

[[Smalltalk logError: name inContext: interruptedContext ] ifErrorDo: [ ]]
[[Smalltalk logError: name inContext: interruptedContext ] onErrorDo: [ ]]
valueWithin: 100 milliSeconds onTimeout: [ ]
]

Expand Down
15 changes: 15 additions & 0 deletions src/Deprecated90/BlockClosure.extension.st
Original file line number Diff line number Diff line change
@@ -0,0 +1,15 @@
Extension { #name : #BlockClosure }

{ #category : #'*Deprecated90' }
BlockClosure >> ifError: errorHandlerBlock [

self deprecated: 'Use #onErrorDo: instead.' transformWith: '`@receiver ifError: `@arg' -> '`@receiver onErrorDo: `@arg'.
^ self onErrorDo: errorHandlerBlock
]

{ #category : #'*Deprecated90' }
BlockClosure >> ifErrorDo: errorHandlerBlock [

self deprecated: 'Use #onErrorDo: instead.' transformWith: '`@receiver ifErrorDo: `@arg' -> '`@receiver onErrorDo: `@arg'.
^ self onErrorDo: errorHandlerBlock
]
2 changes: 1 addition & 1 deletion src/DeprecatedFileStream/FileStream.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -518,7 +518,7 @@ FileStream class >> voidStdioFiles [
each name asFileReference delete
]
]
] ifErrorDo: [ ].
] onErrorDo: [ ].
]
].

Expand Down
2 changes: 1 addition & 1 deletion src/EmergencyEvaluator/Transcripter.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -228,7 +228,7 @@ Transcripter >> readEvalPrint [
ifFalse: [self cr; show: 'Only one level of revert currently supported']]
ifFalse: [self cr;
show: ([self class compiler evaluate: line]
ifErrorDo: [:err | err description])]].
onErrorDo: [:err | err description])]].
self cr; show: 'Done'.

]
Expand Down
2 changes: 1 addition & 1 deletion src/JenkinsTools-Core/HDTestReport.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -258,7 +258,7 @@ HDTestReport >> stackTraceString: err of: aTestCase [
| context |
context := err signalerContext.
[ context isNil or: [ context receiver == aTestCase and: [ context methodSelector == #runCase ] ] ] whileFalse: [
[str print: context; lf.] ifErrorDo: [ str nextPutAll: 'PRINTING ERROR'; lf].
[str print: context; lf.] onErrorDo: [ str nextPutAll: 'PRINTING ERROR'; lf].
context := context sender ] ]
]

Expand Down
2 changes: 1 addition & 1 deletion src/Kernel-Tests-Extended/MutexTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ MutexTest >> testFailedCriticalSectionShouldUnblockWaitingOne [

processHoldingMutex := self fork: [[
mutex critical: [ semaphoreToHoldMutex wait. "here we grab mutex and control it with semaphore"
self error: 'critical section failed' ]] ifErrorDo: []].
self error: 'critical section failed' ]] onErrorDo: []].
self waitLastProcessLock. "wait until first process grabs the mutex"

self fork: [mutex critical: [ lastCriticalExecuted := true ]].
Expand Down
20 changes: 13 additions & 7 deletions src/Kernel-Tests/BlockClosureTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -143,11 +143,11 @@ BlockClosureTest >> testCullCullCullCull [
BlockClosureTest >> testNew [
self should: [Context new: 5] raise: Error.
[Context new: 5]
ifErrorDo: [:error | self assert: error description equals: 'Error: Contexts must only be created with newForMethod:'].
onErrorDo: [:error | self assert: error description equals: 'Error: Contexts must only be created with newForMethod:'].
[Context new]
ifErrorDo: [:error | self assert: error description equals: 'Error: Contexts must only be created with newForMethod:'].
onErrorDo: [:error | self assert: error description equals: 'Error: Contexts must only be created with newForMethod:'].
[Context basicNew]
ifErrorDo: [:error | self assert: error description equals: 'Error: Contexts must only be created with newForMethod:'].
onErrorDo: [:error | self assert: error description equals: 'Error: Contexts must only be created with newForMethod:'].

]

Expand All @@ -157,8 +157,14 @@ BlockClosureTest >> testNoArguments [
"avoid compile error in GemStone"
block1 := [ :arg | 1 + 2 ].
block2 := [ :arg1 :arg2 | 1 + 2 ].
[ 10 timesRepeat: block1 ] ifErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 1 argument, but was called with 0 arguments.' ].
[ 10 timesRepeat: block2 ] ifErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 2 arguments, but was called with 0 arguments.' ]
[ 10 timesRepeat: block1 ] onErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 1 argument, but was called with 0 arguments.' ].
[ 10 timesRepeat: block2 ] onErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 2 arguments, but was called with 0 arguments.' ]
]

{ #category : #tests }
BlockClosureTest >> testOnErrorDo [

self assert: ([1 foo ] onErrorDo: [:err | 'huh?']) equals: 'huh?'
]

{ #category : #'tests - on-fork' }
Expand Down Expand Up @@ -270,8 +276,8 @@ BlockClosureTest >> testOneArgument [
| c |
c := OrderedCollection new.
c add: 'hello'.
[ c do: [ 1 + 2 ] ] ifErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 0 arguments, but was called with 1 argument.' ].
[ c do: [ :arg1 :arg2 | 1 + 2 ] ] ifErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 2 arguments, but was called with 1 argument.' ]
[ c do: [ 1 + 2 ] ] onErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 0 arguments, but was called with 1 argument.' ].
[ c do: [ :arg1 :arg2 | 1 + 2 ] ] onErrorDo: [ :err | self assert: err description equals: 'ArgumentsCountMismatch: This block accepts 2 arguments, but was called with 1 argument.' ]
]

{ #category : #'tests - printing' }
Expand Down
2 changes: 1 addition & 1 deletion src/Kernel-Tests/SemaphoreTest.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ SemaphoreTest >> testCritical [
SemaphoreTest >> testCriticalIfError [
| lock |
lock := Semaphore forMutualExclusion.
[lock critical: [self criticalError ifErrorDo:[]]] forkAt: Processor userInterruptPriority.
[lock critical: [self criticalError onErrorDo:[]]] forkAt: Processor userInterruptPriority.
self assert: lock isSignaled
]

Expand Down
46 changes: 14 additions & 32 deletions src/Kernel/BlockClosure.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -330,38 +330,6 @@ BlockClosure >> ifCurtailed: aBlock [
^result
]

{ #category : #evaluating }
BlockClosure >> ifError: errorHandlerBlock [
"Evaluate the block represented by the receiver, and normally return it's value. If an error occurs, the errorHandlerBlock is evaluated, and it's value is instead returned. The errorHandlerBlock must accept zero, one, or two parameters (the error message and the receiver)."
"Examples:
[1 whatsUpDoc] ifError: [:err :rcvr | 'huh?'].
[1 / 0] ifError: [:err :rcvr |
'ZeroDivide' = err
ifTrue: [Float infinity]
ifFalse: [self error: err]]
"

self deprecated: 'Please use ifErrorDo: instead'.

^ self on: Error do: [:ex |
errorHandlerBlock cull: ex description cull: ex receiver]
]

{ #category : #evaluating }
BlockClosure >> ifErrorDo: errorHandlerBlock [
"Evaluate the block represented by the receiver, and normally return it's value. If an error occurs, the errorHandlerBlock is evaluated, and it's value is instead returned. The errorHandlerBlock must accept zero or one parameter (the error object)."
"Examples:
[1 whatsUpDoc] ifErrorDo: [:err | 'huh?'].
[1 / 0] ifErrorDo: [:err |
ZeroDivide = err class
ifTrue: [Float infinity]
ifFalse: [self error: err]]
"

^ self on: Error do: [:ex |
errorHandlerBlock cull: ex]
]

{ #category : #accessing }
BlockClosure >> isBlock [

Expand Down Expand Up @@ -549,6 +517,20 @@ BlockClosure >> onDNU: selector do: handleBlock [
]
]

{ #category : #evaluating }
BlockClosure >> onErrorDo: errorHandlerBlock [
"Evaluate the block represented by the receiver, and normally return it's value. If an error occurs, the errorHandlerBlock is evaluated, and it's value is instead returned. The errorHandlerBlock must accept zero or one parameter (the error object)."
"Examples:
[1 whatsUpDoc] onErrorDo: [:err | 'huh?'].
[1 / 0] onErrorDo: [:err |
ZeroDivide = err class
ifTrue: [Float infinity]
ifFalse: [self error: err]]
"

^ self on: Error do: [:ex | errorHandlerBlock cull: ex]
]

{ #category : #accessing }
BlockClosure >> outerContext [
^outerContext
Expand Down
8 changes: 4 additions & 4 deletions src/Kernel/Context.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1314,18 +1314,18 @@ Context >> printDetails: stream [
stream cr.
stream tab; nextPutAll: 'Receiver: '.
errorMessage := '<<error during printing>>'.
stream nextPutAll: ([receiver printStringLimitedTo: 90] ifErrorDo: [errorMessage]).
stream nextPutAll: ([receiver printStringLimitedTo: 90] onErrorDo: [errorMessage]).

stream cr; tab; nextPutAll: 'Arguments and temporary variables: '; cr.
string := [(self tempsAndValuesLimitedTo: 80 indent: 2)
padRightTo:1 with: $x] ifErrorDo: [errorMessage].
padRightTo:1 with: $x] onErrorDo: [errorMessage].
stream nextPutAll: (string allButLast).

stream cr; tab; nextPutAll: 'Receiver''s instance variables: '; cr.
receiver class allInstVarNames isEmpty ifTrue: [
stream nextPutAll: ([receiver printStringLimitedTo: 90] ifErrorDo: [ errorMessage ]).
stream nextPutAll: ([receiver printStringLimitedTo: 90] onErrorDo: [ errorMessage ]).
] ifFalse: [
[receiver longPrintOn: stream limitedTo: 80 indent: 2] ifErrorDo: [ stream nextPutAll: errorMessage ].
[receiver longPrintOn: stream limitedTo: 80 indent: 2] onErrorDo: [ stream nextPutAll: errorMessage ].
].
stream cr
]
Expand Down
2 changes: 1 addition & 1 deletion src/Kernel/Semaphore.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ Semaphore >> critical: mutuallyExcludedBlock ifError: errorBlock [
| blockValue hasError errObj |
hasError := false.
self critical:[
blockValue := mutuallyExcludedBlock ifErrorDo: [ :err |
blockValue := mutuallyExcludedBlock onErrorDo: [ :err |
hasError := true.
errObj := err.
].
Expand Down
2 changes: 1 addition & 1 deletion src/Math-Operations-Extensions/Float.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,7 @@ Float >> closeTo: num [
Float >> closeTo: num precision: aPrecision [
"Tell whether the receiver and arguments are close from each other given a precision"

num isNumber ifFalse: [ ^ [self = num] ifErrorDo: [false]].
num isNumber ifFalse: [ ^ [self = num] onErrorDo: [false]].
self = 0.0 ifTrue: [^ num abs < aPrecision].
num = 0 ifTrue: [^self abs < aPrecision].
^self = num asFloat
Expand Down
4 changes: 2 additions & 2 deletions src/Math-Operations-Extensions/Number.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -76,15 +76,15 @@ Number >> closeTo: num [
"Tell whether the receiver and arguments are close from each."

num isFloat ifTrue: [ ^ num closeTo: self asFloat ].
^ [ self = num ] ifErrorDo: [ false ]
^ [ self = num ] onErrorDo: [ false ]
]

{ #category : #'*Math-Operations-Extensions' }
Number >> closeTo: num precision: aPrecision [
"are these two numbers close?"

num isFloat ifTrue: [ ^ num closeTo: self asFloat precision: aPrecision ].
^ [ self = num ] ifErrorDo: [ false ]
^ [ self = num ] onErrorDo: [ false ]
]

{ #category : #'*Math-Operations-Extensions' }
Expand Down
4 changes: 2 additions & 2 deletions src/Monticello/MCWorkingCopy.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -63,8 +63,8 @@ MCWorkingCopy class >> infoFromDictionary: aDictionary cache: cache [
name: (aDictionary at: #name ifAbsent: [''])
id: (UUID fromString: id)
message: (aDictionary at: #message ifAbsent: [''])
date: ([Date fromString: (aDictionary at: #date)] ifErrorDo: [nil])
time: ([Time fromString: (aDictionary at: #time)] ifErrorDo: [nil])
date: ([Date fromString: (aDictionary at: #date)] onErrorDo: [nil])
time: ([Time fromString: (aDictionary at: #time)] onErrorDo: [nil])
author: (aDictionary at: #author ifAbsent: [''])
ancestors: (self ancestorsFromArray: (aDictionary at: #ancestors ifAbsent: []) cache: cache)
stepChildren: (self ancestorsFromArray: (aDictionary at: #stepChildren ifAbsent: []) cache: cache)]
Expand Down
2 changes: 1 addition & 1 deletion src/Morphic-Base/PolygonMorph.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -2074,7 +2074,7 @@ by which the dashes will move in each step of animation]' translated
initialAnswer: '{ 10. 5. Color red }'.
executableSpec isEmptyOrNil ifTrue:
[^ self stopStepping; dashedBorder: nil].
newSpec := [self class compiler evaluate: executableSpec] ifErrorDo:
newSpec := [self class compiler evaluate: executableSpec] onErrorDo:
[^ self stopStepping; dashedBorder: nil].
(newSpec first isNumber and: [newSpec second isNumber and: [newSpec third isColor]]) ifFalse:
[^ self stopStepping; dashedBorder: nil].
Expand Down
4 changes: 2 additions & 2 deletions src/Morphic-Core/PasteUpMorph.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -911,7 +911,7 @@ PasteUpMorph >> setGridSpec [
request: 'New grid origin (usually 0@0):' translated
initialAnswer: self gridOrigin printString.
response isEmpty ifTrue: [^ self].
result := [self class compiler evaluate: response] ifErrorDo: [^ self].
result := [self class compiler evaluate: response] onErrorDo: [^ self].
(result isPoint and: [(result >= (0@0))])
ifTrue: [self gridOrigin: result]
ifFalse: [self inform: ('Must be a Point with coordinates (for example 10@10)' translated )].
Expand All @@ -920,7 +920,7 @@ PasteUpMorph >> setGridSpec [
request: 'New grid spacing:' translated
initialAnswer: self gridModulus printString.
response isEmptyOrNil ifTrue: [^ self].
result := [self class compiler evaluate: response] ifErrorDo: [^ self].
result := [self class compiler evaluate: response] onErrorDo: [^ self].
(result isPoint and: [(result > (0@0)) ])
ifTrue: [self gridModulus: result]
ifFalse: [self inform: ('Must be a Point with coordinates (for example 10@10)' translated )].
Expand Down
2 changes: 1 addition & 1 deletion src/Morphic-Core/WorldState.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -449,7 +449,7 @@ WorldState >> displayWorld: aWorld [
WorldState >> displayWorldSafely: aWorld [
"Update this world's display and keep track of errors during draw methods."

[aWorld displayWorld] ifErrorDo: [:err |
[aWorld displayWorld] onErrorDo: [:err |
"Handle a drawing error"
| errCtx errMorph |
errCtx := thisContext.
Expand Down
2 changes: 1 addition & 1 deletion src/Multilingual-Tests/MultiFontTest.extension.st
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ MultiFontTest >> testMultistringFont [
| text p style height width |
[(TextStyle default fontArray at: JapaneseEnvironment leadingChar)
ifNil: [^ self]]
ifErrorDo: [ ^ self].
onErrorDo: [ ^ self].
text := ((#(20983874 20983876 20983878 )
collect: [:e | e asCharacter])
as: String) asText.
Expand Down
2 changes: 1 addition & 1 deletion src/Network-Mail/MailMessage.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -865,7 +865,7 @@ MailMessage >> text [
MailMessage >> time [
| dateField |
dateField := (self fieldNamed: 'date' ifAbsent: [ ^0 ]) mainValue.
^ [self timeFrom: dateField] ifErrorDo: [Date today asSeconds].
^ [self timeFrom: dateField] onErrorDo: [Date today asSeconds].

]

Expand Down
4 changes: 2 additions & 2 deletions src/OSWindow-SDL2/SDL2.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -108,7 +108,7 @@ SDL2 class >> findSDL2 [
'SDL2.dll' "Windows"
) do: [ :eachName |
[ (self checkLibraryName: eachName) ifTrue: [ ^ eachName ] ]
ifErrorDo: [nil] ].
onErrorDo: [nil] ].
self error: 'Failed to find SDL2 library.'
]

Expand Down Expand Up @@ -236,7 +236,7 @@ SDL2 class >> initVideo [
{ #category : #common }
SDL2 class >> isAvailable [
^ [ (ExternalAddress loadSymbol: 'SDL_Init' from: SDL2 moduleName) notNil ]
ifErrorDo: [ false ]
onErrorDo: [ false ]
]

{ #category : #'game controller' }
Expand Down
2 changes: 1 addition & 1 deletion src/System-Sources/PharoFilesOpener.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -88,7 +88,7 @@ PharoFilesOpener >> changesName [

{ #category : #helper }
PharoFilesOpener >> ignoreIfFail: aBlock [
^ [ aBlock value ] ifErrorDo: [ ]
^ [ aBlock value ] onErrorDo: [ ]
]

{ #category : #'user interaction' }
Expand Down
4 changes: 2 additions & 2 deletions src/System-Support/SmalltalkImage.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -1431,13 +1431,13 @@ SmalltalkImage >> privSaveImageWithCleanup [

[
self snapshot: true andQuit: true.
] ifErrorDo: [:e |
] onErrorDo: [:e |
'PharoDebug.log' asFileReference ensureDelete; writeStreamDo: [ :rep |
rep nextPutAll: 'Error:'; cr.
rep nextPutAll: e asString; cr.
rep nextPutAll: thisContext stack size asString.
thisContext stack copy withIndexDo: [:stck :i |
[ rep nextPutAll: i asString; space; nextPutAll: stck asString; cr] ifErrorDo: []]].
[ rep nextPutAll: i asString; space; nextPutAll: stck asString; cr] onErrorDo: []]].
Smalltalk exitFailure ]
]

Expand Down
Loading

0 comments on commit 26ff285

Please sign in to comment.