[squeak-dev] The Trunk: HelpSystem-Core-mt.66.mcz

commits at source.squeak.org commits at source.squeak.org
Wed Mar 25 10:29:31 UTC 2015


Marcel Taeumel uploaded a new version of HelpSystem-Core to project The Trunk:
http://source.squeak.org/trunk/HelpSystem-Core-mt.66.mcz

==================== Summary ====================

Name: HelpSystem-Core-mt.66
Author: mt
Time: 25 March 2015, 11:29:26.547 am
UUID: c1308541-7e10-544a-97a6-4f2887a2178d
Ancestors: HelpSystem-Core-mt.65

Help browser uses now the tool builder. To increase performance, the help system creates help topics now lazily (that is, the use of topic builders is not suggested but still possible for backwards compatibility). For example, "HelpBrowser openOn: SystemReference" opens now faster. New kinds of help topics should be implemented by subclassing AbstractHelpTopic.

=============== Diff against HelpSystem-Core-mt.65 ===============

Item was added:
+ Object subclass: #AbstractHelpTopic
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'HelpSystem-Core-Model'!
+ 
+ !AbstractHelpTopic commentStamp: 'mt 3/24/2015 16:26' prior: 0!
+ A HelpTopic provides content information that can be used as a help to the user.
+ It can be labeled with a title and marked with an (optional) icon.
+ 
+ Help topics form a hierarchy since any topic is able to have zero or more
+ subtopics. !

Item was added:
+ ----- Method: AbstractHelpTopic>><= (in category 'comparing') -----
+ <= anotherHelpTopic
+ 
+ 	"Priority-based: ... -3 -2 -1 nil nil nil 1 2 3 4 ..."
+ 	(self priority notNil and: [anotherHelpTopic priority notNil])
+ 		ifTrue: [^ self priority <= anotherHelpTopic priority].
+ 
+ 	(self priority notNil and: [anotherHelpTopic priority isNil])
+ 		ifTrue: [^ self priority <= 0].
+ 
+ 	(self priority isNil and: [anotherHelpTopic priority notNil])
+ 		ifTrue: [^ anotherHelpTopic priority >= 0].
+ 
+ 	"Fall-back."
+ 	^ self title <= anotherHelpTopic title!

Item was added:
+ ----- Method: AbstractHelpTopic>>asHelpTopic (in category 'conversion') -----
+ asHelpTopic
+ 
+ 	^ self!

Item was added:
+ ----- Method: AbstractHelpTopic>>contents (in category 'accessing') -----
+ contents
+ 	"Return the text contents of this topic."
+ 	
+ 	self subclassResponsibility.!

Item was added:
+ ----- Method: AbstractHelpTopic>>hasSubtopics (in category 'testing') -----
+ hasSubtopics
+ 
+ 	^ self subtopics notEmpty!

Item was added:
+ ----- Method: AbstractHelpTopic>>icon (in category 'accessing') -----
+ icon
+ 	"Returns a descriptive form to support manual detection in a list of topics. Icons may encode the kind of topic."
+ 	
+ 	^ nil!

Item was added:
+ ----- Method: AbstractHelpTopic>>printOn: (in category 'printing') -----
+ printOn: stream
+ 
+ 	| title |
+ 	super printOn: stream.
+ 	(title := self title) notNil 
+ 		ifTrue: [stream nextPutAll: '<' , title , '>'].!

Item was added:
+ ----- Method: AbstractHelpTopic>>priority (in category 'accessing') -----
+ priority
+ 
+ 	^ nil!

Item was added:
+ ----- Method: AbstractHelpTopic>>subtopics (in category 'accessing') -----
+ subtopics
+ 	"Topics can be nested in a tree structure."
+ 
+ 	^ #()!

Item was added:
+ ----- Method: AbstractHelpTopic>>title (in category 'accessing') -----
+ title
+ 	"A brief description of this topic's contents."
+ 
+ 	^ self contents truncateWithElipsisTo: 20!

