UIPropertyView.st
author Claus Gittinger <cg@exept.de>
Tue, 25 Feb 1997 15:07:09 +0100
changeset 60 7542ab7fbbfe
parent 59 0a2b2ff030a0
child 62 0e8573b4329a
permissions -rw-r--r--
*** empty log message ***

'From Smalltalk/X, Version:3.1.4 on 25-feb-1997 at 2:17:33 pm'                  !

ApplicationModel subclass:#UIPropertyView
	instanceVariableNames:'builderView modified propertyFrame propertyList propertySpecs
		currentView currentSpec propertyAspects staticAspects
		specBeingEdited userSelectedProperty currentSpecChannel'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!


!UIPropertyView class methodsFor:'instance creation'!

in:aTopView receiver:aReceiver
    |application|

    application := self new.
    application in:aTopView receiver:aReceiver.
  ^ application
! !

!UIPropertyView class methodsFor:'constants'!

titleOfLayoutMenu
    ^ 'Dimension'
! !

!UIPropertyView class methodsFor:'specifications'!

specificationAlignmentOrigin
    "
    UIPainter new openOnClass:self andSelector:#specificationAlignmentOrigin
    "
    <resource: #canvas>

    ^

       #(#FullSpec
          #'window:' 
           #(#WindowSpec
              #'layout:' #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #'label:' 'unnamed'
              #'bounds:' #(#Rectangle 0 0 248 304)
          )
          #'component:' 
           #(#SpecCollection
              #'collection:' 
               #(
                 #(#LabelSpec
                    #'name:' 'label1'
                    #'layout:' #(#LayoutFrame 5 0 42 0 48 0 60 0)
                    #'label:' 'left'
                )
                 #(#LabelSpec
                    #'name:' 'label2'
                    #'layout:' #(#LayoutFrame 5 0 69 0 48 0 87 0)
                    #'label:' 'top'
                )
                 #(#LabelSpec
                    #'name:' 'label3'
                    #'layout:' #(#LayoutFrame 57 0 10 0 103 0 27 0)
                    #'label:' 'relative'
                )
                 #(#LabelSpec
                    #'name:' 'label4'
                    #'layout:' #(#LayoutFrame 154 0 11 0 190 0 28 0)
                    #'label:' 'offset'
                )
                 #(#LabelSpec
                    #'name:' 'label5'
                    #'layout:' #(#LayoutFrame 5 0 96 0 48 0 114 0)
                    #'label:' 'align H'
                )
                 #(#LabelSpec
                    #'name:' 'label6'
                    #'layout:' #(#LayoutFrame 5 0 122 0 48 0 140 0)
                    #'label:' 'align V'
                )
                 #(#InputFieldSpec
                    #'name:' 'editField1'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 57 0 42 0 114 0 60 0)
                    #'model:' #leftFraction
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField2'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 57 0 69 0 114 0 87 0)
                    #'model:' #topFraction
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField5'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 57 0 96 0 114 0 114 0)
                    #'model:' #leftAlignmentFraction
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField6'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 56 0 122 0 113 0 140 0)
                    #'model:' #topAlignmentFraction
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField3'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 154 0 42 0 212 0 60 0)
                    #'model:' #leftOffset
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField4'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 154 0 69 0 212 0 87 0)
                    #'model:' #topOffset
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#ActionButtonSpec
                    #'name:' 'button1'
                    #'layout:' #(#LayoutFrame 119 0 42 0 138 0 60 0)
                    #'label:' ''
                    #'model:' #makeRelativeLeft
                )
                 #(#ActionButtonSpec
                    #'name:' 'button2'
                    #'layout:' #(#LayoutFrame 119 0 69 0 138 0 87 0)
                    #'label:' ''
                    #'model:' #makeRelativeTop
                )
                 #(#ActionButtonSpec
                    #'name:' 'button3'
                    #'layout:' #(#LayoutFrame 216 0 42 0 235 0 60 0)
                    #'label:' ''
                    #'model:' #makeOffsetLeft
                )
                 #(#ActionButtonSpec
                    #'name:' 'button4'
                    #'layout:' #(#LayoutFrame 216 0 69 0 235 0 87 0)
                    #'label:' ''
                    #'model:' #makeOffsetTop
                )


               #(#ActionButtonSpec
                  #'name:' 'button'
                  #'layout:' #(#LayoutFrame 16 0 210 0 76 0 240 0)
                  #'label:' 'frame'
                  #'model:' #showLayoutFrame
                )
               #(#ActionButtonSpec
                  #'name:' 'button'
                  #'layout:' #(#LayoutFrame 96 0 210 0 156 0 240 0)
                  #'label:' 'origin'
                  #'model:' #showLayoutOrigin
                )
               #(#ActionButtonSpec
                  #'name:' 'button'
                  #'layout:' #(#LayoutFrame 176 0 210 0 236 0 240 0)
                  #'label:' 'align'
                  #'model:' #showAlignmentOrigin
                  #'initiallyDisabled:' true
                )

              )
          )
      )



