UIHelpTool.st
author ca
Fri, 22 Nov 2002 11:46:08 +0100
changeset 1658 b13027df5c91
parent 1648 d88ec5777284
child 1663 60bd14266560
permissions -rw-r--r--
add help text

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



"{ Package: 'stx:libtool2' }"

ToolApplicationModel subclass:#UIHelpTool
	instanceVariableNames:'specClass specSelector dictionary dictionaries modifiedHolder
		modified listOfKeys listOfKeysModel listOfClasses
		listOfClassesModel contentsModifiedChannel editModel editTextView'
	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 openOnClass:aClass andSelector:#helpSpec

    "
     UIHelpTool openOnClass:self
    "

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

openOnClass:aClass andSelector: aSelector
    "opens a Help Tool on aClass and aSelector"

    ^self new openOnClass:aClass andSelector: aSelector
  
! !

!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 key to the help spec.'

#currentHelpTexts
'Selected help text key.'

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

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

#fileSave
'Saves the current help spec.'

#fileUpdate
'Reload the help spec.'

#helpTextView
'Shows the help text. Menu action ''Accept'' commits changes'

#listOfClasses
'Classes where help specs can be/are implemented.'

#listOfHelpTexts
'List of help text keys.'

#removeHelpTextKey
'Removes the help message from the widget.'

#updateHelpTextKey
'Refetch the help spec.'

)
! !

!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
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'Help Tool'
          #name: 'Help Tool'
          #min: #(#Point 10 10)
          #max: #(#Point 1160 870)
          #bounds: #(#Rectangle 31 306 317 577)
        )
        #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: #(
                       #(#SelectionInListModelViewSpec
                          #name: 'listOfKeys'
                          #activeHelpKey: #listOfHelpTexts
                          #model: #listOfKeysModel
                          #menu: #listOfKeysMenu
                          #hasHorizontalScrollBar: true
                          #hasVerticalScrollBar: true
                          #miniScrollerHorizontal: true
                          #listModel: #listOfKeys
                          #useIndex: false
                          #highlightMode: #line
                        )
                       #(#ViewSpec
                          #name: 'Box'
                          #component: 
                         #(#SpecCollection
                            #collection: #(
                             #(#InputFieldSpec
                                #name: 'helpKeyInputField'
                                #layout: #(#LayoutFrame 2 0.0 2 0 -2 1.0 25 0)
                                #activeHelpKey: #currentHelpTexts
                                #tabable: true
                                #model: #editModel
                                #immediateAccept: true
                                #acceptOnReturn: false
                                #acceptOnTab: false
                                #acceptOnPointerLeave: false
                              )
                             #(#SelectionInListModelViewSpec
                                #name: 'listOfClasses'
                                #layout: #(#LayoutFrame 0 0.0 27 0 0 1.0 0 1.0)
                                #activeHelpKey: #listOfClasses
                                #model: #listOfClassesModel
                                #hasHorizontalScrollBar: true
                                #hasVerticalScrollBar: true
                                #miniScrollerHorizontal: true
                                #miniScrollerVertical: true
                                #listModel: #listOfClasses
                                #useIndex: false
                                #highlightMode: #line
                              )
                             )
                           
                          )
                        )
                       )
                     
                    )
                    #handles: #(#Any 0.5 1.0)
                  )
                 #(#ViewSpec
                    #name: 'Box1'
                    #component: 
                   #(#SpecCollection
                      #collection: #(
                       #(#MenuPanelSpec
                          #name: 'helpTextMenu'
                          #layout: #(#LayoutFrame 0 0.0 0 0 0 1.0 24 0)
                          #menu: #helpTextMenu
                          #textDefault: true
                        )
                       #(#TextEditorSpec
                          #name: 'helpTextView'
                          #layout: #(#LayoutFrame 0 0.0 24 0.0 0 1.0 0 1.0)
                          #activeHelpKey: #helpTextView
                          #tabable: true
                          #hasHorizontalScrollBar: true
                          #hasVerticalScrollBar: true
                          #miniScrollerHorizontal: true
                          #miniScrollerVertical: true
                          #modifiedChannel: #contentsModifiedChannel
                          #postBuildCallback: #postBuildTextView:
                        )
                       )
                     
                    )
                  )
                 )
               
              )
              #handles: #(#Any 0.5 1.0)
            )
           )
         
        )
      )
