View.st
author Claus Gittinger <cg@exept.de>
Fri, 15 Dec 1995 14:05:22 +0100
changeset 321 f31da2a1d387
parent 269 ea536bb319a6
child 616 56cf67c82664
permissions -rw-r--r--
interest is written with one 'r' (shame on me)

"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      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.
"

SimpleView subclass:#View
	 instanceVariableNames:'model aspectMsg changeMsg menuMsg'
	 classVariableNames:''
	 poolDictionaries:''
	 category:'Views-Basic'
!

!View class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1989 by Claus Gittinger
	      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
"
    this class adds provisions for views which show or work on a model.
    This functionality used to be in View, but has been extracted into SimpleView and
    this new View class, to take some of the stuff out of views which do not need
    this functionality (i.e. all views which do only geometry management).
    Instances of View are seldom used, most views in the system inherit 
    from this class. 

    Instance variables:

	model           <nil | any>         the model (if any)

	aspectMsg       <nil | Symbol>      the aspect; typically
					    dependentViews react on changes
					    of this aspect and update their contents.

	changeMsg       <nil | Symbol>      the changeMessage; typically
					    dependentViews send this message to
					    the model to tell it about changes.

	menuMsg         <nil | Symbol>      the menuMessage; typically
					    dependentViews send this message to
					    the model to ask for a popup menu.
					    Some classes allow setting an explicit
					    menuHolder and menuPerformer.
"
! !

!View class methodsFor:'instance creation'!

model:aModel
    "st-80 style view creation: create a new view and set its model"

    ^ self new model:aModel
!

on:aModel aspect:aspectMsg
    "st-80 style view creation: create a new view, set its model
     and selectors for aspect"

    ^ self new 
	on:aModel
	aspect:aspectMsg
!

on:aModel aspect:aspectMsg change:changeMsg
    "st-80 style view creation: create a new view, set its model
     and selectors for aspect and change"

    ^ self new 
	on:aModel
	aspect:aspectMsg
	change:changeMsg
!

on:aModel aspect:aspectMsg change:changeMsg menu:menuMsg
    "st-80 style view creation: create a new view, set its model
     and selectors for aspect, change and menu"

    ^ self new 
	on:aModel
	aspect:aspectMsg
	change:changeMsg
	menu:menuMsg
!

on:aModel aspect:aspectMsg menu:menuMsg
    "st-80 style view creation: create a new view, set its model
     and selectors for aspect and menu"

    ^ self new 
	on:aModel
	aspect:aspectMsg
	menu:menuMsg
! !

!View class methodsFor:'defaults'!

defaultAspectMessage   
    "subclasses which by default do NOT want to be informed about changed
     models should redefine this to return nil"

    ^ #value
!

defaultChangeMessage   
    "subclasses which by default do NOT want to inform the model
     should redefine this to return nil"

    ^ #value:
! !

!View methodsFor:'accessing-channels'!

setupChannel:newChannel for:changeSelector withOld:oldChannel
    "common code to change a channel"

    |oldValue|

    oldChannel notNil ifTrue:[
	oldChannel retractInterestsFor:self.
	oldValue := oldChannel value.
    ].
    newChannel onChangeSend:changeSelector to:self.
    self perform:changeSelector.
    ^ newChannel
! !

!View methodsFor:'accessing-menus'!

menuHolder
    "who has the menu ? 
     By default, its the model if I have one."

    model notNil ifTrue:[^ model].
    ^ self
!

menuPerformer
    "who should perform the menu actions ? 
     By default, its the model if I have one."

    model notNil ifTrue:[^ model].
    ^ self
! !

!View methodsFor:'accessing-mvc'!

addModelInterfaceTo:aDictionary
    "this adds entries for all messages sent to my model
     to aDictionary"

    aDictionary at:#aspectMessage put:aspectMsg.
    aDictionary at:#changeMessage put:changeMsg.
    aDictionary at:#menuMessage put:menuMsg.

    "
     Button new modelInterface 
    "
!

aspect
    "Return the aspect used with changes from/to the model"

    ^ aspectMsg
!

aspectMessage
    "Return the aspect used with changes from/to the model"

    ^ aspectMsg
!

aspectMessage:aspectSymbol
    "ST-80 style updating: If a views aspectSymbol is nonNil, 
     it will respond to changes of this aspect from the model."

    aspectMsg := aspectSymbol
!

change:changeSymbol
    "ST-80 style change notification: If a views changeSymbol is nonNil, 
     it will send it to its model when something changes.
     Alias for changeMessage: for ST-80 compatibility."

    self changeMessage:changeSymbol
!

changeMessage
    "Return the symbol sent to the model if nonNil when something changes."

    ^ changeMsg
!

changeMessage:aSymbol
    "ST-80 style change notification: If a views changeSymbol is nonNil, 
     it will send it to its model when something changes.
     This is the same as change: which was added for ST-80 compatibility."

    changeMsg := aSymbol
!

controller:aController
    "set the controller"

    super controller:aController.
    controller notNil ifTrue:[
	controller model:model
    ]
!

