UILayoutTool.st
author Claus Gittinger <cg@exept.de>
Sat, 05 Feb 2000 15:26:13 +0100
changeset 1332 ba34b85c14d8
parent 1310 572125002ce9
child 1334 36c1ee53aede
permissions -rw-r--r--
do not overwrite defaultFin windowSpec (looks ugly under win32).

"
 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 currentTool layoutView tabList
		layoutSpec toolsDictionary'
	classVariableNames:''
	poolDictionaries:''
	category:'Interface-UIPainter'
!

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

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

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

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

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

ApplicationModel subclass:#LayoutFrame
	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
        #name: #layoutOriginSpec
        #window: 
       #(#WindowSpec
          #label: 'UILayoutTool'
          #name: 'UILayoutTool'
          #min: #(#Point 10 10)
          #max: #(#Point 1152 900)
          #bounds: #(#Rectangle 506 24 851 206)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#FramedBoxSpec
              #label: 'Origin'
              #name: 'FramedBox'
              #layout: #(#LayoutFrame 0 0.0 0 0.0 0 1.0 108 0)
              #labelPosition: #topLeft
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#LabelSpec
                    #label: 'Relative:'
                    #name: 'labelRelative'
                    #layout: #(#Point 87 6)
                  )
                 #(#LabelSpec
                    #label: 'Offset:'
                    #name: 'labelAbsolute'
                    #layout: #(#Point 187 6)
                  )
                 #(#LabelSpec
                    #label: 'Left:'
                    #name: 'labelLeft'
                    #layout: #(#AlignmentOrigin 85 0 27 0 1 0)
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'fieldLeftFraction'
                    #layout: #(#LayoutFrame 87 0 24 0 137 0 46 0)
                    #activeHelpKey: #leftRelative
                    #tabable: true
                    #model: #leftFraction
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionRelativeLeft'
                    #layout: #(#LayoutFrame 142 0 24 0 164 0 46 0)
                    #activeHelpKey: #makeLeftRelative
                    #tabable: true
                    #model: #relativeLeft
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'fieldLeftOffset'
                    #layout: #(#LayoutFrame 187 0 24 0 237 0 46 0)
                    #activeHelpKey: #leftAbsolute
                    #tabable: true
                    #model: #leftOffset
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionAbsoluteLeft'
                    #layout: #(#LayoutFrame 242 0 24 0 264 0 46 0)
                    #activeHelpKey: #makeLeftAbsolute
                    #tabable: true
                    #model: #absoluteLeft
                  )
                 #(#LabelSpec
                    #label: 'Top:'
                    #name: 'labelTop'
                    #layout: #(#AlignmentOrigin 85 0 54 0 1 0)
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'fieldTopFraction'
                    #layout: #(#LayoutFrame 87 0 51 0 137 0 73 0)
                    #activeHelpKey: #topRelative
                    #tabable: true
                    #model: #topFraction
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionRelativeTop'
                    #layout: #(#LayoutFrame 142 0 51 0 164 0 73 0)
                    #activeHelpKey: #makeTopRelative
                    #tabable: true
                    #model: #relativeTop
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'fieldTopOffset'
                    #layout: #(#LayoutFrame 187 0 51 0 237 0 73 0)
                    #activeHelpKey: #topAbsolute
                    #tabable: true
                    #model: #topOffset
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionAbsoluteTop'
                    #layout: #(#LayoutFrame 242 0 51 0 264 0 73 0)
                    #activeHelpKey: #makeTopAbsolute
                    #tabable: true
                    #model: #absoluteTop
                  )
                 )
               
              )
            )
           )
         
        )
      )
!

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 216 0 173 0 493 0 296 0)
              #label: 'UILayoutTool'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 216 173 494 297)
              #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 83 0 14 0 1 0)
                              #label: 'Left:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldOriginX'
                              #layout: #(#LayoutFrame 85 0 11 0 135 0 33 0)
                              #activeHelpKey: #originX
                              #tabable: true
                              #model: #leftOffset
                              #group: #inputGroup
                              #type: #numberOrNil
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                          )
                           #(#LabelSpec
                              #name: 'labelOriginX'
                              #layout: #(#AlignmentOrigin 83 0 39 0 1 0)
                              #label: 'Top:'
                          )
                           #(#InputFieldSpec
                              #name: 'fieldOriginY'
                              #layout: #(#LayoutFrame 85 0 36 0 135 0 58 0)
                              #activeHelpKey: #originY
                              #tabable: true
                              #model: #topOffset
                              #group: #inputGroup
                              #type: #numberOrNil
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                          )
                        )
                    )
                    #label: 'Origin'
                    #labelPosition: #topLeft
                )
              )
          )
      )

    "Modified: / 13.8.1998 / 19:52:15 / cg"