!

specificationLayoutFrame
    "
    UIPainter new openOnClass:self andSelector:#specificationLayoutFrame
    "
    <resource: #canvas>

    ^

       #(#FullSpec
          #'window:' 
           #(#WindowSpec
              #'layout:' #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #'label:' 'unnamed'
              #'bounds:' #(#Rectangle 0 0 300 300)
          )
          #'component:' 
           #(#SpecCollection
              #'collection:' 
               #(
                 #(#LabelSpec
                    #'name:' 'label left'
                    #'layout:' #(#LayoutFrame 12 0 39 0 53 0 57 0)
                    #'label:' 'left'
                )
                 #(#LabelSpec
                    #'name:' 'label top'
                    #'layout:' #(#LayoutFrame 12 0 67 0 53 0 85 0)
                    #'label:' 'top'
                )
                 #(#LabelSpec
                    #'name:' 'label right'
                    #'layout:' #(#LayoutFrame 12 0 95 0 53 0 113 0)
                    #'label:' 'right'
                )
                 #(#LabelSpec
                    #'name:' 'label bottom'
                    #'layout:' #(#LayoutFrame 12 0 123 0 53 0 141 0)
                    #'label:' 'bottom'
                )
                 #(#LabelSpec
                    #'name:' 'label relative'
                    #'layout:' #(#LayoutFrame 65 0 6 0 110 0 24 0)
                    #'label:' 'relative'
                )
                 #(#LabelSpec
                    #'name:' 'label offset'
                    #'layout:' #(#LayoutFrame 159 0 6 0 190 0 24 0)
                    #'label:' 'offset'
                )
                 #(#LabelSpec
                    #'name:' 'label all relative'
                    #'layout:' #(#LayoutFrame 12 0 157 0 53 0 175 0)
                    #'label:' 'all'
                )
                 #(#LabelSpec
                    #'name:' 'label all absolute'
                    #'layout:' #(#LayoutFrame 159 0 157 0 210 0 175 0)
                    #'label:' 'all'
                )
                 #(#InputFieldSpec
                    #'name:' 'relative E1'
                    #'layout:' #(#LayoutFrame 65 0 39 0 113 0 57 0)
                    #'model:' #leftFraction
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'relative E2'
                    #'layout:' #(#LayoutFrame 65 0 67 0 113 0 85 0)
                    #'model:' #topFraction
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'relative E3'
                    #'layout:' #(#LayoutFrame 65 0 95 0 113 0 113 0)
                    #'model:' #rightFraction
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'relative E4'
                    #'layout:' #(#LayoutFrame 65 0 123 0 113 0 141 0)
                    #'model:' #bottomFraction
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'offset E1'
                    #'layout:' #(#LayoutFrame 159 0 39 0 210 0 57 0)
                    #'model:' #leftOffset
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'offset E2'
                    #'layout:' #(#LayoutFrame 159 0 67 0 210 0 85 0)
                    #'model:' #topOffset
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'offset E3'
                    #'layout:' #(#LayoutFrame 159 0 95 0 210 0 113 0)
                    #'model:' #rightOffset
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#InputFieldSpec
                    #'name:' 'offset E4'
                    #'layout:' #(#LayoutFrame 159 0 123 0 210 0 141 0)
                    #'model:' #bottomOffset
                    #'type:' #numberOrNil
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                )
                 #(#ActionButtonSpec
                    #'name:' 'relative B1'
                    #'layout:' #(#LayoutFrame 117 0 39 0 136 0 57 0)
                    #'label:' ' '
                    #'model:' #makeRelativeLeft
                )
                 #(#ActionButtonSpec
                    #'name:' 'relative B2'
                    #'layout:' #(#LayoutFrame 117 0 67 0 136 0 85 0)
                    #'label:' ' '
                    #'model:' #makeRelativeTop
                )
                 #(#ActionButtonSpec
                    #'name:' 'relative B3'
                    #'layout:' #(#LayoutFrame 117 0 95 0 136 0 113 0)
                    #'label:' ' '
                    #'model:' #makeRelativeRight
                )
                 #(#ActionButtonSpec
                    #'name:' 'relative B4'
                    #'layout:' #(#LayoutFrame 117 0 123 0 136 0 141 0)
                    #'label:' ' '
                    #'model:' #makeRelativeBottom
                )
                 #(#ActionButtonSpec
                    #'name:' 'relative BAll'
                    #'layout:' #(#LayoutFrame 117 0 157 0 136 0 175 0)
                    #'label:' ' '
                    #'model:' #makeRelativeAll
                )
                 #(#ActionButtonSpec
                    #'name:' 'offset B1'
                    #'layout:' #(#LayoutFrame 214 0 39 0 233 0 57 0)
                    #'label:' ''
                    #'model:' #makeOffsetLeft
                )
                 #(#ActionButtonSpec
                    #'name:' 'offset B2'
                    #'layout:' #(#LayoutFrame 214 0 67 0 233 0 85 0)
                    #'label:' ''
                    #'model:' #makeOffsetTop
                )
                 #(#ActionButtonSpec
                    #'name:' 'offset B3'
                    #'layout:' #(#LayoutFrame 214 0 95 0 233 0 113 0)
                    #'label:' ''
                    #'model:' #makeOffsetRight
                )
                 #(#ActionButtonSpec
                    #'name:' 'offset B4'
                    #'layout:' #(#LayoutFrame 214 0 123 0 233 0 141 0)
                    #'label:' ''
                    #'model:' #makeOffsetBottom
                )
                 #(#ActionButtonSpec
                    #'name:' 'offset BAll'
                    #'layout:' #(#LayoutFrame 214 0 157 0 233 0 175 0)
                    #'label:' ' '
                    #'model:' #makeOffsetAll
                )
                 #(#ActionButtonSpec
                    #'name:' 'button'
                    #'layout:' #(#LayoutFrame 16 0 210 0 76 0 240 0)
                    #'label:' 'frame'
                    #'model:' #showLayoutFrame
                    #'initiallyDisabled:' true
                )
                 #(#ActionButtonSpec
                    #'name:' 'button10'
                    #'layout:' #(#LayoutFrame 96 0 210 0 156 0 240 0)
                    #'label:' 'origin'
                    #'model:' #showLayoutOrigin
                )
                 #(#ActionButtonSpec
                    #'name:' 'button11'
                    #'layout:' #(#LayoutFrame 176 0 210 0 236 0 240 0)
                    #'label:' 'align'
                    #'model:' #showAlignmentOrigin
                )

              )
          )
      )



