SystemOrganization addCategory: #ShoutCore! !MessageSet methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:31'! shoutAboutToStyle: aMorph self shoutIsModeStyleable ifFalse: [ ^ false ]. aMorph classOrMetaClass: self selectedClassOrMetaClass. ^ true! ! !MCPatchBrowser methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 20:01'! shoutAboutToStyle: aMorph selection ifNotNil: [ self halt. selection isConflict ifTrue: [ ^ false ]. selection isModification ifTrue: [ ^ false ]. selection definition isOrganizationDefinition ifTrue: [ ^ false ]. aMorph classOrMetaClass: (self selectedClassOrMetaClass ifNil: [ Object ]). ^ true ]. ^ false! ! !FileContentsBrowser methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:31'! shoutAboutToStyle: aMorph self shoutIsModeStyleable ifFalse: [ ^ false ]. aMorph classOrMetaClass: self selectedClassOrMetaClass. ^ true! ! !ChangeSorter methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:29'! shoutAboutToStyle: aMorph self shoutIsModeStyleable ifFalse: [ ^ false ]. self currentSelector isNil ifTrue: [ ^ false ]. aMorph classOrMetaClass: self selectedClassOrMetaClass. ^ true! ! !MCSnapshotBrowser methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:42'! bindingOf: aSymbol | binding | (binding := Smalltalk bindingOf: aSymbol) ifNotNil: [ ^ binding ]. items do: [ :each | (each isClassDefinition and: [ each className = aSymbol ]) ifTrue: [ ^ aSymbol -> each ] ]. ^ nil! ! !MCSnapshotBrowser methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:42'! hasBindingThatBeginsWith: aString (Smalltalk hasBindingThatBeginsWith: aString) ifTrue: [ ^ true ]. items do: [ :each | (each isClassDefinition and: [ each className beginsWith: aString ]) ifTrue: [ ^ true ] ]. ^ false! ! !MCSnapshotBrowser methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:55'! shoutAboutToStyle: aMorph | classDef | self switchIsComment ifTrue: [ ^ false ]. methodSelection isNil ifFalse: [ classDef := items detect: [ :ea | ea isClassDefinition and: [ ea className = classSelection ] ] ifNone: [ Smalltalk globals at: classSelection ifPresent: [ :class | class asClassDefinition ] ]. aMorph classOrMetaClass: (classDef ifNotNil: [ SHClassDefinition classDefinition: classDef items: items meta: switch = #class ]). aMorph environment: self. ^ true ]. protocolSelection isNil ifFalse: [ ^ false ]. (classSelection notNil and: [ self text ~= 'This class is defined elsewhere.' ]) ifTrue: [ aMorph classOrMetaClass: nil. aMorph environment: self. ^ true ]. ^ false! ! !CodeHolder methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:17'! shoutAboutToStyle: aMorph "This is a notification that aMorph is about to re-style its text. The default is to answer false to veto the styling." ^ false! ! !CodeHolder methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:17'! shoutIsModeStyleable "Determine if Shout can style in the current mode." ^ self showingSource or: [ self showingPrettyPrint ]! ! !MCTool methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:41'! shoutAboutToStyle: aMorph ^ false! ! !Browser methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:29'! shoutAboutToStyle: aMorph | type | self shoutIsModeStyleable ifFalse: [ ^ false ]. type := self editSelection. (#(newMessage editMessage editClass newClass) includes: type) ifFalse: [ ^ false ]. aMorph classOrMetaClass: (type = #editClass ifFalse: [ self selectedClassOrMetaClass ]). ^ true! ! !MCCodeTool methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:58'! textMorph: aSymbol ^ (super textMorph: aSymbol) beStyled! ! !Debugger methodsFor: '*shoutcore' stamp: 'lr 7/29/2011 19:30'! shoutAboutToStyle: aMorph self shoutIsModeStyleable ifFalse: [ ^ false ]. aMorph classOrMetaClass: self selectedClassOrMetaClass. ^ true! ! Object subclass: #SHClassDefinition instanceVariableNames: 'classDefinition items meta' classVariableNames: '' poolDictionaries: '' category: 'ShoutCore'! !SHClassDefinition class methodsFor: 'class initialization' stamp: 'lr 7/29/2011 19:57'! initialize PluggableTextMorph stylingClass: SHTextStylerST80. PSMCPatchMorph usedByDefault: false! ! !SHClassDefinition methodsFor: 'accessing' stamp: 'tween 5/1/2004 12:35'! allInstVarNames | superclassOrDef answer classOrDef instVars| answer := meta ifTrue:[classDefinition classInstVarNames asArray] ifFalse:[ classDefinition instVarNames asArray]. classOrDef := classDefinition. [superclassOrDef := (classOrDef isKindOf: MCClassDefinition) ifTrue:[ |s| s := classOrDef superclassName. items detect: [:ea | ea isClassDefinition and: [ea className = s]] ifNone: [Smalltalk at: s asSymbol ifAbsent:[nil]]] ifFalse:[ | sc | sc := classOrDef superclass. sc ifNotNil:[ items detect: [:ea | ea isClassDefinition and: [ea className = sc name asString]] ifNone: [sc] ]]. superclassOrDef isNil ] whileFalse:[ instVars := (superclassOrDef isKindOf: MCClassDefinition) ifTrue:[ meta ifTrue:[superclassOrDef classInstVarNames] ifFalse:[superclassOrDef instVarNames]] ifFalse:["real" meta ifTrue:[superclassOrDef theNonMetaClass class instVarNames] ifFalse:[superclassOrDef theNonMetaClass instVarNames]]. answer := answer, instVars. classOrDef := superclassOrDef]. ^answer! ! !SHClassDefinition methodsFor: 'act like environment' stamp: 'tween 5/9/2004 12:27'! bindingOf: aSymbol | binding | (binding := Smalltalk bindingOf: aSymbol) ifNotNil: [^binding]. items do:[:each | (each isClassDefinition and: [each className = aSymbol]) ifTrue:[^aSymbol -> each]]. ^nil! ! !SHClassDefinition methodsFor: 'accessing' stamp: 'tween 5/1/2004 11:38'! classDefinition: aMCClassDefinition classDefinition := aMCClassDefinition! ! !SHClassDefinition methodsFor: 'act like a class' stamp: 'tween 5/1/2004 12:17'! classPool | d | d := Dictionary new. classDefinition classVarNames do:[:each | d at: each put: nil]. ^d! ! !SHClassDefinition methodsFor: 'act like a class' stamp: 'tween 5/9/2004 12:21'! environment ^self! ! !SHClassDefinition methodsFor: 'act like environment' stamp: 'tween 5/9/2004 12:38'! hasBindingThatBeginsWith: aString (Smalltalk hasBindingThatBeginsWith: aString) ifTrue: [^true]. items do:[:each | (each isClassDefinition and: [each className beginsWith: aString]) ifTrue:[^true]]. ^false! ! !SHClassDefinition methodsFor: 'accessing' stamp: 'tween 5/1/2004 11:37'! items: anObject items := anObject! ! !SHClassDefinition methodsFor: 'accessing' stamp: 'tween 5/1/2004 12:26'! meta: aBoolean meta := aBoolean! ! !SHClassDefinition methodsFor: 'act like a class' stamp: 'tween 5/1/2004 12:20'! sharedPools | d | d := Set new. classDefinition poolDictionaries do:[:each | d add: [Smalltalk at: each asSymbol ifAbsent:[nil]] ]. ^d! ! !SHClassDefinition methodsFor: 'act like a class' stamp: 'tween 5/1/2004 12:28'! theNonMetaClass ^self copy meta: false; yourself! ! !SHClassDefinition methodsFor: 'accessing' stamp: 'tween 5/1/2004 12:13'! withAllSuperclasses | superclassOrDef answer classOrDef | answer := Array with: self. classOrDef := classDefinition. [superclassOrDef := (classOrDef isKindOf: MCClassDefinition) ifTrue:[ |s| s := classOrDef superclassName. items detect: [:ea | ea isClassDefinition and: [ea className = s]] ifNone: [Smalltalk at: s asSymbol ifAbsent:[nil]]] ifFalse:[ | sc | sc := classOrDef superclass. sc ifNotNil:[ items detect: [:ea | ea isClassDefinition and: [ea className = sc name asString]] ifNone: [sc] ]]. superclassOrDef isNil ] whileFalse:[ answer := answer, (Array with: superclassOrDef). classOrDef := superclassOrDef]. ^answer! ! SHClassDefinition initialize!