UIHelpTool.st
author tz
Thu, 04 Jun 1998 18:31:19 +0200
changeset 857 eabfba82d601
parent 835 13793eec85d5
child 868 dfa9d6df10d8
permissions -rw-r--r--
set #choices to nil for the preview

"
 COPYRIGHT (c) 1995 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"



ToolApplicationModel subclass:#UIHelpTool
	instanceVariableNames:'specClass specSelector dictionary dictionaries listSelection
		maxCharsPerLine modifiedHolder modified'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

!UIHelpTool class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 by eXept Software AG
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"


!

documentation
"
    The Help Tool allows you to define help dictionaries for the widgets in
    window applications. The tool are able to run stand alone or in other master 
    applications like the GUI Painter and the Menu Editor.
    If the application responds to the selector #showHelp:aHelpText for:aView,
    this selector is called by the widget's view when the mouse cursor moves over. 
    If the application does not responds to that selector, and the activeHelp mode
    is enabled, an active help bubble is shown at the widget's view.

    [instance variables:]
        specClass       <Symbol>        class implementing the help spec
        specSelector    <Symbol>        selector returning the help spec
        dictionary      <Dictionary>    dictionary containing pairs of help keys/texts
        dictionaries    <Dictionary>    dictionary containing pairs of help spec classes/help dictionaries
        listSelection   <String>        current selected help key
        maxCharsPerLine <Integer>       maximum number of allowed characters per text line
        modifiedHolder  <ValueHolder>   value holder for setting as modified
        modified        <Boolean>       flag whether the help spec was modified

    [author:]
        Claus Atzkern, eXept Software AG
        Thomas Zwick, eXept Software AG
"
! !

!UIHelpTool class methodsFor:'instance creation'!

open
    ^ self openOnClass:nil.

"/    |className cls|
"/
"/    className := Dialog request:(ClassResources string:'Open on which class ?').
"/    className size > 0 ifTrue:[
"/        cls := Smalltalk at:className asSymbol.
"/        cls notNil ifTrue:[
"/            ^ self openOnClass:cls.
"/        ].
"/        self warn:(ClassResources string:'No such class').
"/    ].
"/
"/    "Created: / 20.5.1998 / 00:55:05 / cg"
"/

    "Modified: / 20.5.1998 / 01:06:07 / cg"
!

openOnClass:aClass
    "opens a Help Tool on aClass"

    self new openOnClass:aClass

    "
     UIHelpTool openOnClass:self
    "

    "Modified: / 20.5.1998 / 01:06:14 / cg"
! !

!UIHelpTool class methodsFor:'constants'!

label
    "returns the label; used if embedded as sub canvas in the GUI Painter or Menu Editor"

    ^'Help'
! !

!UIHelpTool class methodsFor:'help specs'!

helpSpec
    "This resource specification was automatically generated
     by the UIHelpTool of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIHelpTool may not be able to read the specification."

    "
     UIHelpTool openOnClass:UIHelpTool    
    "

    <resource: #help>

    ^super helpSpec addPairsFrom:#(

#addHelpTextKey
'Adds the help text key to the help spec.'

#currentHelpTexts
'Selected help text key.'

#deleteHelpTextKey
'Deletes the help text key from the help spec.'

#fileLoad
'Opens a dialog for selecting and loading a help spec from a class.'

#fileSave
'Saves current help spec.'

#helpTextView
'Shows the help text.'

#listOfHelpSpecClasses
'List of the classes where help specs can be/are implemented.'

#listOfHelpTexts
'List of the help text keys.'

#removeHelpTextKey
'Removes the help text key from the widget.'

)
! !