!

specificationLayoutOrigin
    "
    UIPainter new openOnClass:self andSelector:#specificationLayoutOrigin
    "
    <resource: #canvas>

    ^

       #(#FullSpec
          #'window:' 
           #(#WindowSpec
              #'layout:' #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
              #'label:' 'unnamed'
              #'bounds:' #(#Rectangle 0 0 248 304)
          )
          #'component:' 
           #(#SpecCollection
              #'collection:' 
               #(
                 #(#LabelSpec
                    #'name:' 'label1'
                    #'layout:' #(#LayoutFrame 16 0 42 0 44 0 60 0)
                    #'label:' 'left'
                )
                 #(#LabelSpec
                    #'name:' 'label2'
                    #'layout:' #(#LayoutFrame 16 0 69 0 44 0 87 0)
                    #'label:' 'top'
                )
                 #(#LabelSpec
                    #'name:' 'label3'
                    #'layout:' #(#LayoutFrame 57 0 10 0 103 0 27 0)
                    #'label:' 'relative'
                )
                 #(#LabelSpec
                    #'name:' 'label4'
                    #'layout:' #(#LayoutFrame 154 0 11 0 190 0 28 0)
                    #'label:' 'offset'
                )
                 #(#InputFieldSpec
                    #'name:' 'editField1'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 57 0 42 0 114 0 60 0)
                    #'model:' #leftFraction
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField2'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 57 0 69 0 114 0 87 0)
                    #'model:' #topFraction
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField3'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 154 0 42 0 212 0 60 0)
                    #'model:' #leftOffset
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#InputFieldSpec
                    #'name:' 'editField4'
                    #'type:' #numberOrNil
                    #'layout:' #(#LayoutFrame 154 0 69 0 212 0 87 0)
                    #'model:' #topOffset
                    #'immediateAccept:' false
                    #'acceptOnReturn:' true
                    #'acceptOnTab:' true
                    #tabable: true
                )
                 #(#ActionButtonSpec
                    #'name:' 'button1'
                    #'layout:' #(#LayoutFrame 119 0 42 0 138 0 60 0)
                    #'label:' ''
                    #'model:' #makeRelativeLeft
                )
                 #(#ActionButtonSpec
                    #'name:' 'button2'
                    #'layout:' #(#LayoutFrame 119 0 69 0 138 0 87 0)
                    #'label:' ''
                    #'model:' #makeRelativeTop
                )
                 #(#ActionButtonSpec
                    #'name:' 'button3'
                    #'layout:' #(#LayoutFrame 216 0 42 0 235 0 60 0)
                    #'label:' ''
                    #'model:' #makeOffsetLeft
                )
                 #(#ActionButtonSpec
                    #'name:' 'button4'
                    #'layout:' #(#LayoutFrame 216 0 69 0 235 0 87 0)
                    #'label:' ''
                    #'model:' #makeOffsetTop
                )


               #(#ActionButtonSpec
                  #'name:' 'button'
                  #'layout:' #(#LayoutFrame 16 0 210 0 76 0 240 0)
                  #'label:' 'frame'
                  #'model:' #showLayoutFrame
                )
               #(#ActionButtonSpec
                  #'name:' 'button'
                  #'layout:' #(#LayoutFrame 96 0 210 0 156 0 240 0)
                  #'label:' 'origin'
                  #'model:' #showLayoutOrigin
                  #'initiallyDisabled:' true
                )
               #(#ActionButtonSpec
                  #'name:' 'button'
                  #'layout:' #(#LayoutFrame 176 0 210 0 236 0 240 0)
                  #'label:' 'align'
                  #'model:' #showAlignmentOrigin
                )

              )
          )
      )



