1: ================================================================================
2:
3: Smalltalk.KSU defineClass: #WorkDataSet
4: superclass: #{UI.ApplicationModel}
5: indexedType: #none
6: private: false
7: instanceVariableNames: 'selectionInList selectedRow currentFilename checkBlock '
8: classInstanceVariableNames: ''
9: imports: ''
10: category: ''
11:
12: ================================================================================
13:
14: KSU.WorkDataSet method for 'adding'
15:
16: addRow: aWorkProcess
17:
18: self addRow: aWorkProcess after: self workProcesses size
19:
20: ------------------------------------------------------------
21:
22: KSU.WorkDataSet method for 'adding'
23:
24: addRow: workProcess after: rowIndex
25:
26: | aList aCollection |
27: aList := List new.
28: aCollection := self workProcesses.
29: rowIndex isZero ifTrue: [aList add: workProcess].
30: aCollection with: (1 to: aCollection size)
31: do:
32: [:aWorkProcess :anIndex |
33: aList add: aWorkProcess.
34: anIndex = rowIndex ifTrue: [aList add: workProcess]].
35: self workProcesses: aList.
36: workProcess workParent: self
37:
38: ------------------------------------------------------------
39:
40: KSU.WorkDataSet method for 'adding'
41:
42: addRow: workProcess before: rowIndex
43:
44: self addRow: workProcess after: rowIndex - 1
45:
46: ------------------------------------------------------------
47:
48: KSU.WorkDataSet method for 'constructing'
49:
50: checkBlock
51:
52: ^checkBlock
53:
54: ------------------------------------------------------------
55:
56: KSU.WorkDataSet method for 'constructing'
57:
58: checkBlock: aBlock
59:
60: checkBlock := aBlock
61:
62: ------------------------------------------------------------
63:
64: KSU.WorkDataSet method for 'csv support'
65:
66: csvString: aString
67:
68: | aStream specialCharacters needDoubleQuote theString |
69: aStream := String new writeStream.
70: aStream
71: nextPut: $";
72: nextPut: $,;
73: nextPut: Character space;
74: nextPut: Character tab;
75: nextPut: Character cr;
76: nextPut: Character lf;
77: nextPut: Character newPage.
78: specialCharacters := aStream contents.
79: aStream close.
80: needDoubleQuote := false.
81: aString do: [:aCharacter | (specialCharacters includes: aCharacter) ifTrue: [needDoubleQuote := true]].
82: theString := aString.
83: needDoubleQuote
84: ifTrue:
85: [aStream := String new writeStream.
86: aStream nextPut: $".
87: aString do:
88: [:aCharacter |
89: aStream nextPut: aCharacter.
90: aCharacter = $" ifTrue: [aStream nextPut: aCharacter]].
91: aStream nextPut: $".
92: theString := aStream contents.
93: aStream close].
94: ^theString
95:
96: ------------------------------------------------------------
97:
98: KSU.WorkDataSet method for 'fileIn/Out'
99:
100: currentFilename
101:
102: ^currentFilename
103:
104: ------------------------------------------------------------
105:
106: KSU.WorkDataSet method for 'private'
107:
108: dataSetController
109:
110: ^[self controllerAt: #selectionInList] on: self class errorSignal
111: do: [:exception | exception returnWith: nil]
112:
113: ------------------------------------------------------------
114:
115: KSU.WorkDataSet method for 'private'
116:
117: dataSetView
118:
119: ^self dataSetController ifNil: [nil] ifNotNil: [:aController | aController view]
120:
121: ------------------------------------------------------------
122:
123: KSU.WorkDataSet method for 'defaults'
124:
125: defaultRowClass
126:
127: ^self class defaultRowClass
128:
129: ------------------------------------------------------------
130:
131: KSU.WorkDataSet method for 'menu messages'
132:
133: deleteRow
134:
135: self editCell
136: ifNil: [JunDialog warn: '削除したい行のセルを選択しておいてください。']
137: ifNotNil:
138: [:aPoint |
139: | aWorkProcess |
140: aWorkProcess := self workProcesses at: aPoint y.
141: (JunDialog confirm: '本当に「' , aWorkProcess workName , '」の行を削除しますか?'
142: initialAnswer: false) ifTrue: [self removeRow: aWorkProcess]]
143:
144: ------------------------------------------------------------
145:
146: KSU.WorkDataSet method for 'private'
147:
148: editCell
149:
150: ^self dataSetView ifNil: [nil] ifNotNil: [:aView | aView editCell]
151:
152: ------------------------------------------------------------
153:
154: KSU.WorkDataSet method for 'csv support'
155:
156: getChar: aStream
157:
158: | aCharacter |
159: aStream atEnd
160: ifTrue: [aCharacter := nil]
161: ifFalse:
162: [aCharacter := aStream next.
163: aCharacter = Character lf
164: ifTrue: [aCharacter := Character cr]
165: ifFalse: [aCharacter = Character cr ifTrue: [aStream peek = Character lf ifTrue: [aStream next]]]].
166: ^aCharacter
167:
168: ------------------------------------------------------------
169:
170: KSU.WorkDataSet method for 'csv support'
171:
172: getRowCSV: aStream
173:
174: | aCollection aBuffer aBoolean |
175: aCollection := OrderedCollection new.
176: aBuffer := String new writeStream.
177: aBoolean := true.
178: [aStream atEnd not and: [aBoolean]] whileTrue:
179: [| aCharacter |
180: aCharacter := self getChar: aStream.
181: aCharacter = Character cr
182: ifTrue: [aBoolean := false]
183: ifFalse:
184: [aCharacter = $,
185: ifTrue:
186: [aCollection add: aBuffer contents.
187: aBuffer close.
188: aBuffer := String new writeStream]
189: ifFalse:
190: [aCharacter = $"
191: ifTrue:
192: [| aLoop |
193: aLoop := true.
194: [aStream atEnd not and: [aLoop]] whileTrue:
195: [aCharacter := self getChar: aStream.
196: aCharacter = $"
197: ifTrue:
198: [aStream peek = $"
199: ifTrue:
200: [aStream next.
201: aBuffer nextPut: $"]
202: ifFalse: [aLoop := false]]
203: ifFalse: [aBuffer nextPut: aCharacter]]]
204: ifFalse: [aBuffer nextPut: aCharacter]]]].
205: aCollection add: aBuffer contents.
206: aBuffer close.
207: ^aCollection
208:
209: ------------------------------------------------------------
210:
211: KSU.WorkDataSet method for 'initialize-release'
212:
213: initialize
214:
215: super initialize.
216: selectionInList := nil.
217: selectedRow := nil.
218: currentFilename := nil.
219: checkBlock := nil.
220: ^self
221:
222: ------------------------------------------------------------
223:
224: KSU.WorkDataSet method for 'menu messages'
225:
226: insertRow
227:
228: | aWorkProcess |
229: aWorkProcess := self defaultRowClass emptyRow.
230: self editCell
231: ifNil: [self addRow: aWorkProcess]
232: ifNotNil: [:aPoint | self addRow: aWorkProcess before: aPoint y]
233:
234: ------------------------------------------------------------
235:
236: KSU.WorkDataSet method for 'menu messages'
237:
238: newDataSet
239:
240: ^(self class new)
241: open;
242: yourself
243:
244: ------------------------------------------------------------
245:
246: KSU.WorkDataSet method for 'menu messages'
247:
248: openDataSet
249:
250: | aFilename |
251: aFilename := JunFileDialog requestFilename: 'ファイルを選んでください。'
252: initialFilename: (self currentFilename ifNil: [self class defaultFilename] ifNotNil: [:it | it yourself]).
253: aFilename ifNil: [^nil].
254: self readDataSetFrom: aFilename
255:
256: ------------------------------------------------------------
257:
258: KSU.WorkDataSet method for 'printing'
259:
260: printOn: aStream
261:
262: aStream nextPutAll: self class name.
263: aStream nextPutAll: '('.
264: self workProcesses do:
265: [:aWorkProcess |
266: aStream crtab.
267: aWorkProcess printOn: aStream]
268: separatedBy: [aStream nextPutAll: ','].
269: aStream nextPutAll: ')'
270:
271: ------------------------------------------------------------
272:
273: KSU.WorkDataSet method for 'csv support'
274:
275: putRowCSV: aStream with: aRow
276:
277: aRow do:
278: [:each |
279: | aString |
280: aString := each isString ifTrue: [each] ifFalse: [each printString].
281: aStream nextPutAll: (self csvString: aString)]
282: separatedBy: [aStream nextPut: $,].
283: aStream cr
284:
285: ------------------------------------------------------------
286:
287: KSU.WorkDataSet method for 'fileIn/Out'
288:
289: readDataSetFrom: aFilename
290:
291: | aList |
292: aList := List new.
293: JunControlUtility
294: assert: [(aFilename withEncoding: #UTF_8) readStream]
295: do:
296: [:aStream |
297: [aStream atEnd not] whileTrue:
298: [| aRow aWorkProcess |
299: aRow := self getRowCSV: aStream.
300: aWorkProcess := self defaultRowClass fromRow: aRow.
301: aList add: aWorkProcess].
302: self workProcesses: aList]
303: ensure: [:aStream | aStream close].
304: currentFilename := aFilename
305:
306: ------------------------------------------------------------
307:
308: KSU.WorkDataSet method for 'removing'
309:
310: removeRow: aWorkProcess
311:
312: self workProcesses: (self workProcesses reject: [:each | each = aWorkProcess])
313:
314: ------------------------------------------------------------
315:
316: KSU.WorkDataSet method for 'menu messages'
317:
318: saveAsDataSet
319:
320: | aFilename |
321: aFilename := JunFileDialog requestNewFilename: 'ファイル名を入れてください。' initialFilename: self class defaultFilename.
322: aFilename ifNil: [^nil].
323: self writeDataSetTo: aFilename
324:
325: ------------------------------------------------------------
326:
327: KSU.WorkDataSet method for 'menu messages'
328:
329: saveDataSet
330:
331: self currentFilename ifNil: [self saveAsDataSet] ifNotNil: [:aFilename | self writeDataSetTo: aFilename]
332:
333: ------------------------------------------------------------
334:
335: KSU.WorkDataSet method for 'aspects'
336:
337: selectedRow
338:
339: selectedRow ifNil: [selectedRow := nil asValue].
340: ^selectedRow
341:
342: ------------------------------------------------------------
343:
344: KSU.WorkDataSet method for 'aspects'
345:
346: selectionInList
347:
348: selectionInList
349: ifNil:
350: [selectionInList := SelectionInList new.
351: selectionInList selectionIndexHolder
352: compute: [:anIndex | self selectedRow value: selectionInList selection]].
353: ^selectionInList
354:
355: ------------------------------------------------------------
356:
357: KSU.WorkDataSet method for 'accessing'
358:
359: workProcesses
360:
361: ^self selectionInList list
362:
363: ------------------------------------------------------------
364:
365: KSU.WorkDataSet method for 'accessing'
366:
367: workProcesses: aList
368:
369: ^self selectionInList list: aList asList
370:
371: ------------------------------------------------------------
372:
373: KSU.WorkDataSet method for 'fileIn/Out'
374:
375: writeDataSetTo: aFilename
376:
377: JunControlUtility
378: assert: [(aFilename withEncoding: #UTF_8) writeStream]
379: do:
380: [:aStream |
381: self workProcesses
382: do: [:aWorkProcess | self putRowCSV: aStream with: aWorkProcess asRow]]
383: ensure: [:aStream | aStream close].
384: currentFilename := aFilename
385:
386: ================================================================================
387:
388: KSU.WorkDataSet class
389: instanceVariableNames: ''
390:
391: ================================================================================
392:
393: KSU.WorkDataSet class method for 'defaults'
394:
395: defaultFilename
396: "KSU.WorkDataSet defaultFilename."
397:
398: | aDirectory aFilename |
399: aDirectory := [JunSystem homeDirectory construct: 'Desktop'] on: self class errorSignal
400: do: [:exception | exception returnWith: Filename defaultDirectory].
401: aFilename := aDirectory construct: 'WorkStataSet.csv'.
402: ^aFilename
403:
404: ------------------------------------------------------------
405:
406: KSU.WorkDataSet class method for 'defaults'
407:
408: defaultRowClass
409: "KSU.WorkDataSet defaultRowClass."
410:
411: ^KSU.WorkProcess
412:
413: ------------------------------------------------------------
414:
415: KSU.WorkDataSet class method for 'examples'
416:
417: example1
418: "KSU.WorkDataSet example1."
419:
420: | anApplication |
421: anApplication := KSU.WorkDataSet new.
422: anApplication open.
423: ^anApplication
424:
425: ------------------------------------------------------------
426:
427: KSU.WorkDataSet class method for 'examples'
428:
429: example2
430: "KSU.WorkDataSet example2."
431:
432: | anApplication |
433: anApplication := KSU.WorkDataSet new.
434: anApplication addRow: ((anApplication defaultRowClass new)
435: workName: '分析(オブジェクト指向分析)';
436: workStart: '2012/07/20';
437: workEnd: '2012/07/31';
438: workPerson: '青木淳';
439: yourself).
440: anApplication addRow: ((anApplication defaultRowClass new)
441: workName: '設計(オブジェクト指向デザイン)';
442: workStart: '2012/08/01';
443: workEnd: '2012/08/15';
444: workPerson: '梅原真奈美';
445: yourself).
446: anApplication addRow: ((anApplication defaultRowClass new)
447: workName: '実装(オブジェクト指向プログラミング)';
448: workStart: '2012/08/16';
449: workEnd: '2012/08/31';
450: workPerson: '西村祐里';
451: yourself).
452: anApplication open.
453: ^anApplication
454:
455: ------------------------------------------------------------
456:
457: KSU.WorkDataSet class method for 'examples'
458:
459: example3
460: "KSU.WorkDataSet example3."
461:
462: | anApplication |
463: anApplication := KSU.WorkDataSet new.
464: anApplication checkBlock:
465: [:aTable |
466: | aStream aString |
467: aStream := String new writeStream.
468: aStream nextPutAll: (aTable at: #column) printString.
469: aStream nextPutAll: 'を'.
470: aStream cr.
471: aStream nextPutAll: (aTable at: #previous) printString.
472: aStream nextPutAll: 'から'.
473: aStream cr.
474: aStream nextPutAll: (aTable at: #current) printString.
475: aStream nextPutAll: 'へと'.
476: aStream cr.
477: aStream nextPutAll: '変更することを許可しますか?'.
478: aString := aStream contents.
479: aStream close.
480: Dialog confirm: aString initialAnswer: false].
481: anApplication addRow: ((anApplication defaultRowClass new)
482: workName: '分析(オブジェクト指向分析)';
483: workStart: '2012/07/20';
484: workEnd: '2012/07/31';
485: workPerson: '青木淳';
486: yourself).
487: anApplication addRow: ((anApplication defaultRowClass new)
488: workName: '設計(オブジェクト指向デザイン)';
489: workStart: '2012/08/01';
490: workEnd: '2012/08/15';
491: workPerson: '梅原真奈美';
492: yourself).
493: anApplication addRow: ((anApplication defaultRowClass new)
494: workName: '実装(オブジェクト指向プログラミング)';
495: workStart: '2012/08/16';
496: workEnd: '2012/08/31';
497: workPerson: '西村祐里';
498: yourself).
499: anApplication open.
500: ^anApplication
501:
502: ------------------------------------------------------------
503:
504: KSU.WorkDataSet class method for 'resources'
505:
506: menuBar
507: "Tools.MenuEditor new openOnClass: self andSelector: #menuBar"
508:
509: <resource: #menu>
510: ^#(#{UI.Menu} #(
511: #(#{UI.MenuItem}
512: #rawLabel: 'ファイル'
513: #submenu: #(#{UI.Menu} #(
514: #(#{UI.MenuItem}
515: #rawLabel: '新規'
516: #value: #newDataSet )
517: #(#{UI.MenuItem}
518: #rawLabel: '開く…'
519: #value: #openDataSet )
520: #(#{UI.MenuItem}
521: #rawLabel: '保存'
522: #value: #saveDataSet )
523: #(#{UI.MenuItem}
524: #rawLabel: '別名で保存…'
525: #value: #saveAsDataSet )
526: #(#{UI.MenuItem}
527: #rawLabel: '終了'
528: #value: #closeRequest ) ) #(2 2 1 ) nil ) )
529: #(#{UI.MenuItem}
530: #rawLabel: '編集'
531: #submenu: #(#{UI.Menu} #(
532: #(#{UI.MenuItem}
533: #rawLabel: '行を挿入'
534: #value: #insertRow )
535: #(#{UI.MenuItem}
536: #rawLabel: '行を削除'
537: #value: #deleteRow ) ) #(1 1 ) nil ) )
538: #(#{UI.MenuItem}
539: #rawLabel: 'その他'
540: #submenu: #(#{UI.Menu} #(
541: #(#{UI.MenuItem}
542: #rawLabel: '検査'
543: #value: #inspect ) ) #(1 ) nil ) ) ) #(3 ) nil ) decodeAsLiteralArray
544:
545: ------------------------------------------------------------
546:
547: KSU.WorkDataSet class method for 'interface specs'
548:
549: windowSpec
550: "Tools.UIPainter new openOnClass: self andSelector: #windowSpec"
551:
552: <resource: #canvas>
553: ^#(#{UI.FullSpec}
554: #window:
555: #(#{UI.WindowSpec}
556: #label: '工程表'
557: #min: #(#{Core.Point} 400 300 )
558: #max: #(#{Core.Point} 0 0 )
559: #bounds: #(#{Graphics.Rectangle} 979 495 1579 945 )
560: #flags: 4
561: #menu: #menuBar )
562: #component:
563: #(#{UI.SpecCollection}
564: #collection: #(
565: #(#{UI.DataSetSpec}
566: #properties: #(#{UI.PropertyListDictionary} #allowColumnReordering false #showLineNumbers false #allowColumnResizing true #showVerticalLines true #rowSize 20 #showHorizontalLines true #rowLabelsAsButtons false )
567: #layout: #(#{Graphics.LayoutFrame} 2 0 2 0 -2 1 -2 1 )
568: #name: #selectionInList
569: #model: #selectionInList
570: #columns: #(
571: #(#{UI.DataSetColumnSpec}
572: #properties: #(#{UI.PropertyListDictionary} #allowSorting true )
573: #model: #'selectedRow workName'
574: #label: '工程名'
575: #labelIsImage: false
576: #width: 300
577: #editorType: #InputField
578: #noScroll: false )
579: #(#{UI.DataSetColumnSpec}
580: #properties: #(#{UI.PropertyListDictionary} #allowSorting true )
581: #model: #'selectedRow workStart'
582: #label: '開始日'
583: #labelIsImage: false
584: #width: 100
585: #editorType: #InputField
586: #noScroll: false )
587: #(#{UI.DataSetColumnSpec}
588: #properties: #(#{UI.PropertyListDictionary} #allowSorting true )
589: #model: #'selectedRow workEnd'
590: #label: '終了日'
591: #labelIsImage: false
592: #width: 100
593: #editorType: #InputField
594: #noScroll: false )
595: #(#{UI.DataSetColumnSpec}
596: #properties: #(#{UI.PropertyListDictionary} #allowSorting true )
597: #model: #'selectedRow workPerson'
598: #label: '担当者'
599: #labelIsImage: false
600: #width: 80
601: #editorType: #InputField
602: #noScroll: false ) ) ) ) ) )
603:
604: ================================================================================
This document was generated by KSU.TextDoclet on 2012/08/07 at 00:07:24.