View.st
author claus
Wed, 03 May 1995 02:27:48 +0200
changeset 135 cf8e46015072
parent 133 ca8ce3916382
child 140 0db355079dc4
permissions -rw-r--r--
.

"
 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.
"

'From Smalltalk/X, Version:2.10.5 on 14-mar-1995 at 11:02:34 am'!

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

View comment:'
COPYRIGHT (c) 1995 by Claus Gittinger
	      All Rights Reserved

$Header: /cvs/stx/stx/libview/View.st,v 1.41 1995-05-03 00:26:19 claus Exp $
'!

!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.
"
!

version
"
$Header: /cvs/stx/stx/libview/View.st,v 1.41 1995-05-03 00:26:19 claus Exp $
"
!

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.
"
! !

!View class methodsFor:'instance creation'!

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

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

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

    ^ self new model:aModel
! !

!View class methodsFor:'defaults'!

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

    ^ #value
!

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

    ^ #value:
! !

!View methodsFor:'accessing-mvc'!

sendChangeMessageWith:arg
    "tell the model about a change"

    self sendChangeMessage:changeMsg with:arg
!

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

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.

    "/
    "/ set default change- and aspectMsgs
    "/ (for ST-80 compatibility)
    "/
    changeMsg isNil ifTrue:[
	changeMsg := self class defaultChangeMsg
    ].
    aspectMsg isNil ifTrue:[
	aspectMsg := self class defaultAspectMsg
    ].

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

controller:aController
    "set the controller"

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

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 menu:menuSymbol
    "ST-80 compatibility: set model, aspect and menu
     messages - needs a view which uses these"

    aspectMsg := aspectSymbol.
    menuMsg := menuSymbol.
    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.
!

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."

    menuMsg := menuSymbol
!

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

    changeMsg := changeSymbol
!

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

    aspectMsg := aspectSymbol
!

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

    ^ changeMsg
!

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

    ^ menuMsg
!

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

    ^ aspectMsg
! !

!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:'initialization'!

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

!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:'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.
! !