UILayoutTool.st
author Claus Gittinger <cg@exept.de>
Fri, 22 May 1998 11:57:38 +0200
changeset 847 15f688710007
parent 751 b182b42defd0
child 922 0a5799408f54
permissions -rw-r--r--
checkin from browser

"
 COPYRIGHT (c) 1995 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.
"




ApplicationModel subclass:#UILayoutTool
	instanceVariableNames:'modifiedHolder aspects selection layoutView tabList'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

ApplicationModel subclass:#AlignmentOrigin
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UILayoutTool
!

ApplicationModel subclass:#Extent
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UILayoutTool
!

ApplicationModel subclass:#LayoutFrame
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UILayoutTool
!

ApplicationModel subclass:#LayoutOrigin
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UILayoutTool
!

ApplicationModel subclass:#Point
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UILayoutTool
!

ApplicationModel subclass:#Rectangle
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	privateIn:UILayoutTool
!

!UILayoutTool class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 1995 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
"
    used by the UIPainter to manipulate the layout of the selected component

    [author:]
        Claus Atzkern

    [see also:]
        UIPainter
        UIHelpTool
        UISpecificationTool
"


! !

!UILayoutTool class methodsFor:'constants'!

label
    ^ 'Layout'
! !

!UILayoutTool class methodsFor:'help specs'!

helpSpec
    "This resource specification was automatically generated
     by the UIHelpTool of ST/X."

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

    "
     UIHelpTool openOnClass:UILayoutTool    
    "

    <resource: #help>

    ^super helpSpec addPairsFrom:#(

#cornerX
'Absolute corner x of the selected widget.'

#cornerY
'Absolute corner y of the selected widget.'

#layoutTool
'Tool to set the layout of the selected widget.'

#leftAbsolute
'Offset of the left edge; positive is to the right, negative to the left.'

#leftRelative
'Relative origin x of the selected widget.'

#makeLeftAbsolute
'Computes current left offset and relative origin x to an absolute origin x.'

#makeLeftRelative
'Compute current relative origin x and offset of the left edge to a relative origin x.'

#makeTopAbsolute
'Computes current top offset and relative origin y to an absolute origin y.'

#makeTopRelative
'Computes current relative origin y and offset of the top edge to a relative origin y.'

#originX
'Absolute origin x of the selected widget.'

#originY
'Absolute origin y of the selected widget.'

#topAbsolute
'Offset of the top edge; positive is to the bottom, negative to the top.'

#topRelative
'Relative origin y of the selected widget.'

)
! !

!UILayoutTool class methodsFor:'interface specs'!

layoutOriginSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool andSelector:#layoutOriginSpec
     UILayoutTool new openInterface:#layoutOriginSpec
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool'
              #layout: #(#LayoutFrame 232 0 400 0 576 0 581 0)
              #label: 'UILayoutTool'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 232 400 577 582)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#FramedBoxSpec
                    #name: 'FramedBox'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 108 0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'labelRelative'
                              #layout: #(#Point 100 18)
                              #label: 'Relative:'
                          )
                           #(#LabelSpec
                              #name: 'labelAbsolute'
                              #layout: #(#Point 200 18)
                              #label: 'Offset:'
                          )
                           #(#LabelSpec
                              #name: 'labelLeft'
                              #layout: #(#AlignmentOrigin 98 0 39 0 1 0)
                              #label: 'Left:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldLeftFraction'
                              #layout: #(#LayoutFrame 100 0 36 0 150 0 58 0)
                              #activeHelpKey: #leftRelative
                              #tabable: true
                              #model: #leftFraction
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionRelativeLeft'
                              #layout: #(#LayoutFrame 155 0 36 0 177 0 58 0)
                              #activeHelpKey: #makeLeftRelative
                              #model: #relativeLeft
                          )
                           #(#InputFieldSpec
                              #name: 'fieldLeftOffset'
                              #layout: #(#LayoutFrame 200 0 36 0 250 0 58 0)
                              #activeHelpKey: #leftAbsolute
                              #tabable: true
                              #model: #leftOffset
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionAbsoluteLeft'
                              #layout: #(#LayoutFrame 255 0 36 0 277 0 58 0)
                              #activeHelpKey: #makeLeftAbsolute
                              #model: #absoluteLeft
                          )
                           #(#LabelSpec
                              #name: 'labelTop'
                              #layout: #(#AlignmentOrigin 98 0 66 0 1 0)
                              #label: 'Top:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldTopFraction'
                              #layout: #(#LayoutFrame 100 0 63 0 150 0 85 0)
                              #activeHelpKey: #topRelative
                              #tabable: true
                              #model: #topFraction
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionRelativeTop'
                              #layout: #(#LayoutFrame 155 0 63 0 177 0 85 0)
                              #activeHelpKey: #makeTopRelative
                              #model: #relativeTop
                          )
                           #(#InputFieldSpec
                              #name: 'fieldTopOffset'
                              #layout: #(#LayoutFrame 200 0 63 0 250 0 85 0)
                              #activeHelpKey: #topAbsolute
                              #tabable: true
                              #model: #topOffset
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionAbsoluteTop'
                              #layout: #(#LayoutFrame 255 0 63 0 277 0 85 0)
                              #activeHelpKey: #makeTopAbsolute
                              #model: #absoluteTop
                          )
                        )
                    )
                    #label: 'Origin'
                    #labelPosition: #topLeft
                )
              )
          )
      )