!

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
        #name: #windowSpecForStandAlone
        #window: 
       #(#WindowSpec
          #label: 'Help Tool'
          #name: 'Help Tool'
          #min: #(#Point 300 300)
          #max: #(#Point 1152 900)
          #bounds: #(#Rectangle 83 333 796 896)
          #menu: #menu
        )
        #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'!

helpTextMenu
    "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:#helpTextMenu
     (Menu new fromLiteralArrayEncoding:(UIHelpTool helpTextMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #activeHelpKey: #commitOK
            #enabled: #contentsModifiedChannel
            #label: 'Accept'
            #itemValue: #accept
            #translateLabel: true
          )
         #(#MenuItem
            #activeHelpKey: #commitCancel
            #enabled: #contentsModifiedChannel
            #label: 'Cancel'
            #itemValue: #cancel
            #translateLabel: true
          )
         )
        nil
        nil
      )
!

listOfKeysMenu
    "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:#listOfKeysMenu
     (Menu new fromLiteralArrayEncoding:(UIHelpTool listOfKeysMenu)) startUp
    "

    <resource: #menu>

    ^ 
     #(#Menu
        #(
         #(#MenuItem
            #activeHelpKey: #deleteHelpTextKey
            #label: 'Delete'
            #itemValue: #doDelete
            #translateLabel: true
          )
         )
        nil
        nil
      )
!

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
                  #activeHelpKey: #fileLoad
                  #label: 'Load...'
                  #itemValue: #doLoad
                  #translateLabel: true
                )
               #(#MenuItem
                  #activeHelpKey: #fileSave
                  #label: 'Save'
                  #itemValue: #doSave
                  #translateLabel: true
                )
               #(#MenuItem
                  #label: '-'
                )
               #(#MenuItem
                  #activeHelpKey: #fileExit
                  #label: 'Exit'
                  #itemValue: #closeRequest
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #label: 'Edit'
            #translateLabel: true
            #submenu: 
           #(#Menu
              #(
               #(#MenuItem
                  #activeHelpKey: #deleteHelpTextKey
                  #label: 'Delete'
                  #itemValue: #doDelete
                  #translateLabel: true
                )
               )
              nil
              nil
            )
          )
         #(#MenuItem
            #activeHelpKey: #help
            #label: 'Help'
            #translateLabel: true
            #startGroup: #right
            #submenuChannel: #menuHelp
          )
         )
        nil
        nil
      )
! !

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

helpKey
    "returns the help key as symbol or nil
    "
    |value|

    value := editModel value.

    value notNil ifTrue:[
        value := value withoutSeparators.
        value notEmpty ifTrue:[ ^ value asSymbol ]
    ].
    ^ nil
!

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

    |key|

    aKey size ~~ 0 ifTrue:[
        aKey isSymbol ifTrue:[
            key := aKey
        ] ifFalse:[
            key := aKey withoutSeparators.
            key notEmpty ifTrue:[ key := key asSymbol ]
                        ifFalse:[ key := nil ].
        ]
    ] ifFalse:[
        key := nil
    ].
    editModel value:key.            
    self cancel.
!

modified
    "true if the helpSpec is modified, items are added, deleted or modified
    "
    ^ modified
!

modified: aBoolean
    "true if the helpSpec is modified, items are added, deleted or modified
    "
    modified := aBoolean.
!

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

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

    modifiedHolder notNil ifTrue:[
        modifiedHolder addDependent:self.
    ]
!

setHelpKey:aKey
    "set the helpKey without notification
    "
    |model|

    model := modifiedHolder.
    modifiedHolder := nil.
    self helpKey:aKey.
    modifiedHolder := model.
!

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

specSelector
    "returns the selector on which the class is opened
    "
    ^ specSelector
! !

!UIHelpTool methodsFor:'aspects'!

contentsModifiedChannel
    "returns the model which indicates whether the current helpText is modified
    "
    ^ contentsModifiedChannel
!

editModel
    "returns the model which keeps the current editing key
    "
    ^ editModel
!

listOfClasses
    "returns the list which keeps the classes
    "
    ^ listOfClasses
!

listOfClassesModel
    "returns the model which keeps the current class selection
     or nil
    "
    ^ listOfClassesModel
!

listOfKeys
    "returns the list which keeps the current keys
    "
    ^ listOfKeys
!

listOfKeysModel
    "returns the model which keeps the current list selection
     or nil
    "
    ^ listOfKeysModel
!

valueOfInfoLabel

    masterApplication notNil ifTrue:[
        ^ masterApplication valueOfInfoLabel
    ].
    ^ super valueOfInfoLabel
