The Trunk: HelpSystem-Core-kfr.62.mcz

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
1 message Options
Reply | Threaded
Open this post in threaded view
|

The Trunk: HelpSystem-Core-kfr.62.mcz

commits-2
Karl Ramberg uploaded a new version of HelpSystem-Core to project The Trunk:
http://source.squeak.org/trunk/HelpSystem-Core-kfr.62.mcz

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

Name: HelpSystem-Core-kfr.62
Author: kfr
Time: 5 July 2014, 5:04:58.241 pm
UUID: bba82d56-63cd-2243-8fd7-f6e05151d6f9
Ancestors: HelpSystem-Core-kfr.61

Add editing and search to HelpBrowser

=============== Diff against HelpSystem-Core-kfr.58 ===============

Item was changed:
  Object subclass: #HelpBrowser
+ instanceVariableNames: 'rootTopic window treeMorph contentMorph topicClass topicMethod topic result'
- instanceVariableNames: 'rootTopic window treeMorph contentMorph'
  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 added:
+ ----- Method: HelpBrowser>>accept: (in category 'actions') -----
+ accept: text
+ "Accept edited text. Compile it into a HelpTopic"
+
+ | 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 refresh.
+     !

Item was changed:
  ----- Method: HelpBrowser>>codePaneMenu:shifted: (in category 'events') -----
  codePaneMenu: aMenu shifted: shifted
- aMenu
- add: 'edit' target: self selector: #editContents argument: self.
 
  ^StringHolder codePaneMenu: aMenu shifted: shifted.
  !

Item was removed:
- ----- Method: HelpBrowser>>editContents (in category 'actions') -----
- editContents
- | classList |
- classList := self find: contentMorph textMorph contents string.
- classList first actualClass theNonMetaClass edit: classList first selector.
- self refresh!

Item was added:
+ ----- Method: HelpBrowser>>find (in category 'actions') -----
+ find
+ "Prompt the user for a string to search for, and search the receiver from the current selection onward for it."
+
+ | reply |
+ reply := UIManager default request: 'Find what? ' initialAnswer: ''.
+ reply size = 0 ifTrue: [
+ ^ self].
+ self findStringInHelpTopic: reply
+ !

Item was changed:
  ----- Method: HelpBrowser>>find: (in category 'actions') -----
  find: aString
  ^SystemNavigation allMethodsSelect: [:method |
  method  hasLiteralSuchThat: [:lit |
  (lit isString and: [lit isSymbol not]) and:
+ [lit includesSubstring: aString caseSensitive: false]]]
+ localTo: CustomHelp
- [lit includesSubstring: aString caseSensitive: true]]]
         !

Item was added:
+ ----- Method: HelpBrowser>>findAgain (in category 'actions') -----
+ findAgain
+ | i |
+ (i := result indexOf: topic) ~= 0
+ ifTrue: [i = result size
+ ifTrue: [(self confirm: 'Start over?')
+ ifTrue: [i := 1]
+ ifFalse: [^ self]].
+ self
+ onItemClicked: (result at: i + 1)]!

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

Item was added:
+ ----- Method: HelpBrowser>>inSubtopic:find: (in category 'actions') -----
+ inSubtopic: aTopic find: aString
+ ((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 changed:
  ----- 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:; getMenuSelector: #codePaneMenu:shifted:.
- treeMorph model: self; setSelectedSelector: #onItemClicked:.
  window addMorph: treeMorph frame: (0@0 corner: 0.3@1).
 
  "Text"
  contentMorph := self defaultViewerClass on: self
+ text: nil accept: #accept:
- text: nil accept: nil
  readSelection: nil menu: #codePaneMenu:shifted:.
  window addMorph: contentMorph frame: (0.3@0 corner: 1@1).
  !

Item was changed:
  ----- Method: HelpBrowser>>onItemClicked: (in category 'events') -----
  onItemClicked: anItem
+ | classList |
  anItem isNil ifTrue: [^contentMorph setText: rootTopic asHelpTopic contents].
+ contentMorph setText: anItem contents.
+ topic := anItem.
+ classList := (self find: anItem contents) asOrderedCollection.
+ classList ifNotEmpty:[
+ topicClass := classList first actualClass theNonMetaClass.
+ topicMethod := classList first selector].
+ !
- contentMorph setText: anItem contents!