├── generated ├── get │ ├── 32 │ ├── 64 │ │ └── 60+vmLatest │ ├── _h5ai │ ├── favicon.ico │ ├── travis │ ├── .htaccess │ ├── travis+vm12 │ ├── travis+vm13 │ ├── travis+vm14 │ ├── travis+vm20 │ ├── travis+vm30 │ ├── travis+vm40 │ ├── travis+vm50 │ ├── travis+vmS12 │ ├── travis+vmS13 │ ├── travis+vmS14 │ ├── travis+vmS20 │ ├── travis+vmS30 │ ├── travis+vmS40 │ ├── travis+vmS50 │ ├── travis+vmLatest40 │ ├── travis+vmLatest50 │ ├── 12+vmS │ ├── 13+vmS │ ├── 14+vmS │ ├── 20+vmS │ ├── 30+vmS │ ├── 40+vmS │ ├── 50+vmS │ ├── 60+vmS │ ├── 40+vmSLatest │ ├── alpha+vmS │ ├── 40+vmLatest │ ├── 50+vmLatest │ ├── 60+vmLatest │ ├── stable+vmS │ └── alpha+vmSLatest ├── favicon.ico ├── travis ├── travis+vm12 ├── travis+vm13 ├── travis+vm14 ├── travis+vm20 ├── travis+vm30 ├── travis+vm40 ├── travis+vm50 ├── travis+vmS12 ├── travis+vmS13 ├── travis+vmS14 ├── travis+vmS20 ├── travis+vmS30 ├── travis+vmS40 ├── travis+vmS50 ├── travis+vmLatest40 ├── travis+vmLatest50 ├── 12+vmS ├── 13+vmS ├── 14+vmS ├── 20+vmS ├── 30+vmS ├── 40+vmS ├── 50+vmS ├── 60+vmS ├── 40+vmSLatest ├── alpha+vmS ├── 40+vmLatest ├── 50+vmLatest ├── 60+vmLatest ├── stable+vmS └── alpha+vmSLatest ├── .project ├── mc ├── .properties ├── ZeroConf │ ├── package.st │ ├── ZeroConfPharoImageScript.class.st │ ├── ZeroConfMinimalImageVersionScript.class.st │ ├── ZeroConfExplicit32BitPlatform.class.st │ ├── ZeroConfExplicit64BitPlatform.class.st │ ├── ZeroConfCurrentPlatform.class.st │ ├── ZeroConfImageVersionScript.class.st │ ├── ZeroConfVMLatestScript.class.st │ └── ZeroConfPrefixedScript.class.st ├── ZeroConf-Tests │ ├── package.st │ ├── ZeroConfPharoImageScriptTest.class.st │ ├── ZeroConfVMLatestScript.extension.st │ ├── ZeroConfImageScriptTest.class.st │ ├── ZeroConfVMScriptTest.class.st │ ├── ZeroConfCombinedScript.extension.st │ ├── ZeroConfCombinedScriptTest.class.st │ ├── AbstractZeroConfBashScriptTest.class.st │ └── AbstractZeroConfBashScript.extension.st └── BaselineOfZeroConf │ ├── package.st │ └── BaselineOfZeroConf.class.st ├── .filetree └── README.md /generated/get/32: -------------------------------------------------------------------------------- 1 | . -------------------------------------------------------------------------------- /.project: -------------------------------------------------------------------------------- 1 | { 2 | 'srcDirectory' : 'mc' 3 | } -------------------------------------------------------------------------------- /generated/get/_h5ai: -------------------------------------------------------------------------------- 1 | ../files/extra/_h5ai -------------------------------------------------------------------------------- /mc/.properties: -------------------------------------------------------------------------------- 1 | { 2 | #format : #tonel 3 | } -------------------------------------------------------------------------------- /generated/get/favicon.ico: -------------------------------------------------------------------------------- 1 | ../files/extra/favicon.ico -------------------------------------------------------------------------------- /mc/ZeroConf/package.st: -------------------------------------------------------------------------------- 1 | Package { #name : 'ZeroConf' } 2 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/package.st: -------------------------------------------------------------------------------- 1 | Package { #name : #'ZeroConf-Tests' } 2 | -------------------------------------------------------------------------------- /mc/BaselineOfZeroConf/package.st: -------------------------------------------------------------------------------- 1 | Package { #name : 'BaselineOfZeroConf' } 2 | -------------------------------------------------------------------------------- /.filetree: -------------------------------------------------------------------------------- 1 | {"packageExtension" : ".package", 2 | "propertyFileExtension" : ".json" } -------------------------------------------------------------------------------- /generated/favicon.ico: -------------------------------------------------------------------------------- https://raw.githubusercontent.com/pharo-project/pharo-zeroconf/HEAD/generated/favicon.ico -------------------------------------------------------------------------------- /generated/travis: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | sudo add-apt-repository ppa:pharo/stable 3 | sudo apt-get update 4 | sudo apt-get install pharo-vm-core:i386 5 | -------------------------------------------------------------------------------- /generated/get/travis: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | sudo add-apt-repository ppa:pharo/stable 3 | sudo apt-get update 4 | sudo apt-get install pharo-vm-core:i386 5 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/ZeroConfPharoImageScriptTest.class.st: -------------------------------------------------------------------------------- 1 | Class { 2 | #name : #ZeroConfPharoImageScriptTest, 3 | #superclass : #ZeroConfImageScriptTest, 4 | #category : 'ZeroConf-Tests' 5 | } 6 | 7 | { #category : #coverage } 8 | ZeroConfPharoImageScriptTest >> classToBeTested [ 9 | ^ ZeroConfPharoImageScript 10 | ] 11 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/ZeroConfVMLatestScript.extension.st: -------------------------------------------------------------------------------- 1 | Extension { #name : #ZeroConfVMLatestScript } 2 | 3 | { #category : #'*ZeroConf-Tests-validation' } 4 | ZeroConfVMLatestScript >> validateGeneratedArtifacts [ 5 | | command | 6 | super validateGeneratedArtifacts. 7 | 8 | command := (self directory / self type) fullName, ' ',self optionDash,'help'. 9 | self 10 | assert: (OSProcess waitForCommand: command) succeeded 11 | description: command, ' did not run properly.' 12 | ] 13 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/ZeroConfImageScriptTest.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I test the default Image zeroconf scripts. 3 | " 4 | Class { 5 | #name : #ZeroConfImageScriptTest, 6 | #superclass : #AbstractZeroConfBashScriptTest, 7 | #category : 'ZeroConf-Tests' 8 | } 9 | 10 | { #category : #coverage } 11 | ZeroConfImageScriptTest >> classToBeTested [ 12 | ^ ZeroConfImageScript 13 | ] 14 | 15 | { #category : #helper } 16 | ZeroConfImageScriptTest >> runImageScriptTest: methodName [ 17 | self runScriptTest: (self classToBeTested perform: methodName) 18 | ] 19 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfPharoImageScript.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I generate a simple script which downloads a Pharo image. 3 | " 4 | Class { 5 | #name : 'ZeroConfPharoImageScript', 6 | #superclass : 'ZeroConfImageScript', 7 | #category : 'ZeroConf', 8 | #package : 'ZeroConf' 9 | } 10 | 11 | { #category : 'instance creation' } 12 | ZeroConfPharoImageScript class >> pharo: releaseString [ 13 | "Create a new zeroconf script exporter for the given release. 14 | A typical release string looks like '30' see also `SystemVersion current majorMinor: ''` " 15 | ^ self new 16 | release: releaseString; 17 | yourself 18 | ] 19 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/ZeroConfVMScriptTest.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I test the default VM zeroconf scripts. 3 | " 4 | Class { 5 | #name : #ZeroConfVMScriptTest, 6 | #superclass : #AbstractZeroConfBashScriptTest, 7 | #category : 'ZeroConf-Tests' 8 | } 9 | 10 | { #category : #coverage } 11 | ZeroConfVMScriptTest >> classToBeTested [ 12 | ^ ZeroConfVMScript 13 | ] 14 | 15 | { #category : #helper } 16 | ZeroConfVMScriptTest >> runVMScriptTest: methodName [ 17 | ^ self runScriptTest: (ZeroConfVMScript perform: methodName) 18 | ] 19 | 20 | { #category : #testing } 21 | ZeroConfVMScriptTest >> testPharo [ 22 | self runVMScriptTest: #pharo 23 | ] 24 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/ZeroConfCombinedScript.extension.st: -------------------------------------------------------------------------------- 1 | Extension { #name : #ZeroConfCombinedScript } 2 | 3 | { #category : #'*ZeroConf-Tests-validation' } 4 | ZeroConfCombinedScript >> validateGeneratedArtifacts [ 5 | "cannot test combined scripts as they download the other scripts from the server which most probably are still using the old data. Hence they might produce outdated artifacts." 6 | ] 7 | 8 | { #category : #'*ZeroConf-Tests-validation' } 9 | ZeroConfCombinedScript >> validateRun [ 10 | "cannot test combined scripts as they download the other scripts from the server which most probably are still using the old data. Hence they might produce outdated artifacts." 11 | ] 12 | -------------------------------------------------------------------------------- /generated/get/.htaccess: -------------------------------------------------------------------------------- 1 | ################################ 2 | # h5ai 0.22.1 3 | # customized .htaccess 4 | ################################ 5 | 6 | Options +Indexes 7 | Options +FollowSymLinks 8 | 9 | HeaderName /_h5ai/server/aai/header.html 10 | ReadmeName /_h5ai/server/aai/footer.html 11 | 12 | IndexIgnore _h5ai* 13 | 14 | IndexOptions Charset=UTF-8 15 | IndexOptions FancyIndexing 16 | IndexOptions FoldersFirst 17 | IndexOptions HTMLTable 18 | IndexOptions NameWidth=* 19 | IndexOptions SuppressDescription 20 | IndexOptions SuppressHTMLPreamble 21 | IndexOptions SuppressRules 22 | IndexOptions Type=text/html;h5ai=0.22.1 23 | IndexOptions XHTML 24 | 25 | # make sure all get.pharo org scripts are treated as html 26 | DefaultType text/html 27 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfMinimalImageVersionScript.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I generate a simple script which downloads a Pharo-minimal image from an url: 3 | 4 | http://files.pharo.org/get-files/VERSION 5 | " 6 | Class { 7 | #name : 'ZeroConfMinimalImageVersionScript', 8 | #superclass : 'ZeroConfImageVersionScript', 9 | #category : 'ZeroConf-Unity', 10 | #package : 'ZeroConf', 11 | #tag : 'Unity' 12 | } 13 | 14 | { #category : 'testing' } 15 | ZeroConfMinimalImageVersionScript class >> canBeGenerated: version [ 16 | ^ version >= 40 17 | ] 18 | 19 | { #category : 'testing' } 20 | ZeroConfMinimalImageVersionScript >> canBeCombined [ 21 | ^ false 22 | ] 23 | 24 | { #category : 'accessing' } 25 | ZeroConfMinimalImageVersionScript >> defaultBasename [ 26 | ^ super defaultBasename, '-minimal' 27 | ] 28 | 29 | { #category : 'accessing' } 30 | ZeroConfMinimalImageVersionScript >> imageFileName [ 31 | ^ 'pharo-minimal' 32 | ] 33 | -------------------------------------------------------------------------------- /README.md: -------------------------------------------------------------------------------- 1 | ZeroConf Scripts for Pharo 2 | =========================== 3 | 4 | This project is used to create bash scripts to easily download and install Pharo images and VMs. 5 | You can see it in live action under . 6 | 7 | 8 | ## Code loading 9 | 10 | ```smalltalk 11 | Metacello new 12 | baseline: 'ZeroConf'; 13 | repository: 'github://pharo-project/pharo-zeroconf/mc'; 14 | load. 15 | ``` 16 | 17 | ## How to 18 | 19 | To make a new Pharo zeroconf release 20 | 21 | 1. Update the class side methods of ZeroConfCommandLineHandler: 22 | - add the new versions to the image and vm version lists 23 | - change the stable and alpha versions 24 | See for example commit (f50e6761af355d228ee651b45fbb421e082e57db) 25 | 2. Commit 26 | 3. Generate the code in `[pwd]/out` from playground: `ZeroConfCommandLineHandler generate` 27 | 4. Copy the generated files to /generated 28 | 5. Commit (from command line) -------------------------------------------------------------------------------- /mc/BaselineOfZeroConf/BaselineOfZeroConf.class.st: -------------------------------------------------------------------------------- 1 | Class { 2 | #name : 'BaselineOfZeroConf', 3 | #superclass : 'BaselineOf', 4 | #category : 'BaselineOfZeroConf', 5 | #package : 'BaselineOfZeroConf' 6 | } 7 | 8 | { #category : 'actions' } 9 | BaselineOfZeroConf class >> load [ 10 | ^ self project latestVersion load. 11 | ] 12 | 13 | { #category : 'accessing' } 14 | BaselineOfZeroConf >> baseline: spec [ 15 | 16 | 17 | spec for: #pharo do: [ 18 | self osSubprocess: spec. 19 | 20 | spec package: 'ZeroConf'. 21 | spec package: 'ZeroConf-Tests' with: [ spec requires: #('OSSubprocess') ]. 22 | 23 | spec group: 'all' with: #('ZeroConf' 'ZeroConf-Tests'). 24 | spec group: 'default' with: #('all') ] 25 | ] 26 | 27 | { #category : 'accessing' } 28 | BaselineOfZeroConf >> osSubprocess: spec [ 29 | spec 30 | baseline: 'OSSubprocess' 31 | with: [ spec repository: 'github://pharo-contributions/OSSubprocess:v2.0.0/repository' ] 32 | 33 | ] 34 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfExplicit32BitPlatform.class.st: -------------------------------------------------------------------------------- 1 | Class { 2 | #name : 'ZeroConfExplicit32BitPlatform', 3 | #superclass : 'ZeroConfCurrentPlatform', 4 | #category : 'ZeroConf', 5 | #package : 'ZeroConf' 6 | } 7 | 8 | { #category : 'generation' } 9 | ZeroConfExplicit32BitPlatform >> baseUrlFor: aScript [ 10 | 11 | "Default scripts are hosted in the 32 bit subdirectory" 12 | ^ aScript basicBaseUrl / '32' 13 | ] 14 | 15 | { #category : 'generation' } 16 | ZeroConfExplicit32BitPlatform >> directoryFor: aScript [ 17 | 18 | "32 bit scripts are written in the 32 bit subdirectory" 19 | ^ aScript baseDirectory / '32' 20 | ] 21 | 22 | { #category : 'generation' } 23 | ZeroConfExplicit32BitPlatform >> generateArchitectureDetectionOn: aStream [ 24 | 25 | super generateArchitectureDetectionOn: aStream. 26 | aStream cr; 27 | <<== 'SEARCH FOR THE CORRESPONDING 32bit ARCHITECTURE'; 28 | << 'case "${ARCH}" in'; cr; 29 | << ' x86_64*) ARCH="x86";;'; cr; 30 | << ' *) OSNAME="UNKNOWN:${ARCH}"'; cr; 31 | << 'esac'; cr 32 | ] 33 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfExplicit64BitPlatform.class.st: -------------------------------------------------------------------------------- 1 | Class { 2 | #name : 'ZeroConfExplicit64BitPlatform', 3 | #superclass : 'ZeroConfCurrentPlatform', 4 | #category : 'ZeroConf', 5 | #package : 'ZeroConf' 6 | } 7 | 8 | { #category : 'generation' } 9 | ZeroConfExplicit64BitPlatform >> baseUrlFor: aScript [ 10 | 11 | "Default scripts are hosted in the 64 bit subdirectory" 12 | ^ aScript basicBaseUrl / '64' 13 | ] 14 | 15 | { #category : 'generation' } 16 | ZeroConfExplicit64BitPlatform >> directoryFor: aScript [ 17 | 18 | "64 bit scripts are written in the 64 bit subdirectory" 19 | ^ aScript baseDirectory / '64' 20 | ] 21 | 22 | { #category : 'generation' } 23 | ZeroConfExplicit64BitPlatform >> generateArchitectureDetectionOn: aStream [ 24 | 25 | super generateArchitectureDetectionOn: aStream. 26 | aStream cr; 27 | <<== 'SEARCH FOR THE CORRESPONDING 64bit ARCHITECTURE'; 28 | << 'case "${ARCH}" in'; cr; 29 | << ' x86*) ARCH="x86_64";;'; cr; 30 | << ' *) OSNAME="UNKNOWN:${ARCH}"'; cr; 31 | << 'esac'; cr 32 | ] 33 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/ZeroConfCombinedScriptTest.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I test the default combined VM and Image zeroconf scripts. 3 | " 4 | Class { 5 | #name : #ZeroConfCombinedScriptTest, 6 | #superclass : #AbstractZeroConfBashScriptTest, 7 | #category : 'ZeroConf-Tests' 8 | } 9 | 10 | { #category : #coverage } 11 | ZeroConfCombinedScriptTest >> classToBeTested [ 12 | ^ ZeroConfCombinedScript 13 | ] 14 | 15 | { #category : #helper } 16 | ZeroConfCombinedScriptTest >> runCombinedScriptTest: methodName [ 17 | self runScriptTest: (ZeroConfCombinedScript perform: methodName) 18 | ] 19 | 20 | { #category : #tests } 21 | ZeroConfCombinedScriptTest >> testCombineBasic [ 22 | | image vm combined | 23 | image := ZeroConfPharoImageScript pharo: '30'. 24 | vm := ZeroConfVMScript pharo. 25 | combined := image , vm. 26 | 27 | self assert: combined basename equals: (image basename, '+', vm basename). 28 | self assert: combined scripts asArray equals: {image. vm}. 29 | self 30 | assert: combined artifacts size 31 | equals: image artifacts size + vm artifacts size 32 | ] 33 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfCurrentPlatform.class.st: -------------------------------------------------------------------------------- 1 | Class { 2 | #name : 'ZeroConfCurrentPlatform', 3 | #superclass : 'Object', 4 | #category : 'ZeroConf', 5 | #package : 'ZeroConf' 6 | } 7 | 8 | { #category : 'generation' } 9 | ZeroConfCurrentPlatform >> baseUrlFor: aScript [ 10 | 11 | "Default scripts are hosted in the root" 12 | ^ aScript basicBaseUrl 13 | ] 14 | 15 | { #category : 'generation' } 16 | ZeroConfCurrentPlatform >> directoryFor: aScript [ 17 | 18 | "Default scripts are written in the root" 19 | ^ aScript baseDirectory 20 | ] 21 | 22 | { #category : 'generation' } 23 | ZeroConfCurrentPlatform >> generateArchitectureDetectionOn: aStream [ 24 | 25 | aStream << 'ARCH=`uname -m`' 26 | ] 27 | 28 | { #category : 'generation' } 29 | ZeroConfCurrentPlatform >> generateOperatingSystemDetectionOn: aStream [ 30 | 31 | aStream <<== 'DETECT SYSTEM PROPERTIES'. 32 | self generateArchitectureDetectionOn: aStream. 33 | 34 | aStream cr; 35 | << 'VM_ARCH=${ARCH}'; cr; 36 | << 'unameOut="$(uname -s)"'; cr; 37 | << 'case "${unameOut}" in'; cr; 38 | << ' Linux*) OSNAME=Linux;;'; cr; 39 | << ' Darwin*) OSNAME=Darwin;;'; cr; 40 | << ' MSYS*|CYGWIN*|MINGW*) OSNAME=Windows;;'; cr; 41 | << ' *) OSNAME="UNKNOWN:${unameOut}"'; cr; 42 | << 'esac'; cr 43 | ] 44 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfImageVersionScript.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I generate a simple script which downloads a Pharo image from an url: 3 | 4 | http://files.pharo.org/get-files/VERSION 5 | 6 | " 7 | Class { 8 | #name : 'ZeroConfImageVersionScript', 9 | #superclass : 'ZeroConfPharoImageScript', 10 | #category : 'ZeroConf-Unity', 11 | #package : 'ZeroConf', 12 | #tag : 'Unity' 13 | } 14 | 15 | { #category : 'testing' } 16 | ZeroConfImageVersionScript >> canBeCombined [ 17 | ^ true 18 | ] 19 | 20 | { #category : 'script generation' } 21 | ZeroConfImageVersionScript >> generateBody [ 22 | self generateVersionProperties; cr; cr. 23 | super generateBody 24 | ] 25 | 26 | { #category : 'script generation' } 27 | ZeroConfImageVersionScript >> generateVersionProperties [ 28 | 29 | self <<== 'RELEASE VERSION'. 30 | platform generateArchitectureDetectionOn: self. 31 | self cr 32 | << 'VERSION="'; << self release asString; << '"'; cr; 33 | << 'FILES_URL="http://files.pharo.org/get-files/${VERSION}"'; cr; 34 | << 'IMAGE_FILE_NAME="'; << self imageFileName; << '-${ARCH}"'; cr. 35 | ] 36 | 37 | { #category : 'accessing' } 38 | ZeroConfImageVersionScript >> imageFileName [ 39 | ^ 'pharoImage' 40 | ] 41 | 42 | { #category : 'accessing' } 43 | ZeroConfImageVersionScript >> imageUrl [ 44 | ^ '${FILES_URL}/${IMAGE_FILE_NAME}.zip' 45 | ] 46 | 47 | { #category : 'printing' } 48 | ZeroConfImageVersionScript >> printOn: aStream [ 49 | 50 | super printOn: aStream. 51 | aStream 52 | nextPutAll: '('; 53 | nextPutAll: self imageFileName; 54 | nextPutAll: version asString; 55 | nextPutAll: release asString; 56 | nextPutAll: ')' 57 | ] 58 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfVMLatestScript.class.st: -------------------------------------------------------------------------------- 1 | " 2 | Temporary script to overcome the migration form single dash ""-help"" options to double dash ""--help"" options in the pharo vm. 3 | " 4 | Class { 5 | #name : 'ZeroConfVMLatestScript', 6 | #superclass : 'ZeroConfVMScript', 7 | #category : 'ZeroConf', 8 | #package : 'ZeroConf' 9 | } 10 | 11 | { #category : 'script generation' } 12 | ZeroConfVMLatestScript >> generateVmScriptCreator [ 13 | self 14 | <<== 'CREATE THE VM LAUNCHER SCRIPTS' 15 | << ('create_vm_script() \{ 16 | VM_SCRIPT=$1 17 | 18 | echo "#!/usr/bin/env bash" > $VM_SCRIPT 19 | echo ''# some magic to find out the real location of this script dealing with symlinks 20 | DIR=`readlink "$0"` || DIR="$0"; 21 | DIR=`dirname "$DIR"`; 22 | cd "$DIR" 23 | DIR=`pwd` 24 | cd - > /dev/null 25 | # disable parameter expansion to forward all arguments unprocessed to the VM 26 | set -f 27 | # run the VM and pass along all arguments as is'' >> $VM_SCRIPT 28 | 29 | # make sure we only substite $PHARO_VM but put "$DIR" in the script 30 | echo -n \\"\\$DIR\\"/\\"$PHARO_VM\\" >> $VM_SCRIPT 31 | 32 | # only output the headless option if the VM_SCRIPT name does not include "ui" 33 | if [[ "\{$VM_SCRIPT}" != *ui* ]]; then 34 | echo -n " {1}headless" >> $VM_SCRIPT 35 | fi 36 | 37 | # forward all arguments unprocessed using $@ 38 | echo " \\"\\$@\\"" >> $VM_SCRIPT 39 | 40 | # make the script executable 41 | chmod +x $VM_SCRIPT 42 | } 43 | 44 | echoerr "Creating starter scripts {2} and {2}-ui" 45 | create_vm_script "{2}" 46 | create_vm_script "{2}-ui"' format: {self optionDash. self type}); cr 47 | ] 48 | 49 | { #category : 'accessing' } 50 | ZeroConfVMLatestScript >> initialize [ 51 | super initialize. 52 | self release: 'latest' 53 | ] 54 | 55 | { #category : 'accessing' } 56 | ZeroConfVMLatestScript >> optionDash [ 57 | ^ '--' 58 | ] 59 | 60 | { #category : 'accessing' } 61 | ZeroConfVMLatestScript >> release [ 62 | ^ 'latest' 63 | ] 64 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/AbstractZeroConfBashScriptTest.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I am an abstract test for the ZeroConf script generators. 3 | I provide simple test for a given zeroconf script, see the methods in the 'helper testing' category. 4 | " 5 | Class { 6 | #name : #AbstractZeroConfBashScriptTest, 7 | #superclass : #ClassTestCase, 8 | #instVars : [ 9 | 'script' 10 | ], 11 | #category : 'ZeroConf-Tests' 12 | } 13 | 14 | { #category : #accessing } 15 | AbstractZeroConfBashScriptTest class >> defaultTimeLimit [ 16 | ^ 1 minute 17 | ] 18 | 19 | { #category : #testing } 20 | AbstractZeroConfBashScriptTest class >> isAbstract [ 21 | ^ self = AbstractZeroConfBashScriptTest 22 | ] 23 | 24 | { #category : #helper } 25 | AbstractZeroConfBashScriptTest >> cleanUp [ 26 | script artifacts do: [ :artifact| 27 | artifact asFileReference ensureDelete ] 28 | ] 29 | 30 | { #category : #'helper testing' } 31 | AbstractZeroConfBashScriptTest >> generateTest [ 32 | "Test if the given ZeroConfBashScript generates a proper bash script" 33 | script generate. 34 | self assert: script file exists. 35 | self assert: script file readStream contents size > 0 36 | ] 37 | 38 | { #category : #'helper testing' } 39 | AbstractZeroConfBashScriptTest >> helpTest [ 40 | "Test if the generate ZeroConf script successfully runs with --help" 41 | OSSUnixSubprocess new 42 | command: 'bash'; 43 | arguments: {script file fullName . '--help'}; 44 | redirectStdout; 45 | runAndWaitOnExitDo: [ :process :outString | 46 | self assert: process isSuccess. 47 | ] 48 | ] 49 | 50 | { #category : #helper } 51 | AbstractZeroConfBashScriptTest >> runScriptTest: aScript [ 52 | | testDirectory | 53 | script := aScript. 54 | testDirectory := 'zeroconf-test' asFileReference. 55 | testDirectory ensureDeleteAll; ensureCreateDirectory. 56 | script directory: testDirectory. 57 | self 58 | generateTest; 59 | helpTest; 60 | runTest; 61 | cleanUp. 62 | ] 63 | 64 | { #category : #'helper testing' } 65 | AbstractZeroConfBashScriptTest >> runTest [ 66 | "Test if the generate ZeroConf script successfully runs and creates the artifacts" 67 | self flag: #todo. 68 | script validateRun. 69 | script artifacts do: [ :artifact| 70 | self assert: (script directory / artifact) exists ] 71 | ] 72 | -------------------------------------------------------------------------------- /generated/travis+vm12: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 12.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm12 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm12 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vm13: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 13.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm13 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm13 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vm14: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 14.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm14 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm14 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vm20: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 20.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm20 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm20 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vm30: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 30.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm30 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm30 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vm40: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 40.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm40 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm40 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vm50: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 50.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm50 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm50 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm12: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 12.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm12 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm12 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm13: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 13.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm13 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm13 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm14: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 14.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm14 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm14 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm20: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 20.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm20 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm20 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm30: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 30.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm30 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm30 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm40: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 40.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm40 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm40 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vm50: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable Pharo VM for 50.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vm50 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vm50 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS12: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 12.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS12 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS12 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS13: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 13.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS13 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS13 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS14: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 14.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS14 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS14 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS20: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 20.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS20 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS20 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS30: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 30.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS30 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS30 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS40: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 40.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS40 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS40 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmS50: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 50.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS50 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS50 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /mc/ZeroConf/ZeroConfPrefixedScript.class.st: -------------------------------------------------------------------------------- 1 | " 2 | I combine several ZeroConf scripts which are treated as prefix for code generation. 3 | The final script name is not altered by the prefix. 4 | 5 | Example: 6 | ======== 7 | prefiexedScript := scriptA / scriptB. 8 | 9 | Then the output script is in `scriptA basename / scriptB basename, '.sh'` and the final script will have both the contents of `scriptA` and `scriptB` 10 | " 11 | Class { 12 | #name : 'ZeroConfPrefixedScript', 13 | #superclass : 'ZeroConfCombinedScript', 14 | #instVars : [ 15 | 'prefixScripts' 16 | ], 17 | #category : 'ZeroConf', 18 | #package : 'ZeroConf' 19 | } 20 | 21 | { #category : 'instance creation' } 22 | ZeroConfPrefixedScript class >> withPrefix: aScript [ 23 | ^ self new 24 | addPrefix: aScript; 25 | yourself 26 | ] 27 | 28 | { #category : 'instance creation' } 29 | ZeroConfPrefixedScript class >> withPrefix: aScript with: anotherScript [ 30 | ^ self new 31 | addPrefix: aScript; 32 | addPrefix: anotherScript; 33 | yourself 34 | ] 35 | 36 | { #category : 'combining' } 37 | ZeroConfPrefixedScript >> / otherZeroConf [ 38 | ^ otherZeroConf prefixedWithAll: self 39 | ] 40 | 41 | { #category : 'accessing' } 42 | ZeroConfPrefixedScript >> addAllPrefix: moreScripts [ 43 | ^ prefixScripts addAll: moreScripts 44 | ] 45 | 46 | { #category : 'accessing' } 47 | ZeroConfPrefixedScript >> addPrefix: script [ 48 | ^ prefixScripts add: script 49 | ] 50 | 51 | { #category : 'accessing' } 52 | ZeroConfPrefixedScript >> defaultDirectory [ 53 | | fileReference | 54 | fileReference := FileLocator workingDirectory. 55 | self prefixScripts do: [ :script | 56 | fileReference := fileReference / script basename ]. 57 | ^ fileReference 58 | ] 59 | 60 | { #category : 'combining' } 61 | ZeroConfPrefixedScript >> for32Bits [ 62 | 63 | | copy | 64 | copy := super for32Bits. 65 | copy prefixScripts: (copy prefixScripts collect: [ :subscript | subscript for32Bits ]). 66 | ^ copy 67 | ] 68 | 69 | { #category : 'combining' } 70 | ZeroConfPrefixedScript >> for64Bits [ 71 | 72 | | copy | 73 | copy := super for64Bits. 74 | copy prefixScripts: (copy prefixScripts collect: [ :subscript | subscript for64Bits ]). 75 | ^ copy 76 | ] 77 | 78 | { #category : 'script generation' } 79 | ZeroConfPrefixedScript >> generatePrefixScripts [ 80 | 81 | self prefixScripts do: [ :script | 82 | script generateBodyOn: self outputStream. 83 | self cr. ]. 84 | ] 85 | 86 | { #category : 'script generation' } 87 | ZeroConfPrefixedScript >> generateScripts [ 88 | 89 | ^ self prefixScripts, self scripts 90 | ] 91 | 92 | { #category : 'initialize-release' } 93 | ZeroConfPrefixedScript >> initialize [ 94 | prefixScripts := OrderedCollection new. 95 | ^ super initialize 96 | ] 97 | 98 | { #category : 'accessing' } 99 | ZeroConfPrefixedScript >> prefixScripts [ 100 | ^ prefixScripts 101 | ] 102 | 103 | { #category : 'accessing' } 104 | ZeroConfPrefixedScript >> prefixScripts: aCollection [ 105 | 106 | prefixScripts := aCollection 107 | ] 108 | -------------------------------------------------------------------------------- /generated/get/travis+vmS12: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 12.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS12 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS12 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmS13: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 13.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS13 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS13 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmS14: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 14.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS14 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS14 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmS20: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 20.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS20 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS20 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmS30: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 30.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS30 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS30 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmS40: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 40.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS40 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS40 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmS50: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the stable PharoS VM for 50.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmS50 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmS50 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmLatest40: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the latest Pharo VM for 40.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmLatest40 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmLatest40 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/travis+vmLatest50: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the latest Pharo VM for 50.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmLatest50 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmLatest50 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmLatest40: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the latest Pharo VM for 40.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmLatest40 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmLatest40 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /generated/get/travis+vmLatest50: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 52 | Pharo Zeroconf Script 53 | 75 | 76 |

Pharo Zeroconf Script

77 |

This script installs the dependencies to run a pharo vm on a travis slave
78 | This script downloads the latest Pharo VM for 50.
79 |

80 |

Usage

81 | curl get.pharo.org/travis+vmLatest50 | bash 82 |
83 | or if curl is not available:
84 | wget -O- get.pharo.org/travis+vmLatest50 | bash 85 | 86 |

Artifacts

87 | 88 | 89 |
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
90 | 91 | -------------------------------------------------------------------------------- /mc/ZeroConf-Tests/AbstractZeroConfBashScript.extension.st: -------------------------------------------------------------------------------- 1 | Extension { #name : #AbstractZeroConfBashScript } 2 | 3 | { #category : #'*ZeroConf-Tests-running' } 4 | AbstractZeroConfBashScript >> redirectOutputOfProcess: process [ 5 | "Creates a simple process that reads stderr from another process and forwards it to stderr of the running image" 6 | 7 | ^ [ | stderr | 8 | stderr := FileStream stderr. 9 | [ process pipeFromError ifNotNil: [ :pipe | 10 | [stderr 11 | nextPutAll: (pipe next: 16); 12 | flush ] 13 | on: Error do: [ :err | 14 | "nothing" 15 | ] 16 | ]] repeat ] fork 17 | ] 18 | 19 | { #category : #'*ZeroConf-Tests-running' } 20 | AbstractZeroConfBashScript >> run [ 21 | OSSUnixSubprocess new 22 | command: 'bash'; 23 | workingDirectory: self directory fullName; 24 | arguments: { self basename }; 25 | redirectStdout; 26 | runAndWaitOnExitDo: [ :process :outString | 27 | self 28 | assert: process isSuccess 29 | description: self file fullName , ' did not succeed' 30 | ]. 31 | 32 | ] 33 | 34 | { #category : #'*ZeroConf-Tests-validation' } 35 | AbstractZeroConfBashScript >> validate [ 36 | "validate the generated script" 37 | self 38 | validateGenerate; 39 | validateScript. 40 | self 41 | validateRun; 42 | validateGeneratedArtifacts. 43 | ] 44 | 45 | { #category : #'*ZeroConf-Tests-validation' } 46 | AbstractZeroConfBashScript >> validateGenerate [ 47 | ^ self generate 48 | ] 49 | 50 | { #category : #'*ZeroConf-Tests-validation' } 51 | AbstractZeroConfBashScript >> validateGeneratedArtifacts [ 52 | | generatedArtifacts expectedArtifacts | 53 | 54 | expectedArtifacts := ({ self basename }, self artifacts) sorted. 55 | expectedArtifacts := expectedArtifacts collect: [ :artifactName | artifactName asFileReference basename ]. 56 | generatedArtifacts := self directory childNames sort. 57 | 58 | generatedArtifacts 59 | ifEmpty: [ ^ self exitFailure: self file fullName, ' did not generate any content' ]. 60 | 61 | generatedArtifacts = expectedArtifacts 62 | ifFalse: [ ^ self exitFailure: (String streamContents: [ :stream | 63 | stream << self file fullName; 64 | << ' did not generate the approriate files:'; lf; 65 | << ' missing: '; print: (expectedArtifacts \ generatedArtifacts); 66 | << ' additional: '; print: (generatedArtifacts \ expectedArtifacts) ])]. 67 | ] 68 | 69 | { #category : #'*ZeroConf-Tests-validation' } 70 | AbstractZeroConfBashScript >> validateRun [ 71 | [ self run ] 72 | valueWithin: self validationTimeout 73 | onTimeout: [ 74 | AssertionFailure signal: (String streamContents: [ :stream| 75 | stream 76 | << 'Timeout: '; print: self file; 77 | << ' took longer than '; print: self validationTimeout; << ' to finish' ])] 78 | ] 79 | 80 | { #category : #'*ZeroConf-Tests-validation' } 81 | AbstractZeroConfBashScript >> validateScript [ 82 | self 83 | assert: self file isFile 84 | description: self file fullName, ' was not exported'. 85 | 86 | self 87 | assert: self file readStream contents size > 0 88 | description: self file fullName, ' was not exported'. 89 | 90 | 91 | ] 92 | 93 | { #category : #'*ZeroConf-Tests-validation' } 94 | AbstractZeroConfBashScript >> validationTimeout [ 95 | ^ 30 seconds 96 | ] 97 | -------------------------------------------------------------------------------- /generated/12+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 12 Image.
80 | This script downloads the stable PharoS VM for 12.
81 |

82 |

Usage

83 | curl get.pharo.org/12+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/12+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/13+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 13 Image.
80 | This script downloads the stable PharoS VM for 13.
81 |

82 |

Usage

83 | curl get.pharo.org/13+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/13+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/14+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 14 Image.
80 | This script downloads the stable PharoS VM for 14.
81 |

82 |

Usage

83 | curl get.pharo.org/14+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/14+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/20+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 20 Image.
80 | This script downloads the stable PharoS VM for 20.
81 |

82 |

Usage

83 | curl get.pharo.org/20+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/20+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/30+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 30 Image.
80 | This script downloads the stable PharoS VM for 30.
81 |

82 |

Usage

83 | curl get.pharo.org/30+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/30+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/40+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the stable PharoS VM for 40.
81 |

82 |

Usage

83 | curl get.pharo.org/40+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/40+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/50+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 50 Image.
80 | This script downloads the stable PharoS VM for 50.
81 |

82 |

Usage

83 | curl get.pharo.org/50+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/50+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/60+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the stable PharoS VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/60+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/60+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/12+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 12 Image.
80 | This script downloads the stable PharoS VM for 12.
81 |

82 |

Usage

83 | curl get.pharo.org/12+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/12+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/13+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 13 Image.
80 | This script downloads the stable PharoS VM for 13.
81 |

82 |

Usage

83 | curl get.pharo.org/13+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/13+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/14+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 14 Image.
80 | This script downloads the stable PharoS VM for 14.
81 |

82 |

Usage

83 | curl get.pharo.org/14+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/14+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/20+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 20 Image.
80 | This script downloads the stable PharoS VM for 20.
81 |

82 |

Usage

83 | curl get.pharo.org/20+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/20+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/30+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 30 Image.
80 | This script downloads the stable PharoS VM for 30.
81 |

82 |

Usage

83 | curl get.pharo.org/30+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/30+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/40+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the stable PharoS VM for 40.
81 |

82 |

Usage

83 | curl get.pharo.org/40+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/40+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/50+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 50 Image.
80 | This script downloads the stable PharoS VM for 50.
81 |

82 |

Usage

83 | curl get.pharo.org/50+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/50+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/60+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the stable PharoS VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/60+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/60+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/40+vmSLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the latest PharoS VM.
81 |

82 |

Usage

83 | curl get.pharo.org/40+vmSLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/40+vmSLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/alpha+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the stable PharoS VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/alpha+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/alpha+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/40+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the latest Pharo VM for 40.
81 |

82 |

Usage

83 | curl get.pharo.org/40+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/40+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | -------------------------------------------------------------------------------- /generated/50+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 50 Image.
80 | This script downloads the latest Pharo VM for 50.
81 |

82 |

Usage

83 | curl get.pharo.org/50+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/50+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | -------------------------------------------------------------------------------- /generated/60+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the latest Pharo VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/60+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/60+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | -------------------------------------------------------------------------------- /generated/get/40+vmSLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the latest PharoS VM.
81 |

82 |

Usage

83 | curl get.pharo.org/40+vmSLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/40+vmSLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/alpha+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the stable PharoS VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/alpha+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/alpha+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/stable+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 50 Image.
80 | This script downloads the stable PharoS VM for 50.
81 |

82 |

Usage

83 | curl get.pharo.org/stable+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/stable+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/40+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the latest Pharo VM for 40.
81 |

82 |

Usage

83 | curl get.pharo.org/40+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/40+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | -------------------------------------------------------------------------------- /generated/get/50+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 50 Image.
80 | This script downloads the latest Pharo VM for 50.
81 |

82 |

Usage

83 | curl get.pharo.org/50+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/50+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | -------------------------------------------------------------------------------- /generated/get/60+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the latest Pharo VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/60+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/60+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | -------------------------------------------------------------------------------- /generated/get/stable+vmS: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 50 Image.
80 | This script downloads the stable PharoS VM for 50.
81 |

82 |

Usage

83 | curl get.pharo.org/stable+vmS | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/stable+vmS | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/alpha+vmSLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the latest PharoS VM.
81 |

82 |

Usage

83 | curl get.pharo.org/alpha+vmSLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/alpha+vmSLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/alpha+vmSLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 40 Image.
80 | This script downloads the latest PharoS VM.
81 |

82 |

Usage

83 | curl get.pharo.org/alpha+vmSLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/alpha+vmSLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharo-vm/Directory containing the VM
pharoSScript to run the downloaded VM in headless mode
pharoS-uiScript to run the downloaded VM in UI mode
94 | 95 | -------------------------------------------------------------------------------- /generated/get/64/60+vmLatest: -------------------------------------------------------------------------------- 1 | #!/usr/bin/env bash 2 | # 54 | Pharo Zeroconf Script 55 | 77 | 78 |

Pharo Zeroconf Script

79 |

This script downloads the latest Pharo 60 Image.
80 | This script downloads the latest Pharo VM for 60.
81 |

82 |

Usage

83 | curl get.pharo.org/64/60+vmLatest | bash 84 |
85 | or if curl is not available:
86 | wget -O- get.pharo.org/64/60+vmLatest | bash 87 | 88 |

Artifacts

89 | 90 | 91 | 92 | 93 |
Pharo.changesA changes file for the Pharo Image
Pharo.imageA Pharo image, to be opened with the Pharo VM
pharoScript to run the downloaded VM in headless mode
pharo-uiScript to run the downloaded VM in UI mode
pharo-vm/Directory containing the VM
94 | 95 | --------------------------------------------------------------------------------