Skip to content

Commit

Permalink
60115
Browse files Browse the repository at this point in the history
18598 avoid DNU when reapplying rules targeting a package
	https://pharo.fogbugz.com/f/cases/18598

18601 #haltIfNil and deprecated:transformWith: have wrong visual
	https://pharo.fogbugz.com/f/cases/18601

18593 Remove Pharo references to Smalltalk evaluate:
	https://pharo.fogbugz.com/f/cases/18593

15859 review rule RBUncommonMessageSendRule
	https://pharo.fogbugz.com/f/cases/15859

http://files.pharo.org/image/60/60115.zip
  • Loading branch information
Jenkins Build Server authored and ci committed Jun 26, 2016
1 parent d8eeee3 commit 0194d49
Show file tree
Hide file tree
Showing 13 changed files with 50 additions and 50 deletions.
Expand Up @@ -2,7 +2,11 @@ deprecated: anExplanationString transformWith: aRule
| rewriteRule method context node |
self class environment
at: #RBParseTreeRewriter
ifAbsent: [ ^self deprecated: anExplanationString ].
ifAbsent: [ ^ (Deprecation
method: thisContext sender method
explanation: anExplanationString
on: 'unknown'
in: 'unknown') signal ].
context := thisContext sender sender.
method := context method.
node := context sourceNodeExecuted.
Expand Down
@@ -1,2 +1,3 @@
haltIfNil
self halt
<debuggerCompleteToSender>
Halt now

This file was deleted.

This file was deleted.

@@ -0,0 +1,2 @@
isUnknownCapitalizedMessage: aSelector
^ aSelector first isUppercase and: [ aSelector isSelectorSymbol not ]
@@ -1,6 +1,6 @@
checkMethod: aMethod
aMethod messages do: [ :each |
(each isEmpty or: [ each first isUppercase or: [ literalNames includes: each ] ]) ifTrue: [
(each isEmpty or: [ (self isUnknownCapitalizedMessage: each) or: [ literalNames includes: each ] ]) ifTrue: [
result
addMethod: aMethod;
addSearchString: each ] ]
@@ -1,2 +1,2 @@
testUncommonMessageSend
self ruleFor: self currentSelector
self ruleFor: self currentSelector plusSelectors: {#uncommonMessageSend2}
@@ -0,0 +1,5 @@
uncommonMessageSend2
|a|
a:=3
Object new.
^ a
@@ -1,4 +1,4 @@
script60114
script60115

^ 'AST-Core-TheIntegrator.430.mcz
AST-Tests-Core-TheIntegrator.99.mcz
Expand Down Expand Up @@ -132,7 +132,7 @@ IssueTracking-TheIntegrator.6.mcz
IssueTracking-Tests-TheIntegrator.3.mcz
Jobs-TheIntegrator.30.mcz
JobsTests-TheIntegrator.2.mcz
Kernel-TheIntegrator.2354.mcz
Kernel-TheIntegrator.2355.mcz
Kernel-Rules-TheIntegrator.6.mcz
Kernel-Tests-TheIntegrator.85.mcz
Kernel-Tests-Rules-TheIntegrator.3.mcz
Expand Down Expand Up @@ -248,11 +248,11 @@ Random-Tests-TheIntegrator.4.mcz
RecentSubmissions-TheIntegrator.244.mcz
Refactoring-Changes-TheIntegrator.67.mcz
Refactoring-Core-TheIntegrator.320.mcz
Refactoring-Critics-TheIntegrator.275.mcz
Refactoring-Critics-TheIntegrator.276.mcz
Refactoring-Environment-TheIntegrator.84.mcz
Refactoring-Tests-Changes-MarcusDenker.38.mcz
Refactoring-Tests-Changes-TheIntegrator.40.mcz
Refactoring-Tests-Core-TheIntegrator.135.mcz
Refactoring-Tests-Critics-TheIntegrator.41.mcz
Refactoring-Tests-Critics-TheIntegrator.44.mcz
Refactoring-Tests-Environment-TheIntegrator.27.mcz
Reflectivity-TheIntegrator.302.mcz
Reflectivity-Examples-TheIntegrator.35.mcz
Expand Down Expand Up @@ -350,7 +350,7 @@ Text-Scanning-TheIntegrator.33.mcz
Text-Tests-EstebanLorenzano.7.mcz
Tool-Base-TheIntegrator.161.mcz
Tool-Catalog-TheIntegrator.40.mcz
Tool-CriticBrowser-TheIntegrator.30.mcz
Tool-CriticBrowser-TheIntegrator.31.mcz
Tool-DependencyAnalyser-ChristopheDemarey.28.mcz
Tool-DependencyAnalyser-Test-ChristopheDemarey.11.mcz
Tool-DependencyAnalyser-UI-ChristopheDemarey.43.mcz
Expand Down

This file was deleted.

@@ -0,0 +1,15 @@
update60115
"self new update60115"
self withUpdateLog: '18598 avoid DNU when reapplying rules targeting a package
https://pharo.fogbugz.com/f/cases/18598
18601 #haltIfNil and deprecated:transformWith: have wrong visual
https://pharo.fogbugz.com/f/cases/18601
18593 Remove Pharo references to Smalltalk evaluate:
https://pharo.fogbugz.com/f/cases/18593
15859 review rule RBUncommonMessageSendRule
https://pharo.fogbugz.com/f/cases/15859'.
self loadTogether: self script60115 merge: false.
self flushCaches.
@@ -1,15 +1,12 @@
commentForCurrentUpdate
^ '18614 add a "Debug" menu for halt / breakpoints
https://pharo.fogbugz.com/f/cases/18614
^ '18598 avoid DNU when reapplying rules targeting a package
https://pharo.fogbugz.com/f/cases/18598
18599 use sendsAnySelectorOf: in RBBadMessageRule
https://pharo.fogbugz.com/f/cases/18599
18601 #haltIfNil and deprecated:transformWith: have wrong visual
https://pharo.fogbugz.com/f/cases/18601
18611 Fix warnings that refer to inexistant methods (maxExternalObjects & maxExternalObjectsSilently:)
https://pharo.fogbugz.com/f/cases/18611
18593 Remove Pharo references to Smalltalk evaluate:
https://pharo.fogbugz.com/f/cases/18593
18305 MCWorkingCopyBrowser class>>#order would benefit to have a comment
https://pharo.fogbugz.com/f/cases/18305
18605 add DoOnlyOnceIconStyler
https://pharo.fogbugz.com/f/cases/18605'
15859 review rule RBUncommonMessageSendRule
https://pharo.fogbugz.com/f/cases/15859'
Expand Up @@ -2,7 +2,9 @@ removeFalsePositive: aCritic forRule: aRule

(falsePositives includesKey: aRule)
ifFalse: [^ self].
(falsePositiveClasses includes: aCritic criticTheNonMetaclassClass)
ifTrue: [^ self].
[ (falsePositiveClasses includes: aCritic criticTheNonMetaclassClass)
ifTrue: [^ self] ]
on: MessageNotUnderstood
do: [ ^ self "#criticTheNonMetaclassClass makes no sense on a Package, ignore"].
(falsePositives at: aRule) remove: aCritic ifAbsent: [^ self].
self updateBrowser
self updateBrowser

0 comments on commit 0194d49

Please sign in to comment.