better save routine + help text added
authortz
Wed, 11 Mar 1998 19:24:28 +0100
changeset 722 a1bb632b1e00
parent 721 325eba9f37b7
child 723 60e8ffac2f38
better save routine + help text added
UIHelpTool.st
--- a/UIHelpTool.st	Wed Mar 11 09:40:55 1998 +0100
+++ b/UIHelpTool.st	Wed Mar 11 19:24:28 1998 +0100
@@ -126,12 +126,12 @@
        #(#FullSpec
           #window: 
            #(#WindowSpec
-              #name: 'HelpTool'
-              #layout: #(#LayoutFrame 90 0 295 0 375 0 565 0)
+              #name: 'unnamed canvas'
+              #layout: #(#LayoutFrame 118 0 430 0 403 0 700 0)
               #label: 'unnamed canvas'
               #min: #(#Point 10 10)
               #max: #(#Point 1160 870)
-              #bounds: #(#Rectangle 90 295 376 566)
+              #bounds: #(#Rectangle 118 430 404 701)
               #usePreferredExtent: false
           )
           #component: 
@@ -161,7 +161,7 @@
                               #name: 'AddButton'
                               #activeHelpKey: #addHelpTextKey
                               #label: 'Add'
-                              #model: #accept
+                              #model: #add
                               #extent: #(#Point 44 24)
                           )
                            #(#ActionButtonSpec
@@ -190,6 +190,7 @@
                     #layout: #(#LayoutFrame 1 0.5 29 0 -3 1 51 0)
                     #activeHelpKey: #currentHelpTexts
                     #model: #listModel
+                    #immediateAccept: false
                 )
                  #(#SequenceViewSpec
                     #name: 'listOfHelpSpecClassesView'
@@ -294,7 +295,7 @@
                       )
                        #(#MenuItem
                           #label: 'Save'
-                          #value: #doInstallHelpSpec
+                          #value: #doSave
                       )
                        #(#MenuItem
                           #label: '-'
@@ -322,14 +323,14 @@
 !UIHelpTool methodsFor:'accessing'!
 
 dictionaries
-    "return dictionaries"
-
+    "get the dictionary of the help dictionaries of the classes having help specs
+    "
     ^dictionaries
 !
 
 dictionaries:aDictionaryOfDictionaries
-    "set dictionaries"
-
+    "set a dictionary of the help dictionaries of the classes having help specs
+    "
     (dictionaries := aDictionaryOfDictionaries) isNil ifTrue:[
         dictionaries := Dictionary new.
     ].
@@ -337,14 +338,14 @@
 !
 
 dictionary
-    "return dictionary"
-
-    ^ dictionary
+    "get the dictionary of the selected class
+    "
+    ^dictionary
 !
 
 dictionary:aDictionary
-    "set dictionary"
-
+    "set dictionary of the selected class
+    "
     (dictionary := aDictionary) isNil ifTrue:[
         dictionary := Dictionary new.
     ].
@@ -352,6 +353,8 @@
 !
 
 helpKey
+    "get the help key of selected help text
+    "
     listSelection size ~~ 0 ifTrue:[
         ^ listSelection asSymbol
     ].
@@ -359,8 +362,9 @@
 !
 
 helpKey:aKey
+    "set the help key into the selection channel in order to show the help text
+    "
     |key|
-
     aKey size ~~ 0 ifTrue:[
         key := aKey asString
     ].
@@ -369,7 +373,8 @@
 !
 
 helpSpecFrom:aClass
-    "read help text from an application associated with the class
+    "read the help dictionary from aClass and find remaining classes 
+     'between' aClass and ApplicationModel 
     "
     |help|
 
@@ -400,11 +405,14 @@
 !
 
 isModified
-    ^ isModified
+    "answer whether the help tool was modified
+    "
+    ^isModified
 !
 
 isModified: aBoolean
-
+    "set the help tool as modified
+    "
     isModified := aBoolean
 !
 
@@ -433,55 +441,16 @@
 !
 
 specClass
-
+    "get the class on which the help tool works
+    "
     ^specClass
 ! !
 
 !UIHelpTool methodsFor:'actions'!
 