!

layoutPointSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool andSelector:#layoutPointSpec
     UILayoutTool new openInterface:#layoutPointSpec
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool'
              #layout: #(#LayoutFrame 84 0 479 0 361 0 602 0)
              #label: 'UILayoutTool'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 84 479 362 603)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#FramedBoxSpec
                    #name: 'FramedBox'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 94 0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'labelOriginY'
                              #layout: #(#AlignmentOrigin 98 0 28 0 1 0)
                              #label: 'Left:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldOriginX'
                              #layout: #(#LayoutFrame 100 0 25 0 150 0 47 0)
                              #activeHelpKey: #originX
                              #tabable: true
                              #model: #leftOffset
                              #type: #numberOrNil
                          )
                           #(#LabelSpec
                              #name: 'labelOriginX'
                              #layout: #(#AlignmentOrigin 98 0 53 0 1 0)
                              #label: 'Top:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldOriginY'
                              #layout: #(#LayoutFrame 100 0 50 0 150 0 72 0)
                              #activeHelpKey: #originY
                              #tabable: true
                              #model: #topOffset
                              #type: #numberOrNil
                          )
                        )
                    )
                    #label: 'Origin'
                    #labelPosition: #topLeft
                )
              )
          )
      )
!

slices
    ^ #(
        ( 'Frame'          LayoutFrame)
        ( 'Origin'         LayoutOrigin)
        ( 'Alig.Origin'    AlignmentOrigin)
        ( 'Point'          Point)
        ( 'Rectangle'      Rectangle)
        ( 'Extent'         Extent)
       ) 

!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool andSelector:#windowSpec
     UILayoutTool new openInterface:#windowSpec
     UILayoutTool open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool'
              #layout: #(#LayoutFrame 571 0 290 0 870 0 589 0)
              #label: 'UILayoutTool'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 571 290 871 590)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#NoteBookViewSpec
                    #name: 'NoteBook'
                    #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 0 1.0)
                    #activeHelpKey: #layoutTool
                    #enableChannel: #enableChannel
                    #tabable: true
                    #model: #noteBookModel
                    #menu: #noteBookList
                    #style: #(#FontDescription #helvetica #medium #roman #'10')
                    #direction: #bottom
                    #canvas: #noteBookView
                )
              )
          )
      )
! !

!UILayoutTool methodsFor:'accessing'!

layout
    "returns configued layout or nil
    "
    |appl|

    (appl := self noteBookView application) notNil ifTrue:[
        ^ appl layout
    ].
  ^ nil
!

layoutType
    "returns current layout type or nil
    "
    |slice|

    (slice := self selectedSlice) notNil ifTrue:[
        ^ slice last
    ].
  ^ nil
!

layoutView
    "returns current edited view
    "
    ^ layoutView
!

layoutView:aView
    "change current edited view
    "
    self layoutView:aView type:nil
!

layoutView:aView type:aTypeOrNil
    "change current edited view
    "
    |type name list|

    layoutView := aView.

    aTypeOrNil notNil ifTrue:[
        self class slices findFirst:[:e|
            e last == aTypeOrNil ifTrue:[name := e first. true]
        ].
        list := Array with:name
    ] ifFalse:[
        (type := UIPainterView layoutType:layoutView) notNil ifTrue:[
            self class slices findFirst:[:e|
                e last == type ifTrue:[name := e first. true]
            ].
            list := tabList.

            type == #Extent ifTrue:[
                aView superView specClass isLayoutContainer ifTrue:[
                    list := Array with:name
                ] ifFalse:[
                    list := list copyWith:name
                ]
            ]
        ]
    ].
    self noteBookList  value:list.
    self noteBookModel value:name.
    self update.
!

modifiedHolder:aValueHolder
    "set the value holder set to true in case of modifying attributes
    "
    modifiedHolder notNil ifTrue:[
        modifiedHolder removeDependent:self. 
    ].

    (modifiedHolder := aValueHolder) notNil ifTrue:[
        modifiedHolder addDependent:self.
    ].

!