Item was added:
+ AbstractHelpTopic subclass: #ClassAPIHelpTopic
+ 	instanceVariableNames: 'theClass withSubclasses withMethods subclassesAsSeparateTopic'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'HelpSystem-Core-Model'!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>contents (in category 'accessing') -----
+ contents
+ 
+ 	^ self theClass instanceSide organization classComment!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>icon (in category 'accessing') -----
+ icon
+ 
+ 	^ ToolIcons iconNamed: (ToolIcons iconForClass: self theClass name)!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>subclassesAsSeparateTopic (in category 'accessing') -----
+ subclassesAsSeparateTopic
+ 
+ 	^ subclassesAsSeparateTopic!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>subclassesAsSeparateTopic: (in category 'accessing') -----
+ subclassesAsSeparateTopic: aBoolean
+ 
+ 	subclassesAsSeparateTopic := aBoolean.!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>subtopics (in category 'accessing') -----
+ subtopics
+ 	
+ 	^ (self withMethods ifFalse: [#()] ifTrue: [ {
+ 		MethodListHelpTopic new theClass: self theClass theNonMetaClass.
+ 		MethodListHelpTopic new theClass: self theClass theMetaClass }]),
+ 
+ 	(self withSubclasses ifFalse: [#()] ifTrue: [
+ 		| topics |
+ 		topics := self theClass subclasses collect: [:cls |
+ 			self class new
+ 				theClass: cls;
+ 				subclassesAsSeparateTopic: self subclassesAsSeparateTopic;
+ 				withMethods: self withMethods;
+ 				withSubclasses: self withSubclasses].
+ 
+ 		self subclassesAsSeparateTopic
+ 			ifTrue: [{(HelpTopic named: 'Subclasses')
+ 				subtopics: topics;
+ 				yourself}]
+ 			ifFalse: [topics]])!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>theClass (in category 'accessing') -----
+ theClass
+ 
+ 	^ theClass!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>theClass: (in category 'accessing') -----
+ theClass: aClassDescription
+ 
+ 	theClass := aClassDescription.!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>title (in category 'accessing') -----
+ title
+ 
+ 	^ self theClass name!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>withMethods (in category 'accessing') -----
+ withMethods
+ 
+ 	^ withMethods!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>withMethods: (in category 'accessing') -----
+ withMethods: aBoolean
+ 
+ 	withMethods := aBoolean.!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>withSubclasses (in category 'accessing') -----
+ withSubclasses
+ 
+ 	^ withSubclasses!

Item was added:
+ ----- Method: ClassAPIHelpTopic>>withSubclasses: (in category 'accessing') -----
+ withSubclasses: aBoolean
+ 
+ 	withSubclasses := aBoolean.!

Item was added:
+ AbstractHelpTopic subclass: #ClassBasedHelpTopic
+ 	instanceVariableNames: 'helpClass'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'HelpSystem-Core-Model'!
+ 
+ !ClassBasedHelpTopic commentStamp: 'mt 3/24/2015 16:28' prior: 0!
+ This kind of topic uses subclasses and methods to encode books and pages.!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>contents (in category 'accessing') -----
+ contents
+ 	"A book has no contents. Only its pages do."
+ 	
+ 	^ ''!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>hasSubtopics (in category 'testing') -----
+ hasSubtopics
+ 
+ 	^ self helpClass pages notEmpty or: [self helpClass subclasses notEmpty]!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>helpClass (in category 'accessing') -----
+ helpClass
+ 
+ 	^ helpClass!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>helpClass: (in category 'accessing') -----
+ helpClass: aHelpClass
+ 
+ 	helpClass := aHelpClass.!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>icon (in category 'accessing') -----
+ icon
+ 	^ self helpClass icon!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>priority (in category 'accessing') -----
+ priority
+ 
+ 	^ self helpClass priority!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>subtopics (in category 'accessing') -----
+ subtopics
+ 
+ 	| pages |
+ 	pages := (self helpClass pages collect: [:pageSelectorOrClassName |
+ 		(Smalltalk hasClassNamed: pageSelectorOrClassName asString)
+ 			ifTrue: [Smalltalk classNamed: pageSelectorOrClassName asString]
+ 			ifFalse: [pageSelectorOrClassName]]) asOrderedCollection.
+ 
+ 	self helpClass subclasses do: [:cls |
+ 		pages addIfNotPresent: cls].	
+ 
+ 	^ pages withIndexCollect: [:pageSelectorOrClass :priority |
+ 		pageSelectorOrClass isBehavior
+ 			ifFalse: [(self helpClass perform: pageSelectorOrClass) priority: priority - pages size; yourself]
+ 			ifTrue: [pageSelectorOrClass asHelpTopic]]!

