1: ================================================================================
2:
3: Smalltalk.KSU defineClass: #DataSheet
4: superclass: #{UI.ApplicationModel}
5: indexedType: #none
6: private: false
7: instanceVariableNames: 'selectionInTable tableInterface inputField '
8: classInstanceVariableNames: ''
9: imports: ''
10: category: 'KSU-Template'
11:
12: ================================================================================
13:
14: KSU.DataSheet method for 'adding'
15:
16: addRow
17:
18: self addRowAfter: self rowSize
19:
20: ------------------------------------------------------------
21:
22: KSU.DataSheet method for 'adding'
23:
24: addRow: dataCollection after: rowIndex
25:
26: | twoDimensionalList aCollection |
27: twoDimensionalList := self selectionInTable table.
28: aCollection := OrderedCollection new: twoDimensionalList size + self columnSize.
29: rowIndex < self rowSize
30: ifTrue:
31: [twoDimensionalList with: (0 to: twoDimensionalList size - 1)
32: do:
33: [:anObject :anIndex |
34: | currentIndex |
35: currentIndex := anIndex // self columnSize.
36: (currentIndex = rowIndex and: [anIndex \\ self columnSize = 0])
37: ifTrue: [aCollection addAll: dataCollection].
38: aCollection add: anObject]]
39: ifFalse:
40: [twoDimensionalList do: [:anObject | aCollection add: anObject].
41: aCollection addAll: dataCollection].
42: twoDimensionalList := TwoDList
43: on: aCollection
44: columns: self columnSize
45: rows: aCollection size // self columnSize.
46: self selectionInTable table: twoDimensionalList.
47: self tableInterface rowLabelsArray: (1 to: self rowSize) asArray
48:
49: ------------------------------------------------------------
50:
51: KSU.DataSheet method for 'adding'
52:
53: addRowAfter: rowIndex
54:
55: self addRow: (Array new: self columnSize withAll: String new) after: rowIndex
56:
57: ------------------------------------------------------------
58:
59: KSU.DataSheet method for 'accessing'
60:
61: columnSize
62:
63: selectionInTable ifNil: [^4].
64: ^self selectionInTable table columnSize
65:
66: ------------------------------------------------------------
67:
68: KSU.DataSheet method for 'actions'
69:
70: contentsChangedInField: aString
71:
72: | aPoint |
73: aPoint := self selectionInTable selectionIndex.
74: aPoint = Point zero
75: ifFalse:
76: [| anObject |
77: anObject := self convertStringToObject: aString cellLocation: aPoint.
78: self selectionInTable table at: aPoint put: anObject]
79:
80: ------------------------------------------------------------
81:
82: KSU.DataSheet method for 'private'
83:
84: convertObjectToString: anObject
85:
86: | aString |
87: aString := (anObject isKindOf: String) ifTrue: [anObject yourself] ifFalse: [anObject printString].
88: ^aString
89:
90: ------------------------------------------------------------
91:
92: KSU.DataSheet method for 'private'
93:
94: convertStringToObject: aString cellLocation: aPoint
95:
96: | anObject |
97: aString isEmpty ifTrue: [^aString].
98: anObject := aPoint x > 1 ifTrue: [aString asNumber] ifFalse: [aString yourself].
99: ^anObject
100:
101: ------------------------------------------------------------
102:
103: KSU.DataSheet method for 'menu messages'
104:
105: deleteRow
106:
107: | aPoint |
108: aPoint := self selectionInTable selectionIndex.
109: aPoint = Point zero ifTrue: [self removeRow] ifFalse: [self removeRow: aPoint y]
110:
111: ------------------------------------------------------------
112:
113: KSU.DataSheet method for 'initialize-release'
114:
115: initialize
116:
117: super initialize.
118: selectionInTable := nil.
119: tableInterface := nil.
120: ^self
121:
122: ------------------------------------------------------------
123:
124: KSU.DataSheet method for 'aspects'
125:
126: inputField
127:
128: inputField
129: ifNil:
130: [inputField := String new asValue.
131: inputField compute: [:aString | self contentsChangedInField: aString]].
132: ^inputField
133:
134: ------------------------------------------------------------
135:
136: KSU.DataSheet method for 'menu messages'
137:
138: insertRow
139:
140: | aPoint |
141: aPoint := self selectionInTable selectionIndex.
142: aPoint = Point zero ifTrue: [self addRow] ifFalse: [self addRowAfter: aPoint y]
143:
144: ------------------------------------------------------------
145:
146: KSU.DataSheet method for 'removing'
147:
148: removeRow
149:
150: ^self removeRow: self rowSize
151:
152: ------------------------------------------------------------
153:
154: KSU.DataSheet method for 'removing'
155:
156: removeRow: rowIndex
157:
158: | twoDimensionalList aCollection aList |
159: rowIndex < 1 ifTrue: [^nil].
160: rowIndex > self rowSize ifTrue: [^nil].
161: twoDimensionalList := self selectionInTable table.
162: aCollection := OrderedCollection new: twoDimensionalList size - self columnSize.
163: aList := List new.
164: twoDimensionalList with: (0 to: twoDimensionalList size - 1)
165: do:
166: [:anObject :anIndex |
167: | currentIndex |
168: currentIndex := anIndex // self columnSize + 1.
169: currentIndex = rowIndex ifTrue: [aList add: anObject] ifFalse: [aCollection add: anObject]].
170: twoDimensionalList := TwoDList
171: on: aCollection
172: columns: self columnSize
173: rows: aCollection size // self columnSize.
174: self selectionInTable table: twoDimensionalList.
175: self tableInterface rowLabelsArray: (1 to: self rowSize) asArray.
176: ^aList asArray
177:
178: ------------------------------------------------------------
179:
180: KSU.DataSheet method for 'accessing'
181:
182: rowSize
183:
184: selectionInTable ifNil: [^0].
185: ^self selectionInTable table rowSize
186:
187: ------------------------------------------------------------
188:
189: KSU.DataSheet method for 'actions'
190:
191: selectionChangedinTable: aPoint
192:
193: aPoint = Point zero
194: ifFalse:
195: [| anObject aString |
196: anObject := self selectionInTable table at: aPoint.
197: aString := self convertObjectToString: anObject.
198: aString = self inputField value ifFalse: [self inputField value: aString]]
199:
200: ------------------------------------------------------------
201:
202: KSU.DataSheet method for 'aspects'
203:
204: selectionInTable
205:
206: selectionInTable
207: ifNil:
208: [| aCollection twoDimensionalList |
209: aCollection := OrderedCollection new.
210: aCollection addAll: #('じゅん for Smalltalk(790)' 990 33591 465281).
211: aCollection addAll: #('じゅん for Smalltalk(791)' 998 33764 467364).
212: aCollection addAll: #('じゅん for Smalltalk(792)' 998 33765 467456).
213: twoDimensionalList := TwoDList
214: on: aCollection
215: columns: self columnSize
216: rows: aCollection size // self columnSize.
217: selectionInTable := SelectionInTable with: twoDimensionalList.
218: selectionInTable selectionIndexHolder compute: [:aPoint | self selectionChangedinTable: aPoint]].
219: ^selectionInTable
220:
221: ------------------------------------------------------------
222:
223: KSU.DataSheet method for 'aspects'
224:
225: tableInterface
226:
227: tableInterface
228: ifNil:
229: [tableInterface := TableInterface new selectionInTable: self selectionInTable.
230: tableInterface
231: columnLabelsArray: #('ソフトウェア(バージョン)' 'クラス数' 'メソッド数' 'ステップ数');
232: columnWidths: #(200 80 80 80);
233: columnLabelsFormats: #(#left #right #right #right);
234: rowLabelsArray: (1 to: self rowSize) asArray;
235: rowLabelsWidth: 25;
236: rowLabelsFormat: #right;
237: elementFormats: #(#left #right #right #right)].
238: ^tableInterface
239:
240: ================================================================================
241:
242: KSU.DataSheet class
243: instanceVariableNames: ''
244:
245: ================================================================================
246:
247: KSU.DataSheet class method for 'examples'
248:
249: example1
250: "KSU.DataSheet example1."
251:
252: | anApplication |
253: anApplication := KSU.DataSheet new.
254: anApplication open.
255: ^anApplication
256:
257: ------------------------------------------------------------
258:
259: KSU.DataSheet class method for 'examples'
260:
261: example2
262: "KSU.DataSheet example2."
263:
264: | anApplication aList |
265: anApplication := KSU.DataSheet new.
266: anApplication open.
267: aList := (List new)
268: add: #('じゅん for Smalltalk(780)' 987 33486 463895);
269: add: #('じゅん for Smalltalk(781)' 987 33486 463897);
270: add: #('じゅん for Smalltalk(782)' 987 33502 464001);
271: add: #('じゅん for Smalltalk(783)' 987 33502 463993);
272: add: #('じゅん for Smalltalk(784)' 987 33502 463993);
273: add: #('じゅん for Smalltalk(785)' 987 33529 464186);
274: add: #('じゅん for Smalltalk(786)' 987 33529 464187);
275: add: #('じゅん for Smalltalk(787)' 990 33580 464964);
276: add: #('じゅん for Smalltalk(788)' 990 33591 465249);
277: add: #('じゅん for Smalltalk(789)' 990 33591 465285);
278: yourself.
279: aList with: (0 to: aList size - 1)
280: do:
281: [:anArray :anIndex |
282: 1 seconds wait.
283: anApplication addRow: anArray after: anIndex].
284: ^anApplication
285:
286: ------------------------------------------------------------
287:
288: KSU.DataSheet class method for 'resources'
289:
290: menuBar
291: "Tools.MenuEditor new openOnClass: self andSelector: #menuBar"
292:
293: <resource: #menu>
294: ^#(#{UI.Menu} #(
295: #(#{UI.MenuItem}
296: #rawLabel: 'ファイル'
297: #submenu: #(#{UI.Menu} #(
298: #(#{UI.MenuItem}
299: #rawLabel: '終了'
300: #value: #closeRequest ) ) #(1 ) nil ) )
301: #(#{UI.MenuItem}
302: #rawLabel: '編集'
303: #submenu: #(#{UI.Menu} #(
304: #(#{UI.MenuItem}
305: #rawLabel: '行を挿入'
306: #value: #insertRow )
307: #(#{UI.MenuItem}
308: #rawLabel: '行を削除'
309: #value: #deleteRow ) ) #(1 1 ) nil ) ) ) #(2 ) nil ) decodeAsLiteralArray
310:
311: ------------------------------------------------------------
312:
313: KSU.DataSheet class method for 'interface specs'
314:
315: windowSpec
316: "Tools.UIPainter new openOnClass: self andSelector: #windowSpec"
317:
318: <resource: #canvas>
319: ^#(#{UI.FullSpec}
320: #window:
321: #(#{UI.WindowSpec}
322: #label: 'データシート'
323: #min: #(#{Core.Point} 250 150 )
324: #max: #(#{Core.Point} 0 0 )
325: #bounds: #(#{Graphics.Rectangle} 1030 650 1530 950 )
326: #flags: 4
327: #menu: #menuBar )
328: #component:
329: #(#{UI.SpecCollection}
330: #collection: #(
331: #(#{UI.TableViewSpec}
332: #layout: #(#{Graphics.LayoutFrame} 2 0 28 0 -2 1 -2 1 )
333: #name: #tableInterface
334: #model: #tableInterface
335: #showHGrid: true
336: #showVGrid: true )
337: #(#{UI.InputFieldSpec}
338: #layout: #(#{Graphics.LayoutFrame} -128 0.5 2 0 128 0.5 26 0 )
339: #name: #inputField
340: #colors:
341: #(#{UI.LookPreferences}
342: #setBackgroundColor: #(#{Graphics.ColorValue} 8191 7167 7167 ) )
343: #model: #inputField ) ) ) )
344:
345: ================================================================================
This document was generated by KSU.TextDoclet on 2012/11/10 at 14:44:11.