Skip to content

Commit

Permalink
60490
Browse files Browse the repository at this point in the history
  • Loading branch information
Jenkins Build Server authored and ci committed May 16, 2017
1 parent 82a3fe5 commit d5e336c
Show file tree
Hide file tree
Showing 3,996 changed files with 17,140 additions and 14 deletions.
The diff you're trying to view is too large. We only load the first 3000 changed files.
Expand Up @@ -57,6 +57,8 @@ additionalInitialization

Pharo3DarkTheme beCurrent.

3 timesRepeat: [
3 timesRepeat: [
Smalltalk garbageCollect.
Undeclared removeUnreferencedKeys.].
Undeclared removeUnreferencedKeys.].

self loadIceberg.
@@ -0,0 +1,7 @@
loadIceberg

Metacello new
baseline: 'Iceberg';
repository: 'github://pharo-vcs/iceberg:v0.4';
load.
(Smalltalk classNamed: #Iceberg) enableMetacelloIntegration: false.
@@ -0,0 +1 @@
Please comment me using the following template inspired by Class Responsibility Collaborator (CRC) design:For the Class part: State a one line summary. For example, "I represent a paragraph of text".For the Responsibility part: Three sentences about my main responsibilities - what I do, what I know.For the Collaborators Part: State my main collaborators and one line about how I interact with them. Public API and Key Messages- message one - message two - (for bonus points) how to create instances. One simple example is simply gorgeous. Internal Representation and Key Implementation Points. Implementation Points
Expand Down
@@ -0,0 +1,5 @@
BaselineOf subclass: #BaselineOfIceberg
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'BaselineOfIceberg'
@@ -0,0 +1,4 @@
customProjectAttributes
Smalltalk os isMacOS ifTrue: [ ^ #(#MacOS) ].
Smalltalk os isUnix ifTrue: [ ^ #(#Unix) ].
Smalltalk os isWindows ifTrue: [ ^ #(#Windows) ]
@@ -0,0 +1,45 @@
baseline: spec
<baseline>
spec for: #common do: [ spec
configuration: 'OSSubprocess' with: [ spec
versionString: #stable;
repository: 'github://marianopeck/OSSubprocess/repository' ];
configuration: 'ProcessWrapper' with: [ spec
versionString: #stable;
repository: 'http://smalltalkhub.com/mc/Pharo/MetaRepoForPharo50/main' ];

baseline: 'FileTree' with: [ spec
repository: 'github://pharo-vcs/filetree:pharo6.0_dev/repository';
loads: 'Git' ];
baseline: 'LibGit' with: [ spec
repository: 'github://pharo-vcs/libgit2-pharo-bindings:development';
loads: 'default' ];
project: 'LibGit-Tests'
copyFrom: 'LibGit'
with: [ spec loads: #('tests') ];

for: #MacOS do: [ spec
package: 'Iceberg-GitCommand'
with: [ spec requires: #('OSSubprocess') ] ];
for: #Unix do: [ spec
package: 'Iceberg-GitCommand'
with: [ spec requires: #('OSSubprocess' ) ] ];
for: #Windows do: [ spec
package: 'Iceberg-GitCommand'
with: [ spec requires: #('ProcessWrapper') ] ];

package: 'Iceberg';
package: 'Iceberg-Plugin';
package: 'Iceberg-Metacello-Integration' with: [ spec requires: #('Iceberg')];
package: 'Iceberg-UI' with: [ spec requires: #('Iceberg' 'Iceberg-Plugin') ];
package: 'Iceberg-Tests' with: [ spec requires: #('Iceberg' 'Iceberg-GitCommand') ];
package: 'Iceberg-UI-Tests' with: [ spec requires: #('Iceberg-UI' 'Iceberg-Tests')];
package: 'Iceberg-GitFileTree' with: [ spec requires: #('Iceberg' 'FileTree') ];
package: 'Iceberg-GitFileTree-Tests' with: [ spec requires: #('Iceberg-GitFileTree' 'Iceberg-Tests') ];
package: 'Iceberg-Libgit' with: [ spec requires: #('Iceberg' 'LibGit') ];

group: 'minimal' with: #('Iceberg' 'Iceberg-Libgit');
group: 'default' with: #(minimal 'Iceberg-Metacello-Integration' 'Iceberg-UI');
group: 'allTests' with: #('Iceberg-Tests' 'LibGit-Tests' 'Iceberg-GitFileTree-Tests' 'Iceberg-UI-Tests' );
group: 'development' with: #(default 'Iceberg-GitFileTree' allTests)
]
1 change: 1 addition & 0 deletions BaselineOfLibGit.package/BaselineOfLibGit.class/README.md
@@ -0,0 +1 @@
Please comment me using the following template inspired by Class Responsibility Collaborator (CRC) design:For the Class part: State a one line summary. For example, "I represent a paragraph of text".For the Responsibility part: Three sentences about my main responsibilities - what I do, what I know.For the Collaborators Part: State my main collaborators and one line about how I interact with them. Public API and Key Messages- message one - message two - (for bonus points) how to create instances. One simple example is simply gorgeous. Internal Representation and Key Implementation Points. Implementation Points
Expand Down
5 changes: 5 additions & 0 deletions BaselineOfLibGit.package/BaselineOfLibGit.class/definition.st
@@ -0,0 +1,5 @@
BaselineOf subclass: #BaselineOfLibGit
instanceVariableNames: ''
classVariableNames: ''
poolDictionaries: ''
category: 'BaselineOfLibGit'
@@ -0,0 +1,20 @@
baseline: spec
<baseline>
spec
for: #(common)
do: [
spec
package: 'LibGit-Tests' with: [ spec requires: 'LibGit-Core' ];
package: 'LibGit-GT' with: [ spec requires: 'LibGit-Core' ];
package: 'LibGit-Patches' with: [ spec requires: 'LibGit-Core' ];
package: 'LibGit-Core'.
spec
group: 'default'
with: #('LibGit-Core').
spec
group: 'development'
with: #('default' 'LibGit-Tests' 'LibGit-Patches' 'LibGit-GT').
spec
group: 'tests'
with: #('LibGit-Tests').
spec postLoadDoIt: #postLoadActions ]
@@ -0,0 +1,20 @@
changeRepositoryType
| repos newRepo |
(Smalltalk hasClassNamed: #MCGitRepository) ifFalse: [ ^ self ].

repos := MCRepositoryGroup default repositories
select: [ :r | (r description includesSubstring: 'LibGit:master') or: [
r description includesSubstring: 'LibGit/master' ] ].
repos ifEmpty: [ ^ self ].

'github-cache/theseion' asFileReference deleteAll.
newRepo := (Smalltalk at: #MCGitRepository) new
repoUrl: 'git@github.com:theseion/LibGit';
ensureDirectory;
yourself.

MCRepositoryGroup allInstances
select: [ :group | group repositories includesAnyOf: repos ]
thenDo: [ :group |
repos do: [ :repo | group removeRepository: repo ].
group addRepository: newRepo ]
@@ -0,0 +1,2 @@
postLoadActions
self changeRepositoryType
1 change: 1 addition & 0 deletions Iceberg-Libgit.package/IceLibgitCommitWalk.class/README.md
@@ -0,0 +1 @@
Utility class for searching through a commit history taking advantage of git revwalk utilities. Found and returned commits will be added to the commit cache of the corresponding IceRepository.
@@ -0,0 +1,5 @@
IceAbstractCommitWalk subclass: #IceLibgitCommitWalk
instanceVariableNames: 'revwalk lgitRepository'
classVariableNames: ''
poolDictionaries: ''
category: 'Iceberg-Libgit'
@@ -0,0 +1,10 @@
revwalk
^ revwalk ifNil: [
repository withRepoDo: [ :repo |
"Keep a reference to the repo so that it does not get garbage collected
(that would free C memory and make leave the revwalk object dumb)"

lgitRepository := repo.
^ revwalk := LGitRevwalk of: repo.
]
]
@@ -0,0 +1,4 @@
rawResultsDo: aBlockClosure
self revwalk
select: [ :result | self shouldInclude: result ]
thenDo: aBlockClosure
@@ -0,0 +1,5 @@
shouldInclude: aLGitCommit
^ self modifyingPackage
ifNil: [ true ]
ifNotNil: [ :package |
aLGitCommit changesFileNamed: package directoryPathString ]
@@ -0,0 +1,8 @@
fromBranch: branch
[ self revwalk pushReference: (lgitRepository lookupBranch: branch name) ]
on: LGit_GIT_EINVALIDSPEC do: [
"branch real branch, so try to find a corresponding treeish using revparse,
this will handle stuff like 'master~1'"
self fromLGitId: (lgitRepository revparse: branch name) id
]

@@ -0,0 +1,2 @@
fromCommitId: commitId
self fromLGitId: (LGitId fromHexString: commitId)
@@ -0,0 +1,2 @@
fromCommit: commit
self fromCommitId: commit id
@@ -0,0 +1,2 @@
fromHead
self revwalk pushHead
@@ -0,0 +1,2 @@
fromLGitId: lGitId
self revwalk pushCommit: lGitId
@@ -0,0 +1,4 @@
fromTag: tag
self revwalk.
^ self fromLGitId: (lgitRepository revparse: tag name) id

@@ -0,0 +1,2 @@
uptoCommit: commit
self revwalk hideCommit: (LGitId fromHexString: commit id)
@@ -0,0 +1,11 @@
commitsDo: aBlock
self maxNumber
ifNil: [ super commitsDo: aBlock ]
ifNotNil: [ | count |
count := 0.
super commitsDo: [ :commit |
aBlock value: commit.
count := count + 1.
count == self maxNumber ifTrue: [ ^ self ]
]
]
@@ -0,0 +1,2 @@
firstCommit
^ self commitsDo: [ :commit | ^ commit ]
1 change: 1 addition & 0 deletions Iceberg-Libgit.package/IceLibgitFileUtils.class/README.md
@@ -0,0 +1 @@
Emulates other 'file utils' classes by reading from a git repository (its blob, not a working copy'). Allows for reading any tree (from any commit) in the repository.
@@ -0,0 +1,2 @@
current
^ Current ifNil: [ Current := self new ]
5 changes: 5 additions & 0 deletions Iceberg-Libgit.package/IceLibgitFileUtils.class/definition.st
@@ -0,0 +1,5 @@
Object subclass: #IceLibgitFileUtils
instanceVariableNames: ''
classVariableNames: 'Current'
poolDictionaries: ''
category: 'Iceberg-Libgit'
@@ -0,0 +1,2 @@
pathNameDelimiter
^ $/
@@ -0,0 +1,2 @@
deleteAll: aTreeBuilder
^ aTreeBuilder deleteAll
@@ -0,0 +1,2 @@
directoryExists: aLGitTreeEntry
^ aLGitTreeEntry type = LGitObjectTypeEnum git_obj_tree
@@ -0,0 +1,2 @@
directoryFromEntry: treeEntry
^ treeEntry object
@@ -0,0 +1,6 @@
directoryFromPath: aString relativeTo: aCommitOrTree
^ aCommitOrTree
entryByPath: aString
ifAbsent: [
IceMissingRepositoryEntry new name: aString; owner: aCommitOrTree; signal ]

@@ -0,0 +1,2 @@
readStreamFor: fileName in: tree do: aBlock
(tree entryByPath: fileName) readStreamDo: aBlock
@@ -0,0 +1,2 @@
writeStreamFor: fileName in: directory do: aBlock
directory addEntryNamed: fileName withContents: (String streamContents: aBlock).
@@ -0,0 +1 @@
Adapter which allows an IceRepository to use libgit as underlying storage.
@@ -0,0 +1,2 @@
description
^ 'Libgit'
@@ -0,0 +1,6 @@
newRepositoryAt: aFileReference origin: anIceRemoteRepository subdirectory: aString
^ self new
location: aFileReference;
origin: anIceRemoteRepository;
subdirectory: aString;
yourself
@@ -0,0 +1,5 @@
newRepositoryAt: aFileReference subdirectory: aString
^ self new
location: aFileReference;
subdirectory: aString;
yourself
@@ -0,0 +1,2 @@
shortName
^ 'Libgit'
@@ -0,0 +1,7 @@
parseCommitInfo: aLGitCommit
^ IceCommitInfo new
commitId: aLGitCommit id hexString;
username: aLGitCommit committer name;
datetime: aLGitCommit time asDateAndTime;
parentIds: (aLGitCommit parents collect: [ :parent | parent id hexString ]);
comment: aLGitCommit message
@@ -0,0 +1,6 @@
Object subclass: #IceLibgitLocalRepository
uses: TIceRepositoryBackend
instanceVariableNames: 'location subdirectory branch frontend'
classVariableNames: ''
poolDictionaries: ''
category: 'Iceberg-Libgit'
@@ -0,0 +1,3 @@
branch
"The branch variable and this accessor are useful when you do not have a real git repository yet. Once created it might be safer to use #currentBranch instead."
^ branch ifNil: [ branch := self lookupHead ]
@@ -0,0 +1,2 @@
branch: aBranch
branch := aBranch
@@ -0,0 +1,2 @@
frontend
^ frontend
@@ -0,0 +1,2 @@
frontend: anObject
frontend := anObject
@@ -0,0 +1,2 @@
location
^ location
@@ -0,0 +1,2 @@
location: anObject
location := anObject
@@ -0,0 +1,7 @@
origin
| remotes |
remotes := self remotes.
remotes ifEmpty: [ ^ nil ].
^ remotes
detect: [ :each | each isOrigin ]
ifNone: [ remotes first ]
@@ -0,0 +1,7 @@
remotes
| gitRemotes |
self withRepoDo: [ :repo | gitRemotes := repo allRemotes ].
^ gitRemotes collect: [ :each |
(IceRemote url: each url)
remoteName: each remoteName;
yourself ]
@@ -0,0 +1,2 @@
repositoryDirectory
^ self location
@@ -0,0 +1,2 @@
subdirectory
^ subdirectory
@@ -0,0 +1,2 @@
subdirectory: anObject
subdirectory := anObject
@@ -0,0 +1,9 @@
username: aName email: anEmail 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
setString: 'user.name' to: aName;
setString: 'user.email' to: anEmail ]
@@ -0,0 +1,7 @@
addFilesToIndex: aListOfPaths
self withRepoDo: [ :repo |
| index |
index := repo index.
index addAll: aListOfPaths.
index writeToDisk.
]
@@ -0,0 +1,3 @@
addRemote: aRemote
self withRepoDo: [ :repo |
repo addRemote: aRemote remoteName url: aRemote url ]
@@ -0,0 +1,4 @@
checkoutBranch: newBranchName
self withRepoDo: [ :repo |
repo checkout: newBranchName ].
self branch: self lookupHead.
@@ -0,0 +1,2 @@
cloneRepository
self cloneRepositoryFrom: self origin

0 comments on commit d5e336c

Please sign in to comment.