[Cuis-dev] LayoutMorph separation

ken.dickey at whidbey.com ken.dickey at whidbey.com
Wed Aug 14 13:59:02 PDT 2024


On 2024-08-13 17:01, Mark Volkmann via Cuis-dev wrote:

> On Tue, Aug 13, 2024 at 9:18 AM <ken.dickey at whidbey.com> wrote:
> 
>> On 2024-08-12 17:01, Mark Volkmann via Cuis-dev wrote:
>> 
>>> I seem to keep running into situations where I want separation in a
>>> LayoutMorph to only be added between the submorphs and not before the
>>> first and after the last. I see that I can achieve that by modifying
>>> the LayoutMorph method layoutSubmorphsHorizontallyIn:. But I don't
>>> always want that behavior. I'd like that to be configurable. Is there
>>> already a way to do this that I'm missing?

> No.

>>> I'd rather not have to insert spacer morphs, especially if there are 
>>> a large number of submorphs.
>>> I attached my solution which is to create a subclass of LayoutMorph 
>>> that adds a boolean instance variable "trim".
>>> When that is true, it avoids adding separation before the first and 
>>> after the last submorph.
>>> This works for my use cases.
>>> It would be great if this was added to LayoutMorph. It wouldn't 
>>> affect its current behavior.

Mark, thanks much for contributing.

Two things:
  [A] I prefer #useEdgeSpace to #trim as 'trim' seems too generic a term 
to me. ['shrinkWrap' might work as well].
  [B] Due to edge cases, the math is a bit difficult to get right.

Please check the code and try `Layout2Morph example1` in the attached.

I am still testing, but think this may be close to what you want.

Thanks again for this!
-KenD
-------------- next part --------------
'From Cuis7.1 [latest update: #6579] on 14 August 2024 at 1:47:45 pm'!
!classDefinition: #Layout2Morph category: #Volkmann!
LayoutMorph subclass: #Layout2Morph
	instanceVariableNames: 'useEdgeSpace'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Volkmann'!
!Layout2Morph commentStamp: '<historical>' prior: 0!
This is a subclass of LayoutMorph that adds the instance variable "useEdgeSpace".
When true, x and y separation are kept between submorphs and the edge of our extent,
othersize no space is kept between submorphs and our outer edge.!


!Layout2Morph methodsFor: 'initialization' stamp: 'KenD 8/14/2024 10:22:14'!
initialize
	super initialize.
	useEdgeSpace := false.! !


