1:- module(cplint_highligh, []).    2:- op(600, xfy, ::).

SWI-Prolog IDE and SWISH highlighting

This module defines highlight support for both the offline tools, notably PceEmacs and the graphical debugger, and the online cplint-on-SWISH. */

   11:- multifile prolog_colour:term_colours/2.   12
   13prolog_colour:term_colours((:- begin_lpad),
   14             neck(directive)-[cplint_directive]):-!.
   15
   16prolog_colour:term_colours((:- end_lpad),
   17             neck(directive)-[cplint_directive]):-!.
   18
   19prolog_colour:term_colours((:- begin_plp),
   20             neck(directive)-[cplint_directive]):-!.
   21
   22prolog_colour:term_colours((:- end_plp),
   23             neck(directive)-[cplint_directive]):-!.
   24
   25prolog_colour:term_colours((:- pita),
   26             neck(directive)-[cplint_directive]):-!.
   27
   28prolog_colour:term_colours((:- mc),
   29             neck(directive)-[cplint_directive]):-!.
   30
   31prolog_colour:term_colours((:- sc),
   32             neck(directive)-[cplint_directive]):-!.
   33
   34prolog_colour:term_colours((:- lemur),
   35             neck(directive)-[cplint_directive]):-!.
   36
   37prolog_colour:term_colours((:- begin_in),
   38             neck(directive)-[cplint_directive]):-!.
   39
   40prolog_colour:term_colours((:- end_in),
   41             neck(directive)-[cplint_directive]):-!.
   42
   43prolog_colour:term_colours((:- begin_bg),
   44             neck(directive)-[cplint_directive]):-!.
   45
   46prolog_colour:term_colours((:- end_bg),
   47             neck(directive)-[cplint_directive]):-!.
   48
   49prolog_colour:term_colours(begin(model(_)), model_delim - [model_delim - [classify]]):-!.
   50
   51prolog_colour:term_colours(end(model(_)), model_delim - [model_delim - [classify]]):-!.
   52
   53
   54prolog_colour:term_colours((H:-Body), neck(clause)-
   55  [C,body(Body)]):-
   56	(H=(_:_;_);(H=(_:P),is_annotation(P))),!,
   57	build_color(H,C).
   58
   59prolog_colour:term_colours(H,C):-
   60	(H=(_:_;_);(H=(_:P),is_annotation(P))),!,
   61	build_color(H,C).
   62
   63prolog_colour:term_colours((H:-Body), neck(clause)-
   64  [C,body(Body)]):-
   65	(H=(_::_;_);H=(_::_)),!,
   66	build_color_pb(H,C).
   67
   68prolog_colour:term_colours(H,C):-
   69	(H=(_::_;_);H=(_::_)),!,
   70	build_color_pb(H,C).
   71
   72is_annotation(A):-
   73	number(A),!.
   74
   75is_annotation(A):-
   76	var(A),!.
   77
   78is_annotation(A):-
   79	functor(A,F,_Ar),
   80	is_func(F),!.
   81
   82is_annotation(A):-
   83	functor(A,F,_Ar),
   84	is_cont_ann(F).
   85
   86
   87is_cont_ann(F):-
   88	member(F,[
   89	  uniform,gaussian,dirichlet,discrete,
   90		gamma,beta,poisson,binomial,geometric]),!.
   91
   92is_func(F):-
   93	member(F,[/,+,-,*,**,^]),!.
   94
   95build_color(H:P,annotation_symbol-[head(head,H),A]):-!,
   96  ann_colour(P,A).
   97
   98build_color((H:P;Rest),disjunction-[annotation_symbol-[head(head,H),A],RC]):-
   99  ann_colour(P,A),
  100	build_color(Rest,RC).
  101
  102build_color_pb(P::H,annotation_symbol-[A,head(head,H)]):-!,
  103  ann_colour(P,A).
  104
  105build_color_pb((P::H;Rest),disjunction-[annotation_symbol-[A,head(head,H)],RC]):-
  106  ann_colour(P,A),
  107	build_color_pb(Rest,RC).
  108
  109ann_colour(A,annotation):-
  110	number(A),!.
  111
  112ann_colour(A,annotation_function):-
  113	var(A),!.
  114
  115ann_colour(A,annotation_function):-
  116	functor(A,F,_Ar),
  117	is_cont_ann(F),!.
  118
  119ann_colour(A,annotation_function-Cols):-
  120	A=..[F|Ar],
  121	is_func(F),!,
  122	maplist(exp_col,Ar,Cols).
  123
  124exp_col(A,annotation):-
  125	number(A),!.
  126
  127exp_col(A,annotation_function):-
  128	var(A),!.
  129
  130exp_col(A,annotation_function-Cols):-
  131	A=..[F|Ar],
  132	is_func(F),!,
  133	maplist(exp_col,Ar,Cols).
  134
  135:- multifile prolog_colour:style/2.  136
  137prolog_colour:style(annotation,                  [colour(maroon), bold(true)]).
  138prolog_colour:style(annotation_function,                  [colour(maroon), bold(true)]).
  139prolog_colour:style(annotation_symbol,                  [colour(dark_red)]).
  140prolog_colour:style(disjunction,                  [colour(deep_pink),bold(true)]).
  141prolog_colour:style(cplint_directive,                  [colour(firebrick),bold(true)]).
  142prolog_colour:style(model_delim,                  [colour(firebrick),bold(true)]).
  143
  144:- multifile swish_highlight:style/3.  145
  146swish_highlight:style(annotation,  annotation, [base(number)]).
  147swish_highlight:style(annotation_function,   annotation_function,  [text, base(functor)]).
  148swish_highlight:style(annotation_symbol,   annotation_symbol,  [text, base(symbol)]).
  149swish_highlight:style(disjunction,  disjunction, [text, base(symbol)]).
  150swish_highlight:style(cplint_directive,  cplint_directive, [text, base(atom)]).
  151swish_highlight:style(model_delim,  model_delim, [text, base(symbol)])