update
    "update from view
    "
    |view appl|

    selection notNil ifTrue:[
        (view := self layoutView) notNil ifTrue:[
            (appl := self noteBookView application) notNil ifTrue:[
                appl fetch:view
            ]
        ]
    ].
        
! !

!UILayoutTool methodsFor:'aspects'!

aspectFor:aKey
    "returns aspect for a key or nil
    "
  ^ aspects at:aKey ifAbsent:[ super aspectFor:aKey ]


!

noteBookList
    "returns list of tab labels
    "
    |holder|

    (holder := builder bindingAt:#noteBookList) isNil ifTrue:[
        holder := nil asValue.
        builder aspectAt:#noteBookList put:holder
    ].
  ^ holder
!

noteBookModel
    "automatically generated by UIPainter ..."

    |holder|

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

noteBookView
    "automatically generated by UIPainter ...
    "
    |holder|

    (holder := builder bindingAt:#noteBookView) isNil ifTrue:[
        holder := SubCanvas new.
        builder aspectAt:#noteBookView put:holder
    ].
  ^ holder
! !

!UILayoutTool methodsFor:'change & update'!

update:something with:aParameter from:changedObject
    "one of my models changed its value
    "
    changedObject ~~ modifiedHolder ifTrue:[
        modifiedHolder value ~~ true ifTrue:[
            modifiedHolder isNil ifFalse:[
                modifiedHolder value:true
            ]
        ]
    ]

! !

!UILayoutTool methodsFor:'converting absolute'!

absolute:what xOrY:xOrY
    |extent fraction offset fractSymb offsetSymb|

    extent     := (self layoutView superView computeExtent) perform:xOrY.
    fractSymb  := (what, 'Fraction') asSymbol.
    offsetSymb := (what,   'Offset') asSymbol.
    fraction   := (self aspectFor:fractSymb)  value.
    offset     := (self aspectFor:offsetSymb) value.
    offset     := offset + ((fraction * extent) asInteger).

    (self aspectFor:offsetSymb) value:offset.
    (self aspectFor:fractSymb)  value:0.



!

absoluteBottom
    self absolute:'bottom' xOrY:#y

!

absoluteLeft
    self absolute:'left' xOrY:#x

!

absoluteRight
    self absolute:'right' xOrY:#x

!

absoluteTop
    self absolute:'top' xOrY:#y

! !

!UILayoutTool methodsFor:'converting relative'!

relative:what xOrY:xOrY
    |extent fraction offset fractSymb offsetSymb|

    extent     := (self layoutView superView computeExtent) perform:xOrY.
    fractSymb  := (what, 'Fraction') asSymbol.
    offsetSymb := (what,   'Offset') asSymbol.
    fraction   := (self aspectFor:fractSymb)  value.
    offset     := (self aspectFor:offsetSymb) value.
    fraction   := (fraction + (offset / extent)) asFloat.

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

    (self aspectFor:offsetSymb) value:0.
    (self aspectFor:fractSymb)  value:fraction.



!

relativeBottom
    self relative:'bottom' xOrY:#y


!

relativeLeft
    self relative:'left' xOrY:#x

!

relativeRight
    self relative:'right' xOrY:#x

!

relativeTop
    self relative:'top' xOrY:#y

! !

!UILayoutTool methodsFor:'initialization'!

initialize
    "initialize channels
    "
    |slices size|

    super initialize.

    aspects  := IdentityDictionary new.

    #(  bottomFraction          bottomOffset
        leftFraction            leftOffset
        topFraction             topOffset
        rightFraction           rightOffset
        leftAlignmentFraction   topAlignmentFraction
    )

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

    slices  := self class slices.
    size    := slices size - 1.
    tabList := Array new:size.

    1 to:size do:[:i| tabList at:i put:((slices at:i) first) ].


! !

!UILayoutTool methodsFor:'selection'!

selectedSlice
    "returns slice assigned to selection or nil
    "
    selection notNil ifTrue:[
        self class slices do:[:aSlice|
            aSlice first = selection ifTrue:[
                ^ aSlice
            ]
        ]
    ].
    ^ nil

!

selection
    ^ selection
!

selection:aSelection
    |appl slice sel noteBook|

    aSelection isNumber ifTrue:[
        aSelection ~~ 0 ifTrue:[sel := tabList at:aSelection]
    ] ifFalse:[
        sel := aSelection
    ].
    selection = sel ifFalse:[
        (selection := sel) notNil ifTrue:[
            slice := self selectedSlice.
            appl  := slice last asString.
            appl := Smalltalk classNamed:(self class name asString, '::', appl).
            appl := appl new.
            appl masterApplication:self.
            modifiedHolder value:true.
        ].
        noteBook := self noteBookView.
        noteBook client:appl.

        appl notNil ifTrue:[
            noteBook scrolledView allViewBackground:(noteBook viewBackground).
            masterApplication updateFonts
        ]
    ].
    self update

