smalltalk
/
osmo-st-all
Archived
1
0
Fork 0

Sync with Squeak changes

This commit is contained in:
Nicolas Petton 2009-09-11 11:24:03 +02:00
parent 2a26157ca0
commit 8b9550fcd1
7 changed files with 179 additions and 63 deletions

View File

@ -50,7 +50,7 @@ UIWidget subclass: Calendar [
contents [
<category: 'building'>
^[:e |
e
(e div class: self csClass)
build:self monthSelectionFormContents;
build: self calendarTableContents]
]

View File

@ -40,6 +40,11 @@ UIWidget subclass: DateSelector [
<comment: nil>
<category: 'Iliad-Core-UI'>
cssClass [
<category: 'accessing'>
^super cssClass, ' date_selector'
]
actionBlock [
<category: 'accessing'>
^actionBlock
@ -102,14 +107,14 @@ UIWidget subclass: DateSelector [
contents [
<category: 'building'>
^[:e |
| form |
^[:e || div form |
div := e div class: self cssClass.
self selectedDateIsValid
ifFalse:
[(e div)
ifFalse: [
div div
class: 'error';
text: 'Invalid date'].
form := e form.
form := div form.
form
build: self monthSelectionContents;
build: self dayInputContents;

View File

@ -58,8 +58,9 @@ UIWidget subclass: Spacer [
contents [
<category: 'building'>
^[:e |
^[:e || div |
div := e div class: self cssClass.
self spaces timesRepeat: [
e nbsp]]
div nbsp]]
]
]

View File

@ -42,6 +42,11 @@ UIWidget subclass: TimeSelector [
<comment: nil>
<category: 'Iliad-Core-UI'>
cssClass [
<category: 'accessing'>
^super cssClass, ' time_selector'
]
actionBlock [
<category: 'accessing'>
^actionBlock
@ -108,12 +113,13 @@ UIWidget subclass: TimeSelector [
contents [
<category: 'building'>
^[:e || form |
^[:e || div form |
div := e div class: self cssClass.
self selectedTimeIsValid ifFalse: [
e div
div div
class: 'error';
text: 'Invalid time'].
form := e form.
form := div form.
form
build: self hoursInputContents;
text: ':';

View File

@ -53,7 +53,7 @@ Tree new
^[:e || div |
div := e div.
self isRoot ifTrue: [
div class: 'tree'].
div class: self cssClass].
div build: self contentsForItem]
]
@ -82,6 +82,11 @@ Tree new
ul listItem build: each]]]
]
cssClass [
<category: 'accessing'>
^super cssClass, ' tree'
]
children [
<category: 'accessing'>
^self childrenBlock value: self item

102
More/UI/ViewTabs.st Normal file
View File

@ -0,0 +1,102 @@
"======================================================================
|
| Iliad.ViewTabs class definition
|
======================================================================"
"======================================================================
|
| Copyright (c) 2009
| Nicolas Petton <petton.nicolas@gmail.com>,
| Sébastien Audier <sebastien.audier@gmail.com>
|
| This file is part of the Iliad framework.
|
| Permission is hereby granted, free of charge, to any person obtaining
| a copy of this software and associated documentation files (the
| 'Software'), to deal in the Software without restriction, including
| without limitation the rights to use, copy, modify, merge, publish,
| distribute, sublicense, and/or sell copies of the Software, and to
| permit persons to whom the Software is furnished to do so, subject to
| the following conditions:
|
| The above copyright notice and this permission notice shall be
| included in all copies or substantial portions of the Software.
|
| THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
| EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF
| MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT.
| IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY
| CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT,
| TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE
| SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.
|
======================================================================"
UIWidget subclass: ViewTabs [
| views labels selectedView |
<comment: nil>
<category: 'Iliad-More-UI'>
contents [
<category: 'building'>
^[:e || ul div |
div := e div class: self cssClass.
ul := div unorderedList.
self views do: [:each || li |
li := ul listItem.
li anchor
text: (self labelFor: each);
linkToLocal: each.
self selectedView = each ifTrue: [li class: 'selected']]]
]
cssClass [
<category: 'accessing'>
^super cssClass, ' tabs'
]
labelFor: aView [
<category: 'accessing'>
^self labels at: (self views indexOf: aView)
]
labels [
<category: 'accessing'>
^labels
]
labels: aCollection [
"aCollection of strings.
aCollection must have the same size as widgets collection"
<category: 'accessing'>
labels := aCollection
]
selectedView [
<category: 'accessing'>
| route |
route := self context route copy.
route position: self application originalRoutePosition.
^route next ifNil: [self views first]
]
views [
<category: 'accessing'>
^views
]
views: aCollection [
"aCollection of strings to be displayed in the tabs.
Each view has an associated label, set with #labels: method"
<category: 'accessing'>
views := aCollection
]
]

View File

@ -35,101 +35,98 @@
UIWidget subclass: WidgetTabs [
| widgets labels hashes selectedWidget |
| contentsBlock labelBlock items selectedItem hashBlock |
<comment: ''>
<category: 'Iliad-More-UI'>
<comment: 'Usage example:
Tabs new
labels: #(''Counter 1'' ''Counter 2'');
widgets: {Counter new. Counter new}'>
contents [
<category: 'building'>
^[:e |
^[:e |
e build: self tabsContents.
e div
class: 'contents';
add: self selectedWidget build]
self contentsBlock value: e value: self selectedItem]
]
tabsContents [
<category: 'building'>
^[:e || div ul |
div := e div class: 'tabs'.
^[:e || ul div |
div := e div class: self cssClass.
ul := div unorderedList.
self widgets do: [:each || li |
self items do: [:each || li |
li := ul listItem.
li anchor
text: (self labelFor: each);
action: [self selectWidget: each]
hash: (self hashFor: each).
self selectedWidget = each ifTrue: [
li class: 'selected']]]
text: (self labelBlock value: each);
action: [self selectItem: each] hash: (self hashBlock value: each).
self selectedItem = each ifTrue: [li class: 'selected']]]
]
labels [
cssClass [
<category: 'accessing'>
^labels
^super cssClass, ' tabs'
]
labels: aCollection [
"aCollection -- of strings -- must have the same size as
widgets collection"
contentsBlock [
<category: 'accessing'>
labels := aCollection
^contentsBlock
]
hashes [
contentsBlock: aViewBlock [
<category: 'accessing'>
^hashes ifNil: [#()]
contentsBlock := aViewBlock
]
hashes: aCollection [
"aCollection -- of strings -- must have the same size as
widgets collection"
hashBlock [
<category: 'accessing'>
hashes := aCollection
^hashBlock ifNil: [[:item | '']]
]
hashFor: aWidget [
hashBlock: aBlock [
<category: 'accessing'>
^self hashes
at: (self widgets indexOf: aWidget)
ifAbsent: ['']
hashBlock := aBlock
]
labelFor: aWidget [
items [
<category: 'accessing'>
^self labels
at: (self widgets indexOf: aWidget)
ifAbsent: ['']
^items
]
selectedWidget [
items: aCollection [
<category: 'accessing'>
^selectedWidget ifNil: [self widgets first]
items := aCollection
]
widgets [
labelBlock [
<category: 'accessing'>
^widgets
^labelBlock
]
widgets: aCollection [
"aCollection of widgets to be displayed in the tabs.
Each widget has an associated label, set with #labels: method"
labelBlock: aBlock [
<category: 'accessing'>
widgets := aCollection
labelBlock := aBlock
]
selectWidget: aWidget [
selectedItem [
<category: 'accessing'>
^selectedItem ifNil: [self items first]
]
selectedItem: anItem [
<category: 'accessing'>
selectedItem := anItem
]
selectItem: anItem [
<category: 'actions'>
selectedWidget := aWidget.
self selectedItem: anItem.
self markDirty
]
updateFromHash: aString [
<category: 'updating'>
self items do: [:each |
(self hashBlock value: each) = aString ifTrue: [
self selectedItem: each.
^self]]
]
]