View source with formatted comments or as raw
    1/*  Part of SWI-Prolog
    2
    3    Author:        Jan Wielemaker
    4    E-mail:        J.Wielemaker@vu.nl
    5    WWW:           http://www.swi-prolog.org
    6    Copyright (c)  2019-2025, VU University Amsterdam
    7                              SWI-Prolog Solutions b.v.
    8    All rights reserved.
    9
   10    Redistribution and use in source and binary forms, with or without
   11    modification, are permitted provided that the following conditions
   12    are met:
   13
   14    1. Redistributions of source code must retain the above copyright
   15       notice, this list of conditions and the following disclaimer.
   16
   17    2. Redistributions in binary form must reproduce the above copyright
   18       notice, this list of conditions and the following disclaimer in
   19       the documentation and/or other materials provided with the
   20       distribution.
   21
   22    THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
   23    "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
   24    LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
   25    FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
   26    COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
   27    INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
   28    BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
   29    LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
   30    CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
   31    LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
   32    ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
   33    POSSIBILITY OF SUCH DAMAGE.
   34*/
   35
   36:- module(prolog_theme_dark, []).   37:- autoload(library(lists), [member/2]).   38:- autoload(library(pce), [send/2]).   39
   40/** <module> SWI-Prolog theme file -- dark
   41
   42To enable the dark theme, use
   43
   44    :- use_module(library(theme/dark)).
   45*/
   46
   47:- multifile
   48    prolog:theme/1,
   49    prolog:console_color/2,
   50    pldoc_style:theme/3.   51
   52prolog:theme(dark).                             % make ourselves known
   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		 /*******************************
   66		 *       PROLOG MESSAGES	*
   67		 *******************************/
   68
   69% code embedded in messages (not used much yet)
   70prolog:console_color(var,                    [hfg(cyan)]).
   71prolog:console_color(code,                   [hfg(yellow)]).
   72% Alert level
   73prolog:console_color(comment,                [hfg(green)]).
   74prolog:console_color(warning,                [fg(yellow)]).
   75prolog:console_color(error,                  [bold, fg(red)]).
   76% toplevel truth value (undefined for well founded semantics)
   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)]).
   81% trace output
   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)]).
   89% print message. the argument for debug(_) is the debug channel.
   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		 /*******************************
   99		 *          ONLINE HELP		*
  100		 *******************************/
  101
  102%!  pldoc_style:theme(+Element, +Condition, -CSSAttributes) is semidet.
  103%
  104%   Return a set of CSS properties to modify on the specified Element if
  105%   Condition   holds.   color(Name)   is   mapped   to   fg(Name)   and
  106%   color(bright_Name) to hfg(Name).
  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		 /*******************************
  117		 *           IDE TOOLS		*
  118		 *******************************/
  119
  120:- multifile
  121    pce:on_load/0,
  122    prolog_colour:style/2.  123
  124prolog_colour:style(Class, Style) :-
  125    style(Class, Style).
  126
  127%!  style(+Class, -Style)
  128%
  129%   Map style classes defined in   library(prolog_colour)  to xpce style
  130%   objects. After making modifications the effect can be tested without
  131%   restarting using this sequence:
  132%
  133%     1. Run ``?- make`` in Prolog
  134%     2. In the editor, use ``M-x reload_styles``
  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		 /*******************************
  239		 *         GUI DEFAULTS         *
  240		 *******************************/
  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
  258%!  pce_set_defaults(+Loaded)
  259%
  260%   Adjust xpce defaults. This can either be   run before xpce is loaded
  261%   or as part of the xpce initialization.
  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
  287%!  pce_style(+Class, -Attributes)
  288%
  289%   Set XPCE class variables for Class. This is normally done by loading
  290%   a _resource file_, but doing it from   Prolog keeps the entire theme
  291%   in a single file.
  292
  293% General
  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
  320% Epilog (next generation swipl-win)
  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),	   % black
  327                                colour(firebrick1),    % red
  328                                colour(forestgreen),   % green
  329                                colour(goldenrod),     % yellow
  330                                colour(steelblue),     % blue
  331                                colour(mediumorchid),  % magenta
  332                                colour(darkturquoise), % cyan
  333                                colour(lightgray),     % white
  334                                /* Bright versions */
  335                                colour(gray40),	   % black
  336                                colour(orangered),     % red
  337                                colour(limegreen),     % green
  338                                colour(khaki),         % yellow
  339                                colour(dodgerblue),    % blue
  340                                colour(violet),        % magenta
  341                                colour(cyan),          % cyan
  342                                colour(snow)           % white
  343                               ))
  344          ]).
  345
  346pce_style(text_cursor,
  347          [ colour(firebrick1)
  348          ]).
  349
  350% Dialog
  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
  366% PceEmacs
  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
  382% Graphical debugger
  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
  403% Profiler
  404
  405pce_style(prof_details,
  406          [ header_background(khaki3)
  407          ]).
  408pce_style(prof_node_text,
  409          [ colour('dodger_blue')
  410          ]).
  411
  412% Debug messages
  413
  414pce_style(prolog_debug_browser,
  415          [ enabled_style(style(colour := green))
  416          ]).
  417
  418% Cross referencer
  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
  430% XPCE manual
  431
  432pce_style(man_editor,
  433          [ jump_style(style(colour := green,
  434                             underline := true))
  435          ]).
  436
  437%!  prolog_source_view:port_style(+Port, -StyleAttributes)
  438%
  439%   Override style attributes for indicating  a   specific  port  in the
  440%   source view. Ports are:  `call`,   `break`,  `exit`, `redo`, `fail`,
  441%   `exception`, `unify`, `choice`, `frame and `breakpoint`.
  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