!UIHelpTool class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:UIHelpTool andSelector:#windowSpec
     UIHelpTool new openInterface:#windowSpec
     UIHelpTool open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Help Tool'
              #layout: #(#LayoutFrame 29 0 447 0 314 0 717 0)
              #label: 'Help Tool'
              #min: #(#Point 10 10)
              #max: #(#Point 1160 870)
              #bounds: #(#Rectangle 29 447 315 718)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#VariableVerticalPanelSpec
                    #name: 'VariableVerticalPanel'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#VariableHorizontalPanelSpec
                              #name: 'VariableHorizontalPanel'
                              #component: 
                               #(#SpecCollection
                                  #collection: 
                                   #(
                                     #(#SequenceViewSpec
                                        #name: 'listOfHelpKeysView'
                                        #activeHelpKey: #listOfHelpTexts
                                        #tabable: true
                                        #model: #listModel
                                        #hasHorizontalScrollBar: true
                                        #hasVerticalScrollBar: true
                                        #miniScrollerHorizontal: true
                                        #useIndex: false
                                        #sequenceList: #listChannel
                                    )
                                     #(#ViewSpec
                                        #name: 'Box'
                                        #component: 
                                         #(#SpecCollection
                                            #collection: 
                                             #(
                                               #(#InputFieldSpec
                                                  #name: 'helpKeyInputField'
                                                  #layout: #(#LayoutFrame 0 0.0 29 0 0 1.0 51 0)
                                                  #activeHelpKey: #currentHelpTexts
                                                  #tabable: true
                                                  #model: #listModel
                                                  #immediateAccept: false
                                              )
                                               #(#SequenceViewSpec
                                                  #name: 'listOfHelpSpecClassesView'
                                                  #layout: #(#LayoutFrame 0 0.0 54 0 0 1.0 0 1.0)
                                                  #activeHelpKey: #listOfHelpSpecClasses
                                                  #tabable: true
                                                  #model: #selectionOfHelpSpecClass
                                                  #hasHorizontalScrollBar: true
                                                  #hasVerticalScrollBar: true
                                                  #miniScrollerHorizontal: true
                                                  #miniScrollerVertical: true
                                                  #valueChangeSelector: #helpSpecClassSelected
                                                  #useIndex: false
                                                  #sequenceList: #listOfHelpSpecClasses
                                              )
                                               #(#HorizontalPanelViewSpec
                                                  #name: 'HorizontalPanel1'
                                                  #layout: #(#LayoutFrame 0 0.0 2 0 0 1.0 26 0)
                                                  #component: 
                                                   #(#SpecCollection
                                                      #collection: 
                                                       #(
                                                         #(#ActionButtonSpec
                                                            #name: 'AddButton'
                                                            #activeHelpKey: #addHelpTextKey
                                                            #label: 'Add'
                                                            #translateLabel: true
                                                            #tabable: true
                                                            #model: #doAdd
                                                            #extent: #(#Point 44 24)
                                                        )
                                                         #(#ActionButtonSpec
                                                            #name: 'RemoveButton'
                                                            #activeHelpKey: #removeHelpTextKey
                                                            #label: 'Remove'
                                                            #translateLabel: true
                                                            #tabable: true
                                                            #model: #doRemove
                                                            #extent: #(#Point 44 24)
                                                        )
                                                         #(#ActionButtonSpec
                                                            #name: 'DeleteButton'
                                                            #activeHelpKey: #deleteHelpTextKey
                                                            #label: 'Delete'
                                                            #translateLabel: true
                                                            #tabable: true
                                                            #model: #doDelete
                                                            #extent: #(#Point 45 24)
                                                        )
                                                      )
                                                  )
                                                  #horizontalLayout: #fit
                                                  #verticalLayout: #fit
                                                  #horizontalSpace: 3
                                                  #verticalSpace: 3
                                              )
                                            )
                                        )
                                    )
                                  )
                              )
                              #handles: #(#Any 0.5 1.0)
                          )
                           #(#TextEditorSpec
                              #name: 'helpTextView'
                              #activeHelpKey: #helpTextView
                              #tabable: true
                              #hasHorizontalScrollBar: true
                              #hasVerticalScrollBar: true
                              #miniScrollerHorizontal: true
                              #miniScrollerVertical: true
                          )
                        )
                    )
                    #handles: #(#Any 0.5 1.0)
                )
              )
          )
      )

    "Modified: / 20.5.1998 / 01:08:59 / cg"
!

windowSpecForStandAlone
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the UIPainter may not be able to read the specification."

    "
     UIPainter new openOnClass:UIHelpTool andSelector:#windowSpecForStandAlone
     UIHelpTool new openInterface:#windowSpecForStandAlone
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'Help Tool'
              #layout: #(#LayoutFrame 191 0 334 0 660 0 663 0)
              #label: 'Help Tool'
              #min: #(#Point 300 300)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 191 334 661 664)
              #menu: #menu
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#UISubSpecification
                    #name: 'windowSpec'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 -26 1.0)
                    #minorKey: #windowSpec
                )
                 #(#UISubSpecification
                    #name: 'windowSpecForInfoBar'
                    #layout: #(#LayoutFrame 0 0 -24 1 0 1 0 1)
                    #majorKey: #ToolApplicationModel
                    #minorKey: #windowSpecForInfoBar
                )
              )
          )
      )