!

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
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'UILayoutTool'
          #name: 'UILayoutTool'
          #min: #(#Point 10 10)
          #max: #(#Point 1152 900)
          #bounds: #(#Rectangle 12 22 312 322)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#NoteBookViewSpec
              #attributes: 
             #(#tabable
                true
              )
              #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
              #direction: #bottom
              #canvas: #layoutCanvasHolder
              #keepCanvasAlive: true
            )
           )
         
        )
      )

    "Modified: / 5.2.2000 / 15:37:02 / cg"
! !

!UILayoutTool methodsFor:'accessing'!

acceptChannel
    "return the value of the instance variable 'acceptChannel' (automatically generated)"

    ^ masterApplication acceptChannel
!

layout
    "returns configued layout or nil
    "
    ^ currentTool notNil ifTrue:[currentTool layout]
                        ifFalse:[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 type:aTypeOrNil spec:aSpec
    "change current edited view
    "
    |type name list|

    layoutView := aView.
    layoutSpec := aSpec.

    (self aspectFor:#defaultExtentEnabled) value:(aSpec class ==  WindowSpec) not.

    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|

    (selection notNil and:[currentTool notNil]) ifTrue:[
        (view := layoutView) notNil ifTrue:[
            currentTool fetch:view spec:layoutSpec
        ]
    ].
        
! !

!UILayoutTool methodsFor:'aspects'!

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


!

layoutCanvasHolder
    |holder|

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

notUsingDefaultExtent
    |holder|

    (holder := builder bindingAt:#notUsingDefaultExtent) isNil ifTrue:[
        holder := BlockValue forLogicalNot:(self aspectFor:#useDefaultExtent).
        builder aspectAt:#notUsingDefaultExtent put:holder.
    ].
    ^ holder

!

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

!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 fractHolder offsetHolder|

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

    offsetHolder value:offset.
    fractHolder  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 fractHolder offsetHolder|

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

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

    offsetHolder value:0.
    fractHolder  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.
    toolsDictionary := IdentityDictionary new.

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

    do:[:aKeyOrPair| |holder key val|
        (key := aKeyOrPair) isSymbol ifFalse:[
            key := aKeyOrPair first.
            val := aKeyOrPair second
        ].
        holder := val asValue.
        holder addDependent:self.
        aspects at:key 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 key view|

    aSelection isNumber ifTrue:[
        aSelection ~~ 0 ifTrue:[sel := tabList at:aSelection]
    ] ifFalse:[
        sel := aSelection
    ].

    selection = sel ifFalse:[
        (selection := sel) notNil ifTrue:[
            key := selection asSymbol.
            appl := toolsDictionary at:key ifAbsent:nil.

            appl isNil ifTrue:[
                view := SimpleView new.
                slice := self selectedSlice.
                appl  := slice last asString.
                appl := Smalltalk classNamed:(self class name asString, '::', appl).
                appl := appl new.
                appl masterApplication:self.
                appl createBuilder.
                view client:appl.
                appl window:view.
                toolsDictionary at:key put:appl.
            ] ifFalse:[
                view := appl window
            ].
            modifiedHolder value:true.
        ].
        currentTool := appl.
        self layoutCanvasHolder value:view.
    ].
    self update

    "Modified: / 4.2.2000 / 22:31:41 / cg"
! !

!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 291 0 130 0 632 0 328 0)
              #label: 'UILayoutTool-Rectangle'
              #min: #(#Point 10 10)
              #max: #(#Point 1152 900)
              #bounds: #(#Rectangle 291 130 633 329)
              #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 83 0 16 0 1 0)
                              #label: 'Right:'
                              #adjust: #left
                          )
                           #(#InputFieldSpec
                              #name: 'fieldCornerX'
                              #layout: #(#LayoutFrame 85 0 13 0 135 0 35 0)
                              #activeHelpKey: #cornerX
                              #tabable: true
                              #model: #rightOffset
                              #group: #inputGroup
                              #type: #numberOrNil
                              #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                          )
                           #(#LabelSpec
                              #name: 'labelCornerX'
                              #layout: #(#AlignmentOrigin 83 0 41 0 1 0)
                              #label: 'Bottom:'
                              #adjust: #left
                          )
                           #(#InputFieldSpec
                              #name: 'fieldCornerY'
                              #layout: #(#LayoutFrame 85 0 38 0 135 0 60 0)
                              #activeHelpKey: #cornerY
                              #tabable: true
                              #model: #bottomOffset
                              #group: #inputGroup
                              #type: #numberOrNil
                              #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                          )
                        )
                    )
                    #label: 'Corner'
                    #labelPosition: #topLeft
                )
              )
          )
      )

    "Modified: / 13.8.1998 / 19:59:16 / cg"
