1: ================================================================================
2:
3: Smalltalk.KSU defineClass: #ColorCMY
4: superclass: #{UI.ApplicationModel}
5: indexedType: #none
6: private: false
7: instanceVariableNames: 'cyanGauge magentaGauge yellowGauge '
8: classInstanceVariableNames: ''
9: imports: ''
10: category: 'KSU-Template'
11:
12: ================================================================================
13:
14: KSU.ColorCMY method for 'accessing'
15:
16: color
17:
18: | aColor |
19: aColor := ColorValue
20: cyan: (0 max: (self cyanGauge value min: 1))
21: magenta: (0 max: (self magentaGauge value min: 1))
22: yellow: (0 max: (self yellowGauge value min: 1)).
23: ^aColor
24:
25: ------------------------------------------------------------
26:
27: KSU.ColorCMY method for 'aspects'
28:
29: cyanGauge
30:
31: cyanGauge
32: ifNil:
33: [cyanGauge := 0.5 asValue.
34: cyanGauge compute: [:aValue | self updateColorCyan: aValue]].
35: ^cyanGauge
36:
37: ------------------------------------------------------------
38:
39: KSU.ColorCMY method for 'initialize-release'
40:
41: initialize
42:
43: super initialize.
44: cyanGauge := nil.
45: magentaGauge := nil.
46: yellowGauge := nil.
47: ^self
48:
49: ------------------------------------------------------------
50:
51: KSU.ColorCMY method for 'aspects'
52:
53: magentaGauge
54:
55: magentaGauge
56: ifNil:
57: [magentaGauge := 0.5 asValue.
58: magentaGauge compute: [:aValue | self updateColorMagenta: aValue]].
59: ^magentaGauge
60:
61: ------------------------------------------------------------
62:
63: KSU.ColorCMY method for 'interface opening'
64:
65: postOpenWith: aBuilder
66:
67: super postOpenWith: aBuilder.
68: self updateColor
69:
70: ------------------------------------------------------------
71:
72: KSU.ColorCMY method for 'private'
73:
74: updateColor
75:
76: self builder
77: ifNotNil:
78: [:aBuilder |
79: aBuilder window
80: ifNotNil:
81: [:aWindow |
82: aWindow
83: background: self color;
84: display]]
85:
86: ------------------------------------------------------------
87:
88: KSU.ColorCMY method for 'private'
89:
90: updateColorCyan: aValue
91:
92: InputState default altDown
93: ifTrue:
94: [self magentaGauge value = aValue ifFalse: [self magentaGauge value: aValue].
95: self yellowGauge value = aValue ifFalse: [self yellowGauge value: aValue]].
96: self updateColor
97:
98: ------------------------------------------------------------
99:
100: KSU.ColorCMY method for 'private'
101:
102: updateColorMagenta: aValue
103:
104: InputState default altDown
105: ifTrue:
106: [self cyanGauge value = aValue ifFalse: [self cyanGauge value: aValue].
107: self yellowGauge value = aValue ifFalse: [self yellowGauge value: aValue]].
108: self updateColor
109:
110: ------------------------------------------------------------
111:
112: KSU.ColorCMY method for 'private'
113:
114: updateColorYellow: aValue
115:
116: InputState default altDown
117: ifTrue:
118: [self cyanGauge value = aValue ifFalse: [self cyanGauge value: aValue].
119: self magentaGauge value = aValue ifFalse: [self magentaGauge value: aValue]].
120: self updateColor
121:
122: ------------------------------------------------------------
123:
124: KSU.ColorCMY method for 'aspects'
125:
126: yellowGauge
127:
128: yellowGauge
129: ifNil:
130: [yellowGauge := 0.5 asValue.
131: yellowGauge compute: [:aValue | self updateColorYellow: aValue]].
132: ^yellowGauge
133:
134: ================================================================================
135:
136: KSU.ColorCMY class
137: instanceVariableNames: ''
138:
139: ================================================================================
140:
141: KSU.ColorCMY class method for 'examples'
142:
143: example1
144: "KSU.ColorCMY example1."
145:
146: | anApplication |
147: anApplication := KSU.ColorCMY new.
148: anApplication open.
149: ^anApplication
150:
151: ------------------------------------------------------------
152:
153: KSU.ColorCMY class method for 'resources'
154:
155: menuBar
156: "Tools.MenuEditor new openOnClass: self andSelector: #menuBar"
157:
158: <resource: #menu>
159: ^#(#{UI.Menu} #(
160: #(#{UI.MenuItem}
161: #rawLabel: 'ファイル'
162: #submenu: #(#{UI.Menu} #(
163: #(#{UI.MenuItem}
164: #rawLabel: '終了'
165: #value: #closeRequest ) ) #(1 ) nil ) ) ) #(1 ) nil ) decodeAsLiteralArray
166:
167: ------------------------------------------------------------
168:
169: KSU.ColorCMY class method for 'interface specs'
170:
171: windowSpec
172: "Tools.UIPainter new openOnClass: self andSelector: #windowSpec"
173:
174: <resource: #canvas>
175: ^#(#{UI.FullSpec}
176: #window:
177: #(#{UI.WindowSpec}
178: #label: '減法混色'
179: #min: #(#{Core.Point} 512 160 )
180: #max: #(#{Core.Point} 512 160 )
181: #bounds: #(#{Graphics.Rectangle} 1023 719 1535 879 )
182: #flags: 4
183: #menu: #menuBar )
184: #component:
185: #(#{UI.SpecCollection}
186: #collection: #(
187: #(#{UI.LabelSpec}
188: #layout: #(#{Core.Point} 24 17 )
189: #name: #cyanLabel
190: #colors:
191: #(#{UI.LookPreferences}
192: #setBackgroundColor: #(#{Graphics.ColorValue} #pink ) )
193: #label: 'シアン :' )
194: #(#{UI.LabelSpec}
195: #layout: #(#{Core.Point} 24 49 )
196: #name: #magentaLabel
197: #colors:
198: #(#{UI.LookPreferences}
199: #setBackgroundColor: #(#{Graphics.ColorValue} 6143 8191 6143 ) )
200: #label: 'マゼンタ:' )
201: #(#{UI.LabelSpec}
202: #layout: #(#{Core.Point} 24 81 )
203: #name: #yellowLabel
204: #colors:
205: #(#{UI.LookPreferences}
206: #setBackgroundColor: #(#{Graphics.ColorValue} 6143 6143 8191 ) )
207: #label: 'イエロー:' )
208: #(#{UI.ProgressWidgetSpec}
209: #layout: #(#{Graphics.Rectangle} 232 17 488 40 )
210: #name: #cyanPercent
211: #isOpaque: true
212: #model: #cyanGauge
213: #direction: #horizontal
214: #position: #topLeft
215: #area: true
216: #reverse: false )
217: #(#{UI.ProgressWidgetSpec}
218: #layout: #(#{Graphics.Rectangle} 232 49 488 72 )
219: #name: #magentaPercent
220: #isOpaque: true
221: #model: #magentaGauge
222: #direction: #horizontal
223: #position: #topLeft
224: #area: true
225: #reverse: false )
226: #(#{UI.ProgressWidgetSpec}
227: #layout: #(#{Graphics.Rectangle} 232 81 488 104 )
228: #name: #yellowPercent
229: #isOpaque: true
230: #model: #yellowGauge
231: #direction: #horizontal
232: #position: #topLeft
233: #area: true
234: #reverse: false )
235: #(#{UI.SpinButtonSpec}
236: #layout: #(#{Graphics.Rectangle} 112 17 208 40 )
237: #name: #cyanGauge
238: #colors:
239: #(#{UI.LookPreferences}
240: #setBackgroundColor: #(#{Graphics.ColorValue} 6143 8191 8191 )
241: #setSelectionBackgroundColor: #(#{Graphics.ColorValue} 6143 8191 8191 ) )
242: #model: #cyanGauge
243: #tabable: false
244: #alignment: #center
245: #type: #number
246: #low: 0
247: #high: 1
248: #interval: 0.01 )
249: #(#{UI.SpinButtonSpec}
250: #layout: #(#{Graphics.Rectangle} 112 49 208 72 )
251: #name: #magentaGauge
252: #colors:
253: #(#{UI.LookPreferences}
254: #setBackgroundColor: #(#{Graphics.ColorValue} 8191 6143 8191 )
255: #setSelectionBackgroundColor: #(#{Graphics.ColorValue} 8191 6143 8191 ) )
256: #model: #magentaGauge
257: #tabable: false
258: #alignment: #center
259: #type: #number
260: #low: 0
261: #high: 1
262: #interval: 0.01 )
263: #(#{UI.SpinButtonSpec}
264: #layout: #(#{Graphics.Rectangle} 112 81 208 104 )
265: #name: #yellowGauge
266: #colors:
267: #(#{UI.LookPreferences}
268: #setBackgroundColor: #(#{Graphics.ColorValue} 8191 8191 6143 )
269: #setSelectionBackgroundColor: #(#{Graphics.ColorValue} 8191 8191 6143 ) )
270: #model: #yellowGauge
271: #tabable: false
272: #alignment: #center
273: #type: #number
274: #low: 0
275: #high: 1
276: #interval: 0.01 ) ) ) )
277:
278: ================================================================================
This document was generated by KSU.TextDoclet on 2012/11/10 at 10:40:36.