Skip to content
2 changes: 2 additions & 0 deletions bootstrap/scripts/4-build.sh
Original file line number Diff line number Diff line change
Expand Up @@ -217,6 +217,8 @@ ${VM} "${PHARO_IMAGE_NAME}.image" "${IMAGE_FLAGS}" eval --save "Smalltalk vm sav
#We can check the statistics of number of pages free using the "Smalltalk vm parameterAt: 61"
${VM} "${PHARO_IMAGE_NAME}.image" "${IMAGE_FLAGS}" eval --save "Smalltalk vm parameterAt: 43 put: 32"

${VM} "${COMPILER_IMAGE_NAME}.image" "${IMAGE_FLAGS}" eval --save "PharoBootstrapInitialization initializeIcebergRepositories"

${VM} "${PHARO_IMAGE_NAME}.image" "${IMAGE_FLAGS}" eval --save "MCCacheRepository uniqueInstance enable. FFIMethodRegistry resetAll. PharoSourcesCondenser condenseNewSources. Smalltalk garbageCollect"
${VM} "${PHARO_IMAGE_NAME}.image" "${IMAGE_FLAGS}" clean --release
${VM} "${PHARO_IMAGE_NAME}.image" "${IMAGE_FLAGS}" eval --save "SystemBuildInfo current initializeForRelease"
Expand Down
108 changes: 15 additions & 93 deletions src/BaselineOfIDE/BaselineOfIDE.class.st
Original file line number Diff line number Diff line change
Expand Up @@ -194,26 +194,20 @@ BaselineOfIDE >> loadIceberg [
(self classNamed: #Iceberg) enableMetacelloIntegration: true.

Smalltalk os environment at: #GITHUB_TOKEN ifPresent: [ :token |
| credentials |
credentials := (self classNamed: #IceTokenCredentials) new
username:
(Smalltalk os environment
at: #GITHUB_USER
ifAbsent: [ self error: 'Github token was found but not the github user associated to this token.' ]);
token: token;
host: 'github.com';
yourself.

(self classNamed: #IceCredentialStore) current storeCredential: credentials forHostname: 'github.com'.
'Using authentification for Github API' traceCr ].

self registerPharo.
self registerProject: 'Spec2' baseline: 'Spec2' otherBaselines: #('SpecCore').
self registerProject: 'NewTools'.
self registerProject: 'Roassal'.
self registerProject: 'Microdown'.
self registerProject: 'DocumentBrowser' baseline: 'NewToolsDocumentBrowser' otherBaselines: #().
self registerIceberg
| credentials |
credentials := (self classNamed: #IceTokenCredentials) new
username:
(Smalltalk os environment
at: #GITHUB_USER
ifAbsent: [ self error: 'Github token was found but not the github user associated to this token.' ]);
token: token;
host: 'github.com';
yourself.

(self classNamed: #IceCredentialStore) current storeCredential: credentials forHostname: 'github.com'.
'Using authentification for Github API' traceCr ].

self registerPharo
]

{ #category : 'actions' }
Expand All @@ -240,12 +234,6 @@ BaselineOfIDE >> newTools: spec [
loads: #('default') ].
]

{ #category : 'private - register' }
BaselineOfIDE >> pharoPluginClass [

^ self classNamed: #IcePharoPlugin
]

{ #category : 'actions' }
BaselineOfIDE >> postload: loader package: packageSpec [
"Ignore pre and post loads if already executed"
Expand Down Expand Up @@ -306,76 +294,10 @@ BaselineOfIDE >> postload: loader package: packageSpec [
Initialized := true.
]

{ #category : 'actions' }
BaselineOfIDE >> registerIceberg [

self pharoPluginClass addIcebergProjectToIceberg.
"Register baselines"
Metacello new baseline: 'Tonel'; register.
Metacello new baseline: 'LibGit'; register.
Metacello new baseline: 'Iceberg'; register
]

{ #category : 'actions' }
BaselineOfIDE >> registerPharo [

self pharoPluginClass addPharoProjectToIceberg
]

{ #category : 'private - register' }
BaselineOfIDE >> registerProject: projectName [

^ self
registerProject: projectName
baseline: projectName
otherBaselines: #()
]

{ #category : 'private - register' }
BaselineOfIDE >> registerProject: projectName baseline: baselineName [

^ self
registerProject: projectName
baseline: baselineName
otherBaselines: #()
]

{ #category : 'private - register' }
BaselineOfIDE >> registerProject: projectName baseline: baselineName otherBaselines: anArray [

^ self
registerProject: projectName
externalProject: projectName
baseline: baselineName
otherBaselines: anArray
]

{ #category : 'private - register' }
BaselineOfIDE >> registerProject: projectName externalProject: externalProject [

^ self
registerProject: projectName
externalProject: externalProject
baseline: projectName
otherBaselines: #()
]

{ #category : 'private - register' }
BaselineOfIDE >> registerProject: projectName externalProject: externalProject baseline: baselineName otherBaselines: anArray [
| baselineClass className |

className := ('BaselineOf', baselineName) asSymbol.
baselineClass := self classNamed: className.
baselineClass ifNil: [ ^ self ].

self pharoPluginClass
addProjectNamed: projectName
commit: (self pharoPluginClass commitOfExternalProject: externalProject)
baselines: { className }
tags: #(#system).
"Register baselines"
({baselineName}, anArray) do: [ :each |
Metacello new baseline: each; register ]
(self classNamed: #IcePharoPlugin) addPharoProjectToIceberg
]

{ #category : 'baselines - dependencies' }
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -93,3 +93,16 @@ PharoBootstrapInitialization class >> initializeCommandLineHandlerAndErrorHandli
Smalltalk snapshot: true andQuit: true.
Processor terminateActive
]

{ #category : 'initialization' }
PharoBootstrapInitialization class >> initializeIcebergRepositories [

| specs repos |
specs := MetacelloProjectRegistration registry baselineProjectSpecs select: [ :spec | spec repositories printString includesSubstring: 'github://' ].
repos := specs collect: [ :spec | spec repositories map anyOne ] as: Set.

repos do: [ :repo |
| monticelloRepo |
monticelloRepo := MCRepository newRepositoryFromSpec: repo.
monticelloRepo getOrCreateIcebergRepository ]
]