! !

!UILayoutTool::Rectangle methodsFor:'accessing'!

fetch:aView spec:aSpec
    "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::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
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'UILayoutTool-AlignmentOrigin'
          #name: 'UILayoutTool-AlignmentOrigin'
          #min: #(#Point 10 10)
          #max: #(#Point 1152 900)
          #bounds: #(#Rectangle 42 231 447 438)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#UISubSpecification
              #name: 'layoutOriginSpec'
              #layout: #(#LayoutFrame 1 0.0 6 0 0 1.0 111 0)
              #majorKey: #UILayoutTool
              #minorKey: #layoutOriginSpec
            )
           #(#FramedBoxSpec
              #label: 'Alignment'
              #name: 'FramedBox'
              #layout: #(#LayoutFrame 1 0.0 113 0 0 1.0 208 0)
              #labelPosition: #topLeft
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#LabelSpec
                    #label: 'Horizontal:'
                    #name: 'alignHLabel'
                    #layout: #(#AlignmentOrigin 88 0 17 0 1 0)
                    #adjust: #right
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'leftAlignmentFractionField'
                    #layout: #(#LayoutFrame 90 0 14 0 147 0 36 0)
                    #activeHelpKey: #alignHorizontal
                    #tabable: true
                    #model: #leftAlignmentFraction
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#LabelSpec
                    #label: 'Vertical:'
                    #name: 'alignVLabel'
                    #layout: #(#AlignmentOrigin 88 0 43 0 1 0)
                    #adjust: #right
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'topAlignmentFractionField'
                    #layout: #(#LayoutFrame 90 0 40 0 147 0 62 0)
                    #activeHelpKey: #alignVertical
                    #tabable: true
                    #model: #topAlignmentFraction
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#DividerSpec
                    #name: 'separator1'
                    #layout: #(#LayoutFrame 204 0 19 0 245 0 22 0)
                  )
                 #(#DividerSpec
                    #name: 'separator2'
                    #layout: #(#LayoutFrame 204 0 55 0 245 0 58 0)
                  )
                 #(#DividerSpec
                    #name: 'separator3'
                    #layout: #(#LayoutFrame 196 0 28 0 199 0 50 0)
                    #orientation: #vertical
                  )
                 #(#DividerSpec
                    #name: 'separator4'
                    #layout: #(#LayoutFrame 250 0 28 0 253 0 50 0)
                    #orientation: #vertical
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignTopLeft'
                    #layout: #(#LayoutFrame 190 0 14 0 204 0 28 0)
                    #activeHelpKey: #alignTopLeft
                    #tabable: true
                    #model: #alignTopLeft
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignTopCenter'
                    #layout: #(#LayoutFrame 217 0 14 0 231 0 28 0)
                    #activeHelpKey: #alignTopCenter
                    #tabable: true
                    #model: #alignTopCenter
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignTopRight'
                    #layout: #(#LayoutFrame 245 0 14 0 259 0 28 0)
                    #activeHelpKey: #alignTopRight
                    #tabable: true
                    #model: #alignTopRight
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignLeftCenter'
                    #layout: #(#LayoutFrame 190 0 32 0 204 0 46 0)
                    #activeHelpKey: #alignLeftCenter
                    #tabable: true
                    #model: #alignLeftCenter
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignCenter'
                    #layout: #(#LayoutFrame 217 0 32 0 231 0 46 0)
                    #activeHelpKey: #alignCenter
                    #tabable: true
                    #model: #alignCenter
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignRightCenter'
                    #layout: #(#LayoutFrame 245 0 32 0 259 0 46 0)
                    #activeHelpKey: #alignRightCenter
                    #tabable: true
                    #model: #alignRightCenter
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignBottomLeft'
                    #layout: #(#LayoutFrame 190 0 50 0 204 0 64 0)
                    #activeHelpKey: #alignBottomLeft
                    #tabable: true
                    #model: #alignBottomLeft
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignBottomCenter'
                    #layout: #(#LayoutFrame 217 0 50 0 231 0 64 0)
                    #activeHelpKey: #alignBottomCenter
                    #tabable: true
                    #model: #alignBottomCenter
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'alignBottomRight'
                    #layout: #(#LayoutFrame 245 0 50 0 259 0 64 0)
                    #activeHelpKey: #alignBottomRight
                    #tabable: true
                    #model: #alignBottomRight
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!UILayoutTool::AlignmentOrigin methodsFor:'accessing'!