Item was added:
+ ----- Method: ClassBasedHelpTopic>>title (in category 'accessing') -----
+ title
+ 	^ self helpClass bookName!

Item was changed:
  ----- Method: CustomHelp class>>asHelpTopic (in category 'converting') -----
  asHelpTopic
  	"Convert the receiver to a help topic"
  	
+ 	^ ClassBasedHelpTopic new helpClass: self!
- 	^self builder buildHelpTopicFrom: self!

Item was removed:
- ----- Method: CustomHelp class>>builder (in category 'defaults') -----
- builder
- 	"Returns the builder that is used to build the given help book from the receiver. You can override this method
- 	 in a subclass to provide an own builder".
- 	
- 	^CustomHelpHelpBuilder!

Item was removed:
- ----- Method: CustomHelp class>>key (in category 'accessing') -----
- key
- 	"Returns a unique key identifying the receiver in the help system"
- 	
- 	^''!

Item was added:
+ ----- Method: CustomHelp class>>priority (in category 'accessing') -----
+ priority
+ 
+ 	^ nil!

Item was added:
+ ----- Method: HelpAPIDocumentation class>>asHelpTopic (in category 'defaults') -----
+ asHelpTopic
+ 
+ 	^ (HelpTopic named: self bookName)
+ 		subtopics: (self packages collect: [:pkgName | PackageAPIHelpTopic new packageName: pkgName]);
+ 		yourself!

Item was removed:
- ----- Method: HelpAPIDocumentation class>>builder (in category 'defaults') -----
- builder
- 	^PackageAPIHelpBuilder!

Item was changed:
  Object subclass: #HelpBrowser
+ 	instanceVariableNames: 'rootTopic topic result'
- 	instanceVariableNames: 'rootTopic window treeMorph contentMorph topicClass topicMethod topic result'
  	classVariableNames: 'DefaultHelpBrowser'
  	poolDictionaries: ''
  	category: 'HelpSystem-Core-UI'!
  
  !HelpBrowser commentStamp: 'tbn 3/8/2010 09:33' prior: 0!
  A HelpBrowser is used to display a hierarchy of help topics and their contents.
  
  Instance Variables
  	rootTopic: 		<HelpTopic>
  	window:			<StandardWindow>	 
  	treeMorph:		<PluggableTreeMorph>
  	contentMorph:		<Morph>			
  
  rootTopic
  	- xxxxx
  
  window
  	- xxxxx
  
  treeMorph 
  	- xxxxx
  
  contentMorph 
  	- xxxxx
  
  !

Item was changed:
  ----- Method: HelpBrowser class>>open (in category 'instance creation') -----
  open
+ 	^self openOn: CustomHelp!
- 	^self openOn: SystemHelp!

Item was changed:
  ----- Method: HelpBrowser class>>openOn: (in category 'instance creation') -----
  openOn: aHelpTopic
          "Open the receiver on the given help topic or any other object that can be transformed into
           a help topic by sending #asHelpTopic."
          
          ^(self defaultHelpBrowser new)
+ 		open;
+ 		rootTopic: aHelpTopic;
+ 		yourself!
-                 rootTopic: aHelpTopic;
-                 open;
-                 yourself!

Item was changed:
  ----- Method: HelpBrowser>>accept: (in category 'actions') -----
  accept: text
  	"Accept edited text. Compile it into a HelpTopic"
  
