35
36:- module(prolog_theme_dark, []). 37:- autoload(library(lists), [member/2]). 38:- autoload(library(pce), [send/2]). 39
46
47:- multifile
48 prolog:theme/1,
49 prolog:console_color/2,
50 pldoc_style:theme/3. 51
52prolog:theme(dark). 53
54:- if(current_predicate(win_window_color/2)). 55set_window_colors :-
56 win_window_color(background, rgb(0,0,0)),
57 win_window_color(foreground, rgb(255,255,255)),
58 win_window_color(selection_background, rgb(0,255,255)),
59 win_window_color(selection_foreground, rgb(0,0,0)).
60
61:- initialization
62 set_window_colors. 63:- endif. 64
65 68
70prolog:console_color(var, [hfg(cyan)]).
71prolog:console_color(code, [hfg(yellow)]).
73prolog:console_color(comment, [hfg(green)]).
74prolog:console_color(warning, [fg(yellow)]).
75prolog:console_color(error, [bold, fg(red)]).
77prolog:console_color(truth(false), [bold, fg(red)]).
78prolog:console_color(truth(true), [bold]).
79prolog:console_color(truth(undefined), [bold, fg(cyan)]).
80prolog:console_color(wfs(residual_program), [fg(cyan)]).
82prolog:console_color(frame(level), [bold]).
83prolog:console_color(port(call), [bold, fg(green)]).
84prolog:console_color(port(exit), [bold, fg(green)]).
85prolog:console_color(port(fail), [bold, fg(red)]).
86prolog:console_color(port(redo), [bold, fg(yellow)]).
87prolog:console_color(port(unify), [bold, fg(blue)]).
88prolog:console_color(port(exception), [bold, fg(magenta)]).
90prolog:console_color(message(informational), [hfg(green)]).
91prolog:console_color(message(information), [hfg(green)]).
92prolog:console_color(message(debug(_)), [hfg(yellow)]).
93prolog:console_color(message(Level), Attrs) :-
94 nonvar(Level),
95 prolog:console_color(Level, Attrs).
96
97
98 101
107
108pldoc_style:theme(var, true, [color(bright_cyan)]).
109pldoc_style:theme(code, true, [color(bright_yellow)]).
110pldoc_style:theme(pre, true, [color(bright_yellow)]).
111pldoc_style:theme(p, class(warning), [color(yellow)]).
112pldoc_style:theme(span, class('synopsis-hdr'), [color(bright_green)]).
113pldoc_style:theme(span, class(autoload), [color(bright_green)]).
114
115
116 119
120:- multifile
121 pce:on_load/0,
122 prolog_colour:style/2. 123
124prolog_colour:style(Class, Style) :-
125 style(Class, Style).
126
135
136style(goal(built_in,_), [colour(cyan)]).
137style(goal(imported(_),_), [colour(cyan)]).
138style(goal(autoload(_),_), [colour(dark_cyan)]).
139style(goal(global,_), [colour(dark_cyan)]).
140style(goal(undefined,_), [colour(orange)]).
141style(goal(thread_local(_),_), [colour(magenta), underline(true)]).
142style(goal(dynamic(_),_), [colour(magenta)]).
143style(goal(multifile(_),_), [colour(pale_green)]).
144style(goal(expanded,_), [colour(cyan), underline(true)]).
145style(goal(extern(_),_), [colour(cyan), underline(true)]).
146style(goal(extern(_,private),_), [colour(red)]).
147style(goal(extern(_,public),_), [colour(cyan)]).
148style(goal(recursion,_), [underline(true)]).
149style(goal(meta,_), [colour(red4)]).
150style(goal(foreign(_),_), [colour(darkturquoise)]).
151style(goal(local(_),_), []).
152style(goal(constraint(_),_), [colour(darkcyan)]).
153style(goal(not_callable,_), [background(orange)]).
154
155style(function, [colour(cyan)]).
156style(no_function, [colour(orange)]).
157
158style(option_name, [colour(dodgerblue)]).
159style(no_option_name, [colour(orange)]).
160
161style(head(exported,_), [colour(cyan), bold(true)]).
162style(head(public(_),_), [colour('#016300'), bold(true)]).
163style(head(extern(_),_), [colour(cyan), bold(true)]).
164style(head(dynamic,_), [colour(magenta), bold(true)]).
165style(head(multifile,_), [colour(pale_green), bold(true)]).
166style(head(unreferenced,_), [colour(red), bold(true)]).
167style(head(hook,_), [colour(cyan), underline(true)]).
168style(head(meta,_), []).
169style(head(constraint(_),_), [colour(darkcyan), bold(true)]).
170style(head(imported(_),_), [colour(darkgoldenrod4), bold(true)]).
171style(head(built_in,_), [background(orange), bold(true)]).
172style(head(iso,_), [background(orange), bold(true)]).
173style(head(def_iso,_), [colour(cyan), bold(true)]).
174style(head(def_swi,_), [colour(cyan), bold(true)]).
175style(head(_,_), [bold(true)]).
176style(rule_condition, [background(darkgreen)]).
177
178style(module(_), [colour(light_slate_blue)]).
179style(comment(_), [colour(green)]).
180
181style(directive, [background(grey20)]).
182style(method(_), [bold(true)]).
183
184style(var, [colour(orangered1)]).
185style(singleton, [bold(true), colour(orangered1)]).
186style(unbound, [colour(red), bold(true)]).
187style(quoted_atom, [colour(pale_green)]).
188style(string, [colour(pale_green)]).
189style(codes, [colour(pale_green)]).
190style(chars, [colour(pale_green)]).
191style(nofile, [colour(red)]).
192style(file(_), [colour(cyan), underline(true)]).
193style(file_no_depend(_), [colour(cyan), underline(true),
194 background(dark_violet)]).
195style(directory(_), [colour(cyan)]).
196style(class(built_in,_), [colour(cyan), underline(true)]).
197style(class(library(_),_), [colour(pale_green), underline(true)]).
198style(class(local(_,_,_),_), [underline(true)]).
199style(class(user(_),_), [underline(true)]).
200style(class(user,_), [underline(true)]).
201style(class(undefined,_), [colour(red), underline(true)]).
202style(prolog_data, [colour(cyan), underline(true)]).
203style(flag_name(_), [colour(cyan)]).
204style(no_flag_name(_), [colour(red)]).
205style(unused_import, [colour(cyan), background(maroon)]).
206style(undefined_import, [colour(red)]).
207
208style(constraint(_), [colour(darkcyan)]).
209
210style(keyword(_), [colour(cyan)]).
211style(identifier, [bold(true)]).
212style(delimiter, [bold(true)]).
213style(expanded, [colour(cyan), underline(true)]).
214style(hook(_), [colour(cyan), underline(true)]).
215style(op_type(_), [colour(cyan)]).
216
217style(qq_type, [bold(true)]).
218style(qq(_), [colour(cyan), bold(true)]).
219style(qq_content(_), [colour(coral2)]).
220
221style(dict_tag, [bold(true)]).
222style(dict_key, [bold(true)]).
223style(dict_function(_), [colour(pale_green)]).
224style(dict_return_op, [colour(cyan)]).
225
226style(hook, [colour(cyan), underline(true)]).
227style(dcg_right_hand_ctx, [background('#609080')]).
228
229style(error, [background(orange)]).
230style(type_error(_), [background(orange)]).
231style(syntax_error(_,_), [background(orange)]).
232style(instantiation_error, [background(orange)]).
233
234style(table_option(_), [bold(true)]).
235style(table_mode(_), [bold(true)]).
236
237
238 241
242:- op(200, fy, @). 243:- op(800, xfx, :=). 244
245pce:on_load :-
246 pce_set_defaults(true).
247
248:- initialization
249 setup_if_loaded. 250
251setup_if_loaded :-
252 current_predicate(pce:send/2),
253 !,
254 pce_set_defaults(true).
255setup_if_loaded.
256
257
262
263pce_set_defaults(Loaded) :-
264 pce_style(Class, Properties),
265 member(Prop, Properties),
266 Prop =.. [Name,Value],
267 term_string(Value, String),
268 send(@default_table, append, Name, vector(Class, String)),
269 update_class_variable(Loaded, Class, Name, Value),
270 update_instances(Class, Prop),
271 fail ; true.
272
273update_class_variable(true, ClassName, Name, Value) :-
274 get(@(classes), member, ClassName, Class),
275 !,
276 get(Class, class_variable, Name, ClassVar),
277 ( get(ClassVar, context, ContextClass),
278 get(ContextClass, name, ClassName)
279 -> send(ClassVar, value, Value)
280 ; new(_, class_variable(ClassName, Name, Value))
281 ).
282update_class_variable(_, _, _, _).
283
284update_instances(display, Prop) :-
285 send(@display, Prop).
286
292
294
295pce_style(display,
296 [ foreground(white),
297 background(black)
298 ]).
299
300pce_style(window,
301 [ colour(white),
302 background(black)
303 ]).
304
305pce_style(dialog,
306 [ colour(black),
307 background(grey80)
308 ]).
309
310pce_style(graphical,
311 [ selected_foreground(black),
312 selected_background(white)
313 ]).
314
315pce_style(text,
316 [ selection_style(style(background := yellow3,
317 colour := black))
318 ]).
319
321
322pce_style(terminal_image,
323 [ background(black),
324 colour(white),
325 selection_style(style(background := yellow, colour := black)),
326 ansi_colours(vector(colour(black), 327 colour(firebrick1), 328 colour(forestgreen), 329 colour(goldenrod), 330 colour(steelblue), 331 colour(mediumorchid), 332 colour(darkturquoise), 333 colour(lightgray), 334 335 colour(gray40), 336 colour(orangered), 337 colour(limegreen), 338 colour(khaki), 339 colour(dodgerblue), 340 colour(violet), 341 colour(cyan), 342 colour(snow) 343 ))
344 ]).
345
346pce_style(text_cursor,
347 [ colour(firebrick1)
348 ]).
349
351
352pce_style(text_item,
353 [ text_colour(white),
354 elevation(elevation('0,25mm', background := black))
355 ]).
356
357pce_style(menu,
358 [ text_colour(white)
359 ]).
360
361pce_style(list_browser,
362 [ selection_style(style(background := yellow, colour := black)),
363 isearch_style(style(background := green, colour := black))
364 ]).
365
367
368pce_style(text_image,
369 [ background(black),
370 colour(white)
371 ]).
372pce_style(text_margin,
373 [ background(grey20)
374 ]).
375pce_style(editor,
376 [ selection_style(style(background := yellow, colour := black)),
377 isearch_style(style(background := green, colour := black)),
378 isearch_other_style(style(background := pale_turquoise,
379 colour := black))
380 ]).
381
383
384pce_style(prolog_stack_view,
385 [ background(black)
386 ]).
387pce_style(prolog_stack_frame,
388 [ background(black),
389 colour(white)
390 ]).
391pce_style(prolog_stack_link,
392 [ colour(white)
393 ]).
394pce_style(prolog_bindings_view,
395 [ background_active(black),
396 background_inactive(grey50)
397 ]).
398pce_style(prolog_source_structure,
399 [ background(black),
400 colour(white)
401 ]).
402
404
405pce_style(prof_details,
406 [ header_background(khaki3)
407 ]).
408pce_style(prof_node_text,
409 [ colour('dodger_blue')
410 ]).
411
413
414pce_style(prolog_debug_browser,
415 [ enabled_style(style(colour := green))
416 ]).
417
419
420pce_style(xref_predicate_text,
421 [ colour(green),
422 colour_autoload(steel_blue),
423 colour_global(steel_blue)
424 ]).
425pce_style(xref_file_graph_node,
426 [ colour(white),
427 background(grey35)
428 ]).
429
431
432pce_style(man_editor,
433 [ jump_style(style(colour := green,
434 underline := true))
435 ]).
436
442
443:- multifile
444 prolog_source_view:port_style/2. 445
446prolog_source_view:port_style(call, [background(forest_green), colour(black)]).
447prolog_source_view:port_style(fail, [background(indian_red), colour(black)]).
448prolog_source_view:port_style(redo, [background(yellow3), colour(black)]).
449prolog_source_view:port_style(Type, [colour(black)]) :-
450 Type \== breakpoint