1/* Part of LogicMOO Base Logicmoo Path Setups
    2% ===================================================================
    3    File:         'logicmoo_util_library.pl'
    4    Purpose:       To load the logicmoo libraries as needed
    5    Contact:       $Author: dmiles $@users.sourceforge.net ;
    6    Version:       'logicmoo_util_library.pl' 1.0.0
    7    Revision:      $Revision: 1.7 $
    8    Revised At:    $Date: 2002/07/11 21:57:28 $
    9    Author:        Douglas R. Miles
   10    Maintainers:   logicmoo
   11    E-mail:        logicmoo@gmail.com
   12    WWW:           http://www.logicmoo.org
   13    SCM:           https://github.com/logicmoo/PrologMUD/tree/master/pack/logicmoo_base
   14    Copyleft:      1999-2015, LogicMOO Prolog Extensions
   15    License:       Lesser GNU Public License
   16% ===================================================================
   17
   18%:- use_module(library(logicmoo/butterfly_console)).
   19
   20*/
   21
   22% We save the name of the module loading this module
   23:- if(current_prolog_flag(xref,true)).  % XREF
   24:- if((prolog_load_context(source,F),prolog_load_context(file,F))).   25:- module(butterfly,[bformat/1,bformat/2,bformat/3,
   26  is_butterfly_console/0,
   27  set_is_butterfly_console/1,
   28  bfly_test/1,
   29  write_html/1,
   30  bfly_tests/0,
   31  send_tokens/1,
   32  sccs/3,
   33  pre_style/0,mouse_over_span/0]).   34:- endif.   35:- endif.   36
   37:- define_into_module([
   38  bformat/1,bformat/2,bformat/3,
   39  is_butterfly_console/0,
   40  set_is_butterfly_console/1,
   41  bfly_test/1,
   42  write_html/1,
   43  bfly_tests/0,
   44  bfly/0,
   45  sccs/3,
   46  print_raw_html_page/1,
   47  send_tokens/1,
   48  pre_style/0,mouse_over_span/0]).   49
   50:- use_module(library(logicmoo_common)).   51:- use_module(library(logicmoo/pretty_clauses)).   52
   53:- thread_local(t_l:in_block_format/0).   54:- dynamic(lmcache:is_butterfly_thread/2).   55
   56%:- use_module(library(pengines)).
   57:- pengine_sandbox:use_module(library(pengines)).   58:- use_module(library(http/html_write)).   59:- autoload(library(http/html_write),[html/3,print_html/1]).   60:- autoload(library(lynx/html_text),[html_text/2]).   61
   62set_is_butterfly_console(TF):- thread_self(X), retractall(lmcache:is_butterfly_thread(X,_)),
   63  asserta(lmcache:is_butterfly_thread(X,TF)),!, (TF==t->pre_style;true).
   64
   65:- meta_predicate(wbfc(0)).   66wbfc(G):-G=true,!,set_is_butterfly_console(t).
   67wbfc(G):-G=false,!,set_is_butterfly_console(f).
   68wbfc(Goal):-with_butterfly_console(t,Goal).
   69
   70:- meta_predicate(with_butterfly_console(+,0)).   71with_butterfly_console(TF,Goal):- in_bfly(TF,Goal).
   72%with_butterfly_console(TF,Goal):- thread_self(X), %retractall(lmcache:is_butterfly_thread(X,_)),
   73%  sccs(asserta(lmcache:is_butterfly_thread(X,TF),Ref),Goal,erase(Ref)).
   74
   75is_butterfly_console:- toplevel_pp(bfly),!.
   76is_butterfly_console:- thread_self(X), lmcache:is_butterfly_thread(X,TF),!,TF==t.
   77is_butterfly_console:- getenv('COLORTERM',butterfly),!.
   78%is_butterfly_console:- thread_self(X),atom(X),(atom_concat(_,'23',X);atom_concat(_,'01',X);atom_concat(_,'00',X)),!.
   79
   80
   81block_format(G):- t_l:in_block_format,!,call(G).
   82block_format(G):- wots((S),locally(t_l:in_block_format,G)),bformat(S),!.
   83
   84
   85%bfly_write_html(S):- !, format_safely("(HTML ~w)",[S]),!.
   86%bfly_write_html(P):- format_safely("\x90;HTML|~w\x93",[P]).
   87%bfly_write_html(P):- format_safely("P;HTML|~wP",[P]),!. %'
   88%bfly_write_html(S):- format_safely("\x1bP;HTML|~w\x1bP",[S]),end_escape.
   89
   90%bfly_write_html(S):- rich_output(Out),!,with_output_to(Out,bfly_write_html(S)).
   91
   92%bformat(P):- is_visible_output,is_butterfly_console,format_safely(string(S),'~w',[P]),atom_contains(S,'<'),!,bformat(S).
   93%
   94
   95
   96%:- /*system:*/use_module(library(http/term_html)).
   97:- /*system:*/use_module(pretty_clauses,[bfly_term//2]).   98
   99:- /*system:*/use_module(library(http/thread_httpd)).  100:- /*system:*/use_module(thread_httpd:library(http/http_dispatch)).  101%:- use_module(library(http/http_dispatch))
  102
  103:- if( exists_source(swi(library/http/html_head))).  104:- /*system:*/use_module(swi(library/http/html_head)).  105:- else.  106  :- if( exists_source(library(http/html_head))).  107    :- /*system:*/use_module(library(http/html_head)).  108  :-endif.  109:-endif.  110
  111
  112:- /*system:*/use_module(library(http/http_dispatch)).  113:- /*system:*/use_module(library(http/http_path)).  114:- /*system:*/use_module(library(http/http_log)).  115:- /*system:*/use_module(library(http/http_client)).  116:- /*system:*/use_module(library(http/http_server_files)).  117:- /*system:*/use_module(library(http/http_parameters)).  118
  119:- /*system:*/use_module(library(uri)).  120:- /*system:*/use_module(library(http/http_openid)).  121:- /*system:*/use_module(library(http/http_host)).  122% :- use_module(library(http/html_write)).
  123:- /*system:*/use_module(library(http/http_error)).  124
  125%:- abolish(bfly_dyn:bfly_style_type/6).
  126:- dynamic(bfly_dyn:bfly_style_type/6).  127:- volatile(bfly_dyn:bfly_style_type/6).  128
  129%:- abolish(bfly_dyn:bfly_style_answered/0).
  130:- dynamic(bfly_dyn:bfly_style_answered/0).  131:- volatile(bfly_dyn:bfly_style_answered/0).  132
  133
  134%:- abolish(bfly_dyn:bfly_style_asked/1).
  135:- dynamic(bfly_dyn:bfly_style_asked/1).  136:- volatile(bfly_dyn:bfly_style_asked/1).  137
  138maybe_into_number(A,Num):- number(A),!,Num=A.
  139maybe_into_number(A,Num):- \+ string(A), sformat_safe(S,'~w',[A]), string(S),!, maybe_into_number(S,Num),!.
  140maybe_into_number(A,Num):- atomic_list_concat([_|Es],'/',A), Es\==[], last(Es,E),!,maybe_into_number(E,Num).
  141maybe_into_number(A,Num):- atom_number(A,Num),!.
  142maybe_into_number(_,Num):- Num is -1.
  143
  144use_pts_files:- fail.
  145
  146bfly_reoffer:- \+ use_pts_files,!.
  147bfly_reoffer:-
  148  bfly_info,
  149  retractall(bfly_dyn:bfly_style_type(_,_,_,_,_,_)),
  150  retractall(bfly_dyn:bfly_style_asked(_)),
  151  retractall(bfly_dyn:bfly_style_answered),
  152  bfly_offer(60),
  153  bfly_info.
  154
  155bfly_offer:- bfly_offer(15).
  156
  157bfly_offer(_Duration):- \+ use_pts_files,!.
  158bfly_offer( Duration):-
  159  expand_file_name('/dev/pts/*',[_,_|X]),
  160  retractall(bfly_dyn:bfly_style_asked(_)),
  161  retractall(bfly_dyn:bfly_style_answered),
  162  forall(member(E,X),bfly_ask_style(E)),
  163  get_time(Time), Until is Time + Duration,
  164  (repeat,
  165    ((get_time(TimeNow), TimeNow > Until)
  166       -> true ;
  167       wait_for_input_or_web)), !.
  168
  169bfly_start:- do_each_main_interval(bfly_offer(15), 60).
  170%bfly_start:- initialization(do_each_main_interval(bfly_offer(15), 60), program).
  171%:- add_history(bfly_start).
  172:- export(bfly_start/0).  173
  174wait_for_input_or_web:- \+ bfly_dyn:bfly_style_asked(_),!.
  175wait_for_input_or_web:- bfly_dyn:bfly_style_answered,!.
  176wait_for_input_or_web:- with_tty_raw((
  177  wait_for_input([user_input], In, 0.3),
  178  (In==[]-> (!,fail) ;
  179   (get_single_char(H),!, asserta(bfly_dyn:bfly_style_answered), bfly_key_accept(H))))),!.
  180
  181bfly_key_accept(H):- H = 32,  retractall(bfly_dyn:bfly_style_asked(_)),!.
  182bfly_key_accept(H):- H> 96, PTS is H-96, bfly_decl_style_key(PTS,ansi),!.
  183bfly_key_accept(H):- H> 64, PTS is H-64, bfly_decl_style_key(PTS,ansi),!.
  184
  185bfly_decl_style_key(Num,_Style):- \+ bfly_dyn:bfly_style_asked(Num),!.
  186bfly_decl_style_key(Num, Style):- thread_self(TID),bfly_decl_1_style(TID,Num,Style).
  187
  188:- export(bfly_decl_style_http/1).  189bfly_decl_style_http(Request) :-
  190  member(search(List),Request),
  191  member(tid=TID,List), member(pts=PTS,List), member(style=Style,List),
  192  bfly_decl_1_style(TID,PTS,Style),!,
  193  print_term_to_html_page(Request).
  194
  195
  196print_term_to_html_page(Tree):-
  197  wots(S,
  198    in_pp_html((nl,print_tree_nl(Tree)))),
  199  print_raw_html_page(S), !.
  200
  201print_raw_html_page(S):-
  202  phrase(pretty_clauses:html([
  203     html([head(''),body(pre( \ html_raw(S)))])]), Tokens),!,
  204     print_html(Tokens).
  205
  206%:-  http_handler(swish(logicmoo), xlisting_web:handler_logicmoo_cyclone, [id(handler_logicmoo_cyclone)]). % chunked
  207%:-  http_handler(swish(nc_logicmoo), xlisting_web:handler_logicmoo_cyclone1, [chunked,id(handler_logicmoo_cyclone1)]).
  208%:- http_handler('/swish/bfly_decl_1_style',butterfly:bfly_decl_1_style,[prefix]).
  209:- http_handler(('/swish/bfly_decl_style'),bfly_decl_style_http,[chunked,methods([get,post,put])]).  210
  211
  212:- export(bfly_decl_1_style/3).  213bfly_decl_1_style(TID,PTSA,Style):- \+ number(PTSA), maybe_into_number(PTSA,Num), number(Num), !, bfly_decl_1_style(TID,Num,Style).
  214%bfly_decl_1_style(_TID,Num,_Style):- \+ bfly_dyn:bfly_style_asked(Num),!.
  215bfly_decl_1_style(TID,Num,Style):-
  216  %id_to_href(ID,HREF),
  217  ignore(bfly_dyn:bfly_style_type(TID,E,Num,In,Out,_Was)),
  218  forall(bfly_dyn:bfly_style_type(TID,E,Num,In,Out,_),
  219          retractall(bfly_dyn:bfly_style_type(TID,E,Num,In,Out,_))),
  220  asserta(bfly_dyn:bfly_style_type(TID,E,Num,In,Out,Style)),
  221  asserta(bfly_dyn:bfly_style_answered),
  222  retractall(bfly_dyn:bfly_style_asked(_)),!.
  223
  224
  225print_tree_html(Term):- current_print_write_options(Options), print_tree_html(Term, Options).
  226print_tree_html(Term, Options):- in_pp_html(print_tree(Term,Options)).
  227
  228
  229print_html_term(Term):- current_print_write_options(Options), print_html_term(Term, Options).
  230print_html_term(Term, Options):-
  231 must_or_rtrace(phrase(bfly_term(Term,Options),Tokens)),!,
  232 must_or_rtrace(send_tokens(Tokens)),!.
  233
  234
  235remove_if_last(Tokens,TokensRight,TokensLeft):-append(TokensLeft,TokensRight,Tokens),!.
  236remove_if_last(TokensRightLeft,_,TokensRightLeft).
  237
  238send_tokens(['<',html,'>'|Tokens]):-!,remove_if_last(Tokens,['</',html,'>'],TokensLeft),send_tokens_1(TokensLeft).
  239send_tokens(Tokens):- send_tokens_1(Tokens).
  240send_tokens_1([nl(1)|Tokens]):-!,remove_if_last(Tokens,[nl(1)],TokensLeft),send_tokens(TokensLeft).
  241send_tokens_1(Tokens):- with_output_to(string(HTMLString), html_write:print_html(Tokens)),write_html(HTMLString).
  242
  243write_html(HTMLString):- our_pengine_output(HTMLString),!.
  244%write_html(HTMLString):- ((pengines:pengine_self(_) -> pengines:pengine_output(HTMLString) ;write(HTMLString))),!.
  245%write_html(HTMLString):- bfly_html_goal(format_safely('~w',HTMLString)).
  246
  247/*
  248set_html_stream_encoding:- set_stream_encoding(utf8).
  249
  250as_html_encoded(Goal):- with_enc(utf8,Goal).
  251
  252with_enc(Enc,Goal):-
  253 stream_property(current_output,encoding(Was)),
  254 sccs(current_prolog_flag(encoding,EncWas),
  255 (( ignore(catch(set_prolog_flag(encoding,Enc),_,true)),
  256    current_prolog_flag(encoding,EncNew),
  257     locally(set_prolog_flag(encoding,EncNew),
  258 sccs(
  259       set_stream_encoding(Enc),
  260   Goal,
  261       set_stream_encoding(Was))))),
  262       set_prolog_flag(encoding,EncWas)).
  263
  264
  265set_stream_encoding(Text):-
  266 %set_prolog_flag(encoding,Text),
  267 notrace((
  268 ignore(catch(set_stream(current_output,encoding(Text)),_,true)),
  269 ignore(catch(set_stream(user_output,encoding(Text)),_,true)),
  270 ignore(catch(set_stream(current_output,tty(true)),_,true)))),!.
  271
  272*/
  273
  274bfly_portray(X):-
  275  \+ tracing, ground(X),
  276  \+ ( nb_current('$inprint_message', Messages), Messages\==[] ),
  277  bfly_get(butterfly,t),
  278  max_html_width(W120),
  279  display_length(X,L), L>W120,
  280  print_tree_html(X).
  281
  282:- meta_predicate(in_bfly(+,0)).  283in_bfly(TF,Goal):-
  284  bfly_get(butterfly,Was),
  285  sccs(
  286    bfly_set(butterfly,TF),
  287    Goal,
  288    bfly_set(butterfly,Was)),!.
  289
  290:- meta_predicate(in_pp_html(0)).  291in_pp_html(Goal):- wants_html,!,locally(t_l:print_mode(html),Goal).
  292in_pp_html(Goal):- with_pp(bfly,Goal).
  293
  294bfly_ask_style(E):- maybe_into_number(E,Num), bfly_ask_style(E, Num).
  295bfly_ask_style(_, Num):- bfly_dyn:bfly_style_asked(Num),!.
  296bfly_ask_style(E,   _):- E=='/dev/pts/ptmx',!.
  297%bfly_ask_style(E,   _):- bfly_dyn:bfly_style_type(_TID,E,  _,_,_,UK), UK\==unknown, !.
  298bfly_ask_style(_, Num):- bfly_dyn:bfly_style_type(_TID,_,Num,_,_,UK), UK\==unknown, !.
  299bfly_ask_style(_, Num):- number(Num), Num is -1, !.
  300bfly_ask_style(E, Num):-
  301 ignore((
  302  atom(E),
  303  thread_self(TID),
  304  current_output(Out), current_input(In),
  305  retractall(bfly_dyn:bfly_style_type(_,_,Num,_,_,_)),
  306  asserta(bfly_dyn:bfly_style_asked(Num)),
  307  sformat_safe(S1,'<font color="gold"><a target="_new" href="/swish/bfly_decl_style?tid=~w&pts=~w&style=html_esc">Click This GOLD text at ~w for an HTMLy Interface.</font></a><p>',
  308   [TID,Num,E]),
  309  bfly_to_pts(E,html_esc,S1),
  310  Key is Num + 64,
  311  sformat_safe(S2,'~nOr Press: <SHIFT+~s>=ansi, <~s>=ansi, <SPACE>=cancel',[[Key],[Key]]),
  312  bfly_to_pts(E,ansi,S2),
  313  nop(asserta(bfly_dyn:bfly_style_type(TID,E,Num,In,Out,ansi))) )).
  314
  315
  316open_for_output(E,_Style,Out,close(Out)):- atom(E), exists_file(E), open(E,append,Out),!.
  317open_for_output(E,_Style,Out,true):- atomic(E), is_stream(E),!,Out = E.
  318open_for_output(N, Style,Out,OnExit):- number(N),atom_concat('/dev/pts/',N,E), open_for_output(E,Style,Out,OnExit).
  319open_for_output(_,_Style,Out,true):- current_output(Out).
  320
  321tty_to_output_style(E,     Style):- \+ number(E),maybe_into_number(E,Num),number(Num),!,tty_to_output_style(Num, Style).
  322tty_to_output_style(Num,   Style):- bfly_dyn:bfly_style_type(_,_,Num,_,_, Style), !.
  323tty_to_output_style(Num, unknown):- bfly_dyn:bfly_style_asked(Num),!.
  324tty_to_output_style(_,   html_esc):- bfly_dyn:bfly_style_type(_,_,_,_,_,ansi),!.
  325tty_to_output_style(_,   ansi).
  326
  327
  328
  329:- meta_predicate(bfly_html_goal(0)).  330
  331%bfly_html_goal(Goal):- inside_bfly_html_esc,!,call(Goal).
  332bfly_html_goal(Goal):- bfly_in_out(Goal).
  333
  334bfly_write_h(S0):- !, bfly_write_hs(S0).
  335bfly_write_h(S0):- prepend_trim_for_html(S0,SM), prepend_trim(SM,S), bfly_write_hs(S),!.
  336
  337%bfly_write_hs(S):- bfly_in_out(write(S)),!.
  338bfly_write_hs(S):- \+string(S),sformat(SS,'~w',[S]),!,bfly_write_hs(SS).
  339bfly_write_hs(S):-
  340 ignore(( \+ empty_str(S),
  341 %replace_in_string([';HTML|'=' '],S,RS),
  342 RS = S,
  343 bfly_in_out(write(RS)))).
  344 %, (bfly_out,flush_output)))),ttyflush,bfly_out,flush_output.
  345
  346/*
  347
  348bformats(S):- in_pp(ansi),!,write(S).
  349bformats(S):- atom_codes(S,Cs), maplist(map_html_entities,Cs,CsO),atomic_list_concat(CsO,W),!,write(W).
  350
  351map_html_entities(Code,S):- name(S,[Code]),!.
  352map_html_entities(62,'&gt;'). map_html_entities(60,'&lt;'). map_html_entities(38,'&amp;').
  353 % map_html_entities(32,'&nbsp;').
  354map_html_entities(Code,S):- Code == 124,!,sformat(S, '&#~w;',[Code]).
  355map_html_entities(Code,S):- Code>160, !, sformat(S, '&#~w;',[Code]).
  356map_html_entities(Code,S):- Code<32, !, sformat(S, '&#~w;',[Code]),!.
  357map_html_entities(Code,S):- name(S,[Code]),!.
  358map_html_entities(Code,S):- sformat(S, '&#~w;',[Code]),!.
  359*/
  360
  361
  362% prepend_trim_for_html(S,S):-!. Fileinfo
  363%prepend_trim_for_html(S,SS):- correct_html_len(S,SS).
  364prepend_trim_for_html(S,SS):- prepend_trim(S,SM),correct_html_len(SM,SS).
  365
  366%correct_html_len(S,S):- atom_contains(S,'<pre>'),!.
  367correct_html_len(S,O):- atomic_list_concat(L,'\n',S),maplist(correct_html_len1,L,LL),!,atomic_list_concat(LL,'\n',O).
  368
  369max_html_width(120).
  370
  371find_and_ofset('<a h',2).
  372find_and_ofset('">',1).
  373find_and_ofset('/>',0).
  374
  375find_and_ofset('<span',1).
  376find_and_ofset('="',1).
  377find_and_ofset("='",1).
  378
  379find_and_ofset('> ',0).
  380
  381
  382find_place_to_split1(S,Before):-
  383  max_html_width(W120), W110 is W120-10,
  384  find_and_ofset(Split,Offset0),
  385  (Offset0 == len, atom_length(Split,Offset) ; Offset = Offset0),
  386  sub_atom(S,Before0,_,_,Split),
  387  Before is Before0+Offset,
  388  Before > 50,  Before < W110,!.
  389
  390
  391find_place_to_split1(S,Before):-
  392  max_html_width(W120),
  393  member(Split,['</','<','/>','>',')','  ','/*',' ']),
  394  sub_atom(S,Before,_,_,Split),
  395  Before > 50,  Before < W120,
  396  sub_atom(S,0,Before,_,Left),
  397  \+ atom_contains(Left,'<pre'),!.
  398
  399
  400correct_html_len1(S,S):- atom_length(S,L),max_html_width(W120),L < W120, !.
  401correct_html_len1(S,O):- find_place_to_split1(S,Before),!,
  402  sub_atom(S,0,Before,_,Left),
  403  sub_atom(S,Before,_,0,Right),
  404  correct_html_len1(Right,Mid),!,
  405  atomic_list_concat([Left,'\n ',Mid],'',O),!.
  406correct_html_len1(S,S).
  407
  408
  409:- meta_predicate(bfly_out_in(0)).  410bfly_out_in(Goal):- inside_bfly_html_esc -> sccs(bfly_out, wotso(Goal), bfly_in) ; call(Goal).
  411
  412%:- meta_predicate(bfly_in_out(0)).
  413%bfly_in_out(Goal):- (inside_bfly_html_esc;in_pp(http)) -> call(Goal) ;  sccs(bfly_in, call(Goal), bfly_out).
  414
  415:- meta_predicate(bfly_in_out(0)).  416bfly_in_out(Goal):- in_pp(http),!,call(Goal).
  417bfly_in_out(Goal):- is_string_output,!,call(Goal).
  418% bfly_in_out(Goal):- inside_bfly_html_esc -> call(Goal) ;  (locally(bfly_tl:bfly_setting('$bfly_style_html_esc',t),wots(S,Goal)),our_pengine_output(S)).
  419bfly_in_out(Goal):- inside_bfly_html_esc -> call(Goal) ;
  420  sccs(bfly_in,
  421    locally(bfly_tl:bfly_setting('$bfly_style_html_esc',t),Goal), bfly_out). % our_pengine_output(S)).
  422
  423bflyw:-!.
  424
  425:- meta_predicate(sccs(:,0,:)).  426:- export(sccs/3).  427sccs(A,B,C):- setup_call_cleanup(sccs_log_error(A),once(B),sccs_log_error(C)),!.
  428sccs_log_error(B):- catch(B,E,sccs_log_error(B,E)),!.
  429%sccs_log_error(_,error(socket_error(epipe,_),_)):-!.
  430sccs_log_error(B,E):- writeq_ue(sccs_log_error(B,E)).
  431writeq_ue(P):- stream_property(O,file_no(2)), writeq(O,P),nl(O),flush_output(O). %%,ttyflush.
  432
  433ccls:- cls,bfly_write(ansi,escape_from_screen([call(cls)])).
  434
  435bfly_title(_Title):- (toplevel_pp(swish);toplevel_pp(http)),!.
  436bfly_title(Title):- escape_from_screen(format("\e]2;~w\a",[Title])).
  437
  438%with_html_mode(Goal):- nb_current(isHtmlMode,t)-> call(Goal);
  439%  sccs(bfly_title("+HtmlMode"),locally(nb_setval(isHtmlMode,t),Goal),bfly_title("-HtmlMode")).
  440
  441:- nb_setval(isMonospace,nil).  442with_monospace(Goal):- nb_current(isMonospace,t)-> call(Goal);
  443  sccs(bfly_title("+Monospace"),locally(nb_setval(isMonospace,t),Goal),bfly_title("-Monospace")).
  444
  445%bfly_in  :- flag('$inside_bfly_html_esc_level',X,X+1), ignore((X == 0, bfly_in_f)).
  446bfly_in  :- ignore(( \+ inside_bfly_html_esc, set_bfly_style('html_esc',t),!,bfly_write(_,[escape_from_screen([esc(80),';HTML|'])]))).
  447
  448%bfly_out :- flag('$inside_bfly_html_esc_level',X,X-1), X \== 1. % bfly_out_f)).
  449bfly_out :- ignore(( inside_bfly_html_esc, set_bfly_style('html_esc',f),!,bfly_write(_,[escape_from_screen([esc(7)])]))).
  450
  451inside_bfly_html_esc:- in_bfly_style('html_esc',t).
  452
  453set_pp(X):- pp_set(X).
  454
  455
  456/*
  457 Assume will be printed to..
  458
  459Stream Type               Starts_in            Will SwitchTo
  460============            ===============       ==============
  461httpd stream              html_esc             pre_tag,html_esc
  462pengines output           html_esc             pre_tag,html_esc
  463ansi terminal             ansi             ansi
  464butterfly terminal        ansi             html_esc,ansi
  465
  466
  467html_esc = unformated body elements
  468ansi = text with color info
  469ansi = text with color info
  470pre_tag = preformat text with HTML embedded
  471
  472
  473*/
  474
  475
  476%bfly_write_html(S):- (nb_current('$in_swish',t);pengines:pengine_self(_Self)),!, pengines:pengine_output(S),!.
  477% bfly_write_html(S):- bfly_to_all_pts(S),!.
  478%bformat(P):- compound(P),wots((S),post_html(P)),bfly_write_html(S),!.
  479
  480%write_direct(S):- in_swish,!, pengines:pengine_output(S).
  481write_direct(S):- write(S).
  482%write_direct(S):- pformat(S).
  483
  484%bformat(P):- atom(P),sformat_safe(S,P,[]),!,bformat(S).
  485%bformat(S):- string(S),atom_concat(PL,'\n',S),!,bformat(PL).
  486%bformat(S):- t_l:in_block_format,!,format_safely("~w",[S]),!.
  487bformat(Stream,Fmt,Args):- atomic(Stream),is_stream(Stream),!, with_output_to(Stream,bformat(Fmt,Args)).
  488bformat(Stream,Fmt,Args):- format_safely(Stream,Fmt,Args).
  489bformat(Fmt,Args):- sformat_safe(P,Fmt,Args),bformat(P).
  490bformat(S):- use_pts_files,!,bfly_to_all_pts(S).
  491bformat(S):- write(S).
  492
  493sformat_safe(Stream,Fmt,Args):- catch(sformat(Stream,Fmt,Args),E,(ansi,wdmsg(E),dumpST,break)).
  494format_safely(Stream,Fmt,Args):- catch(format(Stream,Fmt,Args),E,(ansi,wdmsg(E),dumpST,break)).
  495format_safely(Fmt,Args):- catch(format(Fmt,Args),E,(ansi,wdmsg(E),dumpST,break)).
  496format_safely(Fmt):- catch(format(Fmt),E,(ansi,wdmsg(E),dumpST,break)).
  497
  498%bfly_write(Write):- bfly_html_goal(write(current,Write)).
  499%bfly_write(Write):- bfly_write_hs(Write).
  500bfly_write_plain(Stuff):- bfly_out_in(bfly_write(ansi,Stuff)).
  501bfly_write_html(Stuff):- bfly_html_goal(bfly_write(http,Stuff)).
  502bfly_write_pre(Stuff):- bfly_write_html(pre(Stuff)).
  503
  504
  505bfly_html_pre(Goal):- in_pp(ansi),!,call(Goal).
  506bfly_html_pre(Goal):- wots(S,in_bfly(f,with_pp(ansi,Goal))), bfly_write_pre(S).
  507
  508
  509escape_from_screen(G):- bfly_write(current,escape_from_screen(call(G))).
  510
  511%only_bfly(Goal):- ignore((toplevel_pp(bfly), \+ is_string_output, Goal)).
  512only_bfly(Goal):- ignore((toplevel_pp(bfly), Goal)).
  513
  514guess_is_pp(Guess):- in_pp(Guess).
  515% guess_is_pp(Guess):- toplevel_pp(Guess).
  516
  517is_string_output:- current_output(Out),is_string_output(Out).
  518is_string_output(Out):- stream_property(Out,close_on_abort(true)), \+ stream_property(Out,close_on_exec(false)).
  519
  520bfly_write(Style,S):- var(S),!, bfly_write(Style,var_in_style(Style,S)),!.
  521bfly_write(_Styl, call(X)):-!, call(X).
  522bfly_write(_,  '$html'):- !, only_bfly(bfly_in).
  523bfly_write(_,'$nohtml'):- !, only_bfly(bfly_out).
  524bfly_write(_,esc(Char)):- !, only_bfly(( put(27),!, put_code(Char))).
  525
  526bfly_write(Style,escape_from_screen('$start')):- !, only_bfly(bfly_write(Style,[when_in_screen(esc(80))])).
  527bfly_write(Style,escape_from_screen('$end')):- !, only_bfly(bfly_write(Style,[when_in_screen(esc(92))])).
  528bfly_write(Style,escape_from_screen(X)):-!, bfly_write(Style,[when_in_screen(esc(80)),X,when_in_screen(esc(92))]).
  529bfly_write(Style,when_in_screen(X)):- !, only_bfly(ignore((getenv('TERM',screen),bfly_write(Style,X)))).
  530bfly_write(ansi,pre(X)):- !,bfly_write(ansi,X).
  531bfly_write(_Styl,pre(X)):- !, bfly_write_html([html('<pre>'),X,html('</pre>')]),!.
  532bfly_write(_Styl,html(X)):- !, bfly_write_html(X),!.
  533bfly_write(_Styl,raw_debug(X)):- !, nop(write(X)),!.
  534bfly_write(ansi,term(X)):- !, bfly_out_in(print_tree(X)).
  535bfly_write(_Styl,term(X)):- !, bfly_html_goal(print_html_term(X)).
  536bfly_write(ansi,style(_,X)):- !, bfly_out_in(bfly_write(ansi,X)).
  537bfly_write(Style,style(C,X)):- !,bfly_write(Style,[html('<font style="~w">',[C]),X,html('</font>')]),!.
  538bfly_write(ansi,color(C,X)):- !,color_format(fg(C),'~@',[bfly_write(ansi,X)]).
  539bfly_write(_Styl,color(C,X)):- !,sformat_safe(S,'<font color="~w">',[C]),bfly_write_html([html(S),X,html('</font>')]),!.
  540bfly_write(_Styl,w(Text)):- !, write(Text). % needed in order to write an integer or special atoms
  541bfly_write(_Styl,hwt(0)):- !, bfly_write_html('<pre>hello world</pre>').
  542bfly_write(_Styl,hwt(a)):- !, write("\e]8;;https://example.com\aThis is a link\e]8;;\a\c").
  543bfly_write(Style,hwt(1)):- !, bfly_write(Style,ht('https://example.com','This is a link')).
  544bfly_write(Style,hwt(2)):- !, bfly_write(Style,ht2('https://example.com','This is a link')).
  545bfly_write(_Styl,ht(H,T)):- !, write("\e]8;;"),write(H),write("\a"),write(T),write("\e]8;;\a\c").
  546bfly_write(_Styl,ht2(H,T)):- !, write("\e]8;;"),bfly_write_html(H),write("\a\c"),write(T),write("\e]8;;\a\c").
  547bfly_write(_Styl,ho(H)):-   !, write("\e]8;;"),bfly_write_html(H),write("\a"),write("\e]8;;\a\c").
  548bfly_write(_Styl,ansi(X)):-!, bfly_write_plain(X).
  549bfly_write(Style,'$clr'):- !, bfly_write(Style,esc(92)).
  550bfly_write(Style,nl):- !, (inside_bfly_html_esc -> bfly_write(Style,'<br/>'); nl).
  551bfly_write(_Styl,Code):- integer(Code), !, put(Code).
  552bfly_write(Style,S):- (string(S);is_codelist(S);is_charlist(S)), format_safely(atom(T),'~s',[S]), !, bfly_write(Style,T).
  553bfly_write(Style,IsList):- is_list(IsList), !, bfly_at_once(must_maplist_det(bfly_write(Style),IsList)),!.
  554
  555bfly_write(current,S):- guess_is_pp(What),!,bfly_write1(What,S).
  556bfly_write(Style,S):- bfly_write1(Style,S),!.
  557bfly_write1(_Styl,S):- atom(S),(atom_contains(S,'<'),atom_contains(S,'>')),!,write_direct(S).
  558%bfly_write(ansi,S):- guess_is_pp(ansi),!,writ
  559bfly_write1(_Styl,X):-!, pformat(X).
  560
  561:- multifile(cp_menu:menu_item/2).  562:- dynamic(cp_menu:menu_item/2).  563:- asserta(cp_menu:menu_item('https://logicmoo.org/4123/',	'Butterfly REPL')).  564:- asserta(cp_menu:menu_item('/swish/',	'SWISH')).  565
  566:- meta_predicate(esc_screen(0)).  567esc_screen(X):- Style=current,
  568  sccs(
  569   bfly_write(Style,when_in_screen(esc(80))),
  570   call(X),
  571   bfly_write(Style,when_in_screen(esc(97)))).
  572
  573in_bfly_style(Style,Value):- as_bfly_style(Style,Var), !, bfly_get(Var,Value).
  574
  575set_bfly_style(Style,Value):- as_bfly_style(Style,Var), !, bfly_set(Var,Value).
  576
  577as_bfly_style(Style,Var):- atom_concat('$bfly_style_',Style,Var).
  578
  579:- dynamic(bfly_tl:bfly_setting/2).  580:- thread_local(bfly_tl:bfly_setting/2).  581bfly_set(List):- is_list(List),!,maplist(bfly_set,List).
  582bfly_set(Name):- atomic(Name),!,bfly_set(Name,t).
  583bfly_set(Cmpd):- Cmpd=..[Name,Value],!,bfly_set(Name,Value).
  584
  585bfly_set(Name,Value):- retractall(bfly_tl:bfly_setting(Name,_)),nb_setval(Name,Value),asserta(bfly_tl:bfly_setting(Name,Value)).
  586
  587bfly_get(Style,Was):- nonvar(Was),!,bfly_get(Style,Waz),!,Was=Waz.
  588bfly_get(Name,Value):- nb_current(Name,Value), Value\==[],!.
  589bfly_get(Name,Value):- bfly_tl:bfly_setting(Name,Value),!.
  590bfly_get(_,f).
  591
  592bfly_start_link(String):- % make,
  593   bfly_set(location,String),parse_url(String,Attribs),
  594   bfly_set(Attribs), ignore((sub_string(String,_,1,After,'?'),sub_string(String,_,After,0,Value),bfly_set(command,Value),
  595   www_form_encode(Cmd,Value),atom_to_term(Cmd,Prolog,_),dmsg(cmd=Prolog),on_xf_ignore(Prolog))).
  596
  597:- thread_local(tl:in_bfly_at_once/0).  598:- meta_predicate(bfly_at_once(0)).  599bfly_at_once(G):- tl:in_bfly_at_once, !, call(G).
  600bfly_at_once(G):- flush_output, ttyflush,
  601 locally(tl:in_bfly_at_once,
  602  (wots((S),(G,flush_output)),!,
  603   write(S),flush_output)),
  604  flush_output, ttyflush.
  605
  606
  607bfly_info:- \+ use_pts_files,!,in_cmt(listing(bfly_tl:bfly_setting/2)).
  608bfly_info:-
  609  expand_file_name('/dev/pts/?',[_,_|X]),
  610  nl,wdmsg(bfly_info(X)),nl,
  611  in_cmt(listing(bfly_dyn:bfly_style_asked/1)),
  612  in_cmt(listing(bfly_dyn:bfly_style_answered/0)),
  613  in_cmt(listing(bfly_dyn:bfly_style_type/6)),
  614  in_cmt(listing(bfly_tl:bfly_setting/2)).
  615bfly_to_all_pts(S):-
  616  expand_file_name('/dev/pts/?',[_,_|X]),
  617  forall(member(E,X),bfly_to_pts(E,S)),!.
  618
  619bfly_to_pts(E,S):- ignore((tty_to_output_style(E,Style),!,bfly_to_pts(E,Style,S))).
  620
  621bfly_to_pts(E,Style,S):-
  622 sccs(
  623   open_for_output(E,Style,Out,OnExit),
  624   with_output_to(Out,bfly_write(Style,S)),
  625   OnExit),!.
  626
  627
  628
  629insert_js(File):- bformat('<script src="~w"></script>',[File]).
  630
  631
  632pre_style(''):- !. % TODO uncomment
  633pre_style('<style> pre {
  634    display: inline;
  635    margin: 0;
  636    white-space: pre-wrap;                 /* CSS3 browsers  */
  637    white-space: -moz-pre-wrap !important; /* 1999+ Mozilla  */
  638    white-space: -pre-wrap;                /* Opera 4 thru 6 */
  639    white-space: -o-pre-wrap;              /* Opera 7 and up */
  640    white-space: pre-wrap;                 /* CSS3 browsers  */
  641    word-wrap: break-word;                 /* IE 5.5+ and up */
  642}</style>').
  643
  644pre_style:- pre_style(Style),bfly_write_html(Style).
  645
  646mouse_over_span:-
  647   bfly_write_html('<p>Each word will be wrapped in a span.</p><p>A second paragraph here.
  648   </p>Word: <span id="word"></span>').
  649
  650is_visible_output:- current_output(Out),stream_property(Out,buffer(line)),stream_property(Out,alias(_)).
  651
  652clean_pre(Pre,Clean):- subst_string(Pre,'<pre>\n','<pre>',M),subst_string(M,'\n\n','\n',Clean).
  653subst_string(Pre,B,A,Clean):- atomic_list_concat(List,B,Pre),atomic_list_concat(List,A,Clean).
  654
  655post_html(HTML):- notrace(catch(post_html0(HTML),Err,writeq(post_html((Err),HTML)))).
  656% post_html0(HTML):- is_list(HTML),!,maplist(post_html,HTML).
  657post_html0(HTML):- re_html(HTML, SafeHTML), html_write:html(SafeHTML,O,[]),fix_print_html(O,OO),print_html(OO),!.
  658
  659fix_print_html([nl(2)],[]).
  660fix_print_html([],[]).
  661fix_print_html([pre,>,nl(1)|O],[pre,>|OO]):- !, fix_print_html(O,OO).
  662fix_print_html([nl(1),nl(0),</|O],[nl(0),</|OO]):- !, fix_print_html(O,OO).
  663%fix_print_html([nl(2)|O],OO):- !, fix_print_html(O,OO).
  664fix_print_html([nl(2),<|O],[<|OO]):- !, fix_print_html(O,OO).
  665fix_print_html([nl(2)|O],['&nbsp',nl(1)|OO]):- !, fix_print_html(O,OO).
  666fix_print_html([W|O],[W|OO]):- !, fix_print_html(O,OO).
  667
  668% re_html(HTML, HTML).
  669re_html(MHTML, HTMLSafe) :- strip_module(MHTML,MM,HTML),
  670 (MHTML==HTML -> (pengines:pengine_self(M);prolog_load_context(module, M)) ; M =MM),
  671  re_html(M, HTML, HTMLSafe),!.
  672
  673re_html(M, HTML, SafeHTML):- \+ ground(HTML), !, imploded_copyvars(HTML,COPY), re_html(M, COPY, SafeHTML).
  674re_html(M, HTML, SafeHTML):- is_list(HTML), !, maplist(re_html(M), HTML, SafeHTML).
  675re_html(M, '$VAR'(Var), HTML):- re_html(M, pre(["$VAR-",Var]), HTML).
  676re_html(M, A=B, SafeHTML):- re_html(M, [A,pre(=),B], SafeHTML).
  677re_html(M, element(E,P,L), element(E,P,LL)):- !,re_html(M, L, LL).
  678re_html(M, s(HTML), SafeHTML):- re_html(M, s(' ',HTML), SafeHTML).
  679re_html(M, s(Sep,HTML), SafeHTML):- is_list(HTML), pad_list(HTML,Sep,PaddedHTML),!,re_html(M, PaddedHTML, SafeHTML).
  680re_html(_, ' ', &(nbsp)):-!.
  681re_html(M, HTML, SafeHTML):- \+ compound(HTML), swish_safe_html(HTML, M, SafeHTML),!.
  682re_html(_, HTML, SafeHTML):- \+ compound(HTML),!,SafeHTML= HTML.
  683re_html(_, HTML, \[<,Name,/>]):- compound_name_arity(HTML,Name,0),!.
  684re_html(_, \ List, \ List):- is_list(List),!.
  685re_html(_, '$'(Stuff), \ Flat):- flatten([Stuff],Flat),!.
  686re_html(_, HTML, element(Name,[],[])):- compound_name_arity(HTML,Name,0),!.
  687re_html(M, HTML, SafeHTML):- compound_name_arguments(HTML,F,HTMLList),
  688   re_html(M, HTMLList,SafeHTMLList),
  689  compound_name_arguments(SafeHTML,F,SafeHTMLList).
  690re_html(M, HTML, SafeHTML):- swish_safe_html(HTML, M, SafeHTML),!.
  691
  692pad_list([],_,[]):-!.
  693pad_list([W],_,[W]):-!.
  694pad_list([W|HTML],Pad,[W,Pad|PaddedHTML]):-
  695 pad_list(HTML,Pad,PaddedHTML).
  696
  697swish_safe_html(HTML, M, SafeHTML):-
  698  notrace(catch(call(call,swish_html_output:make_safe_html(HTML, M, SafeHTML)),_,HTML=SafeHTML)).
  699
  700bfly_test(bfly_info):-  bfly_info.
  701bfly_test(a1):-  bfly_in_out(writeln('<img class="owl" src="https://www.swi-prolog.org/icons/swipl.png" alt="writeln SWI-Prolog owl logo" title="SWI-Prolog owl logo">')).
  702bfly_test(a2):-  bfly_html_goal(writeln(('<img class="owl" src="https://www.swi-prolog.org/icons/swipl.png" alt="SWI-Prolog owl logo" title="SWI-Prolog owl logo">'))).
  703bfly_test(a3):-  bfly_html_goal(our_pengine_output(('<img class="owl" src="https://www.swi-prolog.org/icons/swipl.png" alt="SWI-Prolog owl logo" title="SWI-Prolog owl logo">'))).
  704bfly_test(a4):-  our_pengine_output(`<img class="owl" src="https://www.swi-prolog.org/icons/swipl.png" alt="SWI-Prolog owl logo" title="SWI-Prolog owl logo">`).
  705bfly_test(0):-  bfly_write(current,[html('<pre>hi there fred0</pre>'), ' foo']).
  706bfly_test(1):-  bfly_write_html('<div>hi <pre>there </pre>&nbsp;fred1</div>').
  707%bfly_test(2):-  pre_style, bfly_write(html('<pre><a target="_blank" href="https://logicmoo.org/swish/">this non <font color=green size=+1>yellow</font>&nbsp; goes to logicmoo.org</a></pre>')).
  708%bfly_test(2):-  bfly_test(a),writeln(ok),bfly_test(a),bfly_test(a),write(ok),bfly_test(a).
  709%bfly_test(3):-  bformat('<iframe src="about:blank" name="targa" height="200" width="300" title="Iframe Example"></iframe><a target="targa" href="https://github.com">targa</a>').
  710bfly_test(4):-  bformat('<svg width="100" height="100"><circle onload="var ws = new WebSocket(\'ws://localhost:57575/ws\');ws.addEventListener(\'open\', function () {ws.send(\'Stouch /tmp/pwned\\n\');});" cx="50" cy="50" r="40" stroke="green" stroke-width="4" fill="yellow" /></svg>').
  711%bfly_test(5):-  bfly_html_goal(writeln('<pre><iframe src="/xwiki/" name="example" height="200" width="300" title="Html Iframe Example"></iframe></pre>')).
  712%bfly_test(6):-  our_pengine_output(('<iframe src="/swish/" name="example" height="200" width="300" title="Non html Iframe Example"></iframe>')).
  713bfly_test(7):-  write(hi),ansi_format([fg(red)],'Hello there\nHi there bob\n',[]),nl,write(good).
  714
  715into_attribute_q(Obj,TextBoxObj):- sformat_safe(Text,'~q',[Obj]),into_attribute(Text,TextBoxObj).
  716:- export(into_attribute/2).  717:- system:import(into_attribute/2).  718
  719into_attribute(Obj,TextBoxObjO):-
  720  (atomic(Obj)->sformat_safe(Text,'~w',[Obj]);sformat_safe(Text,'~q',[Obj])),
  721   xml_quote_attribute(Text,TextBoxObj,ascii),!,
  722   replace_in_string(['\r\n'='\n','"'='&#34;','\''='&apos;','\r'='\n','\n'='&#13;&#10;'],TextBoxObj,TextBoxObjO).
  723
  724bfly_tests:- forall(clause(bfly_test(Name),Body),
  725               ((writeln(test(Name)),ignore(Body),nl))),!.
  726bfly_test_8:-
  727 our_pengine_output(`
  728
  729
  730  <p>
  731    This is a minimalist HTML and JavaScript skeleton of the GoJS Sample
  732    <a href="https://gojs.net/latest/samples/blockEditor.html">blockEditor.html</a>. It was automatically generated from a button on the sample page,
  733    and does not contain the full HTML. It is intended as a starting point to adapt for your own usage.
  734    For many samples, you may need to inspect the
  735    <a href="https://github.com/NorthwoodsSoftware/GoJS/blob/master/samples/blockEditor.html">full source on Github</a>
  736    and copy other files or scripts.
  737  </p>
  738  <div id="allSampleContent" class="p-4 w-full">
  739  <script src="https://unpkg.com/gojs@2.2.15/release/go.js"></script>
  740  <script src="https://unpkg.com/gojs@2.2.15/extensions/Figures.js"></script>
  741  <script src="https://unpkg.com/gojs@2.2.15/extensions/DrawCommandHandler.js"></script>
  742    <script id="code">
  743    function init() {
  744
  745      // Since 2.2 you can also author concise templates with method chaining instead of GraphObject.make
  746      // For details, see https://gojs.net/latest/intro/buildingObjects.html
  747      const $ = go.GraphObject.make;
  748
  749      myDiagram =
  750        $(go.Diagram, "myDiagramDiv",
  751          {
  752            padding: 20,  // extra space when scrolled all the way
  753            grid: $(go.Panel, "Grid",  // a simple 10x10 grid
  754              $(go.Shape, "LineH", { stroke: "lightgray", strokeWidth: 0.5 }),
  755              $(go.Shape, "LineV", { stroke: "lightgray", strokeWidth: 0.5 })
  756            ),
  757            "draggingTool.isGridSnapEnabled": true,
  758            handlesDragDropForTopLevelParts: true,
  759            mouseDrop: e => {
  760              // when the selection is dropped in the diagram's background,
  761              // make sure the selected Parts no longer belong to any Group
  762              var ok = e.diagram.commandHandler.addTopLevelParts(e.diagram.selection, true);
  763              if (!ok) e.diagram.currentTool.doCancel();
  764            },
  765            commandHandler: $(DrawCommandHandler),  // support offset copy-and-paste
  766            "clickCreatingTool.archetypeNodeData": { text: "NEW NODE" },  // create a new node by double-clicking in background
  767            "PartCreated": e => {
  768              var node = e.subject;  // the newly inserted Node -- now need to snap its location to the grid
  769              node.location = node.location.copy().snapToGridPoint(e.diagram.grid.gridOrigin, e.diagram.grid.gridCellSize);
  770              setTimeout(() => {  // and have the user start editing its text
  771                e.diagram.commandHandler.editTextBlock();
  772              }, 20);
  773            },
  774            "commandHandler.archetypeGroupData": { isGroup: true, text: "NEW GROUP" },
  775            "SelectionGrouped": e => {
  776              var group = e.subject;
  777              setTimeout(() => {  // and have the user start editing its text
  778                e.diagram.commandHandler.editTextBlock();
  779              })
  780            },
  781            "LinkRelinked": e => {
  782              // re-spread the connections of other links connected with both old and new nodes
  783              var oldnode = e.parameter.part;
  784              oldnode.invalidateConnectedLinks();
  785              var link = e.subject;
  786              if (e.diagram.toolManager.linkingTool.isForwards) {
  787                link.toNode.invalidateConnectedLinks();
  788              } else {
  789                link.fromNode.invalidateConnectedLinks();
  790              }
  791            },
  792            "undoManager.isEnabled": true
  793          });
  794
  795
  796      // Node template
  797
  798      myDiagram.nodeTemplate =
  799        $(go.Node, "Auto",
  800          {
  801            locationSpot: go.Spot.Center, locationObjectName: "SHAPE",
  802            desiredSize: new go.Size(120, 60), minSize: new go.Size(40, 40),
  803            resizable: true, resizeCellSize: new go.Size(20, 20)
  804          },
  805          // these Bindings are TwoWay because the DraggingTool and ResizingTool modify the target properties
  806          new go.Binding("location", "loc", go.Point.parse).makeTwoWay(go.Point.stringify),
  807          new go.Binding("desiredSize", "size", go.Size.parse).makeTwoWay(go.Size.stringify),
  808          $(go.Shape,
  809            { // the border
  810              name: "SHAPE", fill: "white",
  811              portId: "", cursor: "pointer",
  812              fromLinkable: true, toLinkable: true,
  813              fromLinkableDuplicates: true, toLinkableDuplicates: true,
  814              fromSpot: go.Spot.AllSides, toSpot: go.Spot.AllSides
  815            },
  816            new go.Binding("figure"),
  817            new go.Binding("fill"),
  818            new go.Binding("stroke", "color"),
  819            new go.Binding("strokeWidth", "thickness"),
  820            new go.Binding("strokeDashArray", "dash")),
  821          // this Shape prevents mouse events from reaching the middle of the port
  822          $(go.Shape, { width: 100, height: 40, strokeWidth: 0, fill: "transparent" }),
  823          $(go.TextBlock,
  824            { margin: 1, textAlign: "center", overflow: go.TextBlock.OverflowEllipsis, editable: true },
  825            // this Binding is TwoWay due to the user editing the text with the TextEditingTool
  826            new go.Binding("text").makeTwoWay(),
  827            new go.Binding("stroke", "color"))
  828        );
  829
  830      myDiagram.nodeTemplate.toolTip =
  831        $("ToolTip",  // show some detailed information
  832          $(go.Panel, "Vertical",
  833            { maxSize: new go.Size(200, NaN) },  // limit width but not height
  834            $(go.TextBlock,
  835              { font: "bold 10pt sans-serif", textAlign: "center" },
  836              new go.Binding("text")),
  837            $(go.TextBlock,
  838              { font: "10pt sans-serif", textAlign: "center" },
  839              new go.Binding("text", "details"))
  840          )
  841        );
  842
  843      // Node selection adornment
  844      // Include four large triangular buttons so that the user can easily make a copy
  845      // of the node, move it to be in that direction relative to the original node,
  846      // and add a link to the new node.
  847
  848      function makeArrowButton(spot, fig) {
  849        var maker = (e, shape) => {
  850            e.handled = true;
  851            e.diagram.model.commit(m => {
  852              var selnode = shape.part.adornedPart;
  853              // create a new node in the direction of the spot
  854              var p = new go.Point().setRectSpot(selnode.actualBounds, spot);
  855              p.subtract(selnode.location);
  856              p.scale(2, 2);
  857              p.x += Math.sign(p.x) * 60;
  858              p.y += Math.sign(p.y) * 60;
  859              p.add(selnode.location);
  860              p.snapToGridPoint(e.diagram.grid.gridOrigin, e.diagram.grid.gridCellSize);
  861              // make the new node a copy of the selected node
  862              var nodedata = m.copyNodeData(selnode.data);
  863              // add to same group as selected node
  864              m.setGroupKeyForNodeData(nodedata, m.getGroupKeyForNodeData(selnode.data));
  865              m.addNodeData(nodedata);  // add to model
  866              // create a link from the selected node to the new node
  867              var linkdata = { from: selnode.key, to: m.getKeyForNodeData(nodedata) };
  868              m.addLinkData(linkdata);  // add to model
  869              // move the new node to the computed location, select it, and start to edit it
  870              var newnode = e.diagram.findNodeForData(nodedata);
  871              newnode.location = p;
  872              e.diagram.select(newnode);
  873              setTimeout(() => {
  874                e.diagram.commandHandler.editTextBlock();
  875              }, 20);
  876            });
  877          };
  878        return $(go.Shape,
  879          {
  880            figure: fig,
  881            alignment: spot, alignmentFocus: spot.opposite(),
  882            width: (spot.equals(go.Spot.Top) || spot.equals(go.Spot.Bottom)) ? 36 : 18,
  883            height: (spot.equals(go.Spot.Top) || spot.equals(go.Spot.Bottom)) ? 18 : 36,
  884            fill: "orange", strokeWidth: 0,
  885            isActionable: true,  // needed because it's in an Adornment
  886            click: maker, contextClick: maker
  887          });
  888      }
  889
  890      // create a button that brings up the context menu
  891      function CMButton(options) {
  892        return $(go.Shape,
  893          {
  894            fill: "orange", stroke: "gray", background: "transparent",
  895            geometryString: "F1 M0 0 M0 4h4v4h-4z M6 4h4v4h-4z M12 4h4v4h-4z M0 12",
  896            isActionable: true, cursor: "context-menu",
  897            click: (e, shape) => {
  898              e.diagram.commandHandler.showContextMenu(shape.part.adornedPart);
  899            }
  900          },
  901          options || {});
  902      }
  903
  904      myDiagram.nodeTemplate.selectionAdornmentTemplate =
  905        $(go.Adornment, "Spot",
  906          $(go.Placeholder, { padding: 10 }),
  907          makeArrowButton(go.Spot.Top, "TriangleUp"),
  908          makeArrowButton(go.Spot.Left, "TriangleLeft"),
  909          makeArrowButton(go.Spot.Right, "TriangleRight"),
  910          makeArrowButton(go.Spot.Bottom, "TriangleDown"),
  911          CMButton({ alignment: new go.Spot(0.75, 0) })
  912        );
  913
  914      // Common context menu button definitions
  915
  916      // All buttons in context menu work on both click and contextClick,
  917      // in case the user context-clicks on the button.
  918      // All buttons modify the node data, not the Node, so the Bindings need not be TwoWay.
  919
  920      // A button-defining helper function that returns a click event handler.
  921      // PROPNAME is the name of the data property that should be set to the given VALUE.
  922      function ClickFunction(propname, value) {
  923        return (e, obj) => {
  924            e.handled = true;  // don't let the click bubble up
  925            e.diagram.model.commit(m => {
  926              m.set(obj.part.adornedPart.data, propname, value);
  927            });
  928          };
  929      }
  930
  931      // Create a context menu button for setting a data property with a color value.
  932      function ColorButton(color, propname) {
  933        if (!propname) propname = "color";
  934        return $(go.Shape,
  935          {
  936            width: 16, height: 16, stroke: "lightgray", fill: color,
  937            margin: 1, background: "transparent",
  938            mouseEnter: (e, shape) => shape.stroke = "dodgerblue",
  939            mouseLeave: (e, shape) => shape.stroke = "lightgray",
  940            click: ClickFunction(propname, color), contextClick: ClickFunction(propname, color)
  941          });
  942      }
  943
  944      function LightFillButtons() {  // used by multiple context menus
  945        return [
  946          $("ContextMenuButton",
  947            $(go.Panel, "Horizontal",
  948              ColorButton("white", "fill"), ColorButton("beige", "fill"), ColorButton("aliceblue", "fill"), ColorButton("lightyellow", "fill")
  949            )
  950          ),
  951          $("ContextMenuButton",
  952            $(go.Panel, "Horizontal",
  953              ColorButton("lightgray", "fill"), ColorButton("lightgreen", "fill"), ColorButton("lightblue", "fill"), ColorButton("pink", "fill")
  954            )
  955          )
  956        ];
  957      }
  958
  959      function DarkColorButtons() {  // used by multiple context menus
  960        return [
  961          $("ContextMenuButton",
  962            $(go.Panel, "Horizontal",
  963              ColorButton("black"), ColorButton("green"), ColorButton("blue"), ColorButton("red")
  964            )
  965          ),
  966          $("ContextMenuButton",
  967            $(go.Panel, "Horizontal",
  968              ColorButton("brown"), ColorButton("magenta"), ColorButton("purple"), ColorButton("orange")
  969            )
  970          )
  971        ];
  972      }
  973
  974      // Create a context menu button for setting a data property with a stroke width value.
  975      function ThicknessButton(sw, propname) {
  976        if (!propname) propname = "thickness";
  977        return $(go.Shape, "LineH",
  978          {
  979            width: 16, height: 16, strokeWidth: sw,
  980            margin: 1, background: "transparent",
  981            mouseEnter: (e, shape) => shape.background = "dodgerblue",
  982            mouseLeave: (e, shape) => shape.background = "transparent",
  983            click: ClickFunction(propname, sw), contextClick: ClickFunction(propname, sw)
  984          });
  985      }
  986
  987      // Create a context menu button for setting a data property with a stroke dash Array value.
  988      function DashButton(dash, propname) {
  989        if (!propname) propname = "dash";
  990        return $(go.Shape, "LineH",
  991          {
  992            width: 24, height: 16, strokeWidth: 2,
  993            strokeDashArray: dash,
  994            margin: 1, background: "transparent",
  995            mouseEnter: (e, shape) => shape.background = "dodgerblue",
  996            mouseLeave: (e, shape) => shape.background = "transparent",
  997            click: ClickFunction(propname, dash), contextClick: ClickFunction(propname, dash)
  998          });
  999      }
 1000
 1001      function StrokeOptionsButtons() {  // used by multiple context menus
 1002        return [
 1003          $("ContextMenuButton",
 1004            $(go.Panel, "Horizontal",
 1005              ThicknessButton(1), ThicknessButton(2), ThicknessButton(3), ThicknessButton(4)
 1006            )
 1007          ),
 1008          $("ContextMenuButton",
 1009            $(go.Panel, "Horizontal",
 1010              DashButton(null), DashButton([2, 4]), DashButton([4, 4])
 1011            )
 1012          )
 1013        ];
 1014      }
 1015
 1016      // Node context menu
 1017
 1018      function FigureButton(fig, propname) {
 1019        if (!propname) propname = "figure";
 1020        return $(go.Shape,
 1021          {
 1022            width: 32, height: 32, scale: 0.5, fill: "lightgray", figure: fig,
 1023            margin: 1, background: "transparent",
 1024            mouseEnter: (e, shape) => shape.fill = "dodgerblue",
 1025            mouseLeave: (e, shape) => shape.fill = "lightgray",
 1026            click: ClickFunction(propname, fig), contextClick: ClickFunction(propname, fig)
 1027          });
 1028      }
 1029
 1030      myDiagram.nodeTemplate.contextMenu =
 1031        $("ContextMenu",
 1032          $("ContextMenuButton",
 1033            $(go.Panel, "Horizontal",
 1034              FigureButton("Rectangle"), FigureButton("RoundedRectangle"), FigureButton("Ellipse"), FigureButton("Diamond")
 1035            )
 1036          ),
 1037          $("ContextMenuButton",
 1038            $(go.Panel, "Horizontal",
 1039              FigureButton("Parallelogram2"), FigureButton("ManualOperation"), FigureButton("Procedure"), FigureButton("Cylinder1")
 1040            )
 1041          ),
 1042          $("ContextMenuButton",
 1043            $(go.Panel, "Horizontal",
 1044              FigureButton("Terminator"), FigureButton("CreateRequest"), FigureButton("Document"), FigureButton("TriangleDown")
 1045            )
 1046          ),
 1047          LightFillButtons(),
 1048          DarkColorButtons(),
 1049          StrokeOptionsButtons()
 1050        );
 1051
 1052
 1053      // Group template
 1054
 1055      myDiagram.groupTemplate =
 1056        $(go.Group, "Spot",
 1057          {
 1058            layerName: "Background",
 1059            ungroupable: true,
 1060            locationSpot: go.Spot.Center,
 1061            selectionObjectName: "BODY",
 1062            computesBoundsAfterDrag: true,  // allow dragging out of a Group that uses a Placeholder
 1063            handlesDragDropForMembers: true,  // don't need to define handlers on Nodes and Links
 1064            mouseDrop: (e, grp) => {  // add dropped nodes as members of the group
 1065              var ok = grp.addMembers(grp.diagram.selection, true);
 1066              if (!ok) grp.diagram.currentTool.doCancel();
 1067            },
 1068            avoidable: false
 1069          },
 1070          new go.Binding("location", "loc", go.Point.parse).makeTwoWay(go.Point.stringify),
 1071          $(go.Panel, "Auto",
 1072            { name: "BODY" },
 1073            $(go.Shape,
 1074              {
 1075                parameter1: 10,
 1076                fill: "white", strokeWidth: 2,
 1077                portId: "", cursor: "pointer",
 1078                fromLinkable: true, toLinkable: true,
 1079                fromLinkableDuplicates: true, toLinkableDuplicates: true,
 1080                fromSpot: go.Spot.AllSides, toSpot: go.Spot.AllSides
 1081              },
 1082              new go.Binding("fill"),
 1083              new go.Binding("stroke", "color"),
 1084              new go.Binding("strokeWidth", "thickness"),
 1085              new go.Binding("strokeDashArray", "dash")),
 1086            $(go.Placeholder,
 1087              { background: "transparent", margin: 10 })
 1088          ),
 1089          $(go.TextBlock,
 1090            {
 1091              alignment: go.Spot.Top, alignmentFocus: go.Spot.Bottom,
 1092              font: "bold 12pt sans-serif", editable: true
 1093            },
 1094            new go.Binding("text"),
 1095            new go.Binding("stroke", "color"))
 1096        );
 1097
 1098      myDiagram.groupTemplate.selectionAdornmentTemplate =
 1099        $(go.Adornment, "Spot",
 1100          $(go.Panel, "Auto",
 1101            $(go.Shape, { fill: null, stroke: "dodgerblue", strokeWidth: 3 }),
 1102            $(go.Placeholder, { margin: 1.5 })
 1103          ),
 1104          CMButton({ alignment: go.Spot.TopRight, alignmentFocus: go.Spot.BottomRight })
 1105        );
 1106
 1107      myDiagram.groupTemplate.contextMenu =
 1108        $("ContextMenu",
 1109          LightFillButtons(),
 1110          DarkColorButtons(),
 1111          StrokeOptionsButtons()
 1112        );
 1113
 1114
 1115      // Link template
 1116
 1117      myDiagram.linkTemplate =
 1118        $(go.Link,
 1119          {
 1120            layerName: "Foreground",
 1121            routing: go.Link.AvoidsNodes, corner: 10,
 1122            toShortLength: 4,  // assume arrowhead at "to" end, need to avoid bad appearance when path is thick
 1123            relinkableFrom: true, relinkableTo: true,
 1124            reshapable: true, resegmentable: true
 1125          },
 1126          new go.Binding("fromSpot", "fromSpot", go.Spot.parse),
 1127          new go.Binding("toSpot", "toSpot", go.Spot.parse),
 1128          new go.Binding("fromShortLength", "dir", dir => dir === 2 ? 4 : 0),
 1129          new go.Binding("toShortLength", "dir", dir => dir >= 1 ? 4 : 0),
 1130          new go.Binding("points").makeTwoWay(),  // TwoWay due to user reshaping with LinkReshapingTool
 1131          $(go.Shape, { strokeWidth: 2 },
 1132            new go.Binding("stroke", "color"),
 1133            new go.Binding("strokeWidth", "thickness"),
 1134            new go.Binding("strokeDashArray", "dash")),
 1135          $(go.Shape, { fromArrow: "Backward", strokeWidth: 0, scale: 4/3, visible: false },
 1136            new go.Binding("visible", "dir", dir => dir === 2),
 1137            new go.Binding("fill", "color"),
 1138            new go.Binding("scale", "thickness", t => (2+t)/3)),
 1139          $(go.Shape, { toArrow: "Standard", strokeWidth: 0, scale: 4/3 },
 1140            new go.Binding("visible", "dir", dir => dir >= 1),
 1141            new go.Binding("fill", "color"),
 1142            new go.Binding("scale", "thickness", t => (2+t)/3)),
 1143          $(go.TextBlock,
 1144            { alignmentFocus: new go.Spot(0, 1, -4, 0), editable: true },
 1145            new go.Binding("text").makeTwoWay(),  // TwoWay due to user editing with TextEditingTool
 1146            new go.Binding("stroke", "color"))
 1147        );
 1148
 1149      myDiagram.linkTemplate.selectionAdornmentTemplate =
 1150        $(go.Adornment,  // use a special selection Adornment that does not obscure the link path itself
 1151          $(go.Shape,
 1152            { // this uses a pathPattern with a gap in it, in order to avoid drawing on top of the link path Shape
 1153              isPanelMain: true,
 1154              stroke: "transparent", strokeWidth: 6,
 1155              pathPattern: makeAdornmentPathPattern(2)  // == thickness or strokeWidth
 1156            },
 1157            new go.Binding("pathPattern", "thickness", makeAdornmentPathPattern)),
 1158          CMButton({ alignmentFocus: new go.Spot(0, 0, -6, -4) })
 1159        );
 1160
 1161      function makeAdornmentPathPattern(w) {
 1162        return $(go.Shape,
 1163          {
 1164            stroke: "dodgerblue", strokeWidth: 2, strokeCap: "square",
 1165            geometryString: "M0 0 M4 2 H3 M4 " + (w+4).toString() + " H3"
 1166          });
 1167      }
 1168
 1169      // Link context menu
 1170      // All buttons in context menu work on both click and contextClick,
 1171      // in case the user context-clicks on the button.
 1172      // All buttons modify the link data, not the Link, so the Bindings need not be TwoWay.
 1173
 1174      function ArrowButton(num) {
 1175        var geo = "M0 0 M16 16 M0 8 L16 8  M12 11 L16 8 L12 5";
 1176        if (num === 0) {
 1177          geo = "M0 0 M16 16 M0 8 L16 8";
 1178        } else if (num === 2) {
 1179          geo = "M0 0 M16 16 M0 8 L16 8  M12 11 L16 8 L12 5  M4 11 L0 8 L4 5";
 1180        }
 1181        return $(go.Shape,
 1182          {
 1183            geometryString: geo,
 1184            margin: 2, background: "transparent",
 1185            mouseEnter: (e, shape) => shape.background = "dodgerblue",
 1186            mouseLeave: (e, shape) => shape.background = "transparent",
 1187            click: ClickFunction("dir", num), contextClick: ClickFunction("dir", num)
 1188          });
 1189      }
 1190
 1191      function AllSidesButton(to) {
 1192        var setter = (e, shape) => {
 1193            e.handled = true;
 1194            e.diagram.model.commit(m => {
 1195              var link = shape.part.adornedPart;
 1196              m.set(link.data, (to ? "toSpot" : "fromSpot"), go.Spot.stringify(go.Spot.AllSides));
 1197              // re-spread the connections of other links connected with the node
 1198              (to ? link.toNode : link.fromNode).invalidateConnectedLinks();
 1199            });
 1200          };
 1201        return $(go.Shape,
 1202          {
 1203            width: 12, height: 12, fill: "transparent",
 1204            mouseEnter: (e, shape) => shape.background = "dodgerblue",
 1205            mouseLeave: (e, shape) => shape.background = "transparent",
 1206            click: setter, contextClick: setter
 1207          });
 1208      }
 1209
 1210      function SpotButton(spot, to) {
 1211        var ang = 0;
 1212        var side = go.Spot.RightSide;
 1213        if (spot.equals(go.Spot.Top)) { ang = 270; side = go.Spot.TopSide; }
 1214        else if (spot.equals(go.Spot.Left)) { ang = 180; side = go.Spot.LeftSide; }
 1215        else if (spot.equals(go.Spot.Bottom)) { ang = 90; side = go.Spot.BottomSide; }
 1216        if (!to) ang -= 180;
 1217        var setter = (e, shape) => {
 1218            e.handled = true;
 1219            e.diagram.model.commit(m => {
 1220              var link = shape.part.adornedPart;
 1221              m.set(link.data, (to ? "toSpot" : "fromSpot"), go.Spot.stringify(side));
 1222              // re-spread the connections of other links connected with the node
 1223              (to ? link.toNode : link.fromNode).invalidateConnectedLinks();
 1224            });
 1225          };
 1226        return $(go.Shape,
 1227          {
 1228            alignment: spot, alignmentFocus: spot.opposite(),
 1229            geometryString: "M0 0 M12 12 M12 6 L1 6 L4 4 M1 6 L4 8",
 1230            angle: ang,
 1231            background: "transparent",
 1232            mouseEnter: (e, shape) => shape.background = "dodgerblue",
 1233            mouseLeave: (e, shape) => shape.background = "transparent",
 1234            click: setter, contextClick: setter
 1235          });
 1236      }
 1237
 1238      myDiagram.linkTemplate.contextMenu =
 1239        $("ContextMenu",
 1240          DarkColorButtons(),
 1241          StrokeOptionsButtons(),
 1242          $("ContextMenuButton",
 1243            $(go.Panel, "Horizontal",
 1244              ArrowButton(0), ArrowButton(1), ArrowButton(2)
 1245            )
 1246          ),
 1247          $("ContextMenuButton",
 1248            $(go.Panel, "Horizontal",
 1249              $(go.Panel, "Spot",
 1250                AllSidesButton(false),
 1251                SpotButton(go.Spot.Top, false), SpotButton(go.Spot.Left, false), SpotButton(go.Spot.Right, false), SpotButton(go.Spot.Bottom, false)
 1252              ),
 1253              $(go.Panel, "Spot",
 1254                { margin: new go.Margin(0, 0, 0, 2) },
 1255                AllSidesButton(true),
 1256                SpotButton(go.Spot.Top, true), SpotButton(go.Spot.Left, true), SpotButton(go.Spot.Right, true), SpotButton(go.Spot.Bottom, true)
 1257              )
 1258            )
 1259          )
 1260        );
 1261
 1262      load();
 1263    }
 1264
 1265    // Show the diagram's model in JSON format
 1266    function save() {
 1267      document.getElementById("mySavedModel").value = myDiagram.model.toJson();
 1268      myDiagram.isModified = false;
 1269    }
 1270    function load() {
 1271      myDiagram.model = go.Model.fromJson(document.getElementById("mySavedModel").value);
 1272    }
 1273    window.addEventListener('DOMContentLoaded', init);
 1274  </script>
 1275
 1276<div id="sample">
 1277  <div id="myDiagramDiv" style="border: 1px solid black; width: 100%; height: 600px; position: relative; -webkit-tap-highlight-color: rgba(255, 255, 255, 0); cursor: auto;"><canvas tabindex="0" width="1054" height="598" style="position: absolute; top: 0px; left: 0px; z-index: 2; user-select: none; touch-action: none; width: 1054px; height: 598px; cursor: auto;">This text is displayed if your browser does not support the Canvas HTML element.</canvas><div style="position: absolute; overflow: auto; width: 1054px; height: 598px; z-index: 1;"><div style="position: absolute; width: 1px; height: 1px;"></div></div></div>
 1278  <p>
 1279    Double-click in the background to create a new node.
 1280    Create groups by selecting nodes and invoking Ctrl-G; Ctrl-Shift-G to ungroup a selected group.
 1281    A selected node will have four orange triangles that when clicked will automatically copy the node and link to it.
 1282    Use the context menu to change the shape, color, thickness, and dashed-ness.
 1283  </p>
 1284  <p>
 1285    Links can be drawn by dragging from the side of each node.
 1286    A selected link can be reconnected by dragging an end handle.
 1287    Use the context menu to change the color, thickness, dashed-ness, and which side the link should connect with.
 1288    Press the F2 key to start editing the label of a selected link.
 1289  </p>
 1290  <div id="buttons">
 1291    <button id="loadModel" onclick="load()">Load</button>
 1292    <button id="saveModel" onclick="save()">Save</button>
 1293  </div>
 1294  <textarea id="mySavedModel" style="width:100%;height:300px">{ "class": "GraphLinksModel",
 1295  "nodeDataArray": [
 1296{"key":1, "loc":"0 0", "text":"Alpha", "details":"some information about Alpha and its importance"},
 1297{"key":2, "loc":"170 0", "text":"Beta", "color":"blue", "thickness":2, "figure":"Procedure"},
 1298{"key":3, "loc":"0 100", "text":"Gamma", "color":"green", "figure":"Cylinder1"},
 1299{"key":4, "loc":"80 180", "text":"Delta", "color":"red", "figure":"Terminator", "size":"80 40"},
 1300{"key":5, "loc":"350 -50", "text":"Zeta", "group":7, "color":"blue", "figure":"CreateRequest"},
 1301{"key":6, "loc":"350 50", "text":"Eta", "group":7, "figure":"Document", "fill":"lightyellow"},
 1302{"key":7, "isGroup":true, "text":"Theta", "color":"green", "fill":"lightgreen"},
 1303{"key":8, "loc":"520 50", "text":"Iota", "fill":"pink"}
 1304 ],
 1305  "linkDataArray": [
 1306{"from":1, "to":2, "dash":[ 6,3 ], "thickness":4},
 1307{"from":1, "to":3, "dash":[ 2,4 ], "color":"green", "text":"label"},
 1308{"from":3, "to":4, "color":"red", "text":"a red label", "fromSpot":"RightSide"},
 1309{"from":2, "to":1},
 1310{"from":5, "to":6, "text":"in a group"},
 1311{"from":2, "to":7},
 1312{"from":6, "to":8, "dir":0},
 1313{"from":6, "to":8, "dir":1},
 1314{"from":6, "to":8, "dir":2}
 1315 ]}
 1316  </textarea>
 1317<p class="text-xs">GoJS version 2.2.15. Copyright 1998-2022 by Northwoods Software.</p></div>
 1318    <p><a href="https://github.com/NorthwoodsSoftware/GoJS/blob/master/samples/blockEditor.html" target="_blank">View this sample page's source on GitHub</a></p></div>
 1319
 1320`).
 1321
 1322
 1323
 1324:- fixup_exports. 1325:- fixup_module_exports_now. 1326
 1327:- multifile(user:portray/1). 1328:- dynamic(user:portray/1). 1329user:portray(_):- tracing, inside_bfly_html_esc, bfly_out,fail.
 1330
 1331% user:portray(X):- \+ current_prolog_flag(debug, true), \+ tracing, bfly_portray(X), !.