! !

!UILayoutTool::AlignmentOrigin class methodsFor:'help specs'!

helpSpec
    "This resource specification was automatically generated
     by the UIHelpTool of ST/X."

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

    "
     UIHelpTool openOnClass:UILayoutTool::AlignmentOrigin    
    "

    <resource: #help>

    ^super helpSpec addPairsFrom:#(

#alignBottomCenter
'Aligns the selected widget bottomCenter to location.'

#alignBottomLeft
'Aligns the selected widget bottomLeft to location.'

#alignBottomRight
'Aligns the selected widget bottomRight to location.'

#alignCenter
'Aligns the selected widget center to location.'

#alignHorizontal
'Horizontal inset to the location point of the selected widget.'

#alignLeftCenter
'Aligns the selected widget leftCenter to location.'

#alignRightCenter
'Aligns the selected widget rightCenter to location.'

#alignTopCenter
'Aligns the selected widget topCenter to location.'

#alignTopLeft
'Aligns the selected widget topLeft to location.'

#alignTopRight
'Aligns the selected widget topRight to location.'

#alignVertical
'Vertical inset to the location point of the widget.'

)
! !

!UILayoutTool::AlignmentOrigin class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool::AlignmentOrigin andSelector:#windowSpec
     UILayoutTool::AlignmentOrigin new openInterface:#windowSpec
     UILayoutTool::AlignmentOrigin open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool-AlignmentOrigin'
              #layout: #(#LayoutFrame 363 0 402 0 767 0 608 0)
              #label: 'UILayoutTool-AlignmentOrigin'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 363 402 768 609)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#UISubSpecification
                    #name: 'layoutOriginSpec'
                    #layout: #(#LayoutFrame 1 0.0 6 0 0 1.0 111 0)
                    #majorKey: #UILayoutTool
                    #minorKey: #layoutOriginSpec
                )
                 #(#FramedBoxSpec
                    #name: 'FramedBox'
                    #layout: #(#LayoutFrame 1 0.0 113 0 0 1.0 208 0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'alignHLabel'
                              #layout: #(#AlignmentOrigin 98 0 28 0 1 0)
                              #label: 'Horizontal:'
                              #adjust: #right
                          )
                           #(#LabelSpec
                              #name: 'alignVLabel'
                              #layout: #(#AlignmentOrigin 98 0 54 0 1 0)
                              #label: 'Vertical:'
                              #adjust: #right
                          )
                           #(#InputFieldSpec
                              #name: 'leftAlignmentFractionField'
                              #layout: #(#LayoutFrame 100 0 25 0 157 0 47 0)
                              #activeHelpKey: #alignHorizontal
                              #tabable: true
                              #model: #leftAlignmentFraction
                              #type: #numberOrNil
                          )
                           #(#InputFieldSpec
                              #name: 'topAlignmentFractionField'
                              #layout: #(#LayoutFrame 100 0 51 0 157 0 73 0)
                              #activeHelpKey: #alignVertical
                              #tabable: true
                              #model: #topAlignmentFraction
                              #type: #numberOrNil
                          )
                           #(#DividerSpec
                              #name: 'separator1'
                              #layout: #(#LayoutFrame 214 0 30 0 255 0 33 0)
                          )
                           #(#DividerSpec
                              #name: 'separator2'
                              #layout: #(#LayoutFrame 214 0 66 0 255 0 69 0)
                          )
                           #(#DividerSpec
                              #name: 'separator3'
                              #layout: #(#LayoutFrame 206 0 39 0 209 0 61 0)
                              #orientation: #vertical
                          )
                           #(#DividerSpec
                              #name: 'separator4'
                              #layout: #(#LayoutFrame 260 0 39 0 263 0 61 0)
                              #orientation: #vertical
                          )
                           #(#ActionButtonSpec
                              #name: 'alignBottomRight'
                              #layout: #(#LayoutFrame 255 0 61 0 269 0 75 0)
                              #activeHelpKey: #alignBottomRight
                              #model: #alignBottomRight
                          )
                           #(#ActionButtonSpec
                              #name: 'alignTopLeft'
                              #layout: #(#LayoutFrame 200 0 25 0 214 0 39 0)
                              #activeHelpKey: #alignTopLeft
                              #model: #alignTopLeft
                          )
                           #(#ActionButtonSpec
                              #name: 'alignTopRight'
                              #layout: #(#LayoutFrame 255 0 25 0 269 0 39 0)
                              #activeHelpKey: #alignTopRight
                              #model: #alignTopRight
                          )
                           #(#ActionButtonSpec
                              #name: 'alignBottomLeft'
                              #layout: #(#LayoutFrame 200 0 61 0 214 0 75 0)
                              #activeHelpKey: #alignBottomLeft
                              #model: #alignBottomLeft
                          )
                           #(#ActionButtonSpec
                              #name: 'alignTopCenter'
                              #layout: #(#LayoutFrame 227 0 25 0 241 0 39 0)
                              #activeHelpKey: #alignTopCenter
                              #model: #alignTopCenter
                          )
                           #(#ActionButtonSpec
                              #name: 'alignBottomCenter'
                              #layout: #(#LayoutFrame 227 0 61 0 241 0 75 0)
                              #activeHelpKey: #alignBottomCenter
                              #model: #alignBottomCenter
                          )
                           #(#ActionButtonSpec
                              #name: 'alignLeftCenter'
                              #layout: #(#LayoutFrame 200 0 43 0 214 0 57 0)
                              #activeHelpKey: #alignLeftCenter
                              #model: #alignLeftCenter
                          )
                           #(#ActionButtonSpec
                              #name: 'alignRightCenter'
                              #layout: #(#LayoutFrame 255 0 43 0 269 0 57 0)
                              #activeHelpKey: #alignRightCenter
                              #model: #alignRightCenter
                          )
                           #(#ActionButtonSpec
                              #name: 'alignCenter'
                              #layout: #(#LayoutFrame 227 0 43 0 241 0 57 0)
                              #activeHelpKey: #alignCenter
                              #model: #alignCenter
                          )
                        )
                    )
                    #label: 'Alignment'
                    #labelPosition: #topLeft
                )
              )
          )
      )
