ResourceSpecEditor.st
author tz
Fri, 20 Mar 1998 16:42:55 +0100
changeset 868 f35e6c622a98
parent 867 9da1ff2ac50d
child 876 585929b1fec2
permissions -rw-r--r--
subclassResponsibility

"
 COPYRIGHT (c) 1997 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:#ResourceSpecEditor
	instanceVariableNames:'modified aspects specClass specSelector tabSelection hasSaved'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-Framework'
!

!ResourceSpecEditor class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1997 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, DataSetBuilder, 
    HierarchicalListEditor, and the TabListEditor.

    [author:]
         Thomas Zwick
"
! !

!ResourceSpecEditor class methodsFor:'instance creation'!

openModalOnClass:aClass andSelector:aSelector
    "Open modal a ListSpecEditor on aClass and aSelector"

    ^self new openModalOnClass:aClass andSelector:aSelector

!

openOnClass:aClass andSelector:aSelector
    "Open a ListSpecEditor on aClass and aSelector"

    ^self new openOnClass:aClass andSelector:aSelector
! !

!ResourceSpecEditor class methodsFor:'accessing'!

codeGenerationComment

    ^self codeGenerationCommentForClass: self




!

codeGenerationCommentForClass: 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

    ^self subclassResponsibility
! !

!ResourceSpecEditor class methodsFor:'aspects'!

aspects
    "get the aspects for the attributes of the list spec components"

    ^#()
! !

!ResourceSpecEditor methodsFor:'accessing'!

modified       
    "return true, if the resource spec was modified"

    ^modified
!

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

    modified := aBoolean
!

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

    ^specClass
!

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

    aClass isBehavior ifTrue:[specClass := aClass name]
                     ifFalse:[specClass := aClass]
!

specSelector
    "get the method selector of the resource spec"

    ^specSelector

!

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

    specSelector := aSelector
! !

!ResourceSpecEditor methodsFor:'aspects'!

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

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

!

tabModel
    "get 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
!

valueOfEnableMovingIn

    ^builder booleanValueAspectFor: #valueOfEnableMovingIn



!

valueOfEnableMovingOut

    ^builder booleanValueAspectFor: #valueOfEnableMovingOut



!

valueOfEnableMovingUpOrDown

    ^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 

! !

!ResourceSpecEditor methodsFor:'help'!

defaultInfoLabel
    "get default label for the info bar"

    |cls|
    (specClass isSymbol and: [(cls := Smalltalk at: specClass) isClass])
    ifTrue:
    [
        (cls class implements: specSelector)
            ifFalse: [^specClass, ' >> ? (no selector defined)'].
        ^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
    "ask for resource item modification"

    self valueOfEnablingCommitButtons value
    ifTrue:
    [          
        ((YesNoBox title:'Resource item was modified!!\Save it?\' withCRs)        
            noText:'No';
            yesText:'Yes';
            showAtPointer;
            accepted) 
        ifFalse: 
        [
            self valueOfEnablingCommitButtons value: false. 
            modified := false.
            ^true
        ].
        self accept
    ].
    ^true

!

askForListModification
    "ask for resource modification"

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

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

    ^self askForItemModification and: [self askForListModification]

!

resolveClassNamed
    "get current class or nil"

    ^Smalltalk resolveName:specClass inClass:self class
!

resourceMessage: aString
    "extract 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
    "if there was loaded a resource spec, update the history"

    |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
    "return true if resource spec has saved"

    ^hasSaved

!

isStandAlone
    "return 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
    "first ask for modification then send close request to super"

    self askForModification ifTrue: [super closeRequest]

!

loadFromMessage:aString
    "load a spec from class and selector"

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

openModalOnClass:aClass andSelector:aSelector

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

    super openInterfaceModal.

!

openModalOnResourceSpec: aListSpec

    self buildFromResourceSpec: aListSpec.

    super openInterfaceModal.

!

openOnClass:aClass andSelector:aSelector

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

    super openInterface.
!

postOpenWith:aBuilder

    super postOpenWith:aBuilder.

    self buildFromClass: specClass andSelector: specSelector. 

! !

!ResourceSpecEditor methodsFor:'user actions'!

accept
    "invoked by the OK button; disable the commit buttons and set modified"

    self valueOfEnablingCommitButtons value: false.
    modified := true
!

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

    |cls|

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

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

    |cls resourceClass resourceSelector imageResourceMessage readStream|

    cls := self resolveName: specClass.
    cls isNil ifTrue:[
        ^ self information:'No valid class defined!!'.
    ].
    (aspects at:#icon) value size > 0
        ifTrue:  [resourceSelector := (aspects at:#icon) value]
        ifFalse: [resourceSelector := #icon].
    (aspects at:#retriever) value size > 0
        ifTrue:  [resourceClass := (aspects at:#retriever) value]
        ifFalse: [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]
    ]


!

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

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

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|  

    self askForItemModification.

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

!ResourceSpecEditor class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview2/ResourceSpecEditor.st,v 1.2 1998-03-20 15:42:55 tz Exp $'
! !