! !

!UIPropertyView methodsFor:'accessing'!

update:something
    |slices list view prevSpecClass|

    (something == #selection or:[something == #tree]) ifFalse:[
        (something == #layout and:[modified not and:[self isLayoutSpec]]) ifTrue:[
            self layoutRead.
        ].
        ^ self
    ].

    view := builderView singleSelection.

    propertyAspects := nil.
    currentView     := view.
    self modified:false.


    currentView isNil ifTrue:[
        "/ the workView itself.

        propertyList selectionIndex:nil.
        currentSpecChannel := nil.

        propertyList list:#().
        propertySpecs := nil.

        "/ must setup for a WindowSpec (to allow entry of min- maxSize etc).
"/        propertyList list:#('Basics' 'Detail').
        ^ self
    ].

    prevSpecClass := specBeingEdited class.

    specBeingEdited := (builderView generateSpecFor:currentView) first.

    (specBeingEdited class ~~ prevSpecClass 
    or:[currentSpecChannel isNil]) ifTrue:[
        propertyList selectionIndex:nil.
        propertyAspects := IdentityDictionary new.
        propertySpecs := OrderedCollection new.
        slices        := currentView specClass slices.

        list := slices collect:[:slice|
            propertySpecs add:(slice last).
            slice first asString
        ].

        list := list, (Array with:(self class titleOfLayoutMenu)).

        currentSpecChannel := specBeingEdited asValue.
        specBeingEdited class addBindingsTo:propertyAspects
                                 for:specBeingEdited
                             channel:currentSpecChannel.
        propertyAspects do:[:anAspect | anAspect addDependent:self ].
        propertyList list:list.
        propertyList selection:userSelectedProperty.
    ] ifFalse:[
        currentSpecChannel value:specBeingEdited
    ]