!Layout2Morph methodsFor: 'geometry' stamp: 'KenD 8/14/2024 12:08:52'!
minimumExtent: cachedValues
	"Answer size sufficient to frame my submorphs."
	
	| width height mle |
	width  := 0.
	height := 0.
	(self direction =  #vertical)
		ifTrue: [ "Column"
			self submorphsToLayout do: [ :sm |
				mle := sm minimumLayoutExtent: cachedValues.
				"use maximum width across submorphs"
				width := width max: mle x.
				"sum up submorph heights, including separation"
				height := height + mle y + self ySeparation.
			].
			useEdgeSpace
			 	ifTrue: [
					width  := width + (2 * self xSeparation). "separation on each side"
					height := height + self ySeparation. "one side already separated"
				]
				ifFalse: [
					height := height - self ySeparation. "remove excess"
				]
		]
		ifFalse: [ "Row"
			self submorphsToLayout do: [ :sm |
				mle := sm minimumLayoutExtent: cachedValues.
				"sum up submorphs width"
				width := width + mle x + self xSeparation.
				"use maximum height across submorph"
				height := height max: mle y.
			].
			useEdgeSpace 
				ifTrue:  [
					height := height + (2 * self ySeparation). "separation on each side"
					width  := width + self xSeparation.       "one side already separated"
				]
				ifFalse: [
					width  := width - self xSeparation.       "remove excess"
				]
		].

	^ (width @ height) + self extentBorder! !


!Layout2Morph methodsFor: 'layout' stamp: 'KenD 8/14/2024 13:47:24'!
layoutSubmorphsHorizontallyIn: boundsForLayout
	"Compute a new layout based on the given layout bounds."

	| visibleSubmorphs gap gapCount widths widthToAllocate leftOver x height y cache |
	"Preconditions: self isRow & morphExtent >= minimumLayoutExtent"
	(visibleSubmorphs := self submorphsToLayout reversed  "Display Order")
		ifEmpty: [ ^ self. "Nothing to layout, besides `sum` below, would fail" ].
	
	gap := self xSeparation.
	gapCount := useEdgeSpace ifFalse: [ visibleSubmorphs size - 1 ] ifTrue: [ visibleSubmorphs size + 1].
	widthToAllocate := (boundsForLayout width - (gapCount * gap)).
	cache := IdentityDictionary new.
	widths := self widthsFor: visibleSubmorphs within: widthToAllocate minLayoutExtentCache: cache.
	leftOver := widthToAllocate - widths sum.
	x := boundsForLayout left + (leftOver * self axisEdgeWeight).
	useEdgeSpace ifTrue: [ x := x + gap ].

	visibleSubmorphs with: widths do: [ :sm :smWidth |
		height := self offAxisHeightFor: sm 
					  within: boundsForLayout height 
					   minLayoutExtentCache: cache.
		y := self offAxisYOffsetFor: sm within: boundsForLayout height - height.
		sm fitInto: (x @ (boundsForLayout top + y) extent: smWidth @ height).
		x := x + smWidth + gap.
	]! !

!Layout2Morph methodsFor: 'layout' stamp: 'KenD 8/14/2024 13:47:30'!
layoutSubmorphsVerticallyIn: boundsForLayout
	"Compute a new layout based on the given layout bounds."

	| visibleSubmorphs gap gapCount heights heightToAllocate leftOver y width x cache |
	"Preconditions: self isRow & morphExtent >= minimumLayoutExtent"
	(visibleSubmorphs := self submorphsToLayout reversed  "Display Order")
		ifEmpty: [ ^ self. "Nothing to layout, besides `sum` below, would fail" ].

	gap := self ySeparation.
	gapCount := useEdgeSpace ifFalse: [ visibleSubmorphs size - 1 ] ifTrue: [ visibleSubmorphs size + 1].
	heightToAllocate := (boundsForLayout height - (gapCount * gap)).
	cache := IdentityDictionary new.
	heights := self heightsFor: visibleSubmorphs 
				    within: heightToAllocate 
				     minLayoutExtentCache: cache.
	leftOver := heightToAllocate - heights sum.
	y := boundsForLayout top + (leftOver * self axisEdgeWeight).
	useEdgeSpace ifTrue: [ y := y + gap ].

	visibleSubmorphs with: heights do: [ :sm :smHeight |
		width := self offAxisWidthFor: sm within: boundsForLayout width minLayoutExtentCache: cache.
		x := self offAxisXOffsetFor: sm within: boundsForLayout width - width.
		sm fitInto: (boundsForLayout left + x @ y extent: width @ smHeight).
		y := y + smHeight + gap.
	]! !

!Layout2Morph methodsFor: 'layout' stamp: 'KenD 8/14/2024 12:15:37'!
offAxisXOffsetFor: aMorph within: availableWidth
	"Answer x offset for a single morph -- offAxis calculation for a Column"

	| leftOver offset |
	leftOver := useEdgeSpace ifTrue: [availableWidth - (2 * self xSeparation)] 
							  ifFalse: [availableWidth ].
	offset := (leftOver * aMorph layoutSpec offAxisEdgeWeight). 
	useEdgeSpace ifTrue: [ ^ self xSeparation + offset ].
	^ offset! !

!Layout2Morph methodsFor: 'layout' stamp: 'KenD 8/14/2024 12:16:49'!
offAxisYOffsetFor: aMorph within: availableHeight
	"Answer y offset for a single morph -- offAxis calculation for a Row"
	
	| leftOver offset |
	leftOver := useEdgeSpace ifTrue: [availableHeight - (2 * self ySeparation)] 
							 ifFalse: [availableHeight ].
	offset := leftOver * aMorph layoutSpec offAxisEdgeWeight.
	useEdgeSpace ifTrue: [ ^ self ySeparation + offset ].
	^offset! !

!Layout2Morph methodsFor: 'layout' stamp: 'KenD 8/14/2024 10:01:57'!
useEdgeSpace
	^ useEdgeSpace! !

!Layout2Morph methodsFor: 'layout' stamp: 'KenD 8/14/2024 10:02:34'!
useEdgeSpace: aBoolean

	useEdgeSpace := aBoolean! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

!classDefinition: 'Layout2Morph class' category: #Volkmann!
Layout2Morph class
	instanceVariableNames: ''!

!Layout2Morph class methodsFor: 'examples' stamp: 'KenD 8/14/2024 13:46:14'!
example1
"
	self example1
"

	| withEdge noEdge upSpec downSpec |
	withEdge := self newRow :: useEdgeSpace: true;  separation: 20.
	noEdge    := self newRow :: useEdgeSpace: false;  separation: 20.
	upSpec     := LayoutSpec keepMorphExtent :: offAxisEdgeWeight: 0.
	upSpec proportionalWidth: 0.8 minimum: 100; proportionalHeight: 0.8 minimum: 100.
	downSpec := LayoutSpec keepMorphExtent :: offAxisEdgeWeight: 1.
	downSpec proportionalWidth: 0.8 minimum: 100; proportionalHeight: 0.8 minimum: 100.
	
	withEdge addMorph: (BoxedMorph new :: color: Color blue;  layoutSpec: upSpec).
	noEdge   addMorph: (BoxedMorph new :: color: Color blue;  layoutSpec: upSpec).
	withEdge addMorph: (LabelMorph new :: contents: 'WITH Edge').
	noEdge addMorph: (LabelMorph new :: contents: 'withOUT Edge').
	withEdge addMorph: (BoxedMorph new :: layoutSpec: downSpec).
	noEdge   addMorph: (BoxedMorph new ::  layoutSpec: downSpec).
	
	withEdge openInWorld.
	noEdge openInWorld.
	! !


More information about the Cuis-dev mailing list