! !

!UILayoutTool::AlignmentOrigin methodsFor:'accessing'!

fetch:aView
    "fetch alignmentOrigin
    "
    |layout type|

    type   := UIPainterView layoutType:aView.
    layout := aView geometryLayout.

    layout isLayout ifTrue:[
        (self aspectFor:#leftOffset)   value:(layout leftOffset).
        (self aspectFor:#leftFraction) value:(layout leftFraction).
        (self aspectFor:#topOffset)    value:(layout topOffset).
        (self aspectFor:#topFraction)  value:(layout topFraction).

        type == #AlignmentOrigin ifTrue:[
            (self aspectFor:#leftAlignmentFraction) value:(layout leftAlignmentFraction).
            (self aspectFor:#topAlignmentFraction)  value:(layout topAlignmentFraction).
          ^ self
        ]
    ] ifFalse:[
        layout := aView computeOrigin.

        (self aspectFor:#leftOffset)   value:(layout x).
        (self aspectFor:#leftFraction) value:0.
        (self aspectFor:#topOffset)    value:(layout y).
        (self aspectFor:#topFraction)  value:0.
    ].
    (self aspectFor:#leftAlignmentFraction) value:0.
    (self aspectFor:#topAlignmentFraction)  value:0.


!

layout
    "returns current layout as alignmentOrigin
    "
    |layout|

    layout  := Smalltalk::AlignmentOrigin new.

    layout   leftOffset:((self aspectFor:#leftOffset)   value) ? 0.
    layout    topOffset:((self aspectFor:#topOffset)    value) ? 0.
    layout leftFraction:((self aspectFor:#leftFraction) value) ? 0.
    layout  topFraction:((self aspectFor:#topFraction)  value) ? 0.

    layout leftAlignmentFraction:((self aspectFor:#leftAlignmentFraction) value) ? 0.
    layout  topAlignmentFraction:((self aspectFor:#topAlignmentFraction)  value) ? 0.

  ^ layout
! !

!UILayoutTool::AlignmentOrigin methodsFor:'alignment'!

alignBottomCenter
    self makeAlignLeft:0.5 top:1


!

alignBottomLeft
    self makeAlignLeft:0 top:1


!

alignBottomRight
    self makeAlignLeft:1 top:1


!

alignCenter
    self makeAlignLeft:0.5 top:0.5


!

alignLeftCenter
    self makeAlignLeft:0 top:0.5


!

alignRightCenter
    self makeAlignLeft:1 top:0.5


!

alignTopCenter
    self makeAlignLeft:0.5 top:0


!

alignTopLeft
    self makeAlignLeft:0 top:0


!

alignTopRight
    self makeAlignLeft:1 top:0


!

makeAlignLeft:leftAlignmentFraction top:topAlignmentFraction
    |lAF tAF lO tO ext|

    lAF     := (self aspectFor:#leftAlignmentFraction) value ? 0.
    tAF     := (self aspectFor:#topAlignmentFraction)  value ? 0.
    ext     := (self aspectFor:#layoutView) computeExtent.

    (self aspectFor:#leftAlignmentFraction) value:leftAlignmentFraction.
    (self aspectFor:#topAlignmentFraction)  value:topAlignmentFraction.

    lO := (self aspectFor:#leftOffset) value ? 0.
    tO := (self aspectFor:#topOffset)  value ? 0.

    lO := lO + (ext x * (leftAlignmentFraction - lAF)).
    tO := tO + (ext y * (topAlignmentFraction  - tAF)).

    (self aspectFor:#leftOffset) value:(lO rounded).
    (self aspectFor:#topOffset)  value:(tO rounded).

!

makeAlignTopRight
    self makeAlignLeft:1 top:0


! !

!UILayoutTool::Extent class methodsFor:'help specs'!

helpSpec
    "This resource specification was automatically generated
     by the UIHelpTool of ST/X."

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

    "
     UIHelpTool openOnClass:UILayoutTool::Extent    
    "

    <resource: #help>

    ^super helpSpec addPairsFrom:#(

#hrzExtent
'Horizontal extent of the selected widget.'

#vrtExtent
'Vertical extent of the selected widget.'

)
! !

!UILayoutTool::Extent class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool::Extent andSelector:#windowSpec
     UILayoutTool::Extent new openInterface:#windowSpec
     UILayoutTool::Extent open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool-Extent'
              #layout: #(#LayoutFrame 54 0 340 0 379 0 488 0)
              #label: 'UILayoutTool-Extent'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 54 340 380 489)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#FramedBoxSpec
                    #name: 'FramedBox'
                    #layout: #(#LayoutFrame 0 0.0 6 0.0 0 1.0 100 0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'labelWidth'
                              #layout: #(#AlignmentOrigin 99 0 36 0 1 0.5)
                              #label: 'Width:'
                              #adjust: #right
                          )
                           #(#InputFieldSpec
                              #name: 'fieldLeftOffset'
                              #layout: #(#LayoutFrame 100 0 25 0 150 0 47 0)
                              #activeHelpKey: #hrzExtent
                              #tabable: true
                              #model: #leftOffset
                              #type: #numberOrNil
                          )
                           #(#LabelSpec
                              #name: 'labelHeight'
                              #layout: #(#AlignmentOrigin 99 0 61 0 1 0.5)
                              #label: 'Height:'
                              #adjust: #right
                          )
                           #(#InputFieldSpec
                              #name: 'fieldRightOffset'
                              #layout: #(#LayoutFrame 100 0 50 0 150 0 72 0)
                              #activeHelpKey: #vrtExtent
                              #tabable: true
                              #model: #rightOffset
                              #type: #numberOrNil
                          )
                        )
                    )
                    #label: 'Extent'
                    #labelPosition: #topLeft
                )
              )
          )
      )
! !

!UILayoutTool::Extent methodsFor:'accessing'!

fetch:aView
    "fetch extent
    "
    |extent|

    extent  := aView computeExtent.

    (self aspectFor:#leftOffset)  value:(extent x).
    (self aspectFor:#rightOffset) value:(extent y).


!

layout
    "returns current extent
    "
  ^ Smalltalk::Point x:(((self aspectFor:#leftOffset)   value) ? 0)
                     y:(((self aspectFor:#rightOffset)  value) ? 0)

! !

!UILayoutTool::LayoutFrame class methodsFor:'help specs'!

helpSpec
    "This resource specification was automatically generated
     by the UIHelpTool of ST/X."

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

    "
     UIHelpTool openOnClass:UILayoutTool::LayoutFrame    
    "

    <resource: #help>

    ^super helpSpec addPairsFrom:#(

#bottomAbsolute
'Offset of the bottom edge; positive is to the bottom, negative to the top.'

#bottomRelative
'Relative corner y of the selected widget.'

#makeBottomAbsolute
'Computes current bottom offset and relative corner y to an absolute corner y.'

#makeBottomRelative
'Computes current relative corner y and offset of the bottom edge to a relative corner y.'

#makeRightAbsolute
'Computes current right offset and relative corner x to an absolute corner x.'

#makeRightRelative
'Computes current relative corner x and offset of the right edge to a relative corner x.'

#rightAbsolute
'Offset of the right edge; positive is to the right, negative to the left.'

#rightRelative
'Relative corner x of the selected widget.'

)
! !

!UILayoutTool::LayoutFrame class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool::LayoutFrame andSelector:#windowSpec
     UILayoutTool::LayoutFrame new openInterface:#windowSpec
     UILayoutTool::LayoutFrame open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool-LayoutFrame'
              #layout: #(#LayoutFrame 149 0 418 0 547 0 651 0)
              #label: 'UILayoutTool-LayoutFrame'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 149 418 548 652)
              #usePreferredExtent: false
              #forceRecursiveBackground: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#UISubSpecification
                    #name: 'layoutOriginSpec'
                    #layout: #(#LayoutFrame 1 0.0 6 0 0 1.0 110 0)
                    #majorKey: #UILayoutTool
                    #minorKey: #layoutOriginSpec
                )
                 #(#FramedBoxSpec
                    #name: 'FramedBox'
                    #layout: #(#LayoutFrame 1 0.0 113 0 0 1.0 214 0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'labelRight'
                              #layout: #(#AlignmentOrigin 98 0 36 0 1 0.5)
                              #label: 'Right:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldRightFraction'
                              #layout: #(#LayoutFrame 100 0 25 0 150 0 47 0)
                              #activeHelpKey: #rightRelative
                              #model: #rightFraction
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionRelativeRight'
                              #layout: #(#LayoutFrame 155 0 25 0 177 0 47 0)
                              #activeHelpKey: #makeRightRelative
                              #model: #relativeRight
                          )
                           #(#InputFieldSpec
                              #name: 'fieldRightOffset'
                              #layout: #(#LayoutFrame 200 0 25 0 250 0 47 0)
                              #activeHelpKey: #rightAbsolute
                              #model: #rightOffset
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionAbsoluteRight'
                              #layout: #(#LayoutFrame 255 0 25 0 277 0 47 0)
                              #activeHelpKey: #makeRightAbsolute
                              #model: #absoluteRight
                          )
                           #(#LabelSpec
                              #name: 'labelBottom'
                              #layout: #(#AlignmentOrigin 98 0 64 0 1 0.5)
                              #label: 'Bottom:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldBottomFraction'
                              #layout: #(#LayoutFrame 100 0 53 0 150 0 75 0)
                              #activeHelpKey: #bottomRelative
                              #model: #bottomFraction
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionRelativeBottom'
                              #layout: #(#LayoutFrame 155 0 53 0 177 0 75 0)
                              #activeHelpKey: #makeBottomRelative
                              #model: #relativeBottom
                          )
                           #(#InputFieldSpec
                              #name: 'fieldBottomOffset'
                              #layout: #(#LayoutFrame 200 0 53 0 250 0 75 0)
                              #activeHelpKey: #bottomAbsolute
                              #model: #bottomOffset
                              #type: #numberOrNil
                          )
                           #(#ActionButtonSpec
                              #name: 'actionAbsoluteBottom'
                              #layout: #(#LayoutFrame 255 0 53 0 277 0 75 0)
                              #activeHelpKey: #makeBottomAbsolute
                              #model: #absoluteBottom
                          )
                        )
                    )
                    #label: 'Corner'
                    #labelPosition: #topLeft
                )
              )
          )
      )
! !

!UILayoutTool::LayoutFrame methodsFor:'accessing'!

fetch:aView
    |layout|

    layout  := UIPainterView asLayoutFrameFromView:aView.

    (self aspectFor:#leftOffset)     value:(layout leftOffset).
    (self aspectFor:#leftFraction)   value:(layout leftFraction).
    (self aspectFor:#topOffset)      value:(layout topOffset).
    (self aspectFor:#topFraction)    value:(layout topFraction).
    (self aspectFor:#rightOffset)    value:(layout rightOffset).
    (self aspectFor:#bottomOffset)   value:(layout bottomOffset).
    (self aspectFor:#rightFraction)  value:(layout rightFraction).
    (self aspectFor:#bottomFraction) value:(layout bottomFraction).

!

layout
    "returns current layout as layoutFrame
    "
    |layout|

    layout  := Smalltalk::LayoutFrame new.

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

  ^ layout

! !

!UILayoutTool::LayoutOrigin class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool::LayoutOrigin andSelector:#windowSpec
     UILayoutTool::LayoutOrigin new openInterface:#windowSpec
     UILayoutTool::LayoutOrigin open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool-LayoutOrigin'
              #layout: #(#LayoutFrame 290 0 420 0 647 0 565 0)
              #label: 'UILayoutTool-LayoutOrigin'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 290 420 648 566)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#UISubSpecification
                    #name: 'layoutOriginSpec'
                    #layout: #(#LayoutFrame 1 0.0 6 0 0 1.0 110 0)
                    #majorKey: #UILayoutTool
                    #minorKey: #layoutOriginSpec
                )
              )
          )
      )
! !

!UILayoutTool::LayoutOrigin methodsFor:'accessing'!

fetch:aView
    "fetch layoutOrigin
    "
    |layout|

    layout  := UIPainterView asLayoutFrameFromView:aView.

    (self aspectFor:#leftOffset)   value:(layout leftOffset).
    (self aspectFor:#leftFraction) value:(layout leftFraction).
    (self aspectFor:#topOffset)    value:(layout topOffset).
    (self aspectFor:#topFraction)  value:(layout topFraction).


!

layout
    "returns current layout as layoutOrigin
    "
    |layout|

    layout  := Smalltalk::LayoutOrigin new.

    layout   leftOffset:((self aspectFor:#leftOffset)   value) ? 0.
    layout    topOffset:((self aspectFor:#topOffset)    value) ? 0.
    layout leftFraction:((self aspectFor:#leftFraction) value) ? 0.
    layout  topFraction:((self aspectFor:#topFraction)  value) ? 0.

  ^ layout

! !

!UILayoutTool::Point class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool::Point andSelector:#windowSpec
     UILayoutTool::Point new openInterface:#windowSpec
     UILayoutTool::Point open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool-Point'
              #layout: #(#LayoutFrame 324 0 410 0 618 0 547 0)
              #label: 'UILayoutTool-Point'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 324 410 619 548)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#UISubSpecification
                    #name: 'layoutPointSpec'
                    #layout: #(#LayoutFrame 1 0.0 6 0 0 1.0 100 0)
                    #majorKey: #UILayoutTool
                    #minorKey: #layoutPointSpec
                )
              )
          )
      )
! !

!UILayoutTool::Point methodsFor:'accessing'!

fetch:aView
    "fetch point
    "
    |origin|

    origin  := aView computeOrigin.

    (self aspectFor:#leftOffset) value:(origin x).
    (self aspectFor:#topOffset)  value:(origin y).


!

layout
    "returns current layout as point
    "
  ^ Smalltalk::Point x:(((self aspectFor:#leftOffset) value) ? 0)
                     y:(((self aspectFor:#topOffset)  value) ? 0)

! !

!UILayoutTool::Rectangle class methodsFor:'interface specs'!

windowSpec
    "This resource specification was automatically generated
     by the UIPainter of ST/X."

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

    "
     UIPainter new openOnClass:UILayoutTool::Rectangle andSelector:#windowSpec
     UILayoutTool::Rectangle new openInterface:#windowSpec
     UILayoutTool::Rectangle open
    "

    <resource: #canvas>

    ^
     
       #(#FullSpec
          #window: 
           #(#WindowSpec
              #name: 'UILayoutTool-Rectangle'
              #layout: #(#LayoutFrame 339 0 411 0 680 0 609 0)
              #label: 'UILayoutTool-Rectangle'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 339 411 681 610)
              #usePreferredExtent: false
          )
          #component: 
           #(#SpecCollection
              #collection: 
               #(
                 #(#UISubSpecification
                    #name: 'subSpecification'
                    #layout: #(#LayoutFrame 1 0.0 6 0 0 1.0 96 0)
                    #majorKey: #UILayoutTool
                    #minorKey: #layoutPointSpec
                )
                 #(#FramedBoxSpec
                    #name: 'FramedBox'
                    #layout: #(#LayoutFrame 1 0.0 99 0 0 1.0 194 0)
                    #component: 
                     #(#SpecCollection
                        #collection: 
                         #(
                           #(#LabelSpec
                              #name: 'labelCornerY'
                              #layout: #(#AlignmentOrigin 98 0 28 0 1 0)
                              #label: 'Right:'
                              #adjust: #left
                          )
                           #(#InputFieldSpec
                              #name: 'fieldCornerX'
                              #layout: #(#LayoutFrame 100 0 25 0 150 0 47 0)
                              #activeHelpKey: #cornerX
                              #tabable: true
                              #model: #rightOffset
                              #type: #numberOrNil
                          )
                           #(#LabelSpec
                              #name: 'labelCornerX'
                              #layout: #(#AlignmentOrigin 98 0 53 0 1 0)
                              #label: 'Bottom:'
                              #adjust: #left
                          )
                           #(#InputFieldSpec
                              #name: 'fieldCornerY'
                              #layout: #(#LayoutFrame 100 0 50 0 150 0 72 0)
                              #activeHelpKey: #cornerY
                              #tabable: true
                              #model: #bottomOffset
                              #type: #numberOrNil
                          )
                        )
                    )
                    #label: 'Corner'
                    #labelPosition: #topLeft
                )
              )
          )
      )
! !

!UILayoutTool::Rectangle methodsFor:'accessing'!

fetch:aView
    "fetch rectangle
    "
    |origin corner|

    origin := aView computeOrigin.
    corner := aView computeCorner.

    (self aspectFor:#leftOffset)   value:(origin x).
    (self aspectFor:#rightOffset)  value:(corner x).
    (self aspectFor:#topOffset)    value:(origin y).
    (self aspectFor:#bottomOffset) value:(corner y).


!

layout
    "returns current layout as rectangle
    "
  ^ Smalltalk::Rectangle left:(((self aspectFor:#leftOffset)   value) ? 0)
                          top:(((self aspectFor:#topOffset)    value) ? 0)
                        right:(((self aspectFor:#rightOffset)  value) ? 0)
                       bottom:(((self aspectFor:#bottomOffset) value) ? 0)


! !

!UILayoutTool class methodsFor:'documentation'!

version
    ^ '$Header$'
! !