Skip to content

Commit

Permalink
Merge pull request #328 from estebanlm/18849-Pharo-should-sync-with-M…
Browse files Browse the repository at this point in the history
…etacello

18849-Pharo-should-sync-with-Metacello
  • Loading branch information
estebanlm committed Oct 9, 2017
2 parents 6d42482 + a39d3ef commit 94155d3
Show file tree
Hide file tree
Showing 247 changed files with 1,230 additions and 484 deletions.
4 changes: 2 additions & 2 deletions bootstrap/scripts/03-metacello-bootstrap/01-loadMetacello.st
Expand Up @@ -17,12 +17,12 @@ mcPackages := #(
'MonticelloFileTree-Core'
'Metacello-MC'
'Metacello-PharoCommonPlatform'
'Metacello-Platform'
'Metacello-ToolBox'
'MonticelloFileTree-FileSystem-Utilities'
'STON-Core'
'Metacello-GitBasedRepository'
'Metacello-GitHub'
'Metacello-Platform'
'Metacello-ToolBox'
).

MCMethodDefinition initializersEnabled: false.
Expand Down
@@ -1,3 +1,3 @@
private
addStatement: selector args: args
self statements add: selector -> args
self statements add: selector -> args
@@ -1,6 +1,6 @@
private
normalizeTagsData: jsonObject
"return a dictionay mapping the tag name to the commit SHA."
"return a dictionay mapping the tag name to the commit SHA"

| tagDict |
jsonObject
Expand Down
@@ -1,3 +1,3 @@
*Metacello-Core-scripting
*metacello-core-scripting
execute: projectSpecBlock against: aScriptExecutor
aScriptExecutor executeBlock: self do: projectSpecBlock
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setAuthorInMetacelloConfig: aMetacelloConfig

aMetacelloConfig setAuthorWithBlock: self
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
setBaseline: aString withInMetacelloConfig: aMetacelloConfig
aMetacelloConfig setBaseline: aString withBlock: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setBlessingInMetacelloConfig: aMetacelloConfig

aMetacelloConfig setBlessingWithBlock: self
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
setConfiguration: aString withInMetacelloConfig: aMetacelloConfig
aMetacelloConfig setConfiguration: aString withBlock: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setDescriptionInMetacelloConfig: aMetacelloConfig

aMetacelloConfig setDescriptionWithBlock: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setPackage: aString withInMetacelloConfig: aMetacelloConfig

aMetacelloConfig setPackage: aString withBlock: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setProject: aString withInMetacelloConfig: aMetacelloConfig

aMetacelloConfig setProject: aString withBlock: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setTimestampInMetacelloConfig: aMetacelloConfig

aMetacelloConfig setTimestampWithBlock: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
addToMetacelloPackages: aMetacelloPackagesSpec

self do: [:each | each addToMetacelloPackages: aMetacelloPackagesSpec ]
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
asMetacelloAttributeList
^ self
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
asMetacelloAttributePath
^ MetacelloMethodSectionPath withAll: self
@@ -1,3 +1,3 @@
*Metacello-Core-scripting
*metacello-core-scripting
execute: projectSpecBlock against: aScriptExecutor
aScriptExecutor executeCollection: self do: projectSpecBlock
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
mergeIntoMetacelloPackages: aMetacelloPackagesSpec

self do: [:each | each mergeIntoMetacelloPackages: aMetacelloPackagesSpec ]
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
removeFromMetacelloPackages: aMetacelloPackagesSpec

self do: [:each | each removeFromMetacelloPackages: aMetacelloPackagesSpec ]
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
setForDo: aBlock withInMetacelloConfig: aMetacelloConstructore
aMetacelloConstructore setFor: self do: aBlock
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
setForVersion: aString withInMetacelloConfig: aMetacelloConstructore
aMetacelloConstructore setFor: self version: aString
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
setImportInVersionSpec: aMetacelloVersionSpec
aMetacelloVersionSpec setImport: self asArray
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setIncludesInMetacelloPackage: aMetacelloPackageSpec

aMetacelloPackageSpec setIncludes: self asArray.
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setLoadsInMetacelloProject: aMetacelloPackageSpec

aMetacelloPackageSpec setLoads: self asArray.
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setRequiresInMetacelloPackage: aMetacelloPackageSpec

aMetacelloPackageSpec setRequires: self asArray.
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
setTimestampInMetacelloConfig: aMetacelloConfig
aMetacelloConfig setTimestampWithString: self printString
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
setTimestampInMetacelloVersion: aMetacelloVersionSpec

aMetacelloVersionSpec setTimestamp:
Expand Down
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
metacelloIntegerLessThanSelf: anInteger

^anInteger < self
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
metacelloSemanticIntegerLessThanSelf: anInteger
^ anInteger < self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
metacelloSemanticStringLessThanSelf: aString
"string version components are always '<' integer component"

Expand Down
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
metacelloSemanticVersionComponentLessThan: aMetacelloVersonComponent
^ aMetacelloVersonComponent metacelloSemanticIntegerLessThanSelf: self
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
metacelloStringLessThanSelf: aString
"string version components are always '<' integer component"

Expand Down
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
metacelloVersionComponentLessThan: aMetacelloVersonComponent

