Skip to content

Commit

Permalink
Use ifNil:, ifNotNil: and ifNil:ifNotNil: instead of isNil an…
Browse files Browse the repository at this point in the history
…d `ifTrue/ifFalse` combinations
  • Loading branch information
gcotelli committed Jul 17, 2019
1 parent 018c771 commit b36049c
Show file tree
Hide file tree
Showing 30 changed files with 630 additions and 580 deletions.
69 changes: 31 additions & 38 deletions src/Manifest-Core/SmalllintManifestChecker.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -42,16 +42,17 @@ SmalllintManifestChecker >> criticsOf: aRule [

{ #category : #manifest }
SmalllintManifestChecker >> falsePositiveOf: aRule [

|critics rId rV mb |
critics := self criticsOf: aRule.

| critics rId rV mb |

critics := self criticsOf: aRule.
rId := aRule class uniqueIdentifierName.
rV := aRule class identifierMinorVersionNumber.
^ critics select: [ :critic | mb := self manifestBuilderOf: critic.
mb isNil
ifTrue: [ false ]
ifFalse: [ mb isFalsePositive: critic onRule: rId version: rV ]]

^ critics
select: [ :critic |
mb := self manifestBuilderOf: critic.
mb ifNil: [ false ] ifNotNil: [ mb isFalsePositive: critic onRule: rId version: rV ]
]
]

{ #category : #initialization }
Expand All @@ -64,23 +65,20 @@ SmalllintManifestChecker >> initialize [

{ #category : #manifest }
SmalllintManifestChecker >> isFalsePositive: aCritic forRuleId: ruleId versionId: versionId [

| mb |
mb := self manifestBuilderOf: aCritic.
^ mb isNil
ifTrue: [ false ]
ifFalse: [ mb isFalsePositive: aCritic onRule: ruleId version: versionId ]

mb := self manifestBuilderOf: aCritic.
^ mb ifNil: [ false ] ifNotNil: [ mb isFalsePositive: aCritic onRule: ruleId version: versionId ]
]

{ #category : #manifest }
SmalllintManifestChecker >> isToDo: aCritic forRuleId: ruleId versionId: versionId [
SmalllintManifestChecker >> isToDo: aCritic forRuleId: ruleId versionId: versionId [

| mb |
mb := self manifestBuilderOf: aCritic.
^ mb isNil
ifTrue: [ false ]
ifFalse: [ mb containsToDo: aCritic onRule: ruleId version: versionId ]

mb := self manifestBuilderOf: aCritic.
^ mb ifNil: [ false ] ifNotNil: [ mb containsToDo: aCritic onRule: ruleId version: versionId ]
]

{ #category : #manifest }
Expand Down Expand Up @@ -137,24 +135,20 @@ SmalllintManifestChecker >> manifestBuilderOfPackage: aPackage [

{ #category : #manifest }
SmalllintManifestChecker >> rejectClassesOf: aPackage [

| mb |
mb := self manifestBuilderOf: aPackage.
^ mb isNil
ifTrue: [{}]
ifFalse: [ mb rejectClasses ]

mb := self manifestBuilderOf: aPackage.
^ mb ifNil: [ {} ] ifNotNil: [ mb rejectClasses ]
]

{ #category : #manifest }
SmalllintManifestChecker >> rejectRulesOf: aPackage [

| mb |

mb := self manifestBuilderOf: aPackage.
^ mb isNil
ifTrue: [{}]
ifFalse: [ mb rejectRules]

^ mb ifNil: [ {} ] ifNotNil: [ mb rejectRules ]
]

{ #category : #accessing }
Expand Down Expand Up @@ -183,16 +177,15 @@ SmalllintManifestChecker >> runRules: aCompositeRule onPackage: aPackage without

{ #category : #manifest }
SmalllintManifestChecker >> toDoOf: aRule [

|critics rId rV mb |
critics := self criticsOf: aRule.

| critics rId rV mb |

critics := self criticsOf: aRule.
rId := aRule class uniqueIdentifierName.
rV := aRule class identifierMinorVersionNumber.
^ critics select: [:critic |
mb := (self manifestBuilderOf: critic).
mb isNil
ifTrue: [ false ]
ifFalse: [ mb containsToDo: critic onRule: rId version: rV ]]


^ critics
select: [ :critic |
mb := self manifestBuilderOf: critic.
mb ifNil: [ false ] ifNotNil: [ mb containsToDo: critic onRule: rId version: rV ]
]
]
35 changes: 23 additions & 12 deletions src/Metacello-Core/MetacelloProject.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -97,39 +97,50 @@ MetacelloProject >> currentVersion [

{ #category : #versions }
MetacelloProject >> currentVersionAgainst: resolvedPackageAndProjectNames [

| cacheKey |
cacheKey := resolvedPackageAndProjectNames isNil
ifTrue: [ Array with: self configuration class with: nil ]
ifFalse: [ Array with: self configuration class with: (resolvedPackageAndProjectNames sort: [ :a :b | a <= b ]) ].

cacheKey := resolvedPackageAndProjectNames
ifNil: [ Array with: self configuration class with: nil ]
ifNotNil: [ Array
with: self configuration class
with: ( resolvedPackageAndProjectNames sort: [ :a :b | a <= b ] )
].
^ MetacelloPlatform current
stackCacheFor: #currentVersionAgainst:
at: cacheKey
doing: [ :cache |
| cv versions latestSomethingLoaded |

cv := nil.
versions := self sortedAndFilteredVersions.
versions
do: [ :version |
| status matchBlock |
status := resolvedPackageAndProjectNames isNil
ifTrue: [ version spec isPartiallyCurrent ]
ifFalse: [ version spec isPartiallyCurrentAgainst: resolvedPackageAndProjectNames ].

status := resolvedPackageAndProjectNames
ifNil: [ version spec isPartiallyCurrent ]
ifNotNil: [ version spec isPartiallyCurrentAgainst: resolvedPackageAndProjectNames ].
matchBlock := [ :matchStatus |
cv := version copy.
cv versionStatus: matchStatus.
^ cache at: cacheKey put: cv ].
^ cache at: cacheKey put: cv
].
status isAllLoadedToSpec: matchBlock.
status isLoadedToSpec: matchBlock.
status isLoadedMatchConstraints: matchBlock.
status
isSomethingLoaded: [ :matchStatus |
latestSomethingLoaded isNil
ifTrue: [
cv := version copy.
latestSomethingLoaded
ifNil: [ cv := version copy.
cv versionStatus: matchStatus.
latestSomethingLoaded := cv ] ] ].
latestSomethingLoaded := cv
]
]
].
latestSomethingLoaded ifNotNil: [ ^ cache at: cacheKey put: latestSomethingLoaded ].
^ cache at: cacheKey put: nil ]
^ cache at: cacheKey put: nil
]
]

{ #category : #accessing }
Expand Down
10 changes: 5 additions & 5 deletions src/Metacello-Core/MetacelloProjectRegistration.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -380,12 +380,12 @@ MetacelloProjectRegistration >> isMutable [

{ #category : #testing }
MetacelloProjectRegistration >> isValid [
" has a name and one or the other of the projectSpecs is non-nil, but not both ... this is CRITICAL"

projectName ifNil: [ ^ false ].
configurationProjectSpec isNil
ifTrue: [ ^ baselineProjectSpec notNil ].
^ baselineProjectSpec isNil
" has a name and one or the other of the projectSpecs is non-nil, but not both ... this is CRITICAL"

projectName ifNil: [ ^ false ].
configurationProjectSpec ifNil: [ ^ baselineProjectSpec notNil ].
^ baselineProjectSpec isNil
]

{ #category : #accessing }
Expand Down
57 changes: 28 additions & 29 deletions src/Metacello-MC/MetacelloCommonMCSpecLoader.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -149,35 +149,34 @@ MetacelloCommonMCSpecLoader >> load [

{ #category : #actions }
MetacelloCommonMCSpecLoader >> loadPackageDirective: aPackageLoadDirective gofer: aGofer [
| packageSpec |
packageSpec := aPackageLoadDirective spec.
MetacelloPlatform current
do: [
| loadBlock goferLoad answers resolvedReference |
aGofer disablePackageCache. "for good luck:)"
resolvedReference := self resolvePackageSpec: packageSpec gofer: aGofer.
resolvedReference isNil
ifTrue: [
"Package version already loaded into image"
^ self ].
loadBlock := [
"mcLoader preLoad: packageSpec."
goferLoad := MetacelloGoferLoad on: aGofer.
goferLoad addResolved: resolvedReference.
goferLoad execute.
MetacelloPlatform current clearCurrentVersionCache "mcLoader postLoad: packageSpec" ].
(answers := packageSpec answers) notEmpty
ifTrue: [ loadBlock valueSupplyingMetacelloAnswers: answers ]
ifFalse: [ loadBlock value ].
resolvedReference workingCopy repositoryGroup
addRepository: aPackageLoadDirective repository.
Transcript
cr;
show:
'Loaded -> ' , resolvedReference name , ' --- '
, aPackageLoadDirective repository repositoryDescription
, ' --- ' , resolvedReference repository description ]
displaying: 'Loading ' , packageSpec file

| packageSpec |

packageSpec := aPackageLoadDirective spec.
MetacelloPlatform current
do: [ | loadBlock goferLoad answers resolvedReference |

aGofer disablePackageCache. "for good luck:)"
resolvedReference := self resolvePackageSpec: packageSpec gofer: aGofer.
resolvedReference ifNil: [ "Package version already loaded into image" ^ self ].
loadBlock := [ "mcLoader preLoad: packageSpec."
goferLoad := MetacelloGoferLoad on: aGofer.
goferLoad addResolved: resolvedReference.
goferLoad execute.
MetacelloPlatform current clearCurrentVersionCache "mcLoader postLoad: packageSpec"
].
( answers := packageSpec answers ) notEmpty
ifTrue: [ loadBlock valueSupplyingMetacelloAnswers: answers ]
ifFalse: [ loadBlock value ].
resolvedReference workingCopy repositoryGroup addRepository: aPackageLoadDirective repository.
Transcript
cr;
show:
'Loaded -> ' , resolvedReference name , ' --- '
, aPackageLoadDirective repository repositoryDescription , ' --- '
, resolvedReference repository description
]
displaying: 'Loading ' , packageSpec file
]

{ #category : #actions }
Expand Down
66 changes: 32 additions & 34 deletions src/Metacello-MC/MetacelloLoadingMCSpecLoader.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -115,40 +115,38 @@ MetacelloLoadingMCSpecLoader >> latestPackage: aString fromRepository: repositor

{ #category : #private }
MetacelloLoadingMCSpecLoader >> linearLoadPackageSpec: packageSpec gofer: gofer [
MetacelloPlatform current
do: [
| loadBlock goferLoad answers resolvedReference repo |
resolvedReference := self resolvePackageSpec: packageSpec gofer: gofer.
resolvedReference isNil
ifTrue: [
"Package version already loaded into image"
^ self ].
loadBlock := [
self preLoad: packageSpec.
goferLoad := MetacelloGoferLoad on: MetacelloGofer new.
goferLoad addResolved: resolvedReference.
goferLoad execute.
MetacelloPlatform current clearCurrentVersionCache.
self postLoad: packageSpec ].
(answers := packageSpec answers) notEmpty
ifTrue: [ loadBlock valueSupplyingMetacelloAnswers: answers ]
ifFalse: [ loadBlock value ].
repo := resolvedReference repository.
self hasRepositoryOverrides
ifTrue: [
repo := self loaderPolicy repositoryMap
at: resolvedReference name
ifAbsent: [ resolvedReference repository ].
resolvedReference workingCopy repositoryGroup addRepository: repo ]
ifFalse: [
resolvedReference workingCopy repositoryGroup
addRepository: resolvedReference repository ].
Transcript
cr;
show:
'Loaded -> ' , resolvedReference name , ' --- ' , repo repositoryDescription
, ' --- ' , resolvedReference repository description ]
displaying: 'Loading ' , packageSpec file

MetacelloPlatform current
do: [ | loadBlock goferLoad answers resolvedReference repo |

resolvedReference := self resolvePackageSpec: packageSpec gofer: gofer.
resolvedReference ifNil: [ "Package version already loaded into image" ^ self ].
loadBlock := [ self preLoad: packageSpec.
goferLoad := MetacelloGoferLoad on: MetacelloGofer new.
goferLoad addResolved: resolvedReference.
goferLoad execute.
MetacelloPlatform current clearCurrentVersionCache.
self postLoad: packageSpec
].
( answers := packageSpec answers ) notEmpty
ifTrue: [ loadBlock valueSupplyingMetacelloAnswers: answers ]
ifFalse: [ loadBlock value ].
repo := resolvedReference repository.
self hasRepositoryOverrides
ifTrue: [ repo := self loaderPolicy repositoryMap
at: resolvedReference name
ifAbsent: [ resolvedReference repository ].
resolvedReference workingCopy repositoryGroup addRepository: repo
]
ifFalse:
[ resolvedReference workingCopy repositoryGroup addRepository: resolvedReference repository ].
Transcript
cr;
show:
'Loaded -> ' , resolvedReference name , ' --- ' , repo repositoryDescription , ' --- '
, resolvedReference repository description
]
displaying: 'Loading ' , packageSpec file
]

{ #category : #'development support' }
Expand Down
8 changes: 5 additions & 3 deletions src/Metacello-MC/MetacelloMCVersionSpec.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -15,10 +15,12 @@ MetacelloMCVersionSpec >> computeVersionStatus: matchBlock [

{ #category : #accessing }
MetacelloMCVersionSpec >> computeVersionStatus: resolvedPackageAndProjectNames matchBlock: matchBlock [

| status |
status := resolvedPackageAndProjectNames isNil
ifTrue: [ self isPartiallyCurrent ]
ifFalse: [ self isPartiallyCurrentAgainst: resolvedPackageAndProjectNames ].

status := resolvedPackageAndProjectNames
ifNil: [ self isPartiallyCurrent ]
ifNotNil: [ self isPartiallyCurrentAgainst: resolvedPackageAndProjectNames ].
status isAllLoadedToSpec: matchBlock.
status isLoadedToSpec: matchBlock.
status isLoadedMatchConstraints: matchBlock.
Expand Down
Loading

0 comments on commit b36049c

Please sign in to comment.