fetch:aView spec:aSpec
    "fetch alignmentOrigin
    "
    |layout type 
     leftAlignmentFractionHolder topAlignmentFractionHolder
     leftOffsetHolder leftFractionHolder topOffsetHolder topFractionHolder|

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

    leftOffsetHolder := (self aspectFor:#leftOffset).
    leftFractionHolder := (self aspectFor:#leftFraction).
    topOffsetHolder := (self aspectFor:#topOffset).
    topFractionHolder := (self aspectFor:#topFraction).
    leftAlignmentFractionHolder := (self aspectFor:#leftAlignmentFraction).
    topAlignmentFractionHolder := (self aspectFor:#topAlignmentFraction).

    layout isLayout ifTrue:[
        leftOffsetHolder   value:(layout leftOffset).
        leftFractionHolder value:(layout leftFraction).
        topOffsetHolder    value:(layout topOffset).
        topFractionHolder  value:(layout topFraction).

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

        leftOffsetHolder   value:(layout x).
        leftFractionHolder value:0.
        topOffsetHolder    value:(layout y).
        topFractionHolder  value:0.
    ].
    leftAlignmentFractionHolder value:0.
    topAlignmentFractionHolder  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 lAHolder tAHolder lOHolder tOHolder|

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

    lAHolder value:leftAlignmentFraction.
    tAHolder  value:topAlignmentFraction.

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

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

    lOHolder value:(lO rounded).
    tOHolder value:(tO rounded).

!

makeAlignTopRight
    self makeAlignLeft:1 top:0


! !

!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 spec:aSpec
    "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 spec:aSpec
    "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::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
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'UILayoutTool-Extent'
          #name: 'UILayoutTool-Extent'
          #min: #(#Point 10 10)
          #max: #(#Point 1152 900)
          #bounds: #(#Rectangle 506 24 832 173)
        )
        #component: 
       #(#SpecCollection
          #collection: #(
           #(#FramedBoxSpec
              #label: 'Extent'
              #name: 'FramedBox'
              #layout: #(#LayoutFrame 0 0.0 6 0.0 0 1.0 137 0)
              #labelPosition: #topLeft
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#LabelSpec
                    #label: 'Width:'
                    #name: 'labelWidth'
                    #layout: #(#AlignmentOrigin 89 0 24 0 1 0.5)
                    #adjust: #right
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'fieldLeftOffset'
                    #layout: #(#LayoutFrame 90 0 13 0 140 0 35 0)
                    #activeHelpKey: #hrzExtent
                    #enableChannel: #notUsingDefaultExtent
                    #tabable: true
                    #model: #leftOffset
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#LabelSpec
                    #label: 'Height:'
                    #name: 'labelHeight'
                    #layout: #(#AlignmentOrigin 89 0 49 0 1 0.5)
                    #adjust: #right
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'fieldRightOffset'
                    #layout: #(#LayoutFrame 90 0 38 0 140 0 60 0)
                    #activeHelpKey: #vrtExtent
                    #enableChannel: #notUsingDefaultExtent
                    #tabable: true
                    #model: #rightOffset
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#CheckBoxSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #label: 'Use Widgets Default Extent'
                    #name: 'useDefaultExtentCheckBox'
                    #layout: #(#Point 5 74)
                    #enableChannel: #defaultExtentEnabled
                    #tabable: true
                    #model: #useDefaultExtent
                    #translateLabel: true
                  )
                 )
               
              )
            )
           )
         
        )
      )