+ 	| code topicClass topicMethod |
+ 	(self find: self topic contents) asArray ifNotEmpty: [:refs |
+ 		topicClass := refs first actualClass theNonMetaClass. 
+ 		topicMethod := refs first selector].
+ 	
- 	| code |
  	code := String streamContents:[:s|
  		s nextPutAll: topicMethod.
  		s crtab; nextPutAll: '"This method was automatically generated. Edit it using:"'.
  		s crtab; nextPutAll: '"', self name,' edit: ', topicMethod storeString,'"'.
  		s crtab; nextPutAll: '^HelpTopic'.
  		s crtab: 2; nextPutAll: 'title: ', topic title storeString.
  		s crtab: 2; nextPutAll: 'contents: '.
  		s cr; nextPutAll: (String streamContents:[:c| c nextChunkPutWithStyle: text]) storeString.
  		s nextPutAll:' readStream nextChunkText'.
  	].
  
  	topicClass class
  		compile: code
  		classified: ((topicClass class organization categoryOfElement: topicMethod) ifNil:['pages']).
+ 
+ 	self flag: #fixme. "mt: Update will not work because the topic builder eagerly cached all the contents and lost track of its origins. We need to get rid of the topic builders and create topic contents lazily resp. live."
+ 
+ 	self changed: #topics.
+ 	self changed: #topic.
+ 	self changed: #topicContents.
- 	self refresh.
      !

Item was added:
+ ----- Method: HelpBrowser>>buildWith: (in category 'toolbuilder') -----
+ buildWith: builder
+ 
+ 	| windowSpec treeSpec textSpec |
+ 	windowSpec := builder pluggableWindowSpec new.
+ 	windowSpec
+ 		model: self;
+ 		children: OrderedCollection new;
+ 		label: #label.
+ 
+ 	treeSpec := builder pluggableTreeSpec new.
+ 	treeSpec
+ 		model: self;
+ 		nodeClass: HelpTopicListItemWrapper;
+ 		roots: #topics;
+ 		getSelected: #topic;
+ 		setSelected: #topic:;
+ 		menu: #menu:;
+ 		autoDeselect: false;
+ 		frame: (0 at 0 corner: 0.3 at 1).
+ 	windowSpec children add: treeSpec.
+ 
+ 	textSpec := builder pluggableTextSpec new.
+ 	textSpec
+ 		model: self;
+ 		getText: #topicContents;
+ 		setText: #accept:;
+ 		menu: #codePaneMenu:shifted:;
+ 		frame: (0.3 at 0 corner: 1 at 1).
+ 	windowSpec children add: textSpec.
+ 
+ 	^ builder build: windowSpec!

Item was removed:
- ----- Method: HelpBrowser>>close (in category 'ui') -----
- close
- 	window notNil ifTrue: [window delete]!

Item was removed:
- ----- Method: HelpBrowser>>defaultRoot (in category 'defaults') -----
- defaultRoot
- 	^CustomHelp!

Item was removed:
- ----- Method: HelpBrowser>>defaultViewerClass (in category 'defaults') -----
- defaultViewerClass	 
- 	^PluggableTextMorph!

Item was changed:
  ----- Method: HelpBrowser>>findStringInHelpTopic: (in category 'actions') -----
  findStringInHelpTopic: aString
+ 
- 	| list |
  	result := OrderedCollection new.
+ 	self inSubtopic: self rootTopic find: aString.
+ 	result ifNotEmpty: [self topic: result first]. 
- 	list := treeMorph scroller submorphs collect: [ :each | each complexContents].
- 	list do:[ : topic | self inSubtopic: topic find: aString ].
- 	self onItemClicked: result first. 
  	!

Item was changed:
  ----- Method: HelpBrowser>>inSubtopic:find: (in category 'actions') -----
  inSubtopic: aTopic find: aString 
+ 	((aTopic title asString includesSubstring: aString caseSensitive: false)
+ 			or: [aTopic contents asString includesSubstring: aString caseSensitive: false])
+ 		ifTrue: [result addIfNotPresent:  aTopic].
+ 	aTopic subtopics
- 	((aTopic asString includesSubString: aString)
- 			or: [aTopic item contents asString includesSubString: aString])
- 		ifTrue: [result addIfNotPresent:  aTopic item].
- 	aTopic contents
  		do: [:sub | self inSubtopic: sub find: aString]!