! !

!UIPropertyView methodsFor:'change & update'!

modified:aState
     "change state of modification flag
     "
     aState ~~ modified ifTrue:[
        (modified := aState) ifTrue:[
            (builder componentAt:#cancelButton) enable.
            (builder componentAt:#applyButton) enable.
        ] ifFalse:[
            (builder componentAt:#cancelButton) disable.
            (builder componentAt:#applyButton) disable.
        ].
    ]
!

propertySelectionChanged
    "called when the property selection changed
    "
    |spec index sel|

    sel := propertyList selection.

    (currentView isNil or:[sel isNil]) ifTrue:[
        "/ must setup for a WindowSpec for workView (to allow entry of min- maxSize etc).
"/        currentView isNil ifTrue:[
"/            currentView := receiver
"/        ].
        ^ self showSpec:nil
    ].
    index := propertyList selectionIndex.
    userSelectedProperty := sel.

    index > propertySpecs size ifTrue:[                 "/ one of my specifications
        (sel == self class titleOfLayoutMenu) ifTrue:[
            spec := self specificationLayout
        ]
    ] ifFalse:[
        spec := currentView specClass perform:(propertySpecs at:index).
    ].
    self showSpec:spec.
!

update:something with:aParameter from:changedObject
    self modified:true
! !

!UIPropertyView methodsFor:'initialization'!

in:aTopView receiver:aBuilderView
    |menu y cancelButton applyButton panel|

    super initialize.
    self initializeStaticAspects.

    builderView := aBuilderView.

    menu := PopUpList label:'properties' in:aTopView.
    menu defaultLabel:'properties'.
    propertyFrame := View in:aTopView.
    panel := HorizontalPanelView in:aTopView.

    cancelButton := Button abortButtonIn:panel.
    applyButton  := Button okButtonIn:panel.

    propertyList := SelectionInList new.
    propertyList list:#( ).
    propertyList selectionIndexHolder onChangeSend:#propertySelectionChanged
                                                to:self.
    menu model:propertyList.

    y := menu preferredExtent y.
    menu  origin:0.0@0.0 corner:1.0@y.
    propertyFrame origin:0.0@y   corner:1.0@1.0.
    panel origin:0.0@1.0 corner:1.0@1.0.

    y := panel preferredExtent y.
    propertyFrame bottomInset:y.
    panel topInset:(y negated).

    builder componentAt:#cancelButton put:cancelButton.
    builder componentAt:#applyButton  put:applyButton.

    cancelButton action:[ self cancel ].
    applyButton  action:[ self apply ].

    modified := true.
    self modified:false.
!

initializeStaticAspects

    staticAspects := IdentityDictionary new.

    #(  bottomFraction          bottomOffset
        leftFraction            leftOffset
        topFraction             topOffset
        rightFraction           rightOffset
        leftAlignmentFraction   topAlignmentFraction
    )
    do:[:aChannel|
        staticAspects at:aChannel put:(ValueHolder new).
    ].

    staticAspects do:[:anAspect | anAspect addDependent:self ].

! !

!UIPropertyView methodsFor:'private'!

aspectFor:aKey
    |aspect|

    propertyAspects notNil ifTrue:[
        aspect := propertyAspects at:aKey ifAbsent:nil.
        aspect notNil ifTrue:[
            ^ aspect
        ]
    ].

    ^ staticAspects at:aKey ifAbsent:[super aspectFor:aKey]
!

showSpec:aSpec
    "switch specification
    "
    currentSpec ~= aSpec ifTrue:[
        propertyFrame destroySubViews.

        aSpec notNil ifTrue:[
            builder buildFromSpec:aSpec in:propertyFrame.
            propertyFrame realizeAllSubViews
        ]
    ].
    currentSpec := aSpec.
    self modified:false.
! !

!UIPropertyView methodsFor:'private actions'!

apply
    modified ifTrue:[
        self modified:false.

        self isLayoutSpec ifFalse:[
            builderView updateFromSpec:specBeingEdited
        ] ifTrue:[
            self layoutWrite
        ]
    ]

!

cancel
    |view|

    modified ifTrue:[
        self modified:false.

        self isLayoutSpec ifFalse:[
            currentView := nil.
            self update:#selection
        ] ifTrue:[
            self layoutRead
        ]
    ]


! !

!UIPropertyView methodsFor:'private layout'!

layoutRead
    |layout extent|

    layout := currentView geometryLayout.
    layout isNil ifTrue:[^ self].
    modified := true.                   "supress event notifications"

    layout isLayout ifFalse:[
        (layout isRectangle or:[layout isPoint]) ifTrue:[
            (staticAspects at:#leftOffset)   value:(layout left).
            (staticAspects at:#rightOffset)  value:(layout right).

            layout isRectangle ifTrue:[
                (staticAspects at:#topOffset)    value:(layout top).
                (staticAspects at:#bottomOffset) value:(layout bottom).
            ].
            modified := false.
          ^ self
        ]
    ].

    (staticAspects at:#leftOffset)   value:(layout leftOffset).
    (staticAspects at:#leftFraction) value:(layout leftFraction).
    (staticAspects at:#topOffset)    value:(layout topOffset).
    (staticAspects at:#topFraction)  value:(layout topFraction).

    layout isLayoutFrame ifTrue:[
        (staticAspects at:#rightOffset)    value:(layout rightOffset).
        (staticAspects at:#bottomOffset)   value:(layout bottomOffset).

        (staticAspects at:#rightFraction)  value:(layout rightFraction).
        (staticAspects at:#bottomFraction) value:(layout bottomFraction).

        (staticAspects at:#leftAlignmentFraction) value:0.
        (staticAspects at:#topAlignmentFraction)  value:0.
    ] ifFalse:[
        extent := currentView extent.

        (staticAspects at:#rightOffset)    value:(layout leftOffset + extent x).
        (staticAspects at:#bottomOffset)   value:(layout topOffset  + extent y).

        (staticAspects at:#rightFraction)  value:0.
        (staticAspects at:#bottomFraction) value:0.

        layout isAlignmentOrigin ifTrue:[
            (staticAspects at:#leftAlignmentFraction) value:(layout leftAlignmentFraction).
            (staticAspects at:#topAlignmentFraction)  value:(layout topAlignmentFraction).
        ] ifFalse:[
            (staticAspects at:#leftAlignmentFraction) value:0.
            (staticAspects at:#topAlignmentFraction)  value:0.
        ]
    ].
    modified := false.

!

layoutWrite
    |layout|

    currentView isNil ifTrue:[
        ^ self
    ].

    (currentSpec == self class specificationLayoutFrame) ifTrue:[
        layout := LayoutFrame new.

        layout     leftOffset:((staticAspects at:#leftOffset)     value) ? 0.
        layout    rightOffset:((staticAspects at:#rightOffset)    value) ? 0.
        layout      topOffset:((staticAspects at:#topOffset)      value) ? 0.
        layout   bottomOffset:((staticAspects at:#bottomOffset)   value) ? 0.
        layout   leftFraction:((staticAspects at:#leftFraction)   value) ? 0.
        layout  rightFraction:((staticAspects at:#rightFraction)  value) ? 0.
        layout    topFraction:((staticAspects at:#topFraction)    value) ? 0.
        layout bottomFraction:((staticAspects at:#bottomFraction) value) ? 0.

        builderView setDimension:layout
    ].

    (currentSpec == self class specificationAlignmentOrigin) ifTrue:[
        layout := AlignmentOrigin new.

        layout   leftOffset:((staticAspects at:#leftOffset)   value) ? 0.
        layout    topOffset:((staticAspects at:#topOffset)    value) ? 0.
        layout leftFraction:((staticAspects at:#leftFraction) value) ? 0.
        layout  topFraction:((staticAspects at:#topFraction)  value) ? 0.

        layout leftAlignmentFraction:((staticAspects at:#leftAlignmentFraction) value) ? 0.
        layout  topAlignmentFraction:((staticAspects at:#topAlignmentFraction)  value) ? 0.

        ^ builderView setDimension:layout.
    ].

    (currentSpec == self class specificationLayoutOrigin) ifTrue:[
        layout := LayoutOrigin new.

        layout   leftOffset:((staticAspects at:#leftOffset)   value) ? 0.
        layout    topOffset:((staticAspects at:#topOffset)    value) ? 0.
        layout leftFraction:((staticAspects at:#leftFraction) value) ? 0.
        layout  topFraction:((staticAspects at:#topFraction)  value) ? 0.

        builderView setDimension:layout.
    ].

!

showAlignmentOrigin
    self switchLayoutSpec:(self class specificationAlignmentOrigin)
!

showLayoutFrame
    self switchLayoutSpec:(self class specificationLayoutFrame)
!

showLayoutOrigin
    self switchLayoutSpec:(self class specificationLayoutOrigin)
!

specificationLayout
    "called from propertyChanged; returns specification assigned to
     current view
    "
    |layout spec|

    (currentView superView specClass basicNew isLayoutContainer) ifTrue:[
        ^ nil
    ].
    layout := currentView geometryLayout.

    layout isLayout ifTrue:[
        layout isLayoutFrame ifTrue:[
            spec := self class specificationLayoutFrame
        ] ifFalse:[
            layout isAlignmentOrigin ifTrue:[
                spec := self class specificationAlignmentOrigin
            ] ifFalse:[
                layout isLayoutOrigin ifTrue:[
                    spec := self class specificationLayoutOrigin
                ]
            ]
        ]
    ].

    spec notNil ifTrue:[
        self layoutRead
    ].
  ^ spec
!

switchLayoutSpec:aSpecification
    self layoutRead.
    self showSpec:aSpecification.
    self modified:true.

! !

!UIPropertyView methodsFor:'private make layout'!

makeLayout:what xOrY:xOrY offset:aBool
    |layout extent fraction offset fractSymb offsetSymb|

    currentView isNil ifTrue:[
        ^ self
    ].
    layout := currentView geometryLayout.

    layout isLayout ifFalse:[
        ^ self
    ].
    fractSymb  := (what, 'Fraction') asSymbol.
    offsetSymb := (what,   'Offset') asSymbol.

    (    (layout respondsTo:fractSymb)
     and:[layout respondsTo:offsetSymb]
    ) ifTrue:[

        fraction := layout perform:fractSymb.
        offset   := layout perform:offsetSymb.
        extent   := (currentView superView computeExtent) perform:xOrY.

        aBool ifTrue:[
            offset := offset + ((fraction * extent) asInteger).
            (staticAspects at:offsetSymb) value:offset.
            (staticAspects at:fractSymb)  value:0.
        ] ifFalse:[
            fraction   := (fraction + (offset / extent)) asFloat.

            (fraction > 1.0) ifTrue:[ fraction := 1.0 ].
            (fraction < 0.0) ifTrue:[ fraction := 0.0 ].

            (staticAspects at:offsetSymb) value:0.
            (staticAspects at:fractSymb)  value:fraction.
        ]
    ]


!

makeOffsetAll
    self makeOffsetLeft.
    self makeOffsetTop.
    self makeOffsetRight.
    self makeOffsetBottom.

!

makeOffsetBottom
    self makeLayout:'bottom' xOrY:#y offset:true.

!

makeOffsetLeft
    self makeLayout:'left' xOrY:#x offset:true.

!

makeOffsetRight
    self makeLayout:'right' xOrY:#x offset:true.

!

makeOffsetTop
    self makeLayout:'top' xOrY:#y offset:true.

!

makeRelativeAll
    self makeRelativeLeft.
    self makeRelativeTop.
    self makeRelativeRight.
    self makeRelativeBottom.

!

makeRelativeBottom
    self makeLayout:'bottom' xOrY:#y offset:false.

!

makeRelativeLeft
    self makeLayout:'left' xOrY:#x offset:false.

!

makeRelativeRight
    self makeLayout:'right' xOrY:#x offset:false.

!

makeRelativeTop
    self makeLayout:'top' xOrY:#y offset:false.

! !

!UIPropertyView methodsFor:'queries'!

isLayoutSpec
    "returns true if current menu is layout
    "
    ^ propertyList selection == self class titleOfLayoutMenu
! !

!UIPropertyView class methodsFor:'documentation'!

version
    ^ '$Header$'
! !