^aMetacelloVersonComponent metacelloIntegerLessThanSelf: self
@@ -1,3 +1,3 @@
*Metacello-Core
*metacello-core
flushForScriptGet
"noop"
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
repositoryBranchName
"extract a branch name from the repository ... if possible"

Expand Down
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
repositoryDescription
"return a description that includes a repositoryVersionString and repositoryBranchName if present"

Expand Down
@@ -1,4 +1,4 @@
*Metacello-Core
*metacello-core
repositoryVersionString
"extract a version string from the repository ... if possible"

Expand Down
@@ -1,4 +1,4 @@
accessing
configurationClass

^ self subclassResponsibility
^self subclassResponsibility
@@ -1,5 +1,7 @@
private
evaluatePragma: pragma
currentContext := pragma.
[ self configuration perform: pragma methodSelector with: self ]
ensure: [ currentContext := nil ]
[ self configuration
perform: (MetacelloPlatform current selectorForPragma: pragma)
with: self ]
ensure: [ currentContext := nil ]
@@ -0,0 +1,7 @@
querying
repository
| specs |
self deprecated: 'Use repositories or repositorySpecs'.
(specs := self repositorySpecs) isEmpty
ifTrue: [ ^ nil ].
^ specs first
@@ -0,0 +1,6 @@
accessing
attribute: anObject
self deprecated: 'Use attributes: instead'.
self attributes size > 1
ifTrue: [ self error: 'invalid use of attribute:' ].
attributes := OrderedCollection with: anObject
@@ -0,0 +1,8 @@
accessing
attribute
self deprecated: 'Use attributes instead'.
self attributes size > 1
ifTrue: [ self error: 'invalid use of attribute' ].
self attributes isEmpty
ifTrue: [ ^ nil ].
^ self attributes first
Empty file.
@@ -0,0 +1,3 @@
private
integerFromString: aString
^ aString asInteger
@@ -0,0 +1,4 @@
private
validateVersionNumber: svn against: aString
"no validation"

@@ -0,0 +1,11 @@
{
"commentStamp" : "",
"super" : "MetacelloSemanticVersionNumber",
"category" : "Metacello-Core-Model",
"classinstvars" : [ ],
"pools" : [ ],
"classvars" : [ ],
"instvars" : [ ],
"name" : "MetacelloOldSemanticVersionNumber",
"type" : "normal"
}
Expand Up @@ -44,7 +44,7 @@ sortPackageSpecs: orderedSpecs packageSpec: packageSpec groupLoops: groupLoops f
cr;
tab;
tab;
show: each name ].
show: each ].
Transcript
cr;
show:
Expand All @@ -58,7 +58,7 @@ sortPackageSpecs: orderedSpecs packageSpec: packageSpec groupLoops: groupLoops f
cr;
tab;
tab;
show: each name ] ].
show: each ] ].
movePackage := movePackage or: [ packageIndex <= targetIndex ].
false
ifTrue: [
Expand Down
Expand Up @@ -25,6 +25,19 @@ createRepository: aRepositorySpec
(self
fileHandleOn:
(aRepositorySpec description copyFrom: headerSize + 1 to: description size)) ] ].
Smalltalk
at: #'TonelRepository'
ifPresent: [ :cl |
type = 'tonel'
ifTrue: [
| description headerSize |
description := aRepositorySpec description.
headerSize := 'tonel://' size.
^ cl new
directory:
(self
fileHandleOn:
(aRepositorySpec description copyFrom: headerSize + 1 to: description size)) ] ].
Smalltalk
at: #'MCGitHubRepository'
ifPresent: [ :cl |
Expand Down
@@ -0,0 +1,3 @@
file system
deleteFileNamed: filePath
(self fileDirectoryClass on: filePath) containingDirectory deleteFileNamed: (self fileDirectoryClass localNameFor: filePath)
@@ -0,0 +1,5 @@
tests
disableUndefinedSybolUpdates
"noop for most platforms - needed for GemStone"

^ nil
Expand Up @@ -8,6 +8,8 @@ extractTypeFromDescription: description
ifTrue: [ ^ 'dictionary' ].
(description beginsWith: 'filetree://')
ifTrue: [ ^ 'filetree' ].
(description beginsWith: 'tonel://')
ifTrue: [ ^ 'tonel' ].
(description beginsWith: 'github://')
ifTrue: [ ^ 'github' ].
(description beginsWith: 'gitorious://')
Expand Down
@@ -1,4 +1,3 @@
github/bitbucket support
fileDirectoryClass

^ self class environment at: #FileDirectory
^ Smalltalk at: #FileDirectory
@@ -0,0 +1,13 @@
caching
primeStackCacheFor: cacheName doing: noArgBlock defaultDictionary: aDictionary

self deprecated: 'use #primeStackCacheWith:doing:'.
self
useStackCacheDuring: [:dict | | cache |
cache := dict at: cacheName ifAbsent: [].
cache == nil
ifTrue: [
cache := Dictionary new.
dict at: cacheName put: cache ].
^noArgBlock value ]
defaultDictionary: aDictionary
@@ -0,0 +1,4 @@
tests
reenableUndefinedSybolUpdates: undefinedSymbols
"noop for most platforms - needed for GemStone"

0 comments on commit 94155d3

Please sign in to comment.