! !

!UIHelpTool class methodsFor:'menu specs'!

menu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

    "Do not manually edit this!! If it is corrupted,
     the MenuEditor may not be able to read the specification."

    "
     MenuEditor new openOnClass:UIHelpTool andSelector:#menu
     (Menu new fromLiteralArrayEncoding:(UIHelpTool menu)) startUp
    "

    <resource: #menu>

    ^
     
       #(#Menu
          
           #(
             #(#MenuItem
                #label: 'File'
                #translateLabel: true
                #submenu: 
                 #(#Menu
                    
                     #(
                       #(#MenuItem
                          #label: 'Load...'
                          #translateLabel: true
                          #value: #doLoad
                          #activeHelpKey: #fileLoad
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Save'
                          #translateLabel: true
                          #value: #doSave
                          #activeHelpKey: #fileSave
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Exit'
                          #translateLabel: true
                          #value: #closeRequest
                          #activeHelpKey: #fileExit
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Edit'
                #translateLabel: true
                #submenu: 
                 #(#Menu
                    
                     #(
                       #(#MenuItem
                          #label: 'Add'
                          #translateLabel: true
                          #value: #doAdd
                          #activeHelpKey: #addHelpTextKey
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Delete'
                          #translateLabel: true
                          #value: #doDelete
                          #activeHelpKey: #deleteHelpTextKey
                      )
                    ) nil
                    nil
                )
            )
             #(#MenuItem
                #label: 'Help'
                #startGroup: #right
                #translateLabel: true
                #submenu: 
                 #(#Menu
                    
                     #(
                       #(#MenuItem
                          #label: 'Documentation'
                          #value: #openHTMLDocument:
                          #translateLabel: true
                          #activeHelpKey: #helpHelpTool
                          #argument: 'tools/uipainter/HelpTool.html'
                      )
                       #(#MenuItem
                          #label: '-'
                      )
                       #(#MenuItem
                          #label: 'Show Help Texts'
                          #translateLabel: true
                          #activeHelpKey: #helpShowHelp
                          #indication: #showHelp:
                      )
                    ) nil
                    nil
                )
            )
          ) nil
          nil
      )

    "Modified: / 20.5.1998 / 01:08:12 / cg"
! !

!UIHelpTool methodsFor:'accessing'!

dictionaries
    "returns the dictionary of the help dictionaries of the classes having help specs"

    ^dictionaries
!

dictionaries:aDictionaryOfDictionaries
    "sets a dictionary of the help dictionaries of the classes having help specs"

    (dictionaries := aDictionaryOfDictionaries) isNil ifTrue:[
        dictionaries := Dictionary new.
    ].
    self updateList.
!

dictionary
    "returns the dictionary of the selected class"

    ^dictionary
!

dictionary:aDictionary
    "sets dictionary of the selected class"

    (dictionary := aDictionary) isNil ifTrue:[
        dictionary := Dictionary new.
    ].
    self updateList
!

helpKey
    "returns the help key of selected help text"

    listSelection size ~~ 0 ifTrue:[
        ^ listSelection asSymbol
    ].
    ^ nil
!

helpKey:aKey
    "sets the help key into the selection channel in order to show the help text"

    |key|
    aKey size ~~ 0 ifTrue:[
        key := aKey asString
    ].
    self listModel value:key

!

modified
    "returns whether the help tool was modified"

    ^modified
!

modified: aBoolean
    "sets the help tool as modified"

    modified := aBoolean
!

modifiedHolder:aValueHolder
    "sets the value holder to true in case of modifying attributes"

    modifiedHolder notNil ifTrue:[
        modifiedHolder removeDependent:self. 
    ].

    (modifiedHolder := aValueHolder) notNil ifTrue:[
        modifiedHolder addDependent:self.

        self editTextView notNil ifTrue: [
            self editTextView modifiedChannel onChangeSend:#value to:[
                modifiedHolder notNil ifTrue:[
                    self editTextView modifiedChannel value ifTrue:[
                        modifiedHolder value:true
                    ]
                ]
            ]
        ]
    ]


!

