[squeak-dev] The Inbox: HelpSystem-Core-mha.45.mcz

commits at source.squeak.org commits at source.squeak.org
Sun May 2 14:11:29 UTC 2010


A new version of HelpSystem-Core was added to project The Inbox:
http://source.squeak.org/inbox/HelpSystem-Core-mha.45.mcz

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

Name: HelpSystem-Core-mha.45
Author: mha
Time: 2 May 2010, 4:04:02.179 pm
UUID: 5bf0c524-6372-47c3-9cec-277d9c349ba5
Ancestors: HelpSystem-Core-mha.44

loadable in trunk; with postscript to update the docking bar menu

==================== Snapshot ====================

(PackageInfo named: 'HelpSystem-Core') postscriptOfRemoval: '"below, add code to clean up after the unloading of this package"'!

(PackageInfo named: 'HelpSystem-Core') preamble: '"below, add code to be run before the loading of this package"'!

SystemOrganization addCategory: #'HelpSystem-Core-Builders'!
SystemOrganization addCategory: #'HelpSystem-Core-Help'!
SystemOrganization addCategory: #'HelpSystem-Core-Model'!
SystemOrganization addCategory: #'HelpSystem-Core-UI'!
SystemOrganization addCategory: #'HelpSystem-Core-Utilities'!

(PackageInfo named: 'HelpSystem-Core') postscript: '"below, add code to be run after the loading of this package"
TheWorldMainDockingBar updateInstances'!

(PackageInfo named: 'HelpSystem-Core') preambleOfRemoval: '"below, add code to prepare for the unloading of this package"'!

PluggableListItemWrapper subclass: #HelpTopicListItemWrapper
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-UI'!

!HelpTopicListItemWrapper commentStamp: 'tbn 3/8/2010 09:30' prior: 0!
This class implements a list item wrapper for help topics.

Instance Variables
!

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

----- Method: HelpTopicListItemWrapper>>balloonText (in category 'accessing') -----
balloonText
	"Returns a string used for fly by help"
	
	^self item title!

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

----- Method: HelpTopicListItemWrapper>>highlightingColor (in category 'accessing') -----
highlightingColor
	"Returns the text color when the receiver is selected in a list."

	^Color blue  !

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

Object subclass: #CustomHelp
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Utilities'!

!CustomHelp commentStamp: 'tbn 3/29/2010 13:23' prior: 0!
This is a common superclass for custom help. Subclasses of this class are automatically included into the system help.

By default the informations provided on the receiver class are converted into help topics by a specific builder 
- here the CustomHelpHelpBuilder. Note that you can provide an own custom builder by overriding the #builder method

!

----- Method: CustomHelp classSide>>accept:title:contents: (in category 'editing') -----
accept: aSelector title: title contents: text
	"Accept edited text. Compile it into a HelpTopic"

	| code |
	code := String streamContents:[:s|
		s nextPutAll: aSelector.
		s crtab; nextPutAll: '"This method was automatically generated. Edit it using:"'.
		s crtab; nextPutAll: '"', self name,' edit: ', aSelector storeString,'"'.
		s crtab; nextPutAll: '^HelpTopic'.
		s crtab: 2; nextPutAll: 'title: ', title storeString.
		s crtab: 2; nextPutAll: 'contents: '.
		s cr; nextPutAll: (String streamContents:[:c| c nextChunkPutWithStyle: text]) storeString.
		s nextPutAll:' readStream nextChunkText'.
	].

	self class 
		compile: code
		classified: ((self class organization categoryOfElement: aSelector) ifNil:['pages']).
!

----- Method: CustomHelp classSide>>asHelpTopic (in category 'converting') -----
asHelpTopic
	"Convert the receiver to a help topic"
	
	^self builder buildHelpTopicFrom: self!

----- Method: CustomHelp classSide>>bookName (in category 'accessing') -----
bookName
	"Returns the name of the custom help book"
	
	^'Help'!

----- Method: CustomHelp classSide>>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!