! !

!UIHelpTool methodsFor:'building'!

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

    |list|

    modified  := false.
    specClass := self getHelpSpecClassFromClass:aClass.

    specClass notNil ifTrue:[   
        dictionary   := Dictionary new.
        dictionaries removeAll.
    ].

    (specClass isClass and:[specClass isLoaded]) ifFalse:[
        self updateList.
        ^ self
    ].
    (specClass class includesSelector:specSelector) ifFalse:[
        dictionaries at:(specClass name) put:dictionary. 
    ].
    list := specClass withAllSuperclasses reverse collect:[:cls| cls name ].

    (list includes: #ApplicationModel) ifTrue:[
        list := list asOrderedCollection.
        list removeAll:(ApplicationModel withAllSuperclasses collect:[:cls| cls name])
    ].
    listOfClasses contents:list.
    listOfClassesModel triggerValue:(specClass name).
!

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

    specSelector := aSelector.
    self buildFromClass:aClass

!

buildFromHelpTool:aHelpTool

    self doNew.

    dictionaries := aHelpTool dictionaries.
    dictionary   := aHelpTool dictionary.

    specSelector := aHelpTool specSelector.
    specClass    := aHelpTool specClass.

    listOfClasses contents:(aHelpTool listOfClasses).
    listOfClassesModel triggerValue:(listOfClasses at:1 ifAbsent:nil).
! !

!UIHelpTool methodsFor:'change & update'!

editModelChanged
    "called if the edit model changed
    "
    |key|

    key := self helpKey.
    modifiedHolder notNil ifTrue:[ modifiedHolder value:true ].

    (key notNil and:[(dictionary at:key ifAbsent:nil) isNil]) ifTrue:[
        listOfClasses do:[:name| |dir|
            dir := self dictionaryForClassNamed:name.

            (dir includesKey:key) ifTrue:[
                "/ setup new class
                listOfKeysModel setValue:key.
                listOfClassesModel value:name.
                ^ self
            ].
        ].
        key := nil.
    ].
    listOfKeysModel value:key.
!

listOfClassesModelChanged
    "called if the class selection changed
    "
    |clsName|

    clsName := listOfClassesModel value.
    clsName isNil ifTrue:[^ self].

    dictionary := self dictionaryForClassNamed:clsName.
    self updateList.
!

listOfKeysModelChanged
    "called if the selection of the key list changed
    "
    |key txt|

    key := listOfKeysModel value.

    key notNil ifTrue:[
        key := key asSymbol.
        txt := dictionary at:key ifAbsent:nil.

        txt isNil ifTrue:[
            listOfKeysModel value:nil.
            ^ self
        ].
        editModel value ~= key ifTrue:[
            editModel value:key withoutNotifying:self.
            modifiedHolder notNil ifTrue:[ modifiedHolder value:true ].
        ].
    ].

    contentsModifiedChannel value ifFalse:[
        self cancel
    ].
!

update:something with:aParameter from:changedObject
    "Invoked when an object that I depend upon sends a change notification."

    editModel == changedObject ifTrue:[
        self editModelChanged.
        ^ self
    ].

    listOfKeysModel == changedObject ifTrue:[
        self listOfKeysModelChanged.
        ^ self
    ].

    listOfClassesModel == changedObject ifTrue:[
        self listOfClassesModelChanged.
        ^ self
    ].

    contentsModifiedChannel == changedObject ifTrue:[
        contentsModifiedChannel value ifTrue:[
            modifiedHolder notNil ifTrue:[modifiedHolder value:true].
        ].
        ^ self
    ].

    super update:something with:aParameter from:changedObject
! !

!UIHelpTool methodsFor:'help'!

openDocumentation
    "opens the documentation file of the Help Tool"

    self openHTMLDocument: 'tools/uipainter/HelpTool.html'
! !

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

dictionaryForClassNamed:clsName
    "returns the directory assigned to a class name
    "
    ^ dictionaries at:clsName
          ifAbsentPut:[ self extractHelpSpecForClass: (Smalltalk at:clsName) ].
!

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

    |helpSpecSuperClass superHelpSpecKeys helpSpec|

    helpSpec := Dictionary new.

    ((aClass class includesSelector: specSelector)
    and: [(helpSpecSuperClass := aClass allSuperclasses detect: [:cls| cls class includesSelector: specSelector] ifNone: nil) notNil])
    ifTrue:[                  
        superHelpSpecKeys := helpSpecSuperClass helpSpec keys.

        aClass helpSpec keysAndValuesDo:[:key :value |
            (superHelpSpecKeys includes:key) ifFalse: [
                helpSpec at:key put:value
            ]
        ].          
    ].
    ^ helpSpec 