-accept
-    "accept the text
+helpSpecClassSelected
+    "extract the help dictionary from the selected class and make it current
     "
-    |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).
-        ]. 
-
-        isModified := true.
-        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
-    ]
-!
-
-delete
-    "delete selected help key
-    "
-    listSelection notNil
-    ifTrue:
-    [
-        dictionary removeKey: listSelection asSymbol ifAbsent: nil.
-        self remove.
-
-        self updateList.
-
-        isModified := true.
-        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
-    ]
-!
-
-helpSpecClassSelected
-
     |clsName|
 
     clsName := self selectionOfHelpSpecClass value.
@@ -511,21 +480,20 @@
 
 !
 
-installHelpSpecInto:aClass
-    "install help text
-    "
+installHelpSpecOnClass:aClass
+    "save the help dicts in aClass which is subclass of ApplicationModel"
+
     |cls src helpSpec|
 
     cls := self applicationClassAssociatedWith:aClass.
 
     cls isNil ifTrue:[
-        ^ self information:'No application class defined!!'.
+        self information:'No application class defined!!'.
+        ^nil
     ].
 
-    aClass = cls name asString       
-        ifTrue: [self listOfHelpSpecClasses value do: [:c| c ~~ cls name ifTrue: [self installHelpSpecInto: (Smalltalk at: c). isModified := true]]].
-
-    isModified not ifTrue:[
+    (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
     ].
 
@@ -558,8 +526,7 @@
     ].
 
     helpSpec isEmpty ifTrue:[
-        (cls superclass respondsTo: #helpSpec) ifTrue: [cls class removeSelector: #helpSpec].
-        ^nil
+        ^(cls superclass respondsTo: #helpSpec) ifTrue: [cls class removeSelector: #helpSpec].
     ].
 
     src  := '' writeStream.
@@ -594,32 +561,48 @@
     ].
     src nextPutLine:')'.
 
-    Compiler compile:(src contents)
-            forClass:cls class 
-          inCategory:'help specs'.
+    Compiler 
+        compile:(src contents)
+        forClass:cls class 
+        inCategory:'help specs'.
 
-    isModified := false.
+
 
 
 !
 
-remove
-    "remove selected help key
+installHelpSpecsOnClass:aClass
+    "save the help dicts on aClass and its superclasses which are subclasses of ApplicationModel
     "
+    |cls helpSpecClasses|
+
+    isModified ifFalse:[
+        ^nil
+    ].
+
+    cls := aClass isClass ifTrue: [aClass name] ifFalse: [aClass].
 
-    self listModel value: nil.
+    (helpSpecClasses := self listOfHelpSpecClasses value) notNil
+    ifTrue:
+    [     
+        (helpSpecClasses includes: cls) ifFalse: [helpSpecClasses add: cls].
+        helpSpecClasses do: [:clsName| (self installHelpSpecOnClass: clsName) isNil ifTrue: [^isModified := false]].
+    ]
+    ifFalse:
+    [
+        self installHelpSpecOnClass: cls
+    ].
 
-    self updateList.
+    isModified := false.
 
-    modifiedHolder notNil ifTrue: [modifiedHolder value:true]
 ! !
 
 !UIHelpTool methodsFor:'aspects'!
 
 listChannel
-
+    "get the value holder of the help texts
+    "
     |holder|
-
     (holder := builder bindingAt:#listChannel) isNil ifTrue:[
         builder aspectAt:#listChannel put:(holder :=  OrderedCollection new asValue).
     ].
@@ -627,9 +610,9 @@
 !
 
 listModel
-
+    "get 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.
@@ -638,7 +621,9 @@
 !
 
 listOfHelpSpecClasses
-
+    "get 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)
@@ -648,7 +633,8 @@
 !
 
 selectionOfHelpSpecClass
-
+    "get the value holder of the selected help spec class
+    "
     |holder|
     (holder := builder bindingAt:#selectionOfHelpSpecClass) isNil ifTrue:[
         builder aspectAt:#selectionOfHelpSpecClass put: (holder := ValueHolder new)
@@ -660,12 +646,13 @@
 !UIHelpTool methodsFor:'initialization'!
 
 initialize
-    "setup instance attributes
+    "initialize instance variables
     "
     super initialize.
+
     dictionary   := Dictionary new.
     dictionaries := Dictionary new.
-    isModified := false.
+    isModified   := false.
 
 ! !
 
@@ -693,7 +680,8 @@
 !
 
 extractHelpSpecForClass: aClass
-
+    "extract the help dictionary of aClass, it current and return it
+    "
     |helpSpecSuperClass superHelpSpecKeys helpSpec|
 
     ((aClass class implements: #helpSpec)
@@ -712,7 +700,7 @@
 !
 
 findHelpSpecForKey: aHelpKey
-    "update list from dictionary
+    "find the help spec class including aHelpKey in its help dictionary and make it current
     "
     |dictTemp helpSpecClass superHelpSpecKeys helpSpec|
 
@@ -739,7 +727,7 @@
 !
 
 updateList
-    "update list from dictionary
+    "update the list channel from dictionary
     "
     self listChannel value: dictionary keys asSortedCollection
 ! !
@@ -751,12 +739,10 @@
     "
     |cls|
 
-    cls := self resolveName:aClass.
-
-    (cls notNil and:[cls includesBehavior:UISpecification]) ifTrue:[
-        ^ UISpecificationTool
+    ((cls := self resolveName:aClass) notNil and:[cls includesBehavior:UISpecification]) ifTrue:[
+        ^UISpecificationTool
     ].
-  ^ cls
+    ^cls
 
 
 ! !
@@ -774,8 +760,9 @@
     "
     |txt view sel|
 
-    aSelection isNil ifTrue: [(builder componentAt: #listOfHelpKeysView) selection: nil].
-    self findHelpSpecForKey: aSelection.
+    aSelection isNil 
+        ifTrue: [(builder componentAt: #listOfHelpKeysView) selection: nil]
+        ifFalse: [(dictionary includesKey: aSelection asSymbol) ifFalse: [self findHelpSpecForKey: aSelection]].
 
     aSelection isNumber ifTrue:[
         aSelection ~~ 0 ifTrue:[
@@ -815,7 +802,8 @@
 !UIHelpTool methodsFor:'startup / release'!
 
 closeRequest
-
+    "before closing the help tool, ask for permission
+    "
     (isModified and:[self masterApplication isNil]) ifTrue:[
         (self confirm:'Exit without saving your modifications?') ifFalse:[
             ^ self
@@ -832,6 +820,54 @@
 
 !UIHelpTool methodsFor:'user interactions'!
 
+accept
+    "accept 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).
+        ]. 
+
+        isModified := true.
+        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
+    ]
+!
+
+add
+    "add help key
+    "
+    self listModel value: (builder componentAt: #helpKeyInputField asSymbol) contents.
+    self accept
+!
+
+delete
+    "delete selected help key
+    "
+    listSelection notNil
+    ifTrue:
+    [
+        dictionary removeKey: listSelection asSymbol ifAbsent: nil.
+        self remove.
+
+        self updateList.
+
+        isModified := true.
+        modifiedHolder notNil ifTrue: [modifiedHolder value:true]
+    ]
+!
+
 doFromClass
     "setup new specification from a class accessed through to a dialog
     "
@@ -859,14 +895,8 @@
     ]
 !
 
-doInstallHelpSpec
-    "install help spec
-    "
-    self installHelpSpecInto:specClass
-!
-
 doReload
-    "reload specification
+    "reload the help dictionaries
     "
     |oldSel model|
 
@@ -877,6 +907,20 @@
     model value:oldSel.
     isModified := false.
 
+!
+
+doSave
+    "save the help dictionaries
+    "
+    self installHelpSpecsOnClass:specClass
+!
+
+remove
+    "remove selected help key
+    "
+    self listModel value: nil.
+    self updateList.
+    modifiedHolder notNil ifTrue: [modifiedHolder value:true]
 ! !
 
 !UIHelpTool class methodsFor:'documentation'!