----- Method: CustomHelp classSide>>edit: (in category 'editing') -----
edit: aSelector
	"Open a Workspace on the text in the given selector.
	When accepted, compile the result as a help topic."

	| topic window |
	topic := (self respondsTo: aSelector) 
			ifTrue:[self perform: aSelector]
			ifFalse:[HelpTopic title: 'Untitled' contents: 'Please edit this topic. 
To change the topic title, edit the window label.'].
	window := UIManager default
		edit: topic contents
		label: topic title
		accept: [:text| self accept: aSelector title: window label contents: text].
!

----- Method: CustomHelp classSide>>icon (in category 'accessing') -----
icon
	"Returns an icon used for displaying the custom help book"
	
	^HelpIcons iconNamed: #bookIcon!

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

----- Method: CustomHelp classSide>>pages (in category 'accessing') -----
pages 
	"Returns a collection of method selectors to return the pages of the custom help book"
		
	^#()!

CustomHelp subclass: #HelpOnHelp
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Help'!

!HelpOnHelp commentStamp: 'tbn 2/12/2010 14:27' prior: 0!
Welcome to Pharo Smalltalk Help System!

HelpOnHelp subclass: #HelpAPIDocumentation
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Help'!

!HelpAPIDocumentation commentStamp: 'tbn 4/30/2010 15:12' prior: 0!
This class represents the browsable package API help for the help system.

Instance Variables
!

----- Method: HelpAPIDocumentation classSide>>bookName (in category 'accessing') -----
bookName
	^'API Documentation'!

----- Method: HelpAPIDocumentation classSide>>builder (in category 'defaults') -----
builder
	^PackageAPIHelpBuilder!

----- Method: HelpAPIDocumentation classSide>>packages (in category 'accessing') -----
packages
	^#('HelpSystem-Core-Model' 'HelpSystem-Core-Utilities' 'HelpSystem-Core-UI')!

HelpOnHelp subclass: #HelpHowToHelpTopics
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Help'!

----- Method: HelpHowToHelpTopics classSide>>bookName (in category 'accessing') -----
bookName
	^'Implementation'!

----- Method: HelpHowToHelpTopics classSide>>overview (in category 'pages') -----
overview
	^HelpTopic 
		title: 'Overview'
		contents:	
	'THE IMPLEMENTATION

The help system typically consists of help books including one or more pages. A book or page is therefore a "topic of interest"  providing contents for help to a user. A topic has a title and an icon and is able to have subtopics forming a hierarchy of topics. This simple model is reflected in the class HelpTopic.

Since this model forms a hierarchical structure of help topics there is a browser with a tree to display the help contents. This browser is implemented in class HelpBrowser.

You can open this browser programmatically using:

   HelpBrowser open
' !

----- Method: HelpHowToHelpTopics classSide>>page1 (in category 'pages') -----
page1
	^HelpTopic 
		title: '1. Simple help topics'
		contents: 'The help browser usually operates on a hierarchy of help topics with one help topic at the root level. Evaluate the following expression in a workspace to contruct a simple help topic and open it as a root topic in the help browser.
		
		|root|
		root := HelpTopic 
			title: ''My first topic''
			contents: ''A simple topic of interest''.					
		
		HelpBrowser openOn: root
		
		
Note that the help browser displays the contents of our topic in the right page and uses the topics title as the title for the help browser window.	
		'!

----- Method: HelpHowToHelpTopics classSide>>page2 (in category 'pages') -----
page2
	^HelpTopic 
		title: '2. Forming a hierarchy'
		contents: 'To form a hierarchy we just have to add new subtopics on our root topic.
		
		|root sub1 sub2|
		root := HelpTopic 
			title: ''My first topic''
			contents: ''A simple topic of interest''.		
		sub1 := HelpTopic 
			title: ''My first subtopic''
			contents: ''First subsection''.		
		sub2 := HelpTopic 
			title: ''My second subtopic''
			contents: ''Second subsection''.		
		root 
			addSubtopic: sub1; 
			addSubtopic: sub2.
		HelpBrowser openOn: root
		
		'!

----- Method: HelpHowToHelpTopics classSide>>page3 (in category 'pages') -----
page3
	^HelpTopic 
		title: '3. Adding icons'
		contents: 'If you dont like the default icon you can add own custom icons to the topics. See the class HelpIcons for more details.
		
		|root sub1 sub2|
		root := HelpTopic 
			title: ''My first topic''
			contents: ''A simple topic of interest''.		
		sub1 := HelpTopic 
			title: ''My first subtopic''
			contents: ''First subsection''.		
		sub2 := HelpTopic 		     
			title: ''My second subtopic''
			 icon: (HelpIcons iconNamed: #packageIcon)
			contents: ''Second subsection''.		
		root 
			addSubtopic: sub1; 
			addSubtopic: sub2.
		HelpBrowser openOn: root
		
		'!

----- Method: HelpHowToHelpTopics classSide>>page4 (in category 'pages') -----
page4
	^HelpTopic 
		title: '4. Own help objects'
		contents:	
	'You can open this help browser directly on an instance of HelpTopic, but it is more common to open it on any object that understands the message #asHelpTopic.

So you can write for instance:

   HelpBrowser openOn: Integer

opening a short API help/system reference on the Integer class.
The above expression is the short form for:

   HelpBrowser openOn: (SystemReference forClass: Integer)

If you want you can include the subclasses:

   HelpBrowser openOn: (SystemReference hierarchyFor: Integer)

or even methods

   HelpBrowser openOn: (SystemReference hierarchyWithMethodsFor: Integer)

You can browse the whole system reference documentation using:

    HelpBrowser openOn: SystemReference

But these are only a few examples what we can extract from the 
system. 

However - the major goal is NOT an API browser, the idea is to 
provide a simple architecture to provide browsable help contents 
depending on the context. For instance it should also be possible
to use the help system to provide end user help on any commercial
application that is written with the Smalltalk system.


' !

----- Method: HelpHowToHelpTopics classSide>>page5 (in category 'pages') -----
page5
	^HelpTopic 
		title: '5. Help sources'
		contents:	
	'Since the underlying model is very simple you can easily fill it with nearly any information from different sources. Try this:

|topic day url sub|
topic := HelpTopic named: ''Last week on Squeak IRC''.
0 to: 7 do: [:index |
	day := (Date today subtractDays: index) printFormat: #(3 2 1 $. 1 2 2).
	url := ''http://tunes.org/~nef/logs/squeak/'' , day.
	sub := HelpTopic 
			title: day contents: (HTTPLoader default retrieveContentsFor: url) contents.
	topic addSubtopic: sub.
].
HelpBrowser openOn: topic

 
 

' !

----- Method: HelpHowToHelpTopics classSide>>pages (in category 'accessing') -----
pages
	^#(overview page1 page2 page3 page4 page5)!

HelpHowToHelpTopics subclass: #HelpHowToHelpTopicsFromCode
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Help'!

----- Method: HelpHowToHelpTopicsFromCode classSide>>bookName (in category 'accessing') -----
bookName
	^'Custom help from code'!

----- Method: HelpHowToHelpTopicsFromCode classSide>>overview (in category 'pages') -----
overview
	^HelpTopic
		title: 'Overview'
		contents:	
	'OVERVIEW
	
The help system allows you to provide own books and help texts. You can open the help browser on any object that is able to understand #asHelpTopic.

This method returns the root node of the displayed topic hierarchy:

      HelpBrowser openOn: myObject

Typically the object does not convert itself to a help topic structure, usually it dispatches to a builder (see HelpBuilder and subclasses) who does all this. 
	
A much more convenient and reproducable way is to implement custom help classes. This allows you to implement and manage your help texts using the standard development and code management tools. These custom help classes are subclasses of "CustomHelp" and are automatically included into the standard help browser. '!

----- Method: HelpHowToHelpTopicsFromCode classSide>>pages (in category 'accessing') -----
pages
	^#(overview step1 step2 step3 step4 step5)!

----- Method: HelpHowToHelpTopicsFromCode classSide>>step1 (in category 'pages') -----
step1
	^HelpTopic 
		title: 'Step 1 - Create a class for the book'
		contents:
		'STEP 1 - CREATE A CLASS FOR THE BOOK
		
There is a predefined class CustomHelp which you have to subclass for a custom help book to show up as a book in the Help browser:
	
  CustomHelp subclass: #MyAppHelp
    	instanceVariableNames: ''''
	  classVariableNames: ''''
	  poolDictionaries: ''''
	  category: ''MyApp-Help'' 

Class methods on this class can reflect pages and if you want to provide nested help books just subclass your own help class to form a hierarchy. Any new subclass of MyAppHelp will then be a new book in your hierarchy.

The class category used should end with "-Help" so it is easy to recognize that it includes the help support of your project.'
!

----- Method: HelpHowToHelpTopicsFromCode classSide>>step2 (in category 'pages') -----
step2
	^HelpTopic
		title: 'Step 2 - Provide a book name'
		contents:
	'STEP 2 - PROVIDE A BOOK NAME
	
Now implement the class method #bookName to return the name of your help book.

   bookName
	    ^''My App help''
	
By implementing this method the system knows how you would like to name your book and uses the given string as a label in the HelpBrowser later.'
!

----- Method: HelpHowToHelpTopicsFromCode classSide>>step3 (in category 'pages') -----
step3
	^HelpTopic
		title: 'Step 3 - Implement pages using methods'
		contents:
	'STEP 3 - IMPLEMENT PAGES USING METHODS 

Implement a page by defining a method that returns an instance of HelpPage defining a page title and a help text displayed in the help browser. 

     firstPage
     	    ^HelpTopic
	           title: ''First Page'' 
                 contents: ''Hello world''

Define a new method for each page of your book. Please group the pages in a method category called "pages".
You can also define an icon for the specific page:

     secondPage
     	    ^HelpTopic
	           title: ''Second Page'' 
    	           icon: (HelpIcons iconNamed: #packageIcon)
                 contents: ''More to come''


Note: 
=====
Later we may add support for better help contents than just plain text (markup descriptions, active morphs, ...)  '
!

----- Method: HelpHowToHelpTopicsFromCode classSide>>step4 (in category 'pages') -----
step4
	^HelpTopic
		title: 'Step 4 - Defining the page order'
		contents:
	'STEP 4 - DEFINING THE PAGE ORDER 

By implementing the class method #pages you return a collection of method selectors to define the order in which the pages appear in your book: 

     pages
     	    ^#(firstPage secondPage)

'
!

----- Method: HelpHowToHelpTopicsFromCode classSide>>step5 (in category 'pages') -----
step5
	^HelpTopic
		title: 'Step 5 - Test your help'
		contents:
	'STEP 5 - TEST YOUR HELP
	
By using 
      
       HelpBrowser open

 
'
!

----- Method: HelpOnHelp classSide>>bookName (in category 'accessing') -----
bookName
	^'Help on Help'!

----- Method: HelpOnHelp classSide>>introduction (in category 'pages') -----
introduction
	"This method was automatically generated. Edit it using:"
	"HelpOnHelp edit: #introduction"
	^HelpTopic
		title: 'Introduction'
		contents: 
'WELCOME TO THE HELP SYSTEM

The help system is a simple user interface to display help contents to the user. It can be accessed from the world menu using "Tools" -> "Help Browser" or by evaluating ''HelpBrowser open'' in a workspace.

There is a predefined mechanism allowing you to have help contents stored as source code using methods in specific help provider classes. This allows to manage the help texts using the standard development tools. But this is only one possible representation.

Yes, this is a good solution.
!!' readStream nextChunkText!

----- Method: HelpOnHelp classSide>>key (in category 'accessing') -----
key
	^'HelpOnHelp'!

----- Method: HelpOnHelp classSide>>pages (in category 'accessing') -----
pages
	^#(introduction)!

Object subclass: #HelpBrowser
	instanceVariableNames: 'rootTopic window treeMorph contentMorph'
	classVariableNames: ''
	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

!

----- Method: HelpBrowser classSide>>defaultHelpBrowser (in category 'instance creation') -----
defaultHelpBrowser
	^self !

----- Method: HelpBrowser classSide>>initialize (in category 'class initialization') -----
initialize
	"Initializes the receiver class"
 
	self isPharo11
		ifFalse: [ TheWorldMenu registerOpenCommand: {'Help Browser'. {self. #open}}. ].
		
	"self open"!

----- Method: HelpBrowser classSide>>isPharo11 (in category 'private') -----
isPharo11
	"Return true if we are in Pharo 1.1."
	
	^(SystemVersion current version includesSubString: '1.1')!

----- Method: HelpBrowser classSide>>isSqueak (in category 'private') -----
isSqueak
	"Return true if we are in Squeak"
	
	^(SystemVersion current version includesSubString: 'Squeak')!

----- Method: HelpBrowser classSide>>menuCommandOn: (in category 'world menu') -----
menuCommandOn: aBuilder 
	<worldMenu> 
	(aBuilder item: #'Help Browser')
		parent: #Tools;
		action:[self open]; 
		icon: (HelpIcons iconNamed: #bookIcon)!

----- Method: HelpBrowser classSide>>open (in category 'instance creation') -----
open
	^self defaultHelpBrowser openOn: SystemHelp!

----- Method: HelpBrowser classSide>>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 new)
		rootTopic: aHelpTopic asHelpTopic;
		open;
		yourself!

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

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

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

----- Method: HelpBrowser>>initWindow (in category 'initialize-release') -----
initWindow
	
	self class isSqueak 
		ifTrue: [self initWindowInSqueak ]
		ifFalse: [self initWindowInPharo ]!

----- Method: HelpBrowser>>initWindowInPharo (in category 'initialize-release') -----
initWindowInPharo
	| toolbar dock|
	window := (Smalltalk at: #StandardWindow) new.
	window model: self.
	
	window title: 'Help Browser'.
	toolbar := window newToolbar: {window
			newButtonFor: self
			getState: nil
			action: #refresh
			arguments: nil
			getEnabled: nil
			labelForm: (HelpIcons iconNamed: #refreshIcon)
			help: 'Refresh' translated.
			}.
			
	dock := window newToolDockingBar.	
	dock addMorphBack: toolbar.
	window
			addMorph: dock
			fullFrame: (LayoutFrame fractions: (0 at 0 corner: 1 at 0) offsets: (0 at 0 corner: 0 @ dock minExtent y)).
	"Tree"
	treeMorph := PluggableTreeMorph new.
	treeMorph model: self; setSelectedSelector: #onItemClicked:.
	window 
		addMorph: treeMorph 
		fullFrame: (LayoutFrame fractions: (0 at 0 corner: 0.3 at 1) offsets: (0 at dock minExtent y corner: 0 @ 0)).

	"Text"
	contentMorph := self defaultViewerClass on: self 
			text: nil accept: nil
			readSelection: nil menu: nil.
	window addMorph: contentMorph fullFrame: (LayoutFrame fractions: (0.3 at 0 corner: 1 at 1) offsets: (0 at dock minExtent y corner: 0 @ 0)).
	 	
 !

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

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

----- Method: HelpBrowser>>onItemClicked: (in category 'events') -----
onItemClicked: anItem
	anItem isNil ifTrue: [^contentMorph setText: rootTopic contents].
	contentMorph setText: anItem contents!

----- Method: HelpBrowser>>open (in category 'ui') -----
open	
 	"Open the receivers window" 

	self refresh.	
	window openInWorld.
	 !

----- Method: HelpBrowser>>refresh (in category 'actions') -----
refresh

	|items|
	window setLabel: rootTopic title.
	items := rootTopic subtopics collect: [:each | HelpTopicListItemWrapper with: each ].
	treeMorph list: items.
	contentMorph setText: rootTopic contents
!

----- Method: HelpBrowser>>rootTopic (in category 'accessing') -----
rootTopic
	^rootTopic!

----- Method: HelpBrowser>>rootTopic: (in category 'accessing') -----
rootTopic: aHelpTopic

	rootTopic := aHelpTopic. 
	self refresh !

Object subclass: #HelpBuilder
	instanceVariableNames: 'topicToBuild rootToBuildFrom'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Builders'!

!HelpBuilder commentStamp: 'tbn 2/12/2010 14:54' prior: 0!
This is an utility class that builds the books for a help system.

Instance Variables
	rootTopics:		<OrderedCollection>

rootTopics
	- a collection of books 
!

HelpBuilder subclass: #ClassAPIHelpBuilder
	instanceVariableNames: 'addSubclasses addMethods subclassesAsSeparateTopic'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Builders'!

!ClassAPIHelpBuilder commentStamp: 'tbn 4/30/2010 15:37' prior: 0!
A builder to build the API Help for a class

Instance Variables
	addMethods:		<Boolean>
	addSubclasses:		<Boolean>
	subclassesAsSeparateTopic:		<Boolean>

addMethods
	- When true the builder will include method help

addSubclasses
	- When true the builder will recursively go through and add subclasses

subclassesAsSeparateTopic
	- xxxxx
!

----- Method: ClassAPIHelpBuilder classSide>>buildHierarchicalHelpTopicFrom:withSubclasses:withMethods: (in category 'building') -----
buildHierarchicalHelpTopicFrom: aClass withSubclasses: aBoolean withMethods: anotherBoolean
	"Start building from the given class"
	
	^(self new)
		addSubclasses: aBoolean;
		addMethods: anotherBoolean;
		rootToBuildFrom: aClass;
		build;
		topicToBuild !

----- Method: ClassAPIHelpBuilder>>addMethods (in category 'accessing') -----
addMethods
	^ addMethods!

----- Method: ClassAPIHelpBuilder>>addMethods: (in category 'accessing') -----
addMethods: anObject
	addMethods := anObject!

----- Method: ClassAPIHelpBuilder>>addSubclasses (in category 'accessing') -----
addSubclasses
	^ addSubclasses!

----- Method: ClassAPIHelpBuilder>>addSubclasses: (in category 'accessing') -----
addSubclasses: anObject
	addSubclasses := anObject!

----- Method: ClassAPIHelpBuilder>>build (in category 'building') -----
build

	| instanceSide classSide |
	topicToBuild := (HelpTopic named: rootToBuildFrom name).
	topicToBuild icon: (HelpIcons iconNamed: #pageIcon).
	topicToBuild contents: rootToBuildFrom comment.
	
	addMethods ifTrue: [ self buildSubnodesForMethods ].
	addSubclasses	 ifTrue: [ self buildSubnodesForSubclasses ].
	 !

----- Method: ClassAPIHelpBuilder>>buildMethodTopicsOn:for: (in category 'private building') -----
buildMethodTopicsOn: topic for: aClass
	|stream comments methodComment|
	stream := String new writeStream.
	aClass selectors asSortedCollection do:
			[:selector | 		
			  stream 
				 nextPutAll: aClass name;
			    nextPutAll: '>>';
			  	 nextPutAll: selector asString;
				 cr.		
			  comments := aClass commentsAt: selector.
			  methodComment := (comments size = 0)
									ifTrue: [ 'Method has no comment.' ]
									ifFalse: [ comments first ].
									
			  stream nextPutAll: methodComment;cr;cr.
	].
	topic contents: stream contents.
	
	!

----- Method: ClassAPIHelpBuilder>>buildSubclassTopicFor: (in category 'private building') -----
buildSubclassTopicFor: aSubclass
	 
	^(self class new) 
			rootToBuildFrom: aSubclass;
			addSubclasses: addSubclasses;
			addMethods: addMethods;
			subclassesAsSeparateTopic: subclassesAsSeparateTopic;
			build;
			topicToBuild 
	 !

----- Method: ClassAPIHelpBuilder>>buildSubnodesForMethods (in category 'private building') -----
buildSubnodesForMethods

	| instanceSide classSide |
	instanceSide := HelpTopic named: 'Instance side'.
	classSide := HelpTopic named: 'Class side'.
	topicToBuild icon: (HelpIcons iconNamed: #bookIcon).
	topicToBuild 
		addSubtopic: instanceSide;
		addSubtopic: classSide.
	self buildMethodTopicsOn: instanceSide for: rootToBuildFrom.	
	self buildMethodTopicsOn: classSide for: rootToBuildFrom class.	!

----- Method: ClassAPIHelpBuilder>>buildSubnodesForSubclasses (in category 'private building') -----
buildSubnodesForSubclasses

	| topic |
	rootToBuildFrom subclasses isEmpty ifTrue: [^self].
	topicToBuild icon: (HelpIcons iconNamed: #bookIcon).
	topic := subclassesAsSeparateTopic 
				ifTrue: [topicToBuild addSubtopic: (HelpTopic named: 'Subclasses')]
				ifFalse: [topicToBuild ].
	rootToBuildFrom subclasses 
		do: [:subclass | topic addSubtopic: (self buildSubclassTopicFor: subclass)].
	topic sortSubtopicsByTitle.

	!

----- Method: ClassAPIHelpBuilder>>initialize (in category 'initialize-release') -----
initialize
	"Initializes the receiver"
	
	super initialize.
	addSubclasses := false.
	addMethods := true.
	subclassesAsSeparateTopic := true.!

----- Method: ClassAPIHelpBuilder>>subclassesAsSeparateTopic (in category 'accessing') -----
subclassesAsSeparateTopic
	^ subclassesAsSeparateTopic!

----- Method: ClassAPIHelpBuilder>>subclassesAsSeparateTopic: (in category 'accessing') -----
subclassesAsSeparateTopic: anObject
	subclassesAsSeparateTopic := anObject!

HelpBuilder subclass: #CustomHelpHelpBuilder
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Builders'!

!CustomHelpHelpBuilder commentStamp: 'tbn 3/29/2010 13:30' prior: 0!
This builder builds help topics from a help topic description (which is typically stored
in a class). 

The help topic description object has to understand the following messages:

  #bookName - should return the name of the help book
  #icon - should return the icon of the help book
  #key - should return a unique key to identify the book
  #pages - should return an array of method selectors to call to get the books pages
!

----- Method: CustomHelpHelpBuilder>>build (in category 'building') -----
build
	"Start building a help topic from a code description"
	
	topicToBuild := self createTopicFrom: rootToBuildFrom 
!

----- Method: CustomHelpHelpBuilder>>createTopicFrom: (in category 'private') -----
createTopicFrom: aDescription
	"Create a topic from a description stored on a class"
	
	|topic page method pragma   |
	topic := HelpTopic named: aDescription bookName.
	topic key: aDescription key.
	topic icon: aDescription icon.	
	aDescription pages do: [:pageSelector|
		page := aDescription perform: pageSelector.	 
		topic addSubtopic: page.
	].	
	aDescription subclasses do: [:subclass |
		topic subtopics add: subclass asHelpTopic ].
	^topic!

----- Method: HelpBuilder classSide>>buildHelpTopicFrom: (in category 'building') -----
buildHelpTopicFrom: aHelpTopicDescription
	"Start building from the given help topic description"
	
	^(self new)
		rootToBuildFrom: aHelpTopicDescription;
		build;
		topicToBuild !

----- Method: HelpBuilder>>build (in category 'building') -----
build
	self subclassResponsibility 
!

----- Method: HelpBuilder>>initialize (in category 'initialize-release') -----
initialize 
	"Initializes the receiver"
	
	super initialize.
	topicToBuild := self topicClass new.
	 !

----- Method: HelpBuilder>>rootToBuildFrom: (in category 'accessing') -----
rootToBuildFrom: anObject
	rootToBuildFrom := anObject!

----- Method: HelpBuilder>>topicClass (in category 'private accessing') -----
topicClass
	^HelpTopic!

----- Method: HelpBuilder>>topicToBuild (in category 'accessing') -----
topicToBuild
	^topicToBuild!

HelpBuilder subclass: #PackageAPIHelpBuilder
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Builders'!

----- Method: PackageAPIHelpBuilder>>build (in category 'building') -----
build 
	|pTopic|
	topicToBuild := (HelpTopic named: rootToBuildFrom bookName).
	rootToBuildFrom packages do: [:package|
		pTopic := HelpTopic named: package.
		topicToBuild addSubtopic: pTopic.
		self buildPackageTopic: pTopic.
		
	]
!

----- Method: PackageAPIHelpBuilder>>buildPackageTopic: (in category 'building') -----
buildPackageTopic: pTopic
 
	| classTopic classes |
	classes := (PackageInfo named: pTopic title) classes asSortedCollection: [:cl1 :cl2 | cl1 name < cl2 name].
	classes
	   do: [:aClass| 
		classTopic := ClassAPIHelpBuilder buildHierarchicalHelpTopicFrom: aClass withSubclasses: false withMethods: true.
		pTopic addSubtopic: classTopic
	]

!

Object subclass: #HelpIcons
	instanceVariableNames: ''
	classVariableNames: 'Icons'
	poolDictionaries: ''
	category: 'HelpSystem-Core-UI'!

!HelpIcons commentStamp: 'tbn 3/8/2010 09:29' prior: 0!
This class is used to store help icons for the help browser. 

Typically one implements a method returning a 12x12 Form instance which
should not be called directly.

Since the class provides an internal icon cache (so the icons can be reused without 
creating too many new instances) the icons should be accessed using the #iconNamed: 
message with the method selector as argument.

To create a form from an icon file stored on disk you can use the following code:

   | image stream |
	image := ColorForm fromFileNamed: '/path/to/icon.png'.
	stream := WriteStream with: String new.
	image storeOn: stream.
	stream contents inspect.!

----- Method: HelpIcons classSide>>blankIcon (in category 'private icons') -----
blankIcon
	^Form extent: 12 @ 1 depth:8!

----- Method: HelpIcons classSide>>bookIcon (in category 'private icons') -----
bookIcon
	^(Form
	extent: 12 at 12
	depth: 32
	fromArray: #( 0 0 0 0 0 284817913 552924404 0 0 0 0 0 0 0 0 0 817149108 3747766882 4287730065 2679749049 549766340 0 0 0 0 0 0 1086110908 4016202338 4287137928 4288914339 4288914339 4289111718 3216290996 1086505666 0 0 0 816754350 4014952271 4287137928 4289309097 4289769648 4289111718 4288453788 4288453788 4288453788 2947658161 0 814846353 4283782485 4287072135 4288059030 4288059030 4288387995 4289243304 4289309097 4287927444 4287598479 2411050421 1081900156 4283585106 4286611584 4287532686 4287532686 4287466893 4287466893 4287401100 4287401100 4287401100 4288716960 2946868645 3211290728 4288651167 4287269514 4287006342 4287006342 4287006342 4286940549 4286940549 4287203721 4289177511 3483213213 281725642 2677183122 4293190884 4292861919 4289177511 4286874756 4286611584 4286611584 4287006342 4289638062 4020084125 549042617 0 282054607 2677643673 4289572269 4293256677 4292796126 4288980132 4287137928 4290164406 4020215711 816754350 0 0 0 0 551082200 2677643673 4289572269 4293256677 4292401368 4289177511 1085584564 0 0 0 0 0 0 0 551213786 2677643673 4288651167 1623244992 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0)
	offset: 0 at 0)!

----- Method: HelpIcons classSide>>iconNamed: (in category 'accessing') -----
iconNamed: aSymbol

	^self icons at: aSymbol ifAbsentPut: [self perform: aSymbol]!

----- Method: HelpIcons classSide>>icons (in category 'accessing') -----
icons
	Icons isNil ifTrue: [Icons := Dictionary new].
	^Icons!

----- Method: HelpIcons classSide>>packageIcon (in category 'private icons') -----
packageIcon
	^(Form
	extent: 12 at 12
	depth: 32
	fromArray: #( 0 0 0 0 1075649821 3744937783 3208395836 807016986 0 0 0 0 0 0 537857807 2939368243 4283256141 4284045657 4284572001 4284111450 2671524924 269488144 0 0 0 2150575919 4014820685 4284111450 4284374622 4284769380 4285098345 4285295724 4286216826 4017057647 1883456323 0 1076505130 4283848278 4284769380 4284966759 4285624689 4285690482 4285887861 4286611584 4287269514 4287861651 4287269514 1074597133 1076965681 4283914071 4283848278 4285953654 4286216826 4286414205 4286940549 4287466893 4287335307 4286808963 4286743170 1074399754 1077163060 4284637794 4284045657 4284835173 4285887861 4287269514 4287335307 4286282619 4286216826 4286874756 4287006342 1074465547 1077294646 4284835173 4284703587 4285361517 4285624689 4286414205 4285624689 4286085240 4286677377 4287269514 4287401100 1074465547 1077426232 4285098345 4285032552 4286019447 4285822068 4286743170 4286348412 4286677377 4287203721 4287730065 4287795858 1074531340 1077492025 4285229931 4285427310 4286808963 4286216826 4287137928 4287072135 4287401100 4287795858 4288256409 4288190616 1074531340 269356558 2672051268 4285493103 4287598479 4286940549 4287532686 4287795858 4287993237 4288387995 4287006342 2404668500 268501249 0 0 1075912993 3479726184 4287598479 4287927444 4288453788 4287993237 2943118444 539371046 0 0 0 0 0 0 1615086660 4017781370 3749148535 1078347334 0 0 0 0)
	offset: 0 at 0)!

----- Method: HelpIcons classSide>>pageIcon (in category 'private icons') -----
pageIcon
	^(Form
	extent: 12 at 12
	depth: 32
	fromArray: #( 0 221196079 1366981242 1366915449 1366915449 1366849656 1366783863 1128876361 33554432 0 0 0 0 726552142 4294309365 4294243572 4294111986 4294046193 4293914607 4292861919 2843705215 319885585 0 0 0 726551886 4294177779 4294111986 4293980400 4293914607 4293848814 4293717228 4292138196 3734147730 269619730 0 0 726486349 4294046193 4293980400 4293914607 4293783021 4293717228 4293585642 4293454056 4291085508 639705377 0 0 726420557 4293980400 4293848814 4293783021 4293651435 4293585642 4293519849 4293388263 4292993505 640034342 0 0 726420556 4293848814 4293717228 4293651435 4293585642 4293454056 4293388263 4293256677 4293190884 623322919 0 0 726354764 4293717228 4293651435 4293519849 4293454056 4293322470 4293256677 4293125091 4293059298 623257126 0 0 726354507 4293585642 4293519849 4293388263 4293322470 4293190884 4293125091 4293059298 4292993505 623191333 0 0 726288970 4293454056 4293388263 4293256677 4293190884 4293125091 4292993505 4292993505 4292993505 623191333 0 0 726223178 4293322470 4293256677 4293190884 4293059298 4292993505 4292993505 4292993505 4292993505 623191333 0 0 726223177 4293256677 4293125091 4293059298 4292993505 4292993505 4292993505 4292993505 4292993505 623191333 0 0 490092087 3080033685 3079967892 3079967892 3079967892 3079967892 3079967892 3079967892 3079967892 454629657 0)
	offset: 0 at 0)!

----- Method: HelpIcons classSide>>refreshIcon (in category 'private icons') -----
refreshIcon
	^(Form
		extent: 16 at 16
		depth: 32
		fromArray: #( 0 0 0 0 0 0 0 895969127 526080859 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1884706390 4168710521 2288675434 271330348 0 0 0 0 0 0 0 0 0 828465505 2609087363 3615917702 4269439610 4285887861 4285624689 3899156584 1766607948 67569415 0 0 0 0 0 50529027 2306242166 4237069452 4286940549 4286611584 4286282619 4285887861 4285558896 4285229931 4268189543 2235514687 0 0 0 0 0 2590862701 4287598479 4287269514 4270097540 3329652342 3312217196 4285887861 4285558896 3345179491 1011567435 0 0 0 0 0 1263423054 4287532686 4287532686 3867378563 1096835168 0 1885166941 3681579120 1549227863 50923785 0 0 0 0 0 0 3061545851 4287795858 4236937866 811951461 0 0 641547581 137441585 0 0 0 0 0 0 0 34936085 4102720138 4287795858 3011016824 0 0 0 0 0 0 0 0 0 0 0 0 272317243 4287861651 4287795858 2489607268 0 0 0 0 0 0 0 0 68095759 0 0 0 204682035 4287730065 4287795858 2658432116 0 0 0 0 0 0 0 34014983 3965146967 4283979864 3125694030 0 0 3767044232 4287795858 3884287365 137244206 0 0 0 0 0 0 1129863256 4284769380 4284506208 2739423304 0 0 2189459584 4287795858 4287532686 2541123190 16843009 0 0 0 0 305805882 3597166696 4284703587 4250885983 910114623 0 0 273698896 3834218889 4287532686 4287335307 3094442353 1094532413 101255433 286199567 1582124365 3731318631 4284966759 4284703587 2689946965 0 0 0 0 879126118 3985082247 4287269514 4286940549 4286611584 4285624689 4285558896 4285624689 4285229931 4284966759 3227212635 220998700 0 0 0 0 0 509698401 2977659771 4286743170 4286545791 4286282619 4285887861 4285558896 4100417383 2170116441 103295016 0 0 0 0 0 0 0 0 575820370 1734895720 2121298032 2037017194 1448564567 255013683 0 0 0 0 0)
	offset: 0 at 0)!

Object subclass: #HelpTopic
	instanceVariableNames: 'title key icon contents subtopics'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Model'!

!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 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
!

----- Method: HelpTopic classSide>>named: (in category 'instance creation') -----
named: aString
	"Create a new instance with given title and empty contents"
	
	^(self new)
		title: aString;
		yourself!

----- Method: HelpTopic classSide>>title:contents: (in category 'instance creation') -----
title: aTitle contents: aText
	"Create a new instance with given title and content"
	
	^(self new)
		title: aTitle;
		contents: aText;
		yourself.
		!

----- Method: HelpTopic classSide>>title:icon:contents: (in category 'instance creation') -----
title: aTitle icon: anIcon contents: aText
	"Create a new instance with given title, icon and content"
	
	^(self new)
		title: aTitle;
		icon: anIcon;
		contents: aText;
		yourself.
		!

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

----- Method: HelpTopic>>addSubtopic: (in category 'accessing') -----
addSubtopic: aTopic
	"Adds the given topic to the receivers collection of subtopics"
	
	self subtopics add: aTopic.
	^aTopic!

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

----- Method: HelpTopic>>contents (in category 'accessing') -----
contents
	"Returns the receivers contents"
	
	^ contents!

----- Method: HelpTopic>>contents: (in category 'accessing') -----
contents: anObject
	"Sets the receivers contents to the given object" 
		
	contents := anObject!

----- Method: HelpTopic>>defaultTitle (in category 'defaults') -----
defaultTitle
	"Returns the receivers default title"
	
	^'Unnamed Topic'
	!

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

----- Method: HelpTopic>>icon (in category 'accessing') -----
icon 
 	"Returns the receivers icon"
	
	^icon!

----- Method: HelpTopic>>icon: (in category 'accessing') -----
icon: aSymbol
	"Sets the receivers icon"
	
	icon := aSymbol !

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

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

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

----- Method: HelpTopic>>sortSubtopicsByTitle (in category 'operating') -----
sortSubtopicsByTitle
	"Sort the subtopics by title"
	
	subtopics := SortedCollection withAll: self subtopics  !

----- Method: HelpTopic>>subtopics (in category 'accessing') -----
subtopics 
	"Returns the receivers list of subtopics"
	
	subtopics isNil ifTrue: [subtopics := OrderedCollection new].
	^subtopics!

----- Method: HelpTopic>>subtopics: (in category 'accessing') -----
subtopics: aCollection 
	"Sets the receivers subtopics"
	
	subtopics := aCollection !

----- Method: HelpTopic>>title (in category 'accessing') -----
title
	"Returns the receivers title"
	
	^ title!

----- Method: HelpTopic>>title: (in category 'accessing') -----
title: anObject
	"Sets the receivers title"
	
	title := anObject!

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".


!

----- Method: SystemHelp classSide>>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.
!

Object subclass: #SystemReference
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'HelpSystem-Core-Utilities'!

!SystemReference commentStamp: 'tbn 4/30/2010 15:35' prior: 0!
This class defines the full reference help for the system.
(contents for the full API Help).

Just run "HelpBrowser openOn: SystemReference".



!

----- Method: SystemReference classSide>>all (in category 'help topic creation') -----
all
	"HelpBrowser openOn: self all "
	
	^(ClassAPIHelpBuilder new)
		rootToBuildFrom: ProtoObject;
		addSubclasses: true;
		addMethods: true;
		subclassesAsSeparateTopic: false;
		build;
		topicToBuild 
	 
		 !

----- Method: SystemReference classSide>>asHelpTopic (in category 'help topic creation') -----
asHelpTopic 
	"HelpBrowser openOn: SystemReference"
	
	^self hierarchyFor: ProtoObject 
	 
		 !

----- Method: SystemReference classSide>>forClass: (in category 'help topic creation') -----
forClass: aClass
	|root topic |
	root := HelpTopic named: 'System reference for ', aClass name.
	topic := ClassAPIHelpBuilder buildHelpTopicFrom: aClass.
	root addSubtopic: topic.
	^root!

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

----- Method: SystemReference classSide>>hierarchyWithMethodsFor: (in category 'help topic creation') -----
hierarchyWithMethodsFor: aClass
	 
	|root topic |
	root := HelpTopic named: 'System reference for ', aClass name.
	topic := (ClassAPIHelpBuilder new)
					rootToBuildFrom: aClass;
					addSubclasses: true;
					addMethods: true;
					subclassesAsSeparateTopic: true;
					build;
					topicToBuild.
	root addSubtopic: topic.
	^root				
	 
		 !

----- Method: Class>>asHelpTopic (in category '*HelpSystem-Core') -----
asHelpTopic
	^SystemReference forClass: self!




More information about the Squeak-dev mailing list