specClass
    "returns the class on which the help tool works"

    ^specClass
! !

!UIHelpTool methodsFor:'aspects'!

listChannel
    "returns the value holder of the help texts"

    |holder|
    (holder := builder bindingAt:#listChannel) isNil ifTrue:[
        builder aspectAt:#listChannel put:(holder :=  OrderedCollection new asValue).
    ].
    ^ holder
!

listModel
    "returns the value holder of the help key"

    |holder|
    (holder := builder bindingAt:#listModel) isNil ifTrue:[
        holder := AspectAdaptor new subject:self; forAspect:#listSelection.
        builder aspectAt:#listModel put:holder.
    ].
    ^ holder
!

listOfHelpSpecClasses
    "returns the value holder of the specClass and its superclasses 
     which are subclasses of ApplicationModel"

    |holder|       
    (holder := builder bindingAt:#listOfHelpSpecClasses) isNil ifTrue:[
        builder aspectAt:#listOfHelpSpecClasses put: (holder := List new)
    ].
    ^ holder

!

selectionOfHelpSpecClass
    "returns the value holder of the selected help spec class"

    |holder|
    (holder := builder bindingAt:#selectionOfHelpSpecClass) isNil ifTrue:[
        builder aspectAt:#selectionOfHelpSpecClass put: (holder := ValueHolder new)
    ].
    ^ holder

! !

!UIHelpTool methodsFor:'building'!

