The Trunk: ReleaseBuilder-eem.173.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: ReleaseBuilder-eem.173.mcz

commits-2
Eliot Miranda uploaded a new version of ReleaseBuilder to project The Trunk:
http://source.squeak.org/trunk/ReleaseBuilder-eem.173.mcz

==================== Summary ====================

Name: ReleaseBuilder-eem.173
Author: eem
Time: 14 January 2018, 9:41:01.742395 am
UUID: 28681eda-100f-47a1-bd88-9f1a3a767951
Ancestors: ReleaseBuilder-eem.172

Allow the user to answer questions up front, hence allowing running the release process without user intervention,.  This to debug the new bytecode set which looks to have a store check issue that is only seen long after the system is recompiied].

=============== Diff against ReleaseBuilder-eem.172 ===============

Item was changed:
  Object subclass: #ReleaseBuilder
  instanceVariableNames: ''
+ classVariableNames: 'DeferredTask NextMajorVersion NextMinorVersion NextTask QAndA'
- classVariableNames: 'DeferredTask NextMajorVersion NextMinorVersion NextTask'
  poolDictionaries: ''
  category: 'ReleaseBuilder'!
 
  !ReleaseBuilder commentStamp: 'mt 6/22/2016 18:08' prior: 0!
  I'm the script that prepares a trunk image for release.
 
  Just do "ReleaseBuilder doNextStep" repeatedly until the next release is done.
 
  For the final release step:
  - If you want to try it locally, change #localBuild to return true.
  - Most of the code operates (read-only) on the build repository, which is usually the trunk. For releases, there is a release repository, to which some package versions will be copied from trunk.!

Item was added:
+ ----- Method: ReleaseBuilder class>>askInAdvance (in category 'preparing') -----
+ askInAdvance
+ "Preload QAndA with answers to any questions that will be asked during saving."
+ "ReleaseBuilder askInAdvance"
+ (self systemNavigation allCallsOn: #confirm:orCancel:title: localTo: self class) do:
+ [:methodRef|
+ methodRef compiledMethod methodNode nodesDo:
+ [:node|
+ (node isMessage
+  and: [node selector key == #confirm:orCancel:title:
+  and: [node receiver isVariableNode
+  and: [node receiver key = 'self']]]) ifTrue:
+ [[:questionNode :ingored :titleNode|
+  QAndA
+ at: titleNode key
+ put: (Project uiManager
+ confirm: questionNode key translated
+ orCancel: [^self]
+ title: titleNode key translated)]
+ valueWithArguments: node arguments asArray]]]!

Item was changed:
  ----- Method: ReleaseBuilder class>>checkForDirtyPackages (in category 'scripts - support') -----
  checkForDirtyPackages
 
  | modifiedWorkingCopies unmergedWorkingCopies |
  MCWorkingCopy checkModified: true.
  modifiedWorkingCopies := MCWorkingCopy allManagers
  select: [:wc | wc ancestors size = 1 and: [wc modified] ].
  unmergedWorkingCopies := MCWorkingCopy allManagers
  select: [:wc | (wc ancestors size = 1) not ].
 
  unmergedWorkingCopies ifNotEmpty: [
  "Sort to simplify exploration. MC browser does also show packages sorted."
  (modifiedWorkingCopies sorted: [:wc1 :wc2 | wc1 packageName <= wc2 packageName]) explore.
  Warning signal: 'There are unmerged packages.'].
 
  modifiedWorkingCopies ifNotEmpty: [
  "Sort to simplify exploration. MC browser does also show packages sorted."
  (modifiedWorkingCopies sorted: [:wc1 :wc2 | wc1 packageName <= wc2 packageName]) explore.
 
+ (self
- (Project current uiManager
  confirm: 'Do you want to discard all local changes?'
  orCancel: [^ Error signal: 'Release building canceled.']
  title: 'Dirty Packages Found')
  ifTrue: [modifiedWorkingCopies do: [:wc |
  [(self buildRepository versionWithInfo: wc ancestors first) load]
  on: Warning do: [:warning | warning resume]]]].!

Item was added:
+ ----- Method: ReleaseBuilder class>>clearQAndA (in category 'preparing') -----
+ clearQAndA
+ "Get rid of any previous answers to questions"
+ QAndA := Dictionary new!

Item was added:
+ ----- Method: ReleaseBuilder class>>confirm:orCancel:title: (in category 'preparing') -----
+ confirm: aString orCancel: cancelBlock title: titleString
+ "Allow questions to be answered in advance."
+ ^QAndA
+ at: titleString
+ ifAbsent:
+ [Project uiManager
+ confirm: aString translated
+ orCancel: cancelBlock
+ title: titleString translated]!

Item was changed:
  ----- Method: ReleaseBuilder class>>initialize (in category 'class initialization') -----
  initialize
+
+ QAndA ifNil: [self clearQAndA].
+
  "We have to be after AutoStart so that Morphic is up and running."
  Smalltalk addToStartUpList: ReleaseBuilder after: AutoStart.
+
+ SystemVersion newVersion: 'Squeak6.0alpha'!
-
- SystemVersion newVersion: 'Squeak6.0alpha'.!

Item was changed:
  ----- Method: ReleaseBuilder class>>initializeTemplate (in category 'class initialization') -----
  initializeTemplate
 
  ^ 'initialize
+
+ QAndA ifNil: [self clearQAndA].
+
  "We have to be after AutoStart so that Morphic is up and running."
  Smalltalk addToStartUpList: ReleaseBuilder after: AutoStart.
+
+ SystemVersion newVersion: ''{1}'''!
-
- SystemVersion newVersion: ''{1}''.'!

Item was changed:
  ----- Method: ReleaseBuilder class>>recompileAll (in category 'scripts - support') -----
  recompileAll
 
  (Smalltalk classNamed: #EncoderForSistaV1) ifNotNil:
  [:sistaBytecodeSet|
  CompiledCode preferredBytecodeSetEncoderClass ~~ sistaBytecodeSet ifTrue:
+ [(self
- [(Project uiManager
  confirm: 'Do you want to make it the default in this release?'
  orCancel: [false]
  title: 'The SistaV1 Bytecode Set Is Available') ifTrue:
  [CompiledCode
  installSecondaryBytecodeSet: sistaBytecodeSet;
  preferredBytecodeSetEncoderClass: sistaBytecodeSet]]].
 
  Compiler recompileAll!

Item was changed:
  ----- Method: ReleaseBuilder class>>setNewSystemVersion: (in category 'manual') -----
  setNewSystemVersion: version
 
+ | initializeMethodSource |
+ initializeMethodSource := self initializeTemplate format: {version}.
+ (self class >> #initialize) getSource asString ~= initializeMethodSource ifTrue:
+ [self class
+ compile: initializeMethodSource
+ classified: 'class initialization'].
- self class
- compile: (self initializeTemplate format: {version})
- classified: 'class initialization'.
 
  self initialize.
  self assert: (SystemVersion current version beginsWith: self versionString).
 
  SystemVersion current isRelease ifFalse: [
+ self inform: ('You just changed the system version to {1}.\Please upload the changed ''ReleaseBuilder'' package to\\   {2}\\so that this version change will be official.' translated withCRs format: {SystemVersion current version. self buildRepository description})]!
- self inform: ('You just changed the system version to {1}.\Please upload the changed ''ReleaseBuilder'' package to\\   {2}\\so that this version change will be official.' translated withCRs format: {SystemVersion current version. self buildRepository description})].!