Item was removed:
- ----- Method: HelpBrowser>>initWindow (in category 'initialize-release') -----
- initWindow
- 	window := SystemWindow labelled: 'Help Browser'.
- 	window model: self.
- 	"Tree"
- 	treeMorph := PluggableTreeMorph new.
- 	treeMorph
- 		model: self;
- 		setSelectedSelector: #onItemClicked:;
- 		getSelectedSelector: #topic;
- 		getMenuSelector: #menu:.
- 	window addMorph: treeMorph frame: (0 at 0 corner: 0.3 at 1).
- 	
- 	"Text"
- 	contentMorph := self defaultViewerClass on: self 
- 			text: nil accept: #accept:
- 			readSelection: nil menu: #codePaneMenu:shifted:.
- 	window addMorph: contentMorph frame: (0.3 at 0 corner: 1 at 1).		
- 			!

Item was removed:
- ----- Method: HelpBrowser>>initialize (in category 'initialize-release') -----
- initialize 
- 	super initialize. 
- 	self initWindow.
-  !

Item was added:
+ ----- Method: HelpBrowser>>label (in category 'accessing - ui') -----
+ label
+ 
+ 	^ self rootTopic
+ 		ifNil: ['Help Browser']
+ 		ifNotNil: [:topic | topic title]!

Item was removed:
- ----- Method: HelpBrowser>>onItemClicked: (in category 'events') -----
- onItemClicked: anItem
- 
- 	anItem ifNil: [^contentMorph setText: rootTopic asHelpTopic contents].
- 	contentMorph setText: anItem contents. 
- 	self topic: anItem.	!

Item was changed:
  ----- Method: HelpBrowser>>open (in category 'ui') -----
  open	
-  	"Open the receivers window" 
  
+ 	ToolBuilder open: self.!
- 	self refresh.	
- 	window openInWorld.
- 	 !

Item was removed:
- ----- Method: HelpBrowser>>refresh (in category 'actions') -----
- refresh
- 
-         |helpTopic items|
-         helpTopic := rootTopic asHelpTopic.
-         window setLabel: helpTopic title.
-         items := helpTopic subtopics collect: [:each | HelpTopicListItemWrapper with: each ].
-         treeMorph list: items.
-         contentMorph setText: helpTopic contents
- !

Item was changed:
  ----- Method: HelpBrowser>>rootTopic: (in category 'accessing') -----
  rootTopic: aHelpTopic
  
+ 	rootTopic := aHelpTopic asHelpTopic. 
+ 	
+ 	self changed: #label.
+ 	self changed: #topics.!
- 	rootTopic := aHelpTopic. 
- 	self refresh !

Item was removed:
- ----- Method: HelpBrowser>>step (in category 'stepping') -----
- step
- 	 "Do nothing when the window dispatches stepping back to the model"!

Item was changed:
  ----- Method: HelpBrowser>>topic (in category 'accessing') -----
  topic
+ 
  	^ topic!

Item was changed:
  ----- Method: HelpBrowser>>topic: (in category 'accessing') -----
+ topic: aHelpTopic
- topic: anItem
  
+ 	self topic == aHelpTopic ifTrue: [^ self].
+ 	
+ 	topic := aHelpTopic.
+ 	
+ 	self changed: #topic.
+ 	self changed: #topicContents.!
- 	| classList |
- 	topic := anItem.
- 	classList := (self find: anItem contents) asOrderedCollection.
- 	classList ifNotEmpty:[
- 		topicClass := classList first actualClass theNonMetaClass. 
- 		topicMethod := classList first selector].
- 	self changed: #topic.!

Item was added:
+ ----- Method: HelpBrowser>>topicContents (in category 'accessing - ui') -----
+ topicContents
+ 
+ 	^ (self topic ifNil: [self rootTopic]) ifNil: '' ifNotNil: #contents!