menu:menuSymbol
    "ST-80 style menus: If a views menuSymbol is nonNil, it
     will send it to its model when the middleButton is pressed.
     That method should return nil or the menu to be shown.
     This is useful for very dynamic menus, where it does not
     make sense to define an initial menu.
     Alias for #menuMessage:, for ST-80 compatibility."

    menuMsg := menuSymbol
!

menuMessage
    "Return the symbol sent to the model to aquire the menu"

    ^ menuMsg
!

menuMessage:aSymbol
    "ST-80 style menus: If a views menuSymbol is nonNil, it
     will send it to its model when the middleButton is pressed.
     That method should return nil or the menu to be shown.
     This is useful for very dynamic menus, where it does not
     make sense to define an initial menu.
     This is the same as #menu: which was added for ST-80 compatibility."

    menuMsg := aSymbol
!

model
    "return the model, for non-MVC views,
     this is nil or the receiver"

    ^ model
!

model:aModel
    "set the model"

    model notNil ifTrue:[
	model removeDependent:self
    ].
    model := aModel.

    model notNil ifTrue:[
	aModel addDependent:self
    ].
    controller notNil ifTrue:[
	controller model:aModel
    ]
!

modelInterface
    "this returns a dictionary of messages sent to my model.
     It can be used for builders and wrappers to get information
     about the messages sent to my model.
     The returned dictionary contains one entry for each get-Msg,
     and the recevier will implement corresponding messages (with a colon)
     to set the message symbol."

    |d|

    d := IdentityDictionary new.
    self addModelInterfaceTo:d.
    ^ d

    "
     Button new modelInterface
     Label new modelInterface 
    "

    "
     does the view support setting the menuMessage ?

     SelectionInListView new modelInterface includesKey:#menuMessage 
    "

    "
     turn off all interaction to the model:

     |m v if|

     m := SelectionInList new.
     m list:#('one' 'two' 'tree' 'four') asValue.
     m selection:1 asValue.
     v := SelectionInListView on:m.
     v open.
     v inspect.

     if := v modelInterface.
     if inspect.

     if keysAndValuesDo:[:what :msg |
	 v perform:(what , ':') asSymbol with:nil.
     ].
    "
!

on:aModel aspect:aspectSymbol
    "ST-80 compatibility: set model and aspect
     messages - needs a view which uses these"

    aspectMsg := aspectSymbol.
    self model:aModel.
!

on:aModel aspect:aspectSymbol change:changeSymbol
    "ST-80 compatibility: set model, aspect and change
     messages - needs a view which uses these"

    aspectMsg := aspectSymbol.
    changeMsg := changeSymbol.
    self model:aModel.
!

on:aModel aspect:aspectSymbol change:changeSymbol menu:menuSymbol
    "ST-80 compatibility: set model, aspect, change and menu
     messages - needs a view which uses these"

    aspectMsg := aspectSymbol.
    changeMsg := changeSymbol.
    menuMsg := menuSymbol.
    self model:aModel.
!

on:aModel aspect:aspectSymbol menu:menuSymbol
    "ST-80 compatibility: set model, aspect and menu
     messages - needs a view which uses these"

    aspectMsg := aspectSymbol.
    menuMsg := menuSymbol.
    self model:aModel.
!

sendChangeMessage:aSelector with:arg
    "tell the model about a change"

    |n selector|

    "/
    "/ MVC way of doing it:
    "/ if the model is a block, evaluate it, optionally
    "/ passing the arg and the receiver as arguments.
    "/
    "/ otherwise (the common case) send it a changeMsg message
    "/ also with arg and the receiver (depending on the number of arguments
    "/ as defined by the selector).
    "/
    (model notNil and:[aSelector notNil]) ifTrue:[
	n := aSelector numArgs.
	model isBlock ifTrue:[
	    n := model numArgs.
	    n == 0 ifTrue:[
		selector := #value
	    ] ifFalse:[
		n == 1 ifTrue:[
		    selector := #value:
		] ifFalse:[
		    selector := #value:value:
		]
	    ]
	] ifFalse:[
	    selector := aSelector
	].
	n == 0 ifTrue:[
	    model perform:selector 
	] ifFalse:[
	    n == 1 ifTrue:[
		model perform:selector with:arg
	    ] ifFalse:[
		model perform:selector with:arg with:self 
	    ]
	]
    ]
!

sendChangeMessageWith:arg
    "tell the model about a change"

    self sendChangeMessage:changeMsg with:arg
! !

!View methodsFor:'drawing'!

redraw
    "redraw myself
     if there is a model, this one shall redraw itself,
     otherwise we cannot do much here - has to be redefined in subclasses"

    model notNil ifTrue:[
	model update:self
    ]
! !

!View methodsFor:'initialization'!

initialize
    super initialize.

    aspectMsg := self class defaultAspectMessage.
    changeMsg := self class defaultChangeMessage.

    model notNil ifTrue:[
	controller notNil ifTrue:[
	    controller model:model
	]
    ].
! !

!View methodsFor:'realization'!

destroy
    "unrealize & destroy - make me invisible, destroy subviews then
     make me unknown to the device"

    model notNil ifTrue:[
	model removeDependent:self.
	model := nil.
    ].
    super destroy.
! !

!View class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libview/View.st,v 1.49 1995-12-15 13:05:22 cg Exp $'
! !