ResourceSpecEditor.st
author Claus Gittinger <cg@exept.de>
Tue, 30 Oct 2001 19:32:00 +0100
changeset 1524 6a0a84872e73
parent 1504 336f460e691b
child 1554 d01ffa42ca7a
permissions -rw-r--r--
added cancel to ask-if-modified dialog

"
 COPYRIGHT (c) 1997-1998 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:libview2' }"

ToolApplicationModel subclass:#ResourceSpecEditor
	instanceVariableNames:'specClass specSelector aspects modified hasSaved tabSelection'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Framework'
!

!ResourceSpecEditor class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997-1998 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
"
    Abstract super class for the MenuEditor, HierarchicalListEditor, 
    and the TabListEditor.
    It provides common behavior for initializing, loading, saving, and
    asking for modifications of the resource specs (#menu, #hierarchicalList, 
    #tabList) for the concrete subclasses.

    [instance variables:]
        specClass       <Symbol>                class implementing the resource spec
        specSelector    <Symbol>                selector returning the resource spec
        aspects         <IdentityDictionary>    dictionary with the attributes of the resource spec
        modified        <Boolean>               flag whether the resource spec was modified
        hasSaved        <Boolean>               flag whether the resource spec was saved
        tabSelection    <Integer>               index of the tab selection

    [see also:]
        MenuEditor
        HierarchicalListEditor
        TabListEditor

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

!ResourceSpecEditor class methodsFor:'instance creation'!

openModalOnClass:aClass andSelector:aSelector
    "opens modal the Resource Spec Editor on aClass and aSelector"

    ^self new openModalOnClass:aClass andSelector:aSelector

!

openOnClass:aClass andSelector:aSelector
    "opens the Resource Spec Editor on aClass and aSelector"

    ^self new openOnClass:aClass andSelector:aSelector
! !

!ResourceSpecEditor class methodsFor:'accessing'!

codeGenerationComment
    "returns a comment for the method code generated by myself"

    ^self codeGenerationCommentForClass: self




!

codeGenerationCommentForClass: aClass
    "returns a comment for the method code generated by aClass"

    ^'    "This resource specification was automatically generated\',
     '     by the ', aClass name, ' of ST/X."\\',

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





!

resourceType
    "returns the type of resource of the method generated by the Resource Spec Editor;
     concrete subclasses has to reimplement this method"

    ^self subclassResponsibility
! !

!ResourceSpecEditor class methodsFor:'aspects'!

aspects
    "returns the aspects for the attributes of the resource spec components;
     concrete subclasses might reimplement this method in order to return an array"

    ^#()
! !

!ResourceSpecEditor class methodsFor:'queries'!

isVisualStartable
    "return true, if this application can be started via #open.
     (to allow start of a change browser via double-click in the browser)"

    self == ResourceSpecEditor ifTrue:[^false].
    ^super isVisualStartable
! !

!ResourceSpecEditor class methodsFor:'startup / release'!

preSnapshot
    "before a snapshot; updates the channels,
     because the clipboard has removed"

    super preSnapshot.

    instances notNil ifTrue:[
        instances do:[:inst |
            inst updateChannels. 
            inst valueOfEnablingCommitButtons value: false.
            inst modifiedChannel value: false. 
        ]
    ]

    "Modified: / 4.2.1999 / 15:32:17 / cg"
! !

!ResourceSpecEditor methodsFor:'accessing'!

modified       
    "returns whether the resource spec was modified"

    ^modified
!

modified: aBoolean         
    "sets the resource spec modified as aBoolean"

    modified := aBoolean
!

specClass
    "returns the class where the resource spec is implemented"

    ^specClass
!

specClass:aClass
    "sets the class (or name) where the resource spec is (or should be) implemented"

    aClass isClass ifTrue: [specClass := aClass name]
                   ifFalse:[specClass := aClass asSymbol]
!

specSelector
    "returns the method selector of the resource spec"

    ^specSelector

!

specSelector:aSelector
    "sets the method selector of the resource spec"

    specSelector := aSelector
! !

!ResourceSpecEditor methodsFor:'aspects'!

aspectFor:aKey
    "returns the aspect for a aKey or nil"

    ^aspects at: aKey ifAbsent: [super aspectFor:aKey]

!

tabModel
    "returns the value holder for the tab selection"

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

valueOfCanPaste
    "returns whether the application can paste; as value holder"

    |holder|
    holder := super valueOfCanPaste.
    holder value: self class clipboard notNil.
    ^ holder
!

valueOfEnableMovingIn
    "returns whether the selected item can move into next item as child; as value holder"

    ^builder booleanValueAspectFor: #valueOfEnableMovingIn
!

valueOfEnableMovingInAbove
    "returns whether the selected item can move into the previous item as child;
     as a value holder"

    ^builder booleanValueAspectFor: #valueOfEnableMovingInAbove
!

valueOfEnableMovingOut
    "returns whether the selected item can move out from its parent item; as value holder"

    ^builder booleanValueAspectFor: #valueOfEnableMovingOut
!

valueOfEnableMovingUpOrDown
    "returns whether the selected item can move up or down; as value holder"

    ^builder booleanValueAspectFor: #valueOfEnableMovingUpOrDown
! !

!ResourceSpecEditor methodsFor:'building'!

buildFromResourceSpec: aResourceSpec
    "concrete subclass has to reimplement this method
     in order to build its resource spec from aResourceSpec"

    ^self subclassResponsibility
! !

!ResourceSpecEditor methodsFor:'change & update'!

update:something with:aParameter from:someObject
    "one of my aspects has changed; update modified channel for the commit buttons"

    self valueOfEnablingCommitButtons value: true 

!

updateAllToolInstances
    "updates the channels of all other instances of my class"

    self allToolInstances do: [:inst| inst updateChannels]

!

updateChannels
    "updates my channels"

    self valueOfCanPaste


! !

!ResourceSpecEditor methodsFor:'help'!

defaultInfoLabel
    "returns the default label for the info bar"

    |cls|
    (specClass isSymbol and: [(cls := Smalltalk at: specClass) isClass])
    ifTrue:
    [
        (cls class implements: specSelector)
        ifFalse: 
        [
            ^specSelector isNil 
                ifTrue:  [specClass, ' >> ? (no selector defined)']
                ifFalse: [specClass, ' >> ', specSelector, ' (not implemented)']
        ].
        ^specClass, ' >> ', specSelector
    ].
    ^'No class and selector defined.'

! !

!ResourceSpecEditor methodsFor:'initialization'!

initialize
    "initialize the flags and the aspects"

    super initialize.

    hasSaved     := modified := false.
    aspects      := IdentityDictionary new.
    tabSelection := 0.

    self class aspects do:
    [:aKey|
        |holder|
        aspects at:aKey put: (holder := ValueHolder new).
        holder addDependent: self
    ]
! !

!ResourceSpecEditor methodsFor:'private'!

askForItemModification
    "asks for resource item modification"

    |anythingChangedHolder anythingChanged answer|

    anythingChangedHolder := self valueOfEnablingCommitButtons.
    anythingChanged := anythingChangedHolder value.
    anythingChanged ifTrue:[          
"/        answer := ((YesNoBox title:'Resource item was modified!!\Save it?\' withCRs)        
"/                        noText:'No';
"/                        yesText:'Yes';
"/                        showAtPointer;
"/                        accepted). 

        answer := Dialog 
                        confirmWithCancel:(resources string:'Item was modified!!\Save it?\' withCRs)
                        labels:#('Cancel' 'No' 'Yes')
                        default:3.
        answer isNil ifTrue:[
            ^ false
        ].

        answer ifTrue:[
            self accept
        ] ifFalse: [
            anythingChangedHolder value: false. 
            self clearModifiedFlag. 
            modified := false.
        ]
    ].
    ^true

    "Modified: / 30.10.2001 / 18:38:34 / cg"
!

askForListModification
    "asks for resource modification"

    modified
    ifTrue:
    [
        ((YesNoBox title:(resources string:'%1 spec was modified !!' with:self class resourceType asUppercaseFirst))        
            noText:(resources string:'Cancel');
            yesText:(resources string:'Forget it and proceed');
            showAtPointer;
            accepted) ifFalse: [^false].
        modified := false
    ].
    ^true

    "Modified: / 20.5.1998 / 03:40:26 / cg"
!

askForModification
    "asks first for item and then for resource modification"

    ^self askForItemModification and: [self askForListModification]

!

resolveClassNamed
    "returns current class or nil"

    ^Smalltalk resolveName:specClass inClass:self class
!

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
!

updateHistory
    "updates the history, if there was loaded a resource spec"

    |cls|             
    ((cls := self resolveClassNamed) notNil and: [cls class implements: specSelector])
    ifTrue:
    [
        |className message|
        specClass isClass  ifTrue: [className := specClass name].
        specClass isString ifTrue: [className := specClass].
        message := className, ' ', specSelector.
        self addToHistory: message -> #loadFromMessage:
    ]
! !

!ResourceSpecEditor methodsFor:'queries'!

hasSaved
    "returns true if resource spec has saved"

    ^hasSaved

!

isStandAlone
    "returns true if the editor was not started from another tool"

    ^self masterApplication isNil
! !

!ResourceSpecEditor methodsFor:'selection'!

tabSelection
    "returns selected tab index or 0"

    ^tabSelection

! !

!ResourceSpecEditor methodsFor:'startup / release'!

closeRequest
    "asks first for modification, then sends close request to super"

    self askForModification ifTrue: [super closeRequest]

!

loadFromMessage:aString
    "builds by evaluating aString the resource spec for editing"

    (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 isStandAlone 
                ifFalse: [self buildFromResourceSpec: (cls perform: sel)]
                ifTrue:  [self buildFromClass: (specClass := cls name) andSelector: (specSelector := sel)].
            ^true
        ]
    ].
    ^false

    "Modified: / 21.5.1998 / 02:56:46 / cg"
!

openModalOnClass:aClass andSelector:aSelector
    "sets the specClass and specSelector and opens modal the interface"

    specClass    := aClass isClass ifTrue: [aClass name] ifFalse: [aClass asSymbol].
    specSelector := aSelector.

    super openInterfaceModal.

!

openModalOnResourceSpec: aListSpec
    "builds first from specClass and specSelector the resource spec for editing,
     then opens modal the interface"

    self buildFromResourceSpec: aListSpec.

    super openInterfaceModal.

!

openOnClass:aClass andSelector:aSelector
    "sets the specClass and specSelector and opens the interface"

    specClass    := aClass isClass ifTrue: [aClass name] ifFalse: [aClass asSymbol].
    specSelector := aSelector.

    super openInterface.
!

postBuildWith:aBuilder
    "after creating the views and before opening,
     adds myself to the instances dictionary in the settings"

    super postBuildWith:aBuilder.

    self class rememberInstance:self

    "Modified: / 4.2.1999 / 15:33:23 / cg"
!

postOpenWith:aBuilder
    "after opening, builds from specClass and specSelector the resource spec for editing"

    super postOpenWith:aBuilder.

    self buildFromClass: specClass andSelector: specSelector 

!

uninitialize
    "uninitializes; removes myself from the instances dictionary in the settings"

    super uninitialize.

    self class forgetInstance:self

    "Modified: / 4.2.1999 / 15:34:25 / cg"
! !

!ResourceSpecEditor methodsFor:'user actions'!

accept
    "invoked by the OK button; disables the commit buttons and sets myself modified"

    self acceptChannel 
        value:false;    
        value:true;      "/ toggle to force inputFields to accept
        value:false.    

    self valueOfEnablingCommitButtons value: false.
    self clearModifiedFlag.
    modified := true
!

doBrowseClass
    "opens a System Browser on the specClass and specSelector"

    |cls|

    (cls := self resolveClassNamed) notNil 
        ifTrue: [UserPreferences systemBrowserClass openInClass:cls class selector: specSelector] 
        ifFalse:[self information:'No class defined!!']
!

doEditImage
    "opens a Image Editor on the resource retriever and the icon selector"

    |cls resourceClass resourceSelector imageResourceMessage readStream icon retriever|

    (icon := (aspects at:#icon) value) size > 0
        ifTrue:  [resourceSelector := icon]
        ifFalse: [resourceSelector := #icon].

    (retriever := (aspects at:#retriever) value) size > 0
    ifTrue:[
        resourceClass := retriever
    ] ifFalse:[
        (cls := self resolveName: specClass) notNil 
        ifTrue:[
            resourceClass := cls withAllSuperclasses detect: [:cls| cls class implements: resourceSelector] ifNone: [cls]
        ]
    ].

    (imageResourceMessage := ImageEditor openModalOnClass: resourceClass andSelector: resourceSelector) notNil
    ifTrue: [
        readStream := imageResourceMessage readStream.
        resourceClass := (readStream upTo: $ ) asSymbol.
        resourceSelector := readStream upToEnd asSymbol.
        resourceClass size > 0 ifTrue: [
            (aspects at:#retriever) value: resourceClass
        ].
        resourceSelector size > 0 ifTrue: [
            (aspects at:#icon) value: resourceSelector. 
            self valueOfEnablingCommitButtons value: true
        ]
    ]

    "Modified: / 21.5.1998 / 02:44:04 / cg"
!

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

    |myResourceType|

    myResourceType := self class resourceType.

    self loadFromMessage: 
        (ResourceSelectionBrowser
            request: 'Load ', myResourceType asUppercaseFirst, ' Spec From Class'
            onSuperclass: nil
            andClass: specClass
            andSelector: specSelector ? myResourceType
            withResourceTypes: (Array with: myResourceType))

    "Modified: / 21.5.1998 / 02:59:02 / cg"
!

doNew
    "first ask for modification; then clean specClass and specSelector,
     but only, if the editor is opened as stand alone;
     finally make a build of a resource spec containing no items"

    self askForModification
    ifTrue: 
    [
        self isStandAlone ifTrue: [specClass := specSelector := nil].
        self buildFromClass: nil andSelector: self class resourceType.
        ^true
    ].
    ^false

!

doSave
    "before saving ask for modification; if no specClass and specSelector
     is defined, do save as"

    self askForItemModification.

    (specClass isNil or:[specSelector isNil]) ifTrue:[
        self doSaveAs.
        ^false
    ].
    ^true
!

doSaveAs
    "first ask for modification; 
     then open a ResourceSelectionBrowser; 
     after that extract the resource message;
     finally do save and make a new build"

    |resourceMessage myResourceType|  

    self askForItemModification.

    myResourceType := self class resourceType.

    (resourceMessage := ResourceSelectionBrowser
            request: 'Save ', myResourceType asUppercaseFirst, ' Spec In Class'
            onSuperclass: #Object
            andClass: specClass
            andSelector: specSelector ? myResourceType
            withResourceTypes: (Array with: myResourceType)) notNil
    ifTrue:
    [  
        modified := false.
        (self resourceMessage: resourceMessage)
        ifTrue:
        [
            self doSave.
            self buildFromClass: specClass andSelector: specSelector.
            ^true
        ]
    ].
    ^false

    "Modified: / 21.5.1998 / 02:59:46 / cg"
! !

!ResourceSpecEditor class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/ResourceSpecEditor.st,v 1.21 2001-10-30 18:32:00 cg Exp $'
! !