! !

!UILayoutTool::Extent methodsFor:'accessing'!

fetch:aView spec:aSpec
    "fetch extent
    "
    |extent|

    extent  := aView computeExtent.

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

    (self aspectFor:#useDefaultExtent) value:aSpec useDefaultExtent 
!

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

#bottomFixPartLayout
'Set the layout for a fixed area at the bottom of the widgets containers space'

#bottomHalfLayout
'Set the layout for the bottom half of the widgets containers space'

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

#leftHalfLayout
'Set the layout for the left half of the widgets containers space'

#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.'

#rightHalfLayout
'Set the layout for the right half of the widgets containers space'

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

#topFixPartLayout
'Set the layout for a fixed area at the top of the widgets containers space'

#topHalfLayout
'Set the layout for the top half of the widgets containers space'

#topLeftQuarterLayout
'Set the layout for the top-left quarter of the widgets containers space'

#topRightQuarterLayout
'Set the layout for the top-right quarter of the widgets containers space'

#bottomRightQuarterLayout
'Set the layout for the bottom-right quarter of the widgets containers space'

#bottomLeftQuarterLayout
'Set the layout for the bottom-left quarter of the widgets containers space'

)
! !

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

setBottomFixPartIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setBottomFixPartIcon inspect
     ImageEditor openOnClass:self andSelector:#setBottomFixPartIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setBottomFixPartIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@H"H"@BH"H @!!DQD@DQDR@BDQDP@QDQH@H"H"@BH"H @@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??>@@X@A @F@@X@A @F@@X@A @G???????????????<b') ; yourself); yourself]!

setBottomHalfIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setBottomHalfIcon inspect
     ImageEditor openOnClass:self andSelector:#setBottomHalfIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setBottomHalfIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@"H"H"H"H"@BDQDQDQDQH@HQDQDQDQD @!!DQDQDQDR@BDQDQDQDQH@H"H"H"H"H @@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??>@@X@A @F@@X@A @F@@_????????????????????<b') ; yourself); yourself]!

setBottomLeftQuarterIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setBottomLeftQuarterIcon inspect
     ImageEditor openOnClass:self andSelector:#setBottomLeftQuarterIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setBottomLeftQuarterIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@H"H"@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@H"H"@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??>@@X@A @F@@X@A @G?@_<A?0G?@_<A?0G?@_<A??<b') ; yourself); yourself]!

setBottomRightQuarterIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setBottomRightQuarterIcon inspect
     ImageEditor openOnClass:self andSelector:#setBottomRightQuarterIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setBottomRightQuarterIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@BH"H"@@@@@@HQDQH@@@@@@!!DQD @@@@@BDQDR@@@@@@HQDQH@@@@@@"H"H @@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??>@@X@A @F@@X@A @F@@XG? _>A?8G? _>A?8G???<b') ; yourself); yourself]!

setLeftHalfIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setLeftHalfIcon inspect
     ImageEditor openOnClass:self andSelector:#setLeftHalfIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setLeftHalfIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@BH"H @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@H"H"@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'????@_<A?0G?@_<A?0G?@_<A?0G?@_<A?0G?@_<A??<b') ; yourself); yourself]!

setRightHalfIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setRightHalfIcon inspect
     ImageEditor openOnClass:self andSelector:#setRightHalfIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setRightHalfIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@"H"H@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BH"H @@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??>@?8C? O>@?8C? O>@?8C? O>@?8C? O>@?8C???<b') ; yourself); yourself]!

setToRightQuarterIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setToRightQuarterIcon inspect
     ImageEditor openOnClass:self andSelector:#setToRightQuarterIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setToRightQuarterIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@@@@@@@"H"H@@@@@@BDQD @@@@@@HQDR@@@@@@@!!DQH@@@@@@BDQD @@@@@@HQDR@@@@@@@"H"H@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'??>@?8C? O>@?8C? O>@?8C? @F@@X@A @F@@X@A??<b') ; yourself); yourself]!

setTopFixPartIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setTopFixPartIcon inspect
     ImageEditor openOnClass:self andSelector:#setTopFixPartIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setTopFixPartIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@BH"H @"H"H@HQDQ@ADQD @!!DQD@DQDR@BH"H @"H"H@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'???????????????? @F@@X@A @F@@X@A @F@@X@A??<b') ; yourself); yourself]!

setTopHalfIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setTopHalfIcon inspect
     ImageEditor openOnClass:self andSelector:#setTopHalfIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setTopHalfIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@BH"H"H"H"H@HQDQDQDQD @!!DQDQDQDR@BDQDQDQDQH@HQDQDQDQD @"H"H"H"H"@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'?????????????????????8@A @F@@X@A @F@@X@A??<b') ; yourself); yourself]!

setTopLeftQuarterIcon
    "This resource specification was automatically generated
     by the ImageEditor of ST/X."

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

    "
     self setTopLeftQuarterIcon inspect
     ImageEditor openOnClass:self andSelector:#setTopLeftQuarterIcon
    "

    <resource: #image>

    ^Icon
        constantNamed:#'UILayoutTool::LayoutFrame setTopLeftQuarterIcon'
        ifAbsentPut:[(Depth4Image new) width: 16; height: 16; photometric:(#palette); bitsPerSample:(#(4 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@@@@@@@@@@BH"H"@@@@@@HQDQH@@@@@@!!DQD @@@@@BDQDR@@@@@@HQDQH@@@@@@"H"H @@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@@b') ; colorMapFromArray:#[0 0 0 255 0 0 255 255 255]; mask:((Depth1Image new) width: 16; height: 16; photometric:(#blackIs0); bitsPerSample:(#(1 )); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'???? _>A?8G? _>A?8G? X@A @F@@X@A @F@@X@A??<b') ; yourself); yourself]! !

!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
        #name: #windowSpec
        #window: 
       #(#WindowSpec
          #label: 'UILayoutTool-LayoutFrame'
          #name: 'UILayoutTool-LayoutFrame'
          #min: #(#Point 10 10)
          #max: #(#Point 1152 900)
          #bounds: #(#Rectangle 12 22 411 325)
          #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
              #label: 'Corner'
              #name: 'FramedBox'
              #layout: #(#LayoutFrame 1 0.0 113 0 0 1.0 214 0)
              #labelPosition: #topLeft
              #component: 
             #(#SpecCollection
                #collection: #(
                 #(#LabelSpec
                    #label: 'Right:'
                    #name: 'labelRight'
                    #layout: #(#AlignmentOrigin 88 0 25 0 1 0.5)
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#fieldRightFraction
                      nil #tabable
                      true
                    )
                    #name: 'fieldRightFraction'
                    #layout: #(#LayoutFrame 90 0 14 0 140 0 36 0)
                    #activeHelpKey: #rightRelative
                    #tabable: true
                    #model: #rightFraction
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionRelativeRight'
                    #layout: #(#LayoutFrame 145 0 14 0 167 0 36 0)
                    #activeHelpKey: #makeRightRelative
                    #tabable: true
                    #model: #relativeRight
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#fieldRightOffset
                      nil #tabable
                      true
                    )
                    #name: 'fieldRightOffset'
                    #layout: #(#LayoutFrame 190 0 14 0 240 0 36 0)
                    #activeHelpKey: #rightAbsolute
                    #tabable: true
                    #model: #rightOffset
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionAbsoluteRight'
                    #layout: #(#LayoutFrame 245 0 14 0 267 0 36 0)
                    #activeHelpKey: #makeRightAbsolute
                    #tabable: true
                    #model: #absoluteRight
                  )
                 #(#LabelSpec
                    #label: 'Bottom:'
                    #name: 'labelBottom'
                    #layout: #(#AlignmentOrigin 88 0 53 0 1 0.5)
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#fieldBottomFraction
                      nil #tabable
                      true
                    )
                    #name: 'fieldBottomFraction'
                    #layout: #(#LayoutFrame 90 0 42 0 140 0 64 0)
                    #activeHelpKey: #bottomRelative
                    #tabable: true
                    #model: #bottomFraction
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionRelativeBottom'
                    #layout: #(#LayoutFrame 145 0 42 0 167 0 64 0)
                    #activeHelpKey: #makeBottomRelative
                    #tabable: true
                    #model: #relativeBottom
                  )
                 #(#InputFieldSpec
                    #attributes: 
                   #(#fieldBottomOffset
                      nil #tabable
                      true
                    )
                    #name: 'fieldBottomOffset'
                    #layout: #(#LayoutFrame 190 0 42 0 240 0 64 0)
                    #activeHelpKey: #bottomAbsolute
                    #tabable: true
                    #model: #bottomOffset
                    #group: #inputGroup
                    #type: #numberOrNil
                    #acceptOnLostFocus: true
                    #acceptChannel: #acceptChannel
                    #modifiedChannel: #modifiedChannel
                    #acceptOnPointerLeave: false
                  )
                 #(#ActionButtonSpec
                    #attributes: 
                   #(#tabable
                      true
                    )
                    #name: 'actionAbsoluteBottom'
                    #layout: #(#LayoutFrame 245 0 42 0 267 0 64 0)
                    #activeHelpKey: #makeBottomAbsolute
                    #tabable: true
                    #model: #absoluteBottom
                  )
                 )
               
              )
            )
           #(#MenuPanelSpec
              #attributes: 
             #(#tabable
                true
              )
              #name: 'commonLayoutToolBar'
              #layout: #(#LayoutFrame 6 0.0 231 0 -4 1.0 263 0)
              #level: 0
              #tabable: true
              #menu: #commonFrameLayoutsMenu
              #textDefault: true
            )
           )
         
        )
      )
