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(global(dynamic,_),_), [colour(magenta)]).
  141style(goal(global(_,_),_),       [colour(dark_cyan)]).
  142style(goal(undefined,_),         [colour(orange)]).
  143style(goal(thread_local(_),_),   [colour(magenta), underline(true)]).
  144style(goal(dynamic(_),_),        [colour(magenta)]).
  145style(goal(multifile(_),_),      [colour(pale_green)]).
  146style(goal(expanded,_),          [colour(cyan), underline(true)]).
  147style(goal(extern(_),_),         [colour(cyan), underline(true)]).
  148style(goal(extern(_,private),_), [colour(red)]).
  149style(goal(extern(_,public),_),  [colour(cyan)]).
  150style(goal(recursion,_),         [underline(true)]).
  151style(goal(meta,_),              [colour(red4)]).
  152style(goal(foreign(_),_),        [colour(darkturquoise)]).
  153style(goal(local(_),_),          []).
  154style(goal(constraint(_),_),     [colour(darkcyan)]).
  155style(goal(not_callable,_),      [background(orange)]).
  156
  157style(function,                  [colour(cyan)]).
  158style(no_function,               [colour(orange)]).
  159
  160style(option_name,               [colour(dodgerblue)]).
  161style(no_option_name,            [colour(orange)]).
  162
  163style(head(exported,_),          [colour(cyan), bold(true)]).
  164style(head(public(_),_),         [colour('#016300'), bold(true)]).
  165style(head(extern(_),_),         [colour(cyan), bold(true)]).
  166style(head(dynamic,_),           [colour(magenta), bold(true)]).
  167style(head(multifile,_),         [colour(pale_green), bold(true)]).
  168style(head(unreferenced,_),      [colour(red), bold(true)]).
  169style(head(hook,_),              [colour(cyan), underline(true)]).
  170style(head(meta,_),              []).
  171style(head(constraint(_),_),     [colour(darkcyan), bold(true)]).
  172style(head(imported(_),_),       [colour(darkgoldenrod4), bold(true)]).
  173style(head(built_in,_),          [background(orange), bold(true)]).
  174style(head(iso,_),               [background(orange), bold(true)]).
  175style(head(def_iso,_),           [colour(cyan), bold(true)]).
  176style(head(def_swi,_),           [colour(cyan), bold(true)]).
  177style(head(_,_),                 [bold(true)]).
  178style(rule_condition,            [background(darkgreen)]).
  179
  180style(module(_),                 [colour(light_slate_blue)]).
  181style(comment(_),                [colour(green)]).
  182
  183style(directive,                 [background(grey20)]).
  184style(method(_),                 [bold(true)]).
  185
  186style(var,                       [colour(orangered1)]).
  187style(singleton,                 [bold(true), colour(orangered1)]).
  188style(unbound,                   [colour(red), bold(true)]).
  189style(quoted_atom,               [colour(pale_green)]).
  190style(string,                    [colour(pale_green)]).
  191style(codes,                     [colour(pale_green)]).
  192style(chars,                     [colour(pale_green)]).
  193style(nofile,                    [colour(red)]).
  194style(file(_),                   [colour(cyan), underline(true)]).
  195style(file_no_depend(_),         [colour(cyan), underline(true),
  196                                  background(dark_violet)]).
  197style(directory(_),              [colour(cyan)]).
  198style(class(built_in,_),         [colour(cyan), underline(true)]).
  199style(class(library(_),_),       [colour(pale_green), underline(true)]).
  200style(class(local(_,_,_),_),     [underline(true)]).
  201style(class(user(_),_),          [underline(true)]).
  202style(class(user,_),             [underline(true)]).
  203style(class(undefined,_),        [colour(red), underline(true)]).
  204style(prolog_data,               [colour(cyan), underline(true)]).
  205style(flag_name(_),              [colour(cyan)]).
  206style(no_flag_name(_),           [colour(red)]).
  207style(unused_import,             [colour(cyan), background(maroon)]).
  208style(undefined_import,          [colour(red)]).
  209
  210style(constraint(_),             [colour(darkcyan)]).
  211
  212style(keyword(_),                [colour(cyan)]).
  213style(identifier,                [bold(true)]).
  214style(delimiter,                 [bold(true)]).
  215style(expanded,                  [colour(cyan), underline(true)]).
  216style(hook(_),                   [colour(cyan), underline(true)]).
  217style(op_type(_),                [colour(cyan)]).
  218
  219style(qq_type,                   [bold(true)]).
  220style(qq(_),                     [colour(cyan), bold(true)]).
  221style(qq_content(_),             [colour(coral2)]).
  222
  223style(dict_tag,                  [bold(true)]).
  224style(dict_key,                  [bold(true)]).
  225style(dict_function(_),          [colour(pale_green)]).
  226style(dict_return_op,            [colour(cyan)]).
  227
  228style(hook,                      [colour(cyan), underline(true)]).
  229style(dcg_right_hand_ctx,        [background('#609080')]).
  230
  231style(error,                     [background(orange)]).
  232style(type_error(_),             [background(orange)]).
  233style(syntax_error(_,_),         [background(orange)]).
  234style(instantiation_error,       [background(orange)]).
  235
  236style(table_option(_),           [bold(true)]).
  237style(table_mode(_),             [bold(true)]).
  238
  239
  240		 /*******************************
  241		 *         GUI DEFAULTS         *
  242		 *******************************/
  243
  244:- op(200, fy,  @).  245:- op(800, xfx, :=).  246
  247pce:on_load :-
  248    pce_set_defaults(true).
  249
  250:- initialization
  251    setup_if_loaded.  252
  253setup_if_loaded :-
  254    current_predicate(pce:send/2),
  255    !,
  256    pce_set_defaults(true).
  257setup_if_loaded.
  258
  259
  260%!  pce_set_defaults(+Loaded)
  261%
  262%   Adjust xpce defaults. This can either be   run before xpce is loaded
  263%   or as part of the xpce initialization.
  264
  265pce_set_defaults(Loaded) :-
  266    pce_style(Class, Properties),
  267    member(Prop, Properties),
  268    Prop =.. [Name,Value],
  269    term_string(Value, String),
  270    send(@default_table, append, Name, vector(Class, String)),
  271    update_class_variable(Loaded, Class, Name, Value),
  272    update_instances(Class, Prop),
  273    fail ; true.
  274
  275update_class_variable(true, ClassName, Name, Value) :-
  276    get(@(classes), member, ClassName, Class),
  277    !,
  278    get(Class, class_variable, Name, ClassVar),
  279    (   get(ClassVar, context, ContextClass),
  280        get(ContextClass, name, ClassName)
  281    ->  send(ClassVar, value, Value)
  282    ;   new(_, class_variable(ClassName, Name, Value))
  283    ).
  284update_class_variable(_, _, _, _).
  285
  286update_instances(display, Prop) :-
  287    send(@display, Prop).
  288
  289%!  pce_style(+Class, -Attributes)
  290%
  291%   Set XPCE class variables for Class. This is normally done by loading
  292%   a _resource file_, but doing it from   Prolog keeps the entire theme
  293%   in a single file.
  294
  295% General
  296
  297pce_style(display,
  298          [ foreground(white),
  299            background(black)
  300          ]).
  301
  302pce_style(window,
  303          [ colour(white),
  304            background(black)
  305          ]).
  306
  307pce_style(dialog,
  308          [ colour(black),
  309            background(grey80)
  310          ]).
  311
  312pce_style(graphical,
  313          [ selected_foreground(black),
  314            selected_background(white)
  315          ]).
  316
  317pce_style(text,
  318          [ selection_style(style(background := yellow3,
  319                                  colour := black))
  320          ]).
  321
  322% Epilog (next generation swipl-win)
  323
  324pce_style(terminal_image,
  325          [ background(black),
  326            colour(white),
  327            selection_style(style(background := yellow, colour := black)),
  328            ansi_colours(vector(colour(black),	   % black
  329                                colour(firebrick1),    % red
  330                                colour(forestgreen),   % green
  331                                colour(goldenrod),     % yellow
  332                                colour(steelblue),     % blue
  333                                colour(mediumorchid),  % magenta
  334                                colour(darkturquoise), % cyan
  335                                colour(lightgray),     % white
  336                                /* Bright versions */
  337                                colour(gray40),	   % black
  338                                colour(orangered),     % red
  339                                colour(limegreen),     % green
  340                                colour(khaki),         % yellow
  341                                colour(dodgerblue),    % blue
  342                                colour(violet),        % magenta
  343                                colour(cyan),          % cyan
  344                                colour(snow)           % white
  345                               ))
  346          ]).
  347
  348pce_style(text_cursor,
  349          [ colour(firebrick1)
  350          ]).
  351
  352% Dialog
  353
  354pce_style(text_item,
  355          [ text_colour(white),
  356            elevation(elevation('0,25mm', background := black))
  357          ]).
  358
  359pce_style(menu,
  360          [ text_colour(white)
  361          ]).
  362
  363pce_style(list_browser,
  364          [ selection_style(style(background := yellow, colour := black)),
  365            isearch_style(style(background := green, colour := black))
  366          ]).
  367
  368% PceEmacs
  369
  370pce_style(text_image,
  371          [ background(black),
  372            colour(white)
  373          ]).
  374pce_style(text_margin,
  375          [ background(grey20)
  376          ]).
  377pce_style(editor,
  378          [ selection_style(style(background := yellow, colour := black)),
  379            isearch_style(style(background := green, colour := black)),
  380            isearch_other_style(style(background := pale_turquoise,
  381                                      colour := black))
  382          ]).
  383
  384% Graphical debugger
  385
  386pce_style(prolog_stack_view,
  387          [ background(black)
  388          ]).
  389pce_style(prolog_stack_frame,
  390          [ background(black),
  391            colour(white)
  392          ]).
  393pce_style(prolog_stack_link,
  394          [ colour(white)
  395          ]).
  396pce_style(prolog_bindings_view,
  397          [ background_active(black),
  398            background_inactive(grey50)
  399          ]).
  400pce_style(prolog_source_structure,
  401          [ background(black),
  402            colour(white)
  403          ]).
  404
  405% Profiler
  406
  407pce_style(prof_details,
  408          [ header_background(khaki3)
  409          ]).
  410pce_style(prof_node_text,
  411          [ colour('dodger_blue')
  412          ]).
  413
  414% Debug messages
  415
  416pce_style(prolog_debug_browser,
  417          [ enabled_style(style(colour := green))
  418          ]).
  419
  420% Cross referencer
  421
  422pce_style(xref_predicate_text,
  423          [ colour(green),
  424            colour_autoload(steel_blue),
  425            colour_global(steel_blue)
  426          ]).
  427pce_style(xref_file_graph_node,
  428          [ colour(white),
  429            background(grey35)
  430          ]).
  431
  432% XPCE manual
  433
  434pce_style(man_editor,
  435          [ jump_style(style(colour := green,
  436                             underline := true))
  437          ]).
  438
  439%!  prolog_source_view:port_style(+Port, -StyleAttributes)
  440%
  441%   Override style attributes for indicating  a   specific  port  in the
  442%   source view. Ports are:  `call`,   `break`,  `exit`, `redo`, `fail`,
  443%   `exception`, `unify`, `choice`, `frame and `breakpoint`.
  444
  445:- multifile
  446    prolog_source_view:port_style/2.  447
  448prolog_source_view:port_style(call, [background(forest_green), colour(black)]).
  449prolog_source_view:port_style(fail, [background(indian_red),   colour(black)]).
  450prolog_source_view:port_style(redo, [background(yellow3),      colour(black)]).
  451prolog_source_view:port_style(Type, [colour(black)]) :-
  452    Type \== breakpoint