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