UIHelpTool.st
changeset 700 2aae4f3b6526
parent 696 e91402372900
child 701 bcd65f75ade4
equal deleted inserted replaced
699:7746185a3621 700:2aae4f3b6526
   125      
   125      
   126        #(#FullSpec
   126        #(#FullSpec
   127           #window: 
   127           #window: 
   128            #(#WindowSpec
   128            #(#WindowSpec
   129               #name: 'HelpTool'
   129               #name: 'HelpTool'
   130               #layout: #(#LayoutFrame 59 0 376 0 344 0 646 0)
   130               #layout: #(#LayoutFrame 90 0 295 0 375 0 565 0)
   131               #label: 'unnamed canvas'
   131               #label: 'unnamed canvas'
   132               #min: #(#Point 10 10)
   132               #min: #(#Point 10 10)
   133               #max: #(#Point 1160 870)
   133               #max: #(#Point 1160 870)
   134               #bounds: #(#Rectangle 59 376 345 647)
   134               #bounds: #(#Rectangle 90 295 376 566)
   135               #usePreferredExtent: false
   135               #usePreferredExtent: false
   136           )
   136           )
   137           #component: 
   137           #component: 
   138            #(#SpecCollection
   138            #(#SpecCollection
   139               #collection: 
   139               #collection: 
   144                     #activeHelpKey: #listOfHelpTexts
   144                     #activeHelpKey: #listOfHelpTexts
   145                     #tabable: true
   145                     #tabable: true
   146                     #model: #listModel
   146                     #model: #listModel
   147                     #hasHorizontalScrollBar: true
   147                     #hasHorizontalScrollBar: true
   148                     #hasVerticalScrollBar: true
   148                     #hasVerticalScrollBar: true
       
   149                     #miniScrollerHorizontal: true
   149                     #useIndex: false
   150                     #useIndex: false
   150                     #sequenceList: #listChannel
   151                     #sequenceList: #listChannel
   151                 )
   152                 )
   152                  #(#HorizontalPanelViewSpec
   153                  #(#HorizontalPanelViewSpec
   153                     #name: 'HorizontalPanelView'
   154                     #name: 'HorizontalPanelView'
   195                     #layout: #(#LayoutFrame 1 0.5 53 0 -3 1 -1 0.5)
   196                     #layout: #(#LayoutFrame 1 0.5 53 0 -3 1 -1 0.5)
   196                     #activeHelpKey: #listOfHelpSpecClasses
   197                     #activeHelpKey: #listOfHelpSpecClasses
   197                     #model: #selectionOfHelpSpecClass
   198                     #model: #selectionOfHelpSpecClass
   198                     #hasHorizontalScrollBar: true
   199                     #hasHorizontalScrollBar: true
   199                     #hasVerticalScrollBar: true
   200                     #hasVerticalScrollBar: true
       
   201                     #miniScrollerHorizontal: true
       
   202                     #miniScrollerVertical: true
   200                     #valueChangeSelector: #helpSpecClassSelected
   203                     #valueChangeSelector: #helpSpecClassSelected
   201                     #useIndex: false
   204                     #useIndex: false
   202                     #sequenceList: #listOfHelpSpecClasses
   205                     #sequenceList: #listOfHelpSpecClasses
   203                 )
   206                 )
   204                  #(#TextEditorSpec
   207                  #(#TextEditorSpec
   325 
   328 
   326 dictionary:aDictionary
   329 dictionary:aDictionary
   327     "set the value of the instance variable 'dictionary' (automatically generated)"
   330     "set the value of the instance variable 'dictionary' (automatically generated)"
   328 
   331 
   329     (dictionary := aDictionary) isNil ifTrue:[
   332     (dictionary := aDictionary) isNil ifTrue:[
   330         dictionary := IdentityDictionary new.
   333         dictionary := Dictionary new.
   331     ].
   334     ].
   332     self updateList
   335     self updateList
   333 !
   336 !
   334 
   337 
   335 helpKey
   338 helpKey
   353     "read help text from an application associated with the class
   356     "read help text from an application associated with the class
   354     "
   357     "
   355     |help|
   358     |help|
   356 
   359 
   357     isModified := false.
   360     isModified := false.
   358     dictionary   := IdentityDictionary new.
   361     specClass notNil
   359     dictionaries := IdentityDictionary new.
   362     ifTrue:
       
   363     [   
       
   364         dictionary   := Dictionary new.
       
   365         dictionaries := Dictionary new.
       
   366     ].
   360     specClass  := self applicationClassAssociatedWith:aClass.
   367     specClass  := self applicationClassAssociatedWith:aClass.
   361     specClass isClass 
   368     (specClass isClass and: [specClass isLoaded])
   362     ifTrue: 
   369     ifTrue: 
   363     [
   370     [                                               
       
   371         (specClass class implements:#helpSpec) ifFalse:[
       
   372             dictionaries at: specClass name put: dictionary 
       
   373         ].
   364         self listOfHelpSpecClasses contents: (specClass withAllSuperclasses reverse collect: [:cls| cls name]).
   374         self listOfHelpSpecClasses contents: (specClass withAllSuperclasses reverse collect: [:cls| cls name]).
   365         self listOfHelpSpecClasses removeAll: (ApplicationModel withAllSuperclasses collect: [:cls| cls name]).
   375         self listOfHelpSpecClasses removeAll: (ApplicationModel withAllSuperclasses collect: [:cls| cls name]).
   366         self selectionOfHelpSpecClass value: specClass name. 
   376         self selectionOfHelpSpecClass value: specClass name. 
   367         (builder componentAt: #listOfHelpSpecClassesView) selection: 
   377         (builder componentAt: #listOfHelpSpecClassesView) selection: 
   368                 (self listOfHelpSpecClasses value indexOf: specClass name).
   378                 (self listOfHelpSpecClasses value indexOf: specClass name).
   369         self helpSpecClassSelected.
   379         self helpSpecClassSelected.
   370     ].
   380     ].
   371     (specClass respondsTo:#helpSpec) ifTrue:[
   381 
   372         help := specClass helpSpec
       
   373     ] ifFalse:[
       
   374         specClass := nil
       
   375     ].
       
   376     self updateList
   382     self updateList
       
   383 !
       
   384 
       
   385 isModified
       
   386     ^ isModified
       
   387 !
       
   388 
       
   389 isModified: aBoolean
       
   390 
       
   391     isModified := aBoolean
   377 !
   392 !
   378 
   393 
   379 modifiedHolder:aValueHolder
   394 modifiedHolder:aValueHolder
   380     "set the value holder set to true in case of modifying attributes
   395     "set the value holder set to true in case of modifying attributes
   381     "
   396     "
   412         key    := listSelection asSymbol.
   427         key    := listSelection asSymbol.
   413         list   := self listChannel value.
   428         list   := self listChannel value.
   414 
   429 
   415         (listChgd := (dictionary at:key ifAbsent:nil) isNil) ifTrue:[
   430         (listChgd := (dictionary at:key ifAbsent:nil) isNil) ifTrue:[
   416             list add:key.
   431             list add:key.
   417         ].          
   432         ].             
   418         dictionary at:key put:txt.
   433         dictionary at:key put:txt.
   419 
   434 
   420         listChgd ifTrue:[
   435         listChgd ifTrue:[
   421             self updateList.
   436             self updateList.
   422             (builder componentAt: #listOfHelpKeysView) selection: (list indexOf: key).
   437             (builder componentAt: #listOfHelpKeysView) selection: (list indexOf: key).
   444 !
   459 !
   445 
   460 
   446 helpSpecClassSelected
   461 helpSpecClassSelected
   447 
   462 
   448     |clsName|
   463     |clsName|
       
   464 
   449     clsName := self selectionOfHelpSpecClass value.
   465     clsName := self selectionOfHelpSpecClass value.
       
   466 
   450     (dictionary := dictionaries at: clsName ifAbsent: nil) isNil
   467     (dictionary := dictionaries at: clsName ifAbsent: nil) isNil
   451     ifTrue:
   468     ifTrue:
   452     [        
   469     [        
   453         dictionary := dictionaries at: clsName put: (self extractHelpSpecForClass: (Smalltalk at: clsName))
   470         dictionary := dictionaries at: clsName put: (self extractHelpSpecForClass: (Smalltalk at: clsName))
   454     ].
   471     ].
   455 
   472 
   456     self updateList.
   473     self updateList.
       
   474 
   457     listSelection notNil
   475     listSelection notNil
   458         ifTrue: [(dictionary keys includes: listSelection asSymbol)
   476     ifTrue: 
   459         ifTrue: [(builder componentAt: #listOfHelpKeysView) selection: 
   477     [
   460         (self listChannel value indexOf: (builder componentAt: #helpKeyInputField) contents)]
   478         (dictionary keys includes: listSelection asSymbol)
   461         ifFalse: [(builder componentAt: #listOfHelpKeysView) selection: nil]].
   479             ifTrue: [(builder componentAt: #listOfHelpKeysView) selection: 
   462     self editTextView contents: ''
   480                      (self listChannel value indexOf: (builder componentAt: #helpKeyInputField) contents)]
       
   481             ifFalse: [(builder componentAt: #listOfHelpKeysView) selection: nil].
       
   482     ].
       
   483     listSelection notNil
       
   484     ifTrue: 
       
   485     [
       
   486         self editTextView contents: (dictionary at: listSelection asSymbol ifAbsent: '')
       
   487     ]
       
   488 
       
   489 
   463 !
   490 !
   464 
   491 
   465 installHelpSpecInto:aClass
   492 installHelpSpecInto:aClass
   466     "install help text
   493     "install help text
   467     "
   494     "
   468     |cls src superHelpSpecKeys helpSpec mayRemoveHelpSpecSelector|
   495     |cls src helpSpec|
   469 
   496 
   470     cls := self applicationClassAssociatedWith:aClass.
   497     cls := self applicationClassAssociatedWith:aClass.
   471 
   498 
   472     cls isNil ifTrue:[
   499     cls isNil ifTrue:[
   473         ^ self information:'No application class defined!!'.
   500         ^ self information:'No application class defined!!'.
   474     ].
   501     ].
   475 
   502 
   476     aClass == cls name 
   503     aClass = cls name asString       
   477         ifTrue: [cls allSuperclasses value do: [:c| self installHelpSpecInto:c]. isModified := true].
   504         ifTrue: [self listOfHelpSpecClasses value do: [:c| c ~~ cls name ifTrue: [self installHelpSpecInto: (Smalltalk at: c)]. isModified := true]].
   478 
   505 
   479     isModified not ifTrue:[
   506     isModified not ifTrue:[
   480         ^nil
   507         ^nil
   481     ].
   508     ].
   482 
   509 
   483     (cls superclass respondsTo: #helpSpec) 
   510     helpSpec := dictionaries at: cls name ifAbsent: [dictionary].
   484         ifTrue:  [superHelpSpecKeys := cls superclass helpSpec keys. mayRemoveHelpSpecSelector := true]
   511 
   485         ifFalse: [superHelpSpecKeys := IdentityDictionary new. mayRemoveHelpSpecSelector := false].
   512     (cls class implements: #helpSpec) 
   486 
   513     ifTrue: 
   487     helpSpec := dictionaries at: cls name ifAbsent: [^nil].
   514     [
       
   515         |superclassHelpKeys implementedHelpSpec hasChanged|
       
   516         implementedHelpSpec := Dictionary new.
       
   517         superclassHelpKeys := (cls superclass respondsTo: #helpSpec)
       
   518             ifTrue:  [cls superclass helpSpec keys]
       
   519             ifFalse: [Array new].
       
   520 
       
   521         cls helpSpec associationsDo: [:h| (superclassHelpKeys includes: h key) 
       
   522             ifFalse: [implementedHelpSpec at: h key put: h value]].
       
   523 
       
   524         hasChanged := false.
       
   525         implementedHelpSpec associationsDo: [:h| (helpSpec            includesAssociation: h) ifFalse: [hasChanged := true]].
       
   526         helpSpec            associationsDo: [:h| (implementedHelpSpec includesAssociation: h) ifFalse: [hasChanged := true]].
       
   527 
       
   528         (implementedHelpSpec notEmpty and: [hasChanged and:
       
   529         [DialogBox confirm: 'Class ', cls name asBoldText, ' already implements\a menu spec!!\\Do only replace, if you have removed\help keys in an existing help spec.\' withCRs yesLabel: ' Merge ' noLabel: ' Replace ']])
       
   530         ifTrue:
       
   531         [
       
   532              implementedHelpSpec associationsDo: [:h| helpSpec at: h key put: h value].
       
   533         ]
       
   534     ].
       
   535 
   488     helpSpec isEmpty ifTrue:[
   536     helpSpec isEmpty ifTrue:[
   489         mayRemoveHelpSpecSelector ifTrue: [cls class removeSelector: #helpSpec].
   537         (cls superclass respondsTo: #helpSpec) ifTrue: [cls class removeSelector: #helpSpec].
   490         ^nil
   538         ^nil
   491     ].
   539     ].
   492 
   540 
   493     src  := '' writeStream.
   541     src  := '' writeStream.
   494 
   542 
   526             forClass:cls class 
   574             forClass:cls class 
   527           inCategory:'help specs'.
   575           inCategory:'help specs'.
   528 
   576 
   529     isModified := false.
   577     isModified := false.
   530 
   578 
       
   579 
   531 !
   580 !
   532 
   581 
   533 remove
   582 remove
   534     "remove selected help key
   583     "remove selected help key
   535     "
   584     "
   588 
   637 
   589 initialize
   638 initialize
   590     "setup instance attributes
   639     "setup instance attributes
   591     "
   640     "
   592     super initialize.
   641     super initialize.
   593     dictionary   := IdentityDictionary new.
   642     dictionary   := Dictionary new.
   594     dictionaries := IdentityDictionary new.
   643     dictionaries := Dictionary new.
   595     isModified := false.
   644     isModified := false.
   596 
   645 
   597 ! !
   646 ! !
   598 
   647 
   599 !UIHelpTool methodsFor:'private'!
   648 !UIHelpTool methodsFor:'private'!
   626     ((aClass class implements: #helpSpec)
   675     ((aClass class implements: #helpSpec)
   627     and: [(helpSpecSuperClass := aClass allSuperclasses detect: [:cls| cls class implements: #helpSpec] ifNone: nil) notNil])
   676     and: [(helpSpecSuperClass := aClass allSuperclasses detect: [:cls| cls class implements: #helpSpec] ifNone: nil) notNil])
   628     ifTrue:
   677     ifTrue:
   629     [                  
   678     [                  
   630         superHelpSpecKeys := helpSpecSuperClass helpSpec keys.
   679         superHelpSpecKeys := helpSpecSuperClass helpSpec keys.
   631         helpSpec := IdentityDictionary new.
   680         helpSpec := Dictionary new.
   632         aClass helpSpec associationsDo:
   681         aClass helpSpec associationsDo:
   633         [:asso|
   682         [:asso|
   634             (superHelpSpecKeys includes: asso key) ifFalse: [helpSpec at: asso key put: asso value]
   683             (superHelpSpecKeys includes: asso key) ifFalse: [helpSpec at: asso key put: asso value]
   635         ].          
   684         ].          
   636         ^dictionary := helpSpec
   685         ^dictionary := helpSpec
   637     ].
   686     ].
   638     ^dictionary := IdentityDictionary new 
   687     ^dictionary := Dictionary new 
   639 !
   688 !
   640 
   689 
   641 findHelpSpecForKey: aHelpKey
   690 findHelpSpecForKey: aHelpKey
   642     "update list from dictionary
   691     "update list from dictionary
   643     "
   692     "
   644     |helpSpecClass superHelpSpecKeys helpSpec|
   693     |dictTemp helpSpecClass superHelpSpecKeys helpSpec|
   645 
   694 
   646     aHelpKey isNil ifTrue: [^nil].
   695     aHelpKey isNil ifTrue: [^nil].
   647 
   696     dictTemp := dictionary.
   648     self listOfHelpSpecClasses value do:
   697     self listOfHelpSpecClasses value do:
   649     [:clsName|            
   698     [:clsName|            
   650         (dictionary := dictionaries at: clsName ifAbsent: nil) isNil
   699         (dictionary := dictionaries at: clsName ifAbsent: nil) isNil
   651         ifTrue:
   700         ifTrue:
   652         [        
   701         [        
   658             self updateList.
   707             self updateList.
   659             ^(builder componentAt: #listOfHelpSpecClassesView) selection: 
   708             ^(builder componentAt: #listOfHelpSpecClassesView) selection: 
   660                 (self listOfHelpSpecClasses value indexOf: clsName).
   709                 (self listOfHelpSpecClasses value indexOf: clsName).
   661         ]
   710         ]
   662     ].
   711     ].
       
   712     dictionary := dictTemp
   663 
   713 
   664 
   714 
   665 !
   715 !
   666 
   716 
   667 updateList
   717 updateList
   683         ^ UISpecificationTool
   733         ^ UISpecificationTool
   684     ].
   734     ].
   685   ^ cls
   735   ^ cls
   686 
   736 
   687 
   737 
   688 !
       
   689 
       
   690 isModified
       
   691     ^ isModified
       
   692 ! !
   738 ! !
   693 
   739 
   694 !UIHelpTool methodsFor:'selection'!
   740 !UIHelpTool methodsFor:'selection'!
   695 
   741 
   696 listSelection
   742 listSelection