Item was added:
+ ----- Method: HelpBrowser>>topics (in category 'accessing - ui') -----
+ topics
+ 
+ 	^ (self rootTopic ifNil: [#()] ifNotNil: #subtopics) sorted!

Item was removed:
- ----- Method: HelpOnHelp class>>key (in category 'accessing') -----
- key
- 	^'HelpOnHelp'!

Item was added:
+ ----- Method: HelpOnHelp class>>priority (in category 'accessing') -----
+ priority
+ 
+ 	^ 9999 "at the bottom"!

Item was changed:
+ AbstractHelpTopic subclass: #HelpTopic
+ 	instanceVariableNames: 'title key icon contents subtopics priority'
- Object subclass: #HelpTopic
- 	instanceVariableNames: 'title key icon contents subtopics'
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'HelpSystem-Core-Model'!
  
+ !HelpTopic commentStamp: 'mt 3/25/2015 11:27' prior: 0!
+ This is a configurable version of a help topic. You can define its contents, title, icon, and subtopics manually.
- !HelpTopic commentStamp: 'tbn 3/29/2010 14:53' prior: 0!
- A HelpTopic provides content information that can be used as a help to the user.
- It can be labeled with a title, identified using an (optional) unique key and marked 
- with an (optional) icon.
  
+ Help builders make use of this.!
- Help topics form a hierarchy since any topic is able to have zero or more
- subtopics. 
- 
- 
- Instance Variables
- 	contents:		<Object>      The help topic contents
- 	icon:			<Form|nil>	   An optional icon for the topic
- 	key:			<String|nil>    An optional unique key
- 	subtopics:	      <Collection>  A collection of subtopics
- 	title:			<String>        The title
- 
- contents
- 	- The help topic contents - typically containing the help topics information
- 
- icon
- 	- An optional icon for the topic
- 
- key
- 	- An optional unique key which can be used to identify the topic. 
- 
- subtopics
- 	- A collection of subtopics. 
- 	  By default the subtopics are not sorted, so the insertion order is used. 
- 	  If necessary it is possible to sort the subtopics by title.
- 
- title
- 	- A meaninful title for the help topic
- !

Item was removed:
- ----- Method: HelpTopic>><= (in category 'comparing') -----
- <= anotherHelpTopic
- 	"Use sorting by title as the default sort order"
- 	
- 	^self title <= anotherHelpTopic title !

Item was removed:
- ----- Method: HelpTopic>>asHelpTopic (in category 'conversion') -----
- asHelpTopic 
- 	"Converts the receiver to a help topic"
- 	
- 	^self!

Item was removed:
- ----- Method: HelpTopic>>hasSubtopics (in category 'testing') -----
- hasSubtopics 
- 	"Returns true if the receiver has subtopics, false otherwise"
- 	
- 	^self subtopics notEmpty !

Item was changed:
  ----- Method: HelpTopic>>initialize (in category 'initialize-release') -----
  initialize 
  	"Initializes the receiver"
  	
  	super initialize.
  	self title: self defaultTitle.
+ 	self contents: ''.!
- 	self contents: ''.
- 	self key: '' !

Item was removed:
- ----- Method: HelpTopic>>key (in category 'accessing') -----
- key 	
- 	"Returns a unique key identifying the receiver in the help system"	
- 		
- 	^key!

Item was removed:
- ----- Method: HelpTopic>>key: (in category 'accessing') -----
- key: aUniqueKey
- 	"Sets a unique key identifying the receiver in the help system"	
- 		
- 	key := aUniqueKey !

Item was added:
+ ----- Method: HelpTopic>>priority (in category 'accessing') -----
+ priority
+ 	"A hint for tools to influence sort order."
+ 	
+ 	^ priority!

Item was added:
+ ----- Method: HelpTopic>>priority: (in category 'accessing') -----
+ priority: anInteger
+ 
+ 	priority := anInteger.!

Item was changed:
  ----- Method: HelpTopicListItemWrapper>>asString (in category 'accessing') -----
  asString
  	"Returns a string used as a label"
  	
+ 	^ self item title!
- 	^item title!

Item was changed:
  ----- Method: HelpTopicListItemWrapper>>contents (in category 'accessing') -----
  contents
- 	"Returns subnodes (if any)"
  	
+ 	^self item subtopics sorted collect: [ :each | 
+ 		HelpTopicListItemWrapper with: each model: self model]
-  	item hasSubtopics ifFalse: [^#()].	
- 	^(item subtopics) collect: [ :each | 
- 		HelpTopicListItemWrapper with: each
- 	].
  !

Item was added:
+ ----- Method: HelpTopicListItemWrapper>>hasContents (in category 'accessing') -----
+ hasContents
+ 	
+ 	^ self item hasSubtopics!

Item was changed:
  ----- Method: HelpTopicListItemWrapper>>icon (in category 'accessing') -----
  icon
  	"Either return the icon for the given topic"
  	
  	| symbol |
+ 	self item icon ifNotNil: [:icon | ^ icon].
+ 	symbol := self item hasSubtopics 
- 	item icon notNil ifTrue: [^item icon].
- 	symbol := item hasSubtopics 
  					 ifTrue: [#bookIcon] 
  			  		 ifFalse: [#pageIcon].
  	^HelpIcons iconNamed: symbol!

Item was added:
+ ----- Method: HelpTopicListItemWrapper>>item (in category 'accessing') -----
+ item
+ 
+ 	^ super item ifNil: [HelpTopic new]!

Item was added:
+ AbstractHelpTopic subclass: #MethodListHelpTopic
+ 	instanceVariableNames: 'theClass'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'HelpSystem-Core-Model'!

Item was added:
+ ----- Method: MethodListHelpTopic>>contents (in category 'accessing') -----
+ contents
+ 
+ 	^ (String streamContents: [ :stream |
+ 		self theClass selectors sort do: [ :selector |
+ 			stream 
+ 				nextPutAll: self theClass name;
+ 				nextPutAll: '>>';
+ 				nextPutAll: selector asString;
+ 				cr;
+ 				nextPutAll: (
+ 					(self theClass commentsAt: selector)
+ 						at: 1
+ 						ifAbsent: [ '-' ]);
+ 				cr; cr ] ])!

Item was added:
+ ----- Method: MethodListHelpTopic>>icon (in category 'accessing') -----
+ icon
+ 
+ 	^ HelpIcons iconNamed: #pageIcon!

Item was added:
+ ----- Method: MethodListHelpTopic>>priority (in category 'accessing') -----
+ priority
+ 
+ 	^ -999!

Item was added:
+ ----- Method: MethodListHelpTopic>>theClass (in category 'accessing') -----
+ theClass
+ 
+ 	^ theClass!

Item was added:
+ ----- Method: MethodListHelpTopic>>theClass: (in category 'accessing') -----
+ theClass: aClassOrMetaClass
+ 
+ 	theClass := aClassOrMetaClass.!

Item was added:
+ ----- Method: MethodListHelpTopic>>title (in category 'accessing') -----
+ title
+ 
+ 	^ self theClass isMeta
+ 		ifTrue: ['Class side']
+ 		ifFalse: ['Instance side']!

Item was added:
+ AbstractHelpTopic subclass: #PackageAPIHelpTopic
+ 	instanceVariableNames: 'packageName'
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'HelpSystem-Core-Model'!

Item was added:
+ ----- Method: PackageAPIHelpTopic>>contents (in category 'accessing') -----
+ contents
+ 
+ 	^ ''!

Item was added:
+ ----- Method: PackageAPIHelpTopic>>hasSubtopics (in category 'testing') -----
+ hasSubtopics
+ 
+ 	^ SystemOrganization categories anySatisfy: [:cat |
+ 		(cat beginsWith: self packageName) and: [(SystemOrganization listAtCategoryNamed: cat) notEmpty]]!

Item was added:
+ ----- Method: PackageAPIHelpTopic>>packageName (in category 'accessing') -----
+ packageName
+ 
+ 	^ packageName!

Item was added:
+ ----- Method: PackageAPIHelpTopic>>packageName: (in category 'accessing') -----
+ packageName: aString
+ 
+ 	packageName := aString.!

Item was added:
+ ----- Method: PackageAPIHelpTopic>>subtopics (in category 'accessing') -----
+ subtopics
+ 
+ 	^ ((PackageInfo named: self packageName) classes
+ 		sorted: [:cl1 :cl2 | cl1 name < cl2 name])
+ 		collect: [:class | ClassAPIHelpTopic new
+ 			theClass: class;
+ 			withSubclasses: false;
+ 			withMethods: true]!

Item was added:
+ ----- Method: PackageAPIHelpTopic>>title (in category 'accessing') -----
+ title
+ 
+ 	^ self packageName!

Item was removed:
- Object subclass: #SystemHelp
- 	instanceVariableNames: ''
- 	classVariableNames: ''
- 	poolDictionaries: ''
- 	category: 'HelpSystem-Core-Utilities'!
- 
- !SystemHelp commentStamp: 'tbn 4/30/2010 15:33' prior: 0!
- This class defines Help for the system in front of you.
- It defines the default contents when you open a help browser.
- 
- So "HelpBrowser open" is the same as "HelpBrowser openOn: SystemHelp".
- 
- 
- !

Item was removed:
- ----- Method: SystemHelp class>>asHelpTopic (in category 'conversion') -----
- asHelpTopic 
- 	|topic helpOnHelp sortedTopics |
- 	topic := CustomHelp asHelpTopic.
- 	topic sortSubtopicsByTitle.
- 	helpOnHelp := topic subtopics detect: [:t | t key = 'HelpOnHelp'] ifNone: [self error: 'Help for the help system is removed'].
- 	sortedTopics := topic subtopics.
- 	sortedTopics remove: helpOnHelp.
- 	sortedTopics addLast: helpOnHelp.
- 	topic subtopics: sortedTopics.
- 	^topic.
- !

Item was changed:
  ----- Method: SystemReference class>>all (in category 'help topic creation') -----
  all
  	"HelpBrowser openOn: self all "
  	
+ 	^(ClassAPIHelpTopic new)
+ 		theClass: ProtoObject;
+ 		withSubclasses: true;
+ 		withMethods: true;
+ 		subclassesAsSeparateTopic: false!
- 	^(ClassAPIHelpBuilder new)
- 		rootToBuildFrom: ProtoObject;
- 		addSubclasses: true;
- 		addMethods: true;
- 		subclassesAsSeparateTopic: false;
- 		build;
- 		topicToBuild 
- 	 
- 		 !

Item was changed:
  ----- Method: SystemReference class>>forClass: (in category 'help topic creation') -----
  forClass: aClass
  	|root topic |
  	root := HelpTopic named: 'System reference for ', aClass name.
+ 	topic := ClassAPIHelpTopic new theClass: aClass.
- 	topic := ClassAPIHelpBuilder buildHelpTopicFrom: aClass.
  	root addSubtopic: topic.
  	^root!

Item was changed:
  ----- Method: SystemReference class>>hierarchyFor: (in category 'help topic creation') -----
  hierarchyFor: aClass
  	 
+ 	| root topic |
- 	|root topic |
  	root := HelpTopic named: 'System reference for ', aClass name.
+ 	topic := (ClassAPIHelpTopic new)
+ 					theClass: aClass;
+ 					withSubclasses: true;
+ 					withMethods: false;
+ 					subclassesAsSeparateTopic: false.
- 	topic := (ClassAPIHelpBuilder new)
- 					rootToBuildFrom: aClass;
- 					addSubclasses: true;
- 					addMethods: false;
- 					subclassesAsSeparateTopic: false;
- 					build;
- 					topicToBuild.
  	root addSubtopic: topic.
+ 	^ root!
- 	^root				
- 	 
- 		 !

Item was changed:
  ----- Method: SystemReference class>>hierarchyWithMethodsFor: (in category 'help topic creation') -----
  hierarchyWithMethodsFor: aClass
  	 
+ 	| root topic |
- 	|root topic |
  	root := HelpTopic named: 'System reference for ', aClass name.
+ 	topic := (ClassAPIHelpTopic new)
+ 					theClass: aClass;
+ 					withSubclasses: true;
+ 					withMethods: true;
+ 					subclassesAsSeparateTopic: true.
- 	topic := (ClassAPIHelpBuilder new)
- 					rootToBuildFrom: aClass;
- 					addSubclasses: true;
- 					addMethods: true;
- 					subclassesAsSeparateTopic: true;
- 					build;
- 					topicToBuild.
  	root addSubtopic: topic.
+ 	^ root!
- 	^root				
- 	 
- 		 !



More information about the Squeak-dev mailing list