Skip to content

Commit

Permalink
Fixes: pharo-project#6500 mainly sinmple code edits and rewrite of sy…
Browse files Browse the repository at this point in the history
…mbol as block use. I reviewed my changed two times so they should be ok. Went up to RGObject
  • Loading branch information
Ducasse committed Jun 7, 2020
1 parent 7fb0fc9 commit 7439c74
Show file tree
Hide file tree
Showing 121 changed files with 162 additions and 232 deletions.
2 changes: 1 addition & 1 deletion src/AST-Core/RBMethodNode.class.st
Expand Up @@ -658,7 +658,7 @@ RBMethodNode >> selectorAndArgumentNames [

{ #category : #accessing }
RBMethodNode >> selectorParts [
^ self keywords collect: #asSymbol.
^ self keywords collect: [:each | each asSymbol]
]

{ #category : #accessing }
Expand Down
2 changes: 0 additions & 2 deletions src/AST-Core/RBParser.class.st
Expand Up @@ -619,9 +619,7 @@ RBParser >> parseLiterals: aString [
stream := (Array new: 5) writeStream.
[self atEnd or: [currentToken isSpecial and: [currentToken value = $)]]]
whileFalse: [stream nextPut: self parseLiteralArrayObject].

self atEnd ifFalse: [ ^ self parserError: 'Unknown input at end'].

^stream contents collect: [ :each | each value ]
]

Expand Down
10 changes: 1 addition & 9 deletions src/Athens-Cairo/AthensCairoSurface.class.st
Expand Up @@ -217,27 +217,19 @@ AthensCairoSurface class >> findSurface: surfaceId [
{ #category : #'instance creation' }
AthensCairoSurface class >> fromForm: aForm [
| form surface newBits |

form := aForm unhibernate; asFormOfDepth: 32.
surface := self extent: aForm extent.

"we should convert form bits with premultiplied alpha"

newBits := form bits collect:[:pixel |
newBits := form bits collect: [:pixel |
| alpha r g b|
alpha := (pixel >> 24) / 255.

r := ( (pixel bitAnd: 255) * alpha ) asInteger.
g := ( (pixel >>8 bitAnd: 255) * alpha ) asInteger.
b := ( (pixel >>16 bitAnd: 255) * alpha ) asInteger.

(pixel bitAnd: 16rFF000000) + (b<<16) + (g<<8) + r
].

LibC memCopy: newBits to: surface getDataPtr getHandle size: (form width * form height *4).

surface markDirty.

^ surface.
]

Expand Down
4 changes: 0 additions & 4 deletions src/Athens-Examples/AthensTreeDemo.class.st
Expand Up @@ -38,17 +38,13 @@ AthensTreeDemo class >> openOn: root extentBlock: extBlock childsBlock: childsBl
{ #category : #private }
AthensTreeDemo >> buildSubtreeFor: aNodeObject level: aLevel [
| node childs |

node := AthensSimpleTreeNode new.
node
subject: aNodeObject;
extent: (nodeExtentBlock value: aNodeObject).

childs := (nodeChildsBlock value: aNodeObject) collect: [ :each | self buildSubtreeFor: each level: aLevel+1 ].
node children: childs.

(self rowAt: aLevel) add: node.

^ node

]
Expand Down
2 changes: 1 addition & 1 deletion src/Athens-Morphic/AthensCompositeStrokePaint.class.st
Expand Up @@ -35,7 +35,7 @@ AthensCompositeStrokePaint >> athensFillRectangle: aRect on: anAthensCanvas [

{ #category : #private }
AthensCompositeStrokePaint >> fromBorderStyles: borders on: anAthensCanvas [
strokePaints := borders collect: [:each | (each asAthensPaintOn: anAthensCanvas ) asStrokePaintOn: anAthensCanvas]
strokePaints := borders collect: [:each | (each asAthensPaintOn: anAthensCanvas) asStrokePaintOn: anAthensCanvas]
]

{ #category : #private }
Expand Down
Expand Up @@ -46,12 +46,10 @@ BaselineOfPharoBootstrap class >> packagesRecursiveIn: aGroupName [

| allMembers allPackagesInBaseline packages groups |
allMembers := self version groups detect: [ :g | g name = aGroupName ].
allPackagesInBaseline := self version packages collect: #name.

allPackagesInBaseline := self version packages collect: [ :each | each name ].
packages := allMembers includes select: [ :aName | allPackagesInBaseline includes: aName ].
groups := allMembers includes reject: [ :aName | allPackagesInBaseline includes: aName ].

^ packages , (groups flatCollect: [:aInnerGroupName | self packagesRecursiveIn: aInnerGroupName]).
groups := allMembers includes reject: [ :aName | allPackagesInBaseline includes: aName ].
^ packages , (groups flatCollect: [ :aInnerGroupName | self packagesRecursiveIn: aInnerGroupName ]).

]

Expand Down
2 changes: 1 addition & 1 deletion src/Calypso-Browser/ClyBrowserMorph.class.st
Expand Up @@ -237,7 +237,7 @@ ClyBrowserMorph >> changeStateOf: aQueryView by: aBlock [
aQueryView changesWasInitiatedByUser ifTrue: [
newTools := OrderedCollection new.
tabManager buildToolsOn: newTools for: aQueryView createSelectionContext.
tabManager desiredSelection: (newTools collect: #class) ].
tabManager desiredSelection: (newTools collect: [:each | each class]) ].
]
]

Expand Down
7 changes: 3 additions & 4 deletions src/Calypso-Browser/ClyBrowserSearchDialogWindow.class.st
Expand Up @@ -70,10 +70,9 @@ ClyBrowserSearchDialogWindow >> defaultFocusMorph [
ClyBrowserSearchDialogWindow >> findObjectsSameAsFilter [
itemsView dataSource numberOfRows = 1 ifTrue: [
"single element means that it was found by filter and we can use it without extra search"
^itemsView dataSource allElements collect: #actualObject ].

^itemsView findItemsSameAsFilter
ifNotEmpty: [ :foundItems | foundItems collect: #actualObject ]
^ itemsView dataSource allElements collect: [:each | each actualObject] ].
^ itemsView findItemsSameAsFilter
ifNotEmpty: [ :foundItems | foundItems collect: [:each | each actualObject] ]
]

{ #category : #controlling }
Expand Down
1 change: 0 additions & 1 deletion src/Calypso-Browser/ClyCollapsedDataSource.class.st
Expand Up @@ -186,7 +186,6 @@ ClyCollapsedDataSource >> initialize [
ClyCollapsedDataSource >> initializeForBrowserStateSpanshot [
| copy |
super initializeForBrowserStateSpanshot.

copy := expandedItems collect: [ :each |
each copyForBrowserStateSnapshotOf: self ].
expandedItems := copy asSortedCollection: [ :a :b | a position < b position ]
Expand Down
6 changes: 2 additions & 4 deletions src/Calypso-Browser/ClyDataSource.class.st
Expand Up @@ -213,8 +213,7 @@ ClyDataSource >> findItemsSimilarTo: dataSourceItems [
select: [ :each | self isBasedOnQueryOf: each type ]
thenCollect: [ :each | each browserItem ].
foundItems := self itemCursor findItemsSimilarTo: relatedItems.

^foundItems collect: [:each | self createElementWith: each ]
^foundItems collect: [:each | self createElementWith: each ]
]

{ #category : #queries }
Expand Down Expand Up @@ -519,8 +518,7 @@ ClyDataSource >> updateItems: dataSourceItems [
"I update given data source items with refreshed environment items which belongs to same actual objects. If there is no actual object anymore for some of data source item I will put nil to it.
Then users should correctly process updated items"
| updatedItems |
updatedItems := itemCursor findItemsWith: (dataSourceItems collect: #actualObject).

updatedItems := itemCursor findItemsWith: (dataSourceItems collect: [:each | each actualObject]).
dataSourceItems with: updatedItems do: [ :myItem :updatedBrowserItem |
myItem updateItemWith: updatedBrowserItem ]
]
Expand Down
4 changes: 2 additions & 2 deletions src/Calypso-Browser/ClyDataSourceSelection.class.st
Expand Up @@ -279,7 +279,7 @@ ClyDataSourceSelection >> restoreTableSelectionSilently: silentSelection [

| selectionIndexes |
items := items reject: [ :each | each isRemoved ].
selectionIndexes := items collect: #globalPosition.
selectionIndexes := items collect: [:each | each globalPosition].

self
setUpSelectedRows: selectionIndexes
Expand Down Expand Up @@ -347,7 +347,7 @@ ClyDataSourceSelection >> uniformActualObjects [
lastItem := self lastSelectedItem.

^(items allSatisfy: [:each | each isSameKindAs: lastItem ])
ifTrue: [ items collect: #actualObject]
ifTrue: [ items collect: [:each | each actualObject] ]
ifFalse: [{lastItem actualObject}]
]

Expand Down
4 changes: 1 addition & 3 deletions src/Calypso-Browser/ClyDesiredSelection.class.st
Expand Up @@ -101,10 +101,8 @@ ClyDesiredSelection >> updateItemsWhichBelongsTo: aDataSource [
- desired selection should never affect actual table selection ofter changes. That's why here we always return false which means that actual selection is not changed"
| relatedItems updatedItems |
relatedItems := items select: [ :each | each belongsToDataSource: aDataSource].
updatedItems := aDataSource itemCursor findItemsWith: (relatedItems collect: #actualObject).

updatedItems := aDataSource itemCursor findItemsWith: (relatedItems collect: [:each | each actualObject]).
relatedItems with: updatedItems do: [ :myItem :updatedBrowserItem |
updatedBrowserItem ifNotNil: [ myItem updateItemWith: updatedBrowserItem ]].

^false
]
1 change: 0 additions & 1 deletion src/Calypso-Browser/ClyExpandedDataSource.class.st
Expand Up @@ -114,7 +114,6 @@ ClyExpandedDataSource >> initialize [
ClyExpandedDataSource >> initializeForBrowserStateSpanshot [
| copy |
super initializeForBrowserStateSpanshot.

copy := collapsedItems collect: [ :each |
each copyForBrowserStateSnapshotOf: self ].
collapsedItems := copy asSortedCollection: [ :a :b | a position < b position ].
Expand Down
2 changes: 1 addition & 1 deletion src/Calypso-NavigationModel/ClyBrowserQueryCursor.class.st
Expand Up @@ -111,7 +111,7 @@ ClyBrowserQueryCursor >> currentItem [
ClyBrowserQueryCursor >> findItemsSimilarTo: sampleBrowserItems [

^cache
findItemsWith: (sampleBrowserItems collect: #actualObject)
findItemsWith: (sampleBrowserItems collect: [:each | each actualObject])
forAbsentDo: [
^queryResult findItemsSimilarTo: sampleBrowserItems]
]
Expand Down
Expand Up @@ -24,6 +24,5 @@ ClyOpenDependencyBrowserCommand >> execute [

| packageNames |
packageNames := packages collect: [ :each | each name ].

(DAPackageAnalyzerPackageDependenciesWindow onPackagesNamed: packageNames) open
]
Expand Up @@ -88,7 +88,7 @@ ClyInheritanceAnalysisEnvironmentPlugin >> checkClassIsAbstract: aClass [
{ #category : #'method groups' }
ClyInheritanceAnalysisEnvironmentPlugin >> collectMethodGroupProviders [
^{ClyAbstractMethodGroupProvider. ClyOverridingMethodGroupProvider. ClyOverriddenMethodGroupProvider. ClyRequiredMethodGroupProvider}
collect: [ :each | each new]
collect: [ :each | each new ]
]

{ #category : #'item decoration' }
Expand Down
Expand Up @@ -48,7 +48,7 @@ ClyCommitMCPackageCommand >> execute [
packages ifEmpty: [ ^ repoBrowser new openWithSpec ].
repos := IceRepository registry select: [ :repo | packages anySatisfy: [ :each | repo includesPackageNamed: each name ] ].
repos ifEmpty: [ ^ self inform: 'Selected packages are not managed by Iceberg' ].
targetRepo := repos size = 1 ifTrue: [ repos first ] ifFalse: [ UIManager default chooseFrom: (repos collect: #name) values: repos title: 'Choose repository' ].
targetRepo := repos size = 1 ifTrue: [ repos first ] ifFalse: [ UIManager default chooseFrom: (repos collect: [:each | each name]) values: repos title: 'Choose repository' ].
targetRepo ifNil: [ ^ self ].
(targetRepo isMissing or: [
targetRepo isCodeMissing or: [
Expand Down
7 changes: 3 additions & 4 deletions src/Calypso-SystemQueries/ClyCompositeScope.extension.st
Expand Up @@ -3,14 +3,14 @@ Extension { #name : #ClyCompositeScope }
{ #category : #'*Calypso-SystemQueries' }
ClyCompositeScope >> asInheritedScope [
| newSubscopes |
newSubscopes := subscopes collect: [ :each | each asInheritedScope ].
newSubscopes := subscopes collect: [ :each | each asInheritedScope ].
^ClyCompositeScope on: newSubscopes in: environment named: ClyClassScope inheritedScopeName
]

{ #category : #'*Calypso-SystemQueries' }
ClyCompositeScope >> asInheritingScope [
| newSubscopes |
newSubscopes := subscopes collect: [ :each | each asInheritingScope ].
newSubscopes := subscopes collect: [ :each | each asInheritingScope ].
^ClyCompositeScope on: newSubscopes in: environment named: ClyClassScope inheritingScopeName
]

Expand Down Expand Up @@ -59,7 +59,6 @@ ClyCompositeScope >> packagesDo: aBlock [
{ #category : #'*Calypso-SystemQueries' }
ClyCompositeScope >> withMetaLevel: aScopeClass [
| newSubscopes |
newSubscopes := subscopes collect: [ :each |
each withMetaLevel: aScopeClass ].
newSubscopes := subscopes collect: [ :each | each withMetaLevel: aScopeClass ].
^ClyCompositeScope on: newSubscopes in: environment named: name
]
Expand Up @@ -25,14 +25,14 @@ ClyDefaultSystemEnvironmentPlugin >> checkPackageHasClassGroups: aPackage [
ClyDefaultSystemEnvironmentPlugin >> collectClassGroupProviders [

^{ClyExtendedClassGroupProvider. ClyNoTagClassGroupProvider. ClyTaggedClassGroupProvider}
collect: [ :each | each new]
collect: [ :each | each new ]
]

{ #category : #'method groups' }
ClyDefaultSystemEnvironmentPlugin >> collectMethodGroupProviders [

^{ClyInheritedMethodGroupProvider. ClyTaggedMethodGroupProvider. ClyUnclassifiedMethodGroupProvider. ClyExtendedMethodGroupProvider}
collect: [ :each | each new]
collect: [ :each | each new ]
]

{ #category : #'item decoration' }
Expand Down
Expand Up @@ -42,7 +42,6 @@ ClyProjectManagerRegistry >> projectManagers: anObject [
ClyProjectManagerRegistry >> projectQueryFor: aScope [

projectManagers isEmpty ifTrue: [ ^ ClyUnknownQuery instance ].

^ (projectManagers collect: [ :found | found queryClass sortedFrom: aScope ])
reduce: [ :a :b | a , b ]
]
Expand Down
2 changes: 1 addition & 1 deletion src/Calypso-SystemQueries/TraitedMetaclass.extension.st
Expand Up @@ -9,7 +9,7 @@ TraitedMetaclass >> tagsForAllMethods [
allProtocols := self organization protocols
reject: [ :each | each name = Protocol unclassified | each isExtensionProtocol ].

selectors := self visibleMethods collect: #selector.
selectors := self visibleMethods collect: [ :each | each selector ].

^ allProtocols
select: [ :protocol |
Expand Down
2 changes: 1 addition & 1 deletion src/Calypso-SystemTools-Core/ClyBrowserMorph.extension.st
Expand Up @@ -130,7 +130,7 @@ ClyBrowserMorph >> requestRemoveMethodStrategyFor: methods [
ifFalse: ['The message #{1} has {2} sender{3}' format: {selectors anyOne. senderCount. plural}].

result := UIManager default
chooseFrom: (strategies collect: #userRequestString) values: strategies title: caption.
chooseFrom: (strategies collect: [:each | each userRequestString]) values: strategies title: caption.

^result ifNil: [ SycNotRemoveMethodStrategy new ]
]
Expand Up @@ -4,6 +4,5 @@ Extension { #name : #ClyVariableReferencesQuery }
ClyVariableReferencesQuery >> decorateResultMethodEditor: aMethodEditor [
| vars |
vars := variableQuery execute items.

aMethodEditor selectAnyVariable: (vars collect: [:each | each name])
]
Expand Up @@ -42,7 +42,7 @@ ClyRemoveMethodGroupCommand >> prepareFullExecutionInContext: aToolContext [
| tagsString confirmed |
super prepareFullExecutionInContext: aToolContext.

tagsString := ', ' join: (methodGroups collect: #name).
tagsString := ', ' join: (methodGroups collect: [:each | each name]).
(methodGroups anySatisfy: [ :each | each methodsSize > 0])
ifTrue: [
confirmed := UIManager default
Expand Down
4 changes: 1 addition & 3 deletions src/Clap-Core/ClapContext.class.st
Expand Up @@ -55,9 +55,7 @@ ClapContext class >> pragmaCommands [
theClass := pragma method methodClass.
theSelector := pragma method selector.
self assert: [ theSelector isUnary ].

theClass instanceSide
perform: theSelector ]
theClass instanceSide perform: theSelector ]
]

{ #category : #'instance creation' }
Expand Down
3 changes: 1 addition & 2 deletions src/Clap-Core/ClapDocumenter.class.st
Expand Up @@ -100,8 +100,7 @@ ClapDocumenter >> section: titleString listing: parameters [
newLine;
text: titleString;
newLine;
tabularize: (parameters collect:
[ :each | each synopsis -> each description ])
tabularize: (parameters collect: [ :each | each synopsis -> each description ])
]

{ #category : #documenting }
Expand Down
2 changes: 1 addition & 1 deletion src/Collections-Strings/String.class.st
Expand Up @@ -231,7 +231,7 @@ String class >> loremIpsum: size [
"self loremIpsum: 2048"
| words out |
words := (self loremIpsum findTokens: ' ,.') collect: #asLowercase.
words := (self loremIpsum findTokens: ' ,.') collect: [:each | each asLowercase].
(out := LimitedWriteStream on: (self new: size))
limit: size - 2;
limitBlock: [
Expand Down
2 changes: 1 addition & 1 deletion src/Colors/Color.class.st
Expand Up @@ -818,7 +818,7 @@ Color class >> registerColor: aColor named: aName [
Color class >> registeredColorNames [
"Returns all the available names of named colors."

^ ColorRegistry keys collect: #asString
^ ColorRegistry keys collect: [ :each | each asString ]
]

{ #category : #accessing }
Expand Down
4 changes: 1 addition & 3 deletions src/Commander2/CmCommandGroup.class.st
Expand Up @@ -131,10 +131,8 @@ CmCommandGroup >> register: aCommandOrGroup before: anotherCommandOrGroup [
CmCommandGroup >> register: aCommandOrGroup insteadOf: anotherCommandOrGroup [
| commandToReplaceIndex |
commandToReplaceIndex := self entriesIndexOf: anotherCommandOrGroup.

((self commands collect: #name) \ { (entries at: commandToReplaceIndex) } includes: aCommandOrGroup name)
((self commands collect: [:each | each name]) \ { (entries at: commandToReplaceIndex) } includes: aCommandOrGroup name)
ifTrue: [ CmDuplicatedEntryName signalEntryNamed: aCommandOrGroup name ].

entries at: commandToReplaceIndex put: aCommandOrGroup
]

Expand Down
2 changes: 1 addition & 1 deletion src/Debugger-Filters/KernelClassesFilter.class.st
Expand Up @@ -16,7 +16,7 @@ KernelClassesFilter >> initialize [
super initialize.
kernelClasses := self kernelClassesToExclude asOrderedCollection.
kernelClasses := kernelClasses
addAll: (kernelClasses collect: #class);
addAll: (kernelClasses collect: [:each | each class]);
yourself

]
Expand Down
2 changes: 1 addition & 1 deletion src/DrTests-TestCoverage/DTTestCoverageResult.class.st
Expand Up @@ -25,7 +25,7 @@ DTTestCoverageResult >> buildTreeForUI [
yourself).
(DTTreeNode new
name: 'Uncovered methods';
subResults: (self methodList collect: #asResultForDrTest);
subResults: (self methodList collect: [:each | each asResultForDrTest]);
yourself)}
]

Expand Down
4 changes: 2 additions & 2 deletions src/Epicea/EpCompositeRefactoring.class.st
Expand Up @@ -20,7 +20,7 @@ EpCompositeRefactoring class >> withAll: someRefactorings [
{ #category : #converting }
EpCompositeRefactoring >> asRBRefactoring [
^ RBCompositeRefactoryChange new
changes: (childrenRefactorings collect: #asRBRefactoring);
changes: (childrenRefactorings collect: [:each | each asRBRefactoring]);
yourself
]

Expand All @@ -32,5 +32,5 @@ EpCompositeRefactoring >> childrenRefactorings [
{ #category : #initializing }
EpCompositeRefactoring >> initializeWith: someRefactorings [
self initialize.
childrenRefactorings := someRefactorings collect: #asEpiceaEvent
childrenRefactorings := someRefactorings collect: [:each | each asEpiceaEvent]
]
2 changes: 1 addition & 1 deletion src/Epicea/EpLog.class.st
Expand Up @@ -228,7 +228,7 @@ EpLog >> entryReferences [
{ #category : #accessing }
EpLog >> events [

^ self entries collect: #content
^ self entries collect: [:each | each content]
]

{ #category : #accessing }
Expand Down

0 comments on commit 7439c74

Please sign in to comment.