! !

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

commonFrameLayoutsMenu
    "This resource specification was automatically generated
     by the MenuEditor of ST/X."

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

    "
     MenuEditor new openOnClass:UILayoutTool::LayoutFrame andSelector:#commonFrameLayoutsMenu
     (Menu new fromLiteralArrayEncoding:(UILayoutTool::LayoutFrame commonFrameLayoutsMenu)) startUp
    "

    <resource: #menu>

    ^
     
       #(#Menu
          
           #(
             #(#MenuItem
                #label: 'setTopHalfFrame'
                #translateLabel: true
                #isButton: true
                #nameKey: #setTopHalfFrame
                #value: #setTopHalfFrame
                #activeHelpKey: #topHalfLayout
                #labelImage: #(#ResourceRetriever #'UILayoutTool::LayoutFrame' #setTopHalfIcon)
            )
             #(#MenuItem
                #label: 'setBottomHalfFrame'
                #translateLabel: true
                #isButton: true
                #nameKey: #setBottomHalfFrame
                #value: #setBottomHalfFrame
                #activeHelpKey: #bottomHalfLayout
                #labelImage: #(#ResourceRetriever nil #setBottomHalfIcon)
            )
             #(#MenuItem
                #label: 'setLeftHalfFrame'
                #translateLabel: true
                #isButton: true
                #nameKey: #setLeftHalfFrame
                #value: #setLeftHalfFrame
                #activeHelpKey: #leftHalfLayout
                #labelImage: #(#ResourceRetriever nil #setLeftHalfIcon)
            )
             #(#MenuItem
                #label: 'setRightHalfFrame'
                #translateLabel: true
                #isButton: true
                #nameKey: #setRightHalfFrame
                #value: #setRightHalfFrame
                #activeHelpKey: #rightHalfLayout
                #labelImage: #(#ResourceRetriever nil #setRightHalfIcon)
            )
             #(#MenuItem
                #label: ''
            )
             #(#MenuItem
                #label: 'setTopLeftQuarterFrame'
                #translateLabel: true
                #isButton: true
                #activeHelpKey: #topLeftQuarterLayout
                #nameKey: #setTopLeftQuarterFrame
                #value: #setTopLeftQuarterFrame
                #labelImage: #(#ResourceRetriever nil #setTopLeftQuarterIcon)
            )
             #(#MenuItem
                #label: 'setTopRightQuarterFrame'
                #translateLabel: true
                #isButton: true
                #activeHelpKey: #topRightQuarterLayout
                #nameKey: #setTopRightQuarterFrame
                #value: #setTopRightQuarterFrame
                #labelImage: #(#ResourceRetriever nil #setToRightQuarterIcon)
            )
             #(#MenuItem
                #label: 'setBottomRightQuarterFrame'
                #translateLabel: true
                #isButton: true
                #activeHelpKey: #bottomRightQuarterLayout
                #nameKey: #setBottomRightQuarterFrame
                #value: #setBottomRightQuarterFrame
                #labelImage: #(#ResourceRetriever nil #setBottomRightQuarterIcon)
            )
             #(#MenuItem
                #label: 'setBottomLeftQuarterFrame'
                #translateLabel: true
                #activeHelpKey: #bottomLeftQuarterLayout
                #isButton: true
                #nameKey: #setBottomLeftQuarterFrame
                #value: #setBottomLeftQuarterFrame
                #labelImage: #(#ResourceRetriever nil #setBottomLeftQuarterIcon)
            )
             #(#MenuItem
                #label: ''
            )
             #(#MenuItem
                #label: 'setTopFixPartFrame'
                #translateLabel: true
                #isButton: true
                #nameKey: #setTopFixPartFrame
                #value: #setTopFixPartFrame
                #activeHelpKey: #topFixPartLayout
                #labelImage: #(#ResourceRetriever nil #setTopFixPartIcon)
            )
             #(#MenuItem
                #label: 'setBottomFixPartFrame'
                #translateLabel: true
                #isButton: true
                #nameKey: #setBottomFixPartFrame
                #value: #setBottomFixPartFrame
                #activeHelpKey: #bottomFixPartLayout
                #labelImage: #(#ResourceRetriever nil #setBottomFixPartIcon)
            )
          ) nil
          nil
      )