buildFromClass:aClass
    "reads the help dictionary from aClass and find remaining classes 
     'between' aClass and ApplicationModel" 

    modified := false.
    specClass notNil
    ifTrue:
    [   
        dictionary   := Dictionary new.
        dictionaries := Dictionary new.
    ].
    specClass  := self getHelpSpecClassFromClass:aClass.
    (specClass isClass and: [specClass isLoaded])
    ifTrue: 
    [                                               
        (specClass class implements:specSelector) ifFalse:[
            dictionaries at: specClass name put: dictionary 
        ].
        self listOfHelpSpecClasses contents:  (specClass withAllSuperclasses reverse collect: [:cls| cls name]).
        (self listOfHelpSpecClasses includes: #ApplicationModel)
            ifTrue: [self listOfHelpSpecClasses removeAll: (ApplicationModel withAllSuperclasses collect: [:cls| cls name])].
        self selectionOfHelpSpecClass value: specClass name.  
        (builder componentAt: #listOfHelpSpecClassesView) selection: 
                (self listOfHelpSpecClasses value indexOf: specClass name).
        self helpSpecClassSelected.
    ].

    self updateList
!

buildFromClass: aClass andSelector: aSelector
    "sets aSelector and reads the help dictionary from aClass"

    specSelector := aSelector.
    self buildFromClass:aClass

! !

!UIHelpTool methodsFor:'callbacks'!

helpSpecClassSelected
    "extracts the help dictionary from the selected class and make it current"

    |clsName|

    clsName := self selectionOfHelpSpecClass value.

    (dictionary := dictionaries at: clsName ifAbsent: nil) isNil
    ifTrue:
    [        
        dictionary := dictionaries at: clsName put: (self extractHelpSpecForClass: (Smalltalk at: clsName))
    ].

    self updateList.

    listSelection notNil
    ifTrue: 
    [
        (dictionary keys includes: listSelection asSymbol)
            ifTrue: [(builder componentAt: #listOfHelpKeysView) selection: 
                     (self listChannel value indexOf: (builder componentAt: #helpKeyInputField) contents)]
            ifFalse: [(builder componentAt: #listOfHelpKeysView) selection: nil].
    ].
    listSelection notNil
    ifTrue: 
    [
        self editTextView contents: (dictionary at: listSelection asSymbol ifAbsent: '')
    ]


! !

!UIHelpTool methodsFor:'help'!

defaultInfoLabel
    "returns the default label for the info bar"

    specClass isClass
    ifTrue:
    [
        (specClass class implements: specSelector)
        ifFalse: 
        [
            ^specSelector isNil 
                ifTrue:  [specClass name, ' >> ? (no selector defined)']
                ifFalse: [specClass name, ' >> ', specSelector, ' (not implemented)']
        ].
        ^specClass name, ' >> ', specSelector
    ].
    ^'No class and selector defined.'



! !

!UIHelpTool methodsFor:'private'!

askForModification
    "asks for modification"

    modified
    ifTrue:
    [
        ((YesNoBox title: 'List was modified!!')        
            noText:'Cancel';
            yesText:'Waste it and proceed';
            showAtPointer;
            accepted) ifFalse: [^false].
        modified := false
    ].
    ^true



!

editTextView
    "returns the editTextView or nil"

    |view|

    (view := builder componentAt:#helpTextView) notNil ifTrue:[
        view := view scrolledView.

        view acceptAction isNil ifTrue:[
            view acceptAction:[:aList| self accept ].
        ].

        view left ~~ 0 ifTrue:[
            (maxCharsPerLine := view extent x // view font width) < 10 ifTrue:[
                maxCharsPerLine := nil
            ]
        ].
    ].       
    ^ view
!

extractHelpSpecForClass: aClass
    "extracts the help dictionary of aClass, it current and return it"

    |helpSpecSuperClass superHelpSpecKeys helpSpec|

    ((aClass class implements: specSelector)
    and: [(helpSpecSuperClass := aClass allSuperclasses detect: [:cls| cls class implements: specSelector] ifNone: nil) notNil])
    ifTrue:
    [                  
        superHelpSpecKeys := helpSpecSuperClass helpSpec keys.
        helpSpec := Dictionary new.
        aClass helpSpec associationsDo:
        [:asso|
            (superHelpSpecKeys includes: asso key) ifFalse: [helpSpec at: asso key put: asso value]
        ].          
        ^dictionary := helpSpec
    ].
    ^dictionary := Dictionary new 
!

findHelpSpecForKey: aHelpKey
    "finds the help spec class including aHelpKey in its help dictionary and make it current"

    |dictTemp|

    aHelpKey isNil ifTrue: [^nil].
    dictTemp := dictionary.
    self listOfHelpSpecClasses value do:
    [:clsName|            
        (dictionary := dictionaries at: clsName ifAbsent: nil) isNil
        ifTrue:
        [        
            dictionary := dictionaries at: clsName put: (self extractHelpSpecForClass: (Smalltalk at: clsName))
        ].
        (dictionary includesKey: aHelpKey asSymbol)  
        ifTrue:
        [            
            self updateList.
            ^(builder componentAt: #listOfHelpSpecClassesView) selection: 
                (self listOfHelpSpecClasses value indexOf: clsName).
        ]
    ].
    dictionary := dictTemp


!

getHelpSpecClassFromClass:aClass
    "returns application class keeping the associated help text or nil"

    |cls|

    ((cls := self resolveName:aClass) notNil and:[cls respondsTo: #helpSpecClass]) ifTrue:[
        ^cls helpSpecClass
    ].
    ^cls


!

getUnformattedHelpText: aHelpText
    "unformats aHelpText and returns it"

    |helpText|
    helpText := aHelpText asString replaceAll: Character cr with: Character space.
    (helpText endsWith:Character space) ifTrue:[
        helpText := helpText copyWithoutLast:1
    ].
    ^helpText
!

installHelpSpecOnClass:aClass
    "saves the help dicts in aClass which is subclass of ApplicationModel"

    |cls src helpSpec|

    cls := self getHelpSpecClassFromClass: aClass.

    cls isNil ifTrue:[
        self information:'No application class defined!!'.
        ^nil
    ].

    (cls isSubclassOf: ApplicationModel) ifFalse:[
        self information: 'Cannot save help spec into class ', cls name asBoldText, ',\because it is not a subclass of ApplicationModel!!' withCRs.
        ^nil
    ].

    helpSpec := dictionaries 
        at: cls name 
        ifAbsent: [specClass notNil 
            ifTrue:  [dictionaries at: aClass put: (self extractHelpSpecForClass: (Smalltalk at: aClass))]
            ifFalse: [dictionary size > 0 ifTrue: [dictionary] ifFalse: [Dictionary new]]].

    helpSpec associationsDo:
    [:h|
        helpSpec at: h key put: (self getUnformattedHelpText: h value)
    ].

    (cls class implements: specSelector) 
    ifTrue: 
    [
        |superclassHelpKeys implementedHelpSpec hasChanged|
        implementedHelpSpec := Dictionary new.
        superclassHelpKeys := (cls superclass respondsTo: specSelector)
            ifTrue:  [cls superclass helpSpec keys]
            ifFalse: [Array new].

        cls helpSpec associationsDo: [:h| (superclassHelpKeys includes: h key) 
            ifFalse: [implementedHelpSpec at: h key put: h value]].

        hasChanged := false.
        implementedHelpSpec associationsDo: [:h| (helpSpec            includesAssociation: h) ifFalse: [hasChanged := true]].
        helpSpec            associationsDo: [:h| (implementedHelpSpec includesAssociation: h) ifFalse: [hasChanged := true]].

        (implementedHelpSpec notEmpty and: [hasChanged and:
        [DialogBox confirm: 'Class ', cls name asBoldText, ' already implements\a help spec!!\\Do only replace, if you have removed\help keys in an existing help spec.\' withCRs yesLabel: ' Merge ' noLabel: ' Replace ']])
        ifTrue:
        [      
             implementedHelpSpec associationsDo: [:h| (helpSpec includesKey: h key) 
                ifFalse: [helpSpec at: h key put: h value]].
        ]
    ].

    helpSpec isEmpty ifTrue:[
        ^(cls superclass respondsTo: specSelector) ifTrue: [cls class removeSelector: specSelector].
    ].

    src  := '' writeStream.

    src nextPutAll:
        specSelector, '\' withCRs,
        (ResourceSpecEditor codeGenerationCommentForClass: UIHelpTool) withCRs,
    '\\' withCRs,
    '    "\' withCRs,
    '     UIHelpTool openOnClass:', cls name asString ,'    
    "

    <resource: #help>

    ^super ', specSelector, ' addPairsFrom:#(

'.

    helpSpec keys asSortedCollection do:
    [:key|
        src nextPutLine: key storeString.
        src nextPutLine: (helpSpec at: key) storeString; cr.
    ].
    src nextPutLine:')'.

    Compiler 
        compile:(src contents)
        forClass:cls class 
        inCategory:'help specs'.
!

installHelpSpecsOnClass:aClass
    "saves the help dicts on aClass and its superclasses which are subclasses of ApplicationModel"

    |cls helpSpecClasses|

    cls := self getHelpSpecClassFromClass:aClass.
    cls isNil ifTrue: [^self information:'No application class defined!!'].

    modified ifFalse:[
        masterApplication isNil ifTrue: [self information:'Nothing was modified!!'].
        ^nil
    ].

    (helpSpecClasses := self listOfHelpSpecClasses value) notNil
    ifTrue:
    [        
        (helpSpecClasses includes: cls name) ifFalse: [helpSpecClasses add: cls name].
        helpSpecClasses do: [:clsName| (self installHelpSpecOnClass: clsName) isNil ifTrue: [^modified := false]].
    ]
    ifFalse:
    [      
        self installHelpSpecOnClass: cls
    ].

    modified := false.

!

resourceMessage: aString
    "extracts from aString the specClass and the specSelector"

    (aString notNil and: [self askForModification]) 
    ifTrue:
    [            
        |msg cls sel|
        msg := aString asCollectionOfWords.
        (msg size == 2 and:
        [(cls := self resolveName:(msg at:1)) notNil])
        ifTrue:
        [
            specClass := cls name.
            specSelector := (msg at: 2) asSymbol.
            ^true
        ]
    ].
    ^false

!

updateList
    "updates the list channel from dictionary"

    self listChannel value: dictionary keys asSortedCollection
! !

!UIHelpTool methodsFor:'selection'!

listSelection
    "returns current selection"

    ^ listSelection
!

listSelection:aSelection
    "sets current selection"

    |txt view sel|

    aSelection isNil 
        ifTrue: [(builder componentAt: #listOfHelpKeysView) selection: nil]
        ifFalse: [(dictionary includesKey: aSelection asSymbol) ifFalse: [self findHelpSpecForKey: aSelection]].

    aSelection isNumber ifTrue:[
        aSelection ~~ 0 ifTrue:[
            sel := self listChannel value at:aSelection
        ]
    ] ifFalse:[
        aSelection size ~~ 0 ifTrue:[
            sel := aSelection withoutSeparators.
            sel size == 0 ifTrue:[
                sel := nil
            ]
        ]
    ].

    listSelection = sel ifFalse:[
        listSelection := sel.

        modifiedHolder notNil ifTrue:[
            modifiedHolder value:true.
        ].

        (view := self editTextView) notNil ifTrue:[
            listSelection notNil ifTrue:[
                txt := dictionary at:(listSelection asSymbol) ifAbsent:nil.

                (txt isNil or:[maxCharsPerLine isNil]) ifFalse:[
                    txt := UIPainter convertString:(txt asString) maxLineSize:maxCharsPerLine skipLineFeed:false.
                ]
            ]. 
            view contents:txt.
            view modified:false.
        ]
    ]

! !

!UIHelpTool methodsFor:'startup / release'!

closeRequest
    "asks for permission before closing"

    (self masterApplication isNil and:[self askForModification]) ifTrue:[super closeRequest]
!

initialize
    "initializes instance variables"

    super initialize.

    specSelector := #helpSpec.
    dictionary   := Dictionary new.
    dictionaries := Dictionary new.
    modified   := false.

!

loadFromMessage:aString
    "loads a help spec by evaluating aString"

    (aString notNil and: [self askForModification]) 
    ifTrue:
    [            
        |msg cls sel|
        msg := aString asCollectionOfWords.
        (msg size == 2 and:
        [(cls := self resolveName:(msg at:1)) notNil and:
        [cls class implements: (sel := (msg at: 2) asSymbol)]])
        ifTrue:
        [               
            self buildFromClass: (specClass := cls name) andSelector: (specSelector := sel).
            ^true
        ]
    ].
    ^false

!

openInterface:aSymbol
    "do not open as stand alone"


   
!

openOnClass:aClass
    "opens the UIHelpTool on aClass"

    super openInterface: #windowSpecForStandAlone.
    self masterApplication isNil ifTrue: [(builder componentAt: #RemoveButton) beInvisible].
    builder window label: 'Help Tool'.
    self buildFromClass: aClass
! !

!UIHelpTool methodsFor:'user actions'!

accept
    "accepts the help text"

    |view key txt list listChgd|   

    (listSelection size == 0 or:[(view := self editTextView) isNil]) ifFalse:[
        txt    := view contents asString.
        key    := listSelection asSymbol.
        list   := self listChannel value.

        (listChgd := (dictionary at:key ifAbsent:nil) isNil) ifTrue:[
            list add:key.
        ].             
        dictionary at:key put:txt.

        listChgd ifTrue:[
            self updateList.
            (builder componentAt: #listOfHelpKeysView) selection: (list indexOf: key).
        ]. 

        modified := true.
        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
    ]
!

doAdd
    "adds a help key"

    |helpKey|
    (helpKey := (builder componentAt: #helpKeyInputField asSymbol) contents) size > 0
    ifTrue:
    [
        self listModel value: helpKey.
        self accept
    ]
    ifFalse:
    [
        self warn:'No key was entered !!'
    ]

    "Modified: / 20.5.1998 / 01:15:06 / cg"
!

doDelete
    "deletes the selected help key"

    listSelection notNil
    ifTrue:
    [
        dictionary removeKey: listSelection asSymbol ifAbsent: nil.
        self doRemove.
        self updateList.
        modified := true.
        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
    ]
    ifFalse:
    [
        self warn:'No key selected !!'
    ]

    "Modified: / 20.5.1998 / 01:15:00 / cg"
!

doLoad
    "opens a Resource Selection Browser in order to get a resource message"

    self loadFromMessage: 
        (ResourceSelectionBrowser
            request: 'Load Help Spec From Class'
            onSuperclass: nil
            andClass: specClass
            andSelector: specSelector ? #help
            withResourceTypes: (Array with: #help)).

    self updateInfoLabel

!

doNew
    "resets the help tool"

    specClass := listSelection := nil.
    self dictionary: nil.
    self dictionaries: nil.
    self listOfHelpSpecClasses removeAll.
    modified := false.
!

doReload
    "reloads the help dictionaries"

    |oldSel model|

    model  := self listModel.
    oldSel := model value.
    model value:nil.
    self helpSpecFrom:specClass.
    model value:oldSel.
    modified := false.

!

doRemove
    "removes the selected help key"

    listSelection notNil
    ifTrue:
    [
        self listModel value: nil.
        self updateList.
        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
    ]
    ifFalse:
    [
        self warn:'No key selected !!'
    ]

    "Modified: / 20.5.1998 / 01:15:11 / cg"
!

doSave
    "saves the help dictionaries on specClass"

    self installHelpSpecsOnClass:specClass
! !

!UIHelpTool class methodsFor:'documentation'!

version
    ^ '$Header$'
! !