!

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 copyReplaceAll:(Character cr) with:(Character space).
    (helpText endsWith:(Character space)) ifTrue:[
        helpText := helpText copyWithoutLast:1
    ].
    ^ helpText

    "Modified: / 20.7.1998 / 13:17:52 / cg"
!

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 includesSelector: 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!!'.
        ^ self  
    ].

    modified ifFalse:[
        masterApplication isNil ifTrue: [self information:'Nothing was modified!!'].
        ^ self
    ].
    helpSpecClasses := listOfClasses copy.

    helpSpecClasses notEmpty ifTrue:[
        (helpSpecClasses includes: cls name) ifFalse: [helpSpecClasses add: cls name].

        helpSpecClasses do:[:clsName|
            (self installHelpSpecOnClass: clsName) isNil ifTrue:[
                modified := false.
                ^ self
            ]
        ].
    ]
    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 of keys
    "
    |key|

    listOfKeysModel setValue:nil.
    listOfKeys contents:(dictionary keys asSortedCollection).

    key := self helpKey.

    (key notNil and:[listOfKeys includes:key]) ifFalse:[
        key := nil.
    ].
    listOfKeysModel triggerValue:key
! !

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

    editModel := nil asValue.
    editModel addDependent:self.

    listOfKeys   := List new.
    listOfKeysModel := nil asValue.
    listOfKeysModel addDependent:self.

    listOfClasses := List new.
    listOfClassesModel := nil asValue.
    listOfClassesModel addDependent:self.

    contentsModifiedChannel := false asValue.
    contentsModifiedChannel addDependent:self.
!

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 includesSelector: (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"

    self openOnClass:aClass andSelector:nil

    "
     self openOnClass:NewLauncher
    "
!

openOnClass:aClass andSelector: aSelector
    "opens the UIHelpTool on aClass and aSelector"

    super openInterface: #windowSpecForStandAlone.

    builder window label: 'Help Tool'.
    self buildFromClass:aClass andSelector:aSelector
!

postBuildTextView:aView

    editTextView := aView scrolledView.
    editTextView acceptAction:[:dummy| self accept ].
! !

!UIHelpTool methodsFor:'user actions'!

accept
    "accepts the help text"

    |key txt|   

    key := self helpKey.
    key isNil ifTrue:[^ self].

    contentsModifiedChannel value ifFalse:[
        (dictionary includes:key) ifTrue:[^ self].   
    ].
    contentsModifiedChannel value:false.

    txt := editTextView contents ? ''.
    txt := txt asString.

    dictionary at:key put:txt.

    listOfKeys detect:[:el| el = key ] ifNone:[ |idx|
        idx := listOfKeys findFirst:[:el| el > key ].
        idx == 0 ifTrue:[ listOfKeys add:key ]
                ifFalse:[ listOfKeys add:key beforeIndex:idx]
    ].

    listOfKeysModel value:key withoutNotifying:self.

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

cancel
    |key txt|

    editTextView notNil ifTrue:[
        key := listOfKeysModel value.

        key notNil ifTrue:[
            txt := dictionary at:key ifAbsent:nil.
        ] ifFalse:[
            txt := nil
        ].
        editTextView contents:txt.
    ].
    contentsModifiedChannel value:false.
!

doDelete
    "deletes the selected help key
    "
    |key|

    key := listOfKeysModel value.

    key isNil ifTrue:[
        self warn:'No key selected !!'.
        ^ self
    ].

    listOfKeysModel value:nil.

    key := key asSymbol.
    listOfKeys remove:key ifAbsent:nil.

    (dictionary removeKey:key ifAbsent:nil) notNil ifTrue:[
        modified := true.
        modifiedHolder notNil ifTrue: [modifiedHolder value:true].
    ].
!

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 := nil.

    editModel          value:nil withoutNotifying:self.
    listOfKeysModel    value:nil.
    listOfClassesModel value:nil.

    listOfKeys    removeAll.
    listOfClasses removeAll.
    dictionaries  removeAll.

    dictionary   := Dictionary new.
    modified     := false.
!

doSave
    "saves the help dictionaries on specClass"

    self installHelpSpecsOnClass:specClass
! !

!UIHelpTool class methodsFor:'documentation'!

version
    ^ '$Header$'
! !