! !

!UILayoutTool::LayoutFrame methodsFor:'accessing'!

fetch:aView spec:aSpec
    |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::LayoutFrame methodsFor:'common frames'!

setBottomFixPartFrame
    self
        setFrameLeft:0   offset:0 
        right:1          offset:0 
        top:1            offset:-30 
        bottom:1         offset:0
!

setBottomHalfFrame
    self
        setFrameLeft:0  offset:0 
        right:1         offset:0 
        top:0.5         offset:0 
        bottom:1        offset:0
!

setBottomLeftQuarterFrame
    self
        setFrameLeft:0   offset:0 
        right:0.5        offset:0 
        top:0.5          offset:0 
        bottom:1         offset:0
!

setBottomRightQuarterFrame
    self
        setFrameLeft:0.5 offset:0 
        right:1          offset:0 
        top:0.5          offset:0 
        bottom:1         offset:0
!

setFrameLeft:lF offset:lO right:rF offset:rO top:tF offset:tO bottom:bF offset:bO
    (self aspectFor:#leftOffset)     value:lO.
    (self aspectFor:#rightOffset)    value:rO.
    (self aspectFor:#topOffset)      value:tO.
    (self aspectFor:#bottomOffset)   value:bO.

    (self aspectFor:#leftFraction)   value:lF.
    (self aspectFor:#rightFraction)  value:rF.
    (self aspectFor:#topFraction)    value:tF.
    (self aspectFor:#bottomFraction) value:bF.
!

setLeftHalfFrame
    self
        setFrameLeft:0  offset:0 
        right:0.5       offset:0 
        top:0           offset:0 
        bottom:1        offset:0
!

setRightHalfFrame
    self
        setFrameLeft:0.5 offset:0 
        right:1          offset:0 
        top:0            offset:0 
        bottom:1         offset:0
!

setTopFixPartFrame
    self
        setFrameLeft:0   offset:0 
        right:1          offset:0 
        top:0            offset:0 
        bottom:0         offset:30
!

setTopHalfFrame
    self
        setFrameLeft:0   offset:0 
        right:1          offset:0 
        top:0            offset:0 
        bottom:0.5       offset:0
!

setTopLeftQuarterFrame
    self
        setFrameLeft:0   offset:0 
        right:0.5        offset:0 
        top:0            offset:0 
        bottom:0.5       offset:0
!

setTopRightQuarterFrame
    self
        setFrameLeft:0.5 offset:0 
        right:1          offset:0 
        top:0            offset:0 
        bottom:0.5       offset:0
! !

!UILayoutTool class methodsFor:'documentation'!

version
    ^ '$Header$'
! !