Skip to content

Commit

Permalink
60510
Browse files Browse the repository at this point in the history
  • Loading branch information
Jenkins Build Server authored and ci committed Jul 24, 2017
1 parent dbb6599 commit f35877b
Show file tree
Hide file tree
Showing 29 changed files with 88 additions and 33 deletions.
@@ -0,0 +1,7 @@
setLongpaths: aBoolean global: globalBoolean
"set user.name and user.email properties.
this could be a nonsense with other backends, but git has them and needs them :)"
self withRepoDo: [ :repo | | config |
config := repo config.
globalBoolean ifTrue: [ config := config openGlobal ].
config setBoolean: 'core.longpaths' to: aBoolean ]
@@ -0,0 +1 @@
I resolve Bitbucket repositories
@@ -0,0 +1,2 @@
type
^ 'bitbucket'
@@ -0,0 +1,5 @@
IceProviderRepositoryType subclass: #IceBitbucketRepositoryType
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Iceberg-Metacello-Integration'
@@ -1 +1 @@
I resolve Github repositories.A github repositoy is composed of: github://username/repository[:commitish][/subdir]github - The github identifierusername - The github userrepository - The guthub repositorycommitish - an optional commitish (a branch, a tag, a commit id)subdir - an optional subdirectory where the packages exist. Example: ------------A script to install voyage using this would like more or less like this:Metacello new repository: 'github://pharo-nosql/voyage:master/mc'; baseline: 'Voyage'; load: 'mongo tests'.
I resolve Github repositories
@@ -1,4 +1,4 @@
IceMetacelloRepositoryType subclass: #IceGithubRepositoryType
IceProviderRepositoryType subclass: #IceGithubRepositoryType
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
Expand Down
Expand Up @@ -2,15 +2,11 @@ mcRepository
| baseRepo |

baseRepo := MCGitHubRepository location: self location.
(Iceberg icebergRepositoriesURLs includes: baseRepo scpUrl)
^ (Iceberg icebergRepositoriesURLs includes: baseRepo scpUrl)
ifTrue: [
"Do not use Iceberg to load iceberg code,
see https://github.com/npasserini/iceberg/issues/168"
^ baseRepo ]
see https://github.com/pharo-vcs/iceberg/issues/168"
baseRepo ]
ifFalse: [
Transcript
show: 'Creating iceberg-metacello adapter for: ';
show: self location;
cr.
^ baseRepo getOrCreateIcebergRepository metacelloAdapter ]
baseRepo getOrCreateIcebergRepository metacelloAdapter ]

@@ -0,0 +1 @@
I resolve Gilab repositories
@@ -0,0 +1,2 @@
type
^ 'gitlab'
@@ -0,0 +1,5 @@
IceProviderRepositoryType subclass: #IceGitlabRepositoryType
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Iceberg-Metacello-Integration'
@@ -1,6 +1,6 @@
createRepository: aRepositorySpec

| type |

type := aRepositorySpec type.
type = 'ftp' ifTrue: [ | description headerSize index host directory |
description := aRepositorySpec description.
Expand Down
@@ -1,2 +1,2 @@
allTypes
^ self allSubclasses
^ self allSubclasses select: [ :each | each isAbstract not ]
@@ -1,4 +1,4 @@
for: aLocationString
^ (self allSubclasses
^ (self allTypes
detect: [ :each | each isSuitableForLocation: aLocationString ])
location: aLocationString
@@ -0,0 +1,2 @@
isAbstract
^ self = IceMetacelloRepositoryType
@@ -0,0 +1 @@
I 'm a base class to resolve provider-based repositories.A provider repositoy is composed of: provider://username/repository[:commitish][/subdir]provider - The provider identifier (e.g. github, bitbucket, etc.)username - The provider userrepository - The provider repositorycommitish - an optional commitish (a branch, a tag, a commit id)subdir - an optional subdirectory where the packages exist. Example: ------------A script to install voyage using this would like more or less like this:Metacello new repository: 'github//pharo-nosql/voyage:master/mc'; baseline: 'Voyage'; load: 'mongo tests'.
Expand Down
@@ -0,0 +1,3 @@
isAbstract
^ super isAbstract
or: [ self = IceProviderRepositoryType ]
@@ -0,0 +1,5 @@
IceMetacelloRepositoryType subclass: #IceProviderRepositoryType
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'Iceberg-Metacello-Integration'
@@ -0,0 +1,5 @@
mcRepository
| baseRepo |

baseRepo := MCGitHubRepository location: self location.
^ baseRepo getOrCreateIcebergRepository metacelloAdapter
@@ -0,0 +1,2 @@
mergeBaseCommitFor: commitInfo
^ commitInfo repository commitAt: (self mergeBaseFor: commitInfo)
@@ -0,0 +1,4 @@
mergeBaseFor: commitInfo
^ commitInfo repository
mergeBaseBetween: commitInfo commitId
and: self baseSHA
Expand Up @@ -2,7 +2,7 @@ addChangesTreeTo: a with: commitInfo
(IceDiffChangeTreeBuilder new
entity: commitInfo;
diff: (commitInfo ifNotNil: [
commitInfo diffTo: (commitInfo repository commitAt: self baseSHA) ]);
commitInfo diffTo: (self mergeBaseCommitFor: commitInfo) ]);
buildOn: a)
title: 'Changes vs. destination' .
super addChangesTreeTo: a with: commitInfo
@@ -1,7 +1,7 @@
initializeWidgets
issueNumberText := self newTextInput autoAccept: true.
issueText := self newTextInput autoAccept: true.
createButton := self newButton.
createButton := self newButton enabled: false.


issueNumberText whenBuiltDo: [ :w | w widget wrapFlag: false ].
Expand Down
Expand Up @@ -10,5 +10,7 @@ validateIssue: aString
issue := PharoIssue number: number.
[ "Fork to allow UI to continue"
issue downloadTitle.
World defer: [ self updateText: (self sanitizeTitle: issue title) ] ] fork ]
UIManager default defer: [
self updateText: (self sanitizeTitle: issue title).
self createButton enabled: true ] ] fork ]

@@ -0,0 +1,7 @@
compatibleTimestamp
"I'm a timestamp as system: likes authorname MM/DD/YYYY HH:MM"
^ String streamContents: [ :stream |
stream
<< self compatibleUsername
<< ' '
<< self datetime asStringYMDHM ]
@@ -0,0 +1,4 @@
mergeBaseBetween: anId and: otherId
^ self backend
mergeBaseBetween: anId
and: otherId
@@ -1,4 +1,4 @@
script60509
script60510

^ 'AST-Core-TheIntegrator.496.mcz
AST-Tests-Core-TheIntegrator.134.mcz
Expand Down Expand Up @@ -151,6 +151,7 @@ Iceberg-cypress.1.mcz
Iceberg-Libgit-cypress.1.mcz
Iceberg-Metacello-Integration-cypress.1.mcz
Iceberg-Plugin-cypress.1.mcz
Iceberg-Plugin-GitHub-cypress.1.mcz
Iceberg-UI-cypress.1.mcz
ImportingResource-Help-TheIntegrator.8.mcz
IssueTracking-TheIntegrator.6.mcz
Expand Down

This file was deleted.

@@ -0,0 +1,14 @@
update60510
"self new update60510"
self withUpdateLog: '20268 update iceberg v0.5.5
https://pharo.fogbugz.com/f/cases/20268'.
self loadTogether: self script60510 merge: false.

#('Iceberg-UI' 'Iceberg-Plugin-GitHub' 'Iceberg-Plugin' 'Iceberg-Metacello-Integration' 'Iceberg-Libgit' 'Iceberg' 'BaselineOfIceberg' 'LibGit-Core' 'BaselineOfLibGit')
do: [ :each | each asPackage removeFromSystem ].
Metacello new
baseline: 'Iceberg';
repository: 'github://pharo-vcs/iceberg:v0.5.5';
load.
(Smalltalk classNamed: #Iceberg) enableMetacelloIntegration: false.
self flushCaches.
@@ -1,3 +1,3 @@
commentForCurrentUpdate
^ '20262 Update Iceberg to 0.5.4
https://pharo.fogbugz.com/f/cases/20262'
^ '20268 update iceberg v0.5.5
https://pharo.fogbugz.com/f/cases/20268'

0 comments on commit f35877b

Please sign in to comment.