34
38
39:- module(pce_style_item, []). 40:- use_module(library(pce)). 41:- require([ default/3
42 , forall/2
43 ]). 44
45:- pce_autoload(font_item, library(pce_font_item)). 46:- pce_autoload(image_item, library(pce_image_item)). 47:- pce_autoload(tick_box, library(pce_tick_box)). 48
49style_attribute(highlight).
50style_attribute(underline).
51style_attribute(bold).
52style_attribute(grey).
53
54:- pce_begin_class(style_item, figure, ).
55
56variable(message, code*, both, ).
57variable(default, style, get, ).
58variable(selection, style, none, ).
59
60initialise(SI, Label:name, Default:[style], Message:[message]) :->
61 ::
62 send(SI, send_super, initialise),
63 send(SI, name, Label),
64 default(Message, @nil, Msg),
65 default(Default, new(style), Def),
66 send(SI, message, Msg),
67 send(SI, append_dialog_item,
68 tick_box(has_font, @off,
69 message(?(SI, member, font), active, @arg1))),
70 send(SI, append_dialog_item, font_item(font), right),
71 send(SI, append_dialog_item,
72 tick_box(has_icon, @off,
73 message(?(SI, member, icon), active, @arg1))),
74 send(SI, append_dialog_item, image_item(icon), right),
75 send(SI, append_dialog_item, new(AI, menu(attributes, toggle)), below),
76 forall(style_attribute(Att),
77 send(AI, append, Att)),
78 send(SI, layout_dialog, size(0,5)),
79 send(SI, default, Def).
80
81get_attributes(Style, Attrs) :-
82 new(Attrs, chain),
83 forall(style_attribute(Att),
84 ( get(Style, Att, @on)
85 -> send(Attrs, append, Att)
86 ; true
87 )).
88
89set_attributes(Style, Attrs) :-
90 forall(style_attribute(Att),
91 ( send(Attrs, member, Att)
92 -> send(Style, Att, @on)
93 ; send(Style, Att, @off)
94 )).
95
96
97font(SI, Font:[font]) :->
98 get(SI, member, has_font, Box),
99 get(SI, member, font, FontItem),
100 ( Font == @default
101 -> send(Box, selection, @off),
102 send(FontItem, active, @off)
103 ; send(Box, selection, has_font),
104 send(FontItem, active, @on),
105 send(FontItem, selection, Font)
106 ).
107font(SI, Font:[font]) :<-
108 get(SI, member, has_font, Box),
109 ( get(Box, selected, has_font, @off)
110 -> Font = @default
111 ; get(SI, member, font, FontItem),
112 get(FontItem, selection, Font)
113 ).
114
115icon(SI, Icon:image*) :->
116 get(SI, member, has_icon, Box),
117 get(SI, member, icon, ImageItem),
118 ( Icon == @nil
119 -> send(Box, selection, @off),
120 send(ImageItem, active, @off)
121 ; send(Box, selection, has_icon),
122 send(ImageItem, active, @on),
123 send(ImageItem, selection, Icon)
124 ).
125icon(SI, Icon:image*) :<-
126 get(SI, member, has_icon, Box),
127 ( get(Box, selected, has_icon, @off)
128 -> Icon = @nil
129 ; get(SI, member, icon, ImageItem),
130 get(ImageItem, selection, Icon)
131 ).
132
133
134selection(SI, Style:style) :->
135 ::
136 send(SI, slot, selection, Style),
137 send(SI, font, Style?font),
138 send(SI, icon, Style?icon),
139 get(SI, member, attributes, AI),
140 get_attributes(Style, Attrs),
141 send(AI, selection, Attrs).
142
143
144selection(SI, Style:style) :<-
145 ::
146 get(SI, slot, selection, Style),
147 send(Style, font, SI?font),
148 send(Style, icon, SI?icon),
149 get(SI, member, attributes, AI),
150 get(AI, selection, Attrs),
151 set_attributes(Style, Attrs).
152
153
154default(SI, Style:style) :->
155 ::
156 send(SI, slot, default, Style),
157 send(SI, restore).
158
159
160restore(SI) :->
161 ::
162 send(SI, selection, SI?default).
163
164
165apply(SI, _Always:[bool]) :->
166 ::
167 get(SI, message, Message),
168 ( Message \== @nil
169 -> get(SI, selection, Style),
170 send(Message, forward, Style)
171 ; true
172 ).
173
174
175:- pce_end_class