Skip to content

Commit

Permalink
Monticello dependencies
Browse files Browse the repository at this point in the history
  • Loading branch information
pavel-krivanek committed Nov 2, 2019
1 parent 1c5826b commit 70d198b
Show file tree
Hide file tree
Showing 6 changed files with 23 additions and 21 deletions.
9 changes: 9 additions & 0 deletions src/Monticello/CommandLineUIManager.extension.st
@@ -0,0 +1,9 @@
Extension { #name : #CommandLineUIManager }

{ #category : #'*Monticello' }
CommandLineUIManager >> merge: merger informing: aString [
"Check for conflicts, if there are none, just continue.
Merger will accept all conflicts"
merger hasConflicts ifFalse: [ ^ self ].
self abort: aString title: 'Conflict detected'
]
9 changes: 9 additions & 0 deletions src/Monticello/NonInteractiveUIManager.extension.st
@@ -0,0 +1,9 @@
Extension { #name : #NonInteractiveUIManager }

{ #category : #'*Monticello' }
NonInteractiveUIManager >> merge: merger informing: aString [
"Check for conflicts, if there are none, just continue.
Merger will accept all conflicts"
super merge: merger informing: aString.
merger hasConflicts ifTrue: [ self exitFailure ]
]
8 changes: 4 additions & 4 deletions src/System-DependenciesTests/SystemDependenciesTest.class.st
Expand Up @@ -68,7 +68,7 @@ SystemDependenciesTest >> knownCompilerDependencies [

"ideally this list should be empty"

^ #(#DeprecatedFileStream #'FileSystem-Core' #Monticello #'System-Changes' #'System-Localization' #'Transcript-Core')
^ #(#DeprecatedFileStream #'FileSystem-Core' #'System-Changes' #'System-Localization' #'Transcript-Core')
]

{ #category : #'known dependencies' }
Expand All @@ -84,7 +84,7 @@ SystemDependenciesTest >> knownFileSystemDependencies [

"ideally this list should be empty"

^ #(#Monticello #'System-Changes' #'System-Localization' #'Transcript-Core' #'Zinc-Resource-Meta-Core')
^ #(#'System-Changes' #'System-Localization' #'Transcript-Core' #'Zinc-Resource-Meta-Core')
]

{ #category : #'known dependencies' }
Expand All @@ -101,7 +101,7 @@ SystemDependenciesTest >> knownKernelDependencies [

"ideally this list should be empty"

^ #(#'FileSystem-Core' #Monticello #'OpalCompiler-Core' #'System-Changes' #'AST-Core')
^ #(#'FileSystem-Core' #'OpalCompiler-Core' #'System-Changes' #'AST-Core')
]

{ #category : #'known dependencies' }
Expand Down Expand Up @@ -157,7 +157,7 @@ SystemDependenciesTest >> knownSUnitKernelDependencies [

"ideally this list should be empty"

^ #(#'FileSystem-Core' #Monticello #'OpalCompiler-Core' #'System-Changes' #'AST-Core')
^ #(#'FileSystem-Core' #'OpalCompiler-Core' #'System-Changes' #'AST-Core')
]

{ #category : #'known dependencies' }
Expand Down
8 changes: 0 additions & 8 deletions src/UIManager/CommandLineUIManager.class.st
Expand Up @@ -273,14 +273,6 @@ CommandLineUIManager >> logYellowDuring: aBlock [
^ self logColored: '33' during: aBlock
]

{ #category : #'ui requests' }
CommandLineUIManager >> merge: merger informing: aString [
"Check for conflicts, if there are none, just continue.
Merger will accept all conflicts"
merger hasConflicts ifFalse: [ ^ self ].
self abort: aString title: 'Conflict detected'
]

{ #category : #display }
CommandLineUIManager >> newDisplayDepthNoRestore: pixelSize [
"do nothing"
Expand Down
2 changes: 1 addition & 1 deletion src/UIManager/ManifestUIManager.class.st
Expand Up @@ -14,5 +14,5 @@ ManifestUIManager class >> ignoredDependencies [

{ #category : #'meta-data - dependency analyser' }
ManifestUIManager class >> manuallyResolvedDependencies [
^ #(#'Collections-Streams' #'System-Support' #'OpalCompiler-Core' #Monticello #'System-Settings-Core')
^ #(#'Collections-Streams' #'System-Support' #'OpalCompiler-Core' #'System-Settings-Core')
]
8 changes: 0 additions & 8 deletions src/UIManager/NonInteractiveUIManager.class.st
Expand Up @@ -128,14 +128,6 @@ NonInteractiveUIManager >> lowSpaceWatcherDefaultAction: preemptedProcess [
self error. "what else we can do? "
]

{ #category : #'ui requests' }
NonInteractiveUIManager >> merge: merger informing: aString [
"Check for conflicts, if there are none, just continue.
Merger will accept all conflicts"
super merge: merger informing: aString.
merger hasConflicts ifTrue: [ self exitFailure ]
]

{ #category : #'ui requests' }
NonInteractiveUIManager >> multiLineRequest: queryString initialAnswer: defaultAnswer answerHeight: answerHeight [
^ self nonInteractiveRequest: queryString
Expand Down

0 comments on commit 70d198b

Please sign in to comment.