swish/commit

New upstream versions

authorJan Wielemaker
Mon Jul 6 15:42:52 2015 +0200
committerJan Wielemaker
Mon Jul 6 15:42:52 2015 +0200
commit8c205d689f268c99e22990d90398955c9af64961
treecffc260a038620933c2c97c6ecf5175922ca76c6
parent39112273799c287e254b2e5842aa843016e6f3cd
Diff style: patch stat
diff --git a/lib/swish/gitty.pl b/lib/swish/gitty.pl
index ccc7f3e..5d04f1a 100644
--- a/lib/swish/gitty.pl
+++ b/lib/swish/gitty.pl
@@ -496,9 +496,19 @@ update_head(Store, head(Name, OldCommit, NewCommit)) :-
 	assert(head(Store, Name, NewCommit)).
 update_head(_, _).
 
+%%	remote_updates(+Store, -List) is det.
+%
+%	Find updates from other gitties  on   the  same filesystem. Note
+%	that we have to push/pop the input   context to avoid creating a
+%	notion of an  input  context   which  possibly  relate  messages
+%	incorrectly to the sync file.
+
 remote_updates(Store, List) :-
 	heads_input_stream(Store, Stream),
-	read_new_terms(Stream, List).
+	setup_call_cleanup(
+	    '$push_input_context'(gitty_sync),
+	    read_new_terms(Stream, List),
+	    '$pop_input_context').
 
 read_new_terms(Stream, Terms) :-
 	read(Stream, First),
diff --git a/lib/swish/markdown.pl b/lib/swish/markdown.pl
index 2dff03f..39da6ee 100644
--- a/lib/swish/markdown.pl
+++ b/lib/swish/markdown.pl
@@ -37,7 +37,10 @@
 		     ])).
 :- use_module(library(pldoc/doc_wiki)).
 :- use_module(library(option)).
+:- use_module(library(filesex)).
+
 :- use_module(storage).
+:- use_module(config).
 
 /** <module> SWISH Notebook markdown support
 
@@ -98,19 +101,27 @@ prolog:doc_autolink_extension(swinb, notebook).
 %
 %	  ```
 %	  - [My first book](mybook.swinb)
+%	  - [Label](store.pl)
+%	  - [Label](library/lists.pl)
 %	  ```
 
 file(File, Options) -->
-	{ file_name_extension(_Base, swinb, File),
-	  option(label(Label), Options)
+	{ once(sub_atom(File, Pre, _, _Post, /)),
+	  sub_atom(File, 0, Pre, _, Alias),
+	  swish_config:source_alias(Alias, _Options),
+	  option(label(Label), Options),
+	  http_location_by_id(swish, Swish),
+	  directory_file_path(Swish, File, HREF)
 	}, !,
-	html(a([class(swinb), href(File)], Label)).
+	html(a([class([alias,file]), href(HREF)], Label)).
 file(File, Options) -->
-	{ file_name_extension(_Base, pl, File),
-	  storage_file(File),
-	  option(label(Label), Options)
+	{ storage_file(File),
+	  option(label(Label), Options),
+	  http_location_by_id(swish, Swish),
+	  directory_file_path(Swish, p, StoreDir),
+	  directory_file_path(StoreDir, File, HREF)
 	}, !,
-	html(a([class(store), href(File)], Label)).
+	html(a([class(store), href(HREF)], Label)).
 file(File, Options) -->
 	pldoc_html:file(File, Options).
 
diff --git a/lib/swish/page.pl b/lib/swish/page.pl
index e307e48..bd6cda3 100644
--- a/lib/swish/page.pl
+++ b/lib/swish/page.pl
@@ -44,6 +44,7 @@
 :- use_module(library(http/http_header)).
 :- use_module(library(http/html_write)).
 :- use_module(library(http/js_write)).
+:- use_module(library(http/json)).
 :- use_module(library(http/http_json)).
 :- use_module(library(http/http_path)).
 :- if(exists_source(library(http/http_ssl_plugin))).
@@ -289,7 +290,7 @@ pengine_logo(_Options) -->
 	},
 	html(a([href(HREF), class('pengine-logo')], &(nbsp))).
 swish_logo(_Options) -->
-	{ http_absolute_location(swish('index.html'), HREF, [])
+	{ http_absolute_location(swish(.), HREF, [])
 	},
 	html(a([href(HREF), class('swish-logo')], &(nbsp))).
 
@@ -319,11 +320,8 @@ swish_content(Options) -->
 		 [ div([class([tile, horizontal]), 'data-split'('50%')],
 		       [ div([ class([editors, tabbed])
 			     ],
-			     [ div([ class(['prolog-editor']),
-				     'data-label'('Program')
-				   ],
-				   \source(Type, Options))
-			     | \notebooks(Type, Options)
+			     [ \source(Type, Options),
+			       \notebooks(Type, Options)
 			     ]),
 			 div([class([tile, vertical]), 'data-split'('70%')],
 			     [ div(class('prolog-runners'), []),
@@ -364,14 +362,19 @@ swish_config_hash -->
 source(pl, Options) -->
 	{ option(code(Spec), Options), !,
 	  download_source(Spec, Source, Options),
-	  phrase(source_data_attrs(Options), Extra)
+	  phrase(source_data_attrs(Options), Extra),
+	  source_meta_data(MetaAttrs, Options)
 	},
-	source_meta_data(Options),
-	html(textarea([ class([source,prolog]),
-			style('display:none')
-		      | Extra
-		      ],
-		      Source)).
+	html(div([ class(['prolog-editor']),
+		   'data-label'('Program')
+		 | MetaAttrs
+		 ],
+		 [ textarea([ class([source,prolog]),
+			      style('display:none')
+			    | Extra
+			    ],
+			    Source)
+		 ])).
 source(_, _) --> [].
 
 source_data_attrs(Options) -->
@@ -390,19 +393,16 @@ source_title_data(Options) -->
 	['data-title'(File)].
 
 
-%%	source_meta_data(+Options)//
+%%	source_meta_data(-Extra, +Options)
 %
 %	Dump the meta-data of the provided file into swish.meta_data.
+%	@tbd: serialize and add
 
-source_meta_data(Options) -->
-	{ option(file(_), Options),
-	  option(meta(Meta), Options)
-	}, !,
-	js_script({|javascript(Meta)||
-		   window.swish = window.swish||{};
-		   window.swish.meta_data = Meta;
-		   |}).
-source_meta_data(_) --> [].
+source_meta_data(['data-meta'(Text)], Options) :-
+	option(file(_), Options),
+	option(meta(Meta), Options), !,
+	atom_json_dict(Text, Meta, []).
+source_meta_data([], _).
 
 background(Options) -->
 	{ option(background(Spec), Options), !,
@@ -442,17 +442,18 @@ query(_) --> [].
 notebooks(swinb, Options) -->
 	{ option(code(Spec), Options),
 	  download_source(Spec, NoteBookText, Options),
-	  phrase(source_data_attrs(Options), Extra)
+	  phrase(source_data_attrs(Options), Extra),
+	  source_meta_data(MetaAttrs, Options)
 	},
 	html(div([ class('notebook'),
 		   'data-label'('Notebook')		% Use file?
+		 | MetaAttrs
 		 ],
 		 [ pre([ class('notebook-data'),
 			 style('display:none')
 		       | Extra
 		       ],
-		       NoteBookText),
-		   \source_meta_data(Options)
+		       NoteBookText)
 		 ])).
 notebooks(_, _) --> [].
 
diff --git a/lib/swish/render/table.pl b/lib/swish/render/table.pl
index d2348fb..d11962e 100644
--- a/lib/swish/render/table.pl
+++ b/lib/swish/render/table.pl
@@ -3,7 +3,7 @@
     Author:        Jan Wielemaker
     E-mail:        J.Wielemaker@cs.vu.nl
     WWW:           http://www.swi-prolog.org
-    Copyright (C): 2014, VU University Amsterdam
+    Copyright (C): 2014-2015, VU University Amsterdam
 
     This program is free software; you can redistribute it and/or
     modify it under the terms of the GNU General Public License
@@ -31,6 +31,8 @@
 	  [ term_rendering//3			% +Term, +Vars, +Options
 	  ]).
 :- use_module(library(apply)).
+:- use_module(library(lists)).
+:- use_module(library(option)).
 :- use_module(library(http/html_write)).
 :- use_module(library(http/term_html)).
 :- use_module('../render').
@@ -50,28 +52,29 @@ Render table-like data.
 %	  $ A list of terms of equal arity :
 %	  $ A list of lists of equal length :
 %
-%	@tbd: recogniser more formats, provide options to specify the
-%	header, etc.
+%	@tbd: recognise more formats
 
 term_rendering(Term, _Vars, Options) -->
-	{ is_list_of_terms(Term, _Rows, Cols)
+	{ is_list_of_terms(Term, _Rows, _Cols),
+	  header(Term, Header, Options)
 	}, !,
 	html(div([ style('display:inline-block'),
 		   'data-render'('List of terms as a table')
 		 ],
 		 [ table(class('render-table'),
-			 [ \header(Cols, Options),
+			 [ \header_row(Header),
 			   \rows(Term)
 			 ])
 		 ])).
 term_rendering(Term, _Vars, Options) -->
-	{ is_list_of_lists(Term, _Rows, Cols)
+	{ is_list_of_lists(Term, _Rows, _Cols),
+	  header(Term, Header, Options)
 	}, !,
 	html(div([ style('display:inline-block'),
 		   'data-render'('List of lists as a table')
 		 ],
 		 [ table(class('render-table'),
-			 [ \header(Cols, Options),
+			 [ \header_row(Header),
 			   \rows(Term)
 			 ])
 		 ])).
@@ -94,22 +97,48 @@ cells(Row, Cells) :-
 	compound(Row),
 	compound_name_arguments(Row, _, Cells).
 
-%%	header(+NCols, +Options)// is det.
+%%	header(+Table, -Header:list(Term), +Options) is semidet.
 %
-%	Include a header row  if   an  option header(+ListOfColNames) is
-%	present, whose length matches NCols.
-
-header(Cols, Options) -->
-	{ option(header(ColNames), Options),
-	  length(ColNames, Cols)
-	},
-	html(tr(class(hrow), \header_row(ColNames))).
-header(_, _) --> [].
-
-header_row([]) --> [].
-header_row([H|T]) -->
+%	Compute the header to use. Fails if   a  header is specified but
+%	does not match.
+
+header(_, _, Options) :-
+	\+ option(header(_), Options), !.
+header([Row|_], ColHead, Options) :-
+	member(header(Header), Options),
+	generalise(Row, GRow),
+	generalise(Header, GRow), !,
+	header_list(Header, ColHead).
+
+generalise(List, VList) :-
+	is_list(List), !,
+	length(List, Len),
+	length(VList0, Len),
+	VList = VList0.
+generalise(Compound, VCompound) :-
+	compound(Compound), !,
+	compound_name_arity(Compound, Name, Arity),
+	compound_name_arity(VCompound0, Name, Arity),
+	VCompound = VCompound0.
+
+header_list(List, List) :- is_list(List), !.
+header_list(Compound, List) :-
+	Compound =.. [_|List].
+
+
+%%	header_row(ColNames:list)// is det.
+%
+%	Include a header row  if ColNames is not unbound.
+
+header_row(ColNames) -->
+	{ var(ColNames) }, !.
+header_row(ColNames) -->
+	html(tr(class(hrow), \header_columns(ColNames))).
+
+header_columns([]) --> [].
+header_columns([H|T]) -->
 	html(th(\term(H, []))),
-	header_row(T).
+	header_columns(T).
 
 
 %%	is_list_of_terms(@Term, -Rows, -Cols) is semidet.
diff --git a/lib/swish/storage.pl b/lib/swish/storage.pl
index c0ae8b6..1968e43 100644
--- a/lib/swish/storage.pl
+++ b/lib/swish/storage.pl
@@ -28,7 +28,8 @@
 */
 
 :- module(web_storage,
-	  [ storage_file/1			% ?File
+	  [ storage_file/1,			% ?File
+	    storage_file/3			% +File, -Data, -Meta
 	  ]).
 :- use_module(library(http/http_dispatch)).
 :- use_module(library(http/http_parameters)).
@@ -41,6 +42,7 @@
 :- use_module(library(apply)).
 :- use_module(library(option)).
 :- use_module(library(debug)).
+:- use_module(library(solution_sequences)).
 
 :- use_module(page).
 :- use_module(gitty).
@@ -320,6 +322,7 @@ random_char(Char) :-
 		 *******************************/
 
 %%	storage_file(?File) is semidet.
+%%	storage_file(?File, -Data, -Meta) is semidet.
 %
 %	True if File is known in the store.
 
@@ -327,6 +330,10 @@ storage_file(File) :-
 	setting(directory, Dir),
 	gitty_file(Dir, File, _Head).
 
+storage_file(File, Data, Meta) :-
+	setting(directory, Dir),
+	gitty_data(Dir, File, Data, Meta).
+
 
 		 /*******************************
 		 *	 SEARCH SUPPORT		*
@@ -337,7 +344,13 @@ storage_file(File) :-
 
 %%	swish_search:typeahead(+Set, +Query, -Match) is nondet.
 %
-%	Find files using typeahead from the SWISH search box.
+%	Find files using typeahead  from  the   SWISH  search  box. This
+%	version defines the following sets:
+%
+%	  - file: Search the store for matching file names, matching tag
+%	    or title.
+%	  - store_content: Search the content of the store for matching
+%	    lines.
 %
 %	@tbd caching?
 %	@tbd We should only demand public on public servers.
@@ -368,3 +381,21 @@ meta_match_query(Query, Meta) :-
 	    sub_atom(Title, Before, 1, _, C),
 	    \+ char_type(C, csym)
 	).
+
+swish_search:typeahead(store_content, Query, FileInfo) :-
+	limit(25, search_store_content(Query, FileInfo)).
+
+search_store_content(Query, FileInfo) :-
+	setting(directory, Dir),
+	gitty_file(Dir, File, Head),
+	gitty_data(Dir, Head, Data, Meta),
+	Meta.get(public) == true,
+	limit(5, search_file(File, Meta, Data, Query, FileInfo)).
+
+search_file(File, Meta, Data, Query, FileInfo) :-
+	split_string(Data, "\n", "\r", Lines),
+	nth1(LineNo, Lines, Line),
+	once(sub_string(Line, _, _, _, Query)),
+	FileInfo = Meta.put(_{type:"store", file:File,
+			      line:LineNo, text:Line, query:Query
+			     }).
diff --git a/lib/swish/trace.pl b/lib/swish/trace.pl
index 51475c4..3772053 100644
--- a/lib/swish/trace.pl
+++ b/lib/swish/trace.pl
@@ -34,6 +34,7 @@
 :- use_module(library(settings)).
 :- use_module(library(pengines)).
 :- use_module(library(apply)).
+:- use_module(library(lists)).
 :- use_module(library(option)).
 :- use_module(library(solution_sequences)).
 :- use_module(library(edinburgh), [debug/0]).
@@ -44,6 +45,8 @@
 :- use_module(library(http/term_html)).
 :- use_module(library(http/html_write)).
 
+:- use_module(storage).
+
 :- if(current_setting(swish:debug_info)).
 :- set_setting(swish:debug_info, true).
 :- endif.
@@ -80,10 +83,11 @@ user:prolog_trace_interception(Port, Frame, _CHP, Action) :-
 	debug(trace, '[~d] ~w: Goal ~p', [Depth0, Port, Goal]),
 	term_html(Goal, GoalString),
 	functor(Port, PortName, _),
-	Prompt0 = _{type:  trace,
-		    port:  PortName,
-		    depth: Depth,
-		    goal:  GoalString
+	Prompt0 = _{type:    trace,
+		    port:    PortName,
+		    depth:   Depth,
+		    goal:    GoalString,
+		    pengine: Pengine
 		   },
 	add_context(Port, Frame, Prompt0, Prompt1),
 	add_source(Port, Frame, Prompt1, Prompt),
@@ -284,8 +288,15 @@ frame_file(Frame, File) :-
 	clause(QGoal, _Body, ClauseRef), !,
 	clause_property(ClauseRef, file(File)).
 
+%%	pengine_file(+File) is semidet.
+%
+%	True if File is a Pengine controlled file. This is currently the
+%	main file (pengine://) and (swish://) for included files.
+
 pengine_file(File) :-
-	sub_atom(File, 0, _, _, 'pengine://').
+	sub_atom(File, 0, _, _, 'pengine://'), !.
+pengine_file(File) :-
+	sub_atom(File, 0, _, _, 'swish://').
 
 %%	clause_position(+PC) is semidet.
 %
@@ -324,9 +335,10 @@ subgoal_position(ClauseRef, Port, File, CharA, CharZ) :-
 	end_port(Port), !,
 	clause_end(ClauseRef, File, CharA, CharZ).
 subgoal_position(ClauseRef, PC, File, CharA, CharZ) :-
+	debug(trace(source), 'In clause ~p at ~p', [ClauseRef, PC]),
 	clause_info(ClauseRef, File, TPos, _),
 	(   '$clause_term_position'(ClauseRef, PC, List)
-	->  debug(gtrace(position), 'Term-position: for ref=~w at PC=~w: ~w',
+	->  debug(trace(source), 'Term-position: for ref=~w at PC=~w: ~w',
 		  [ClauseRef, PC, List]),
 	    (   find_subgoal(List, TPos, PosTerm)
 	    ->  true
@@ -413,22 +425,44 @@ find_source(Predicate, File, Line) :-
 %
 %	Handle the breakpoints(List) option to  set breakpoints prior to
 %	execution of the query. If breakpoints  are present and enabled,
-%	the goal is executed in debug mode.
+%	the goal is executed in debug mode.  `List` is a list, holding a
+%	dict for each source that  has   breakpoints.  The dict contains
+%	these keys:
+%
+%	  - `file` is the source file.  For the current Pengine source
+%	    this is =|pengine://<pengine>/src|=.
+%	  - `breakpoints` is a list of lines (integers) where to put
+%	    break points.
 
 :- multifile pengines:prepare_goal/3.
 
 pengines:prepare_goal(Goal0, Goal, Options) :-
 	option(breakpoints(Breakpoints), Options),
 	Breakpoints \== [],
-	maplist(set_breakpoint, Breakpoints),
-	Goal = (debug, Goal0).
-
-set_breakpoint(Line) :-
-	debug(trace(break), 'Set breakpoint at line ~p', [Line]),
 	pengine_self(Pengine),
 	pengine_property(Pengine, source(File, Text)),
+	maplist(set_file_breakpoints(Pengine, File, Text), Breakpoints),
+	Goal = (debug, Goal0).
+
+set_file_breakpoints(_Pengine, PFile, Text, Dict) :-
+	debug(trace(break), 'Set breakpoints at ~p', [Dict]),
+	_{file:FileS, breakpoints:List} :< Dict,
+	atom_string(File, FileS),
+	(   PFile == File
+	->  debug(trace(break), 'Pengine main source', []),
+	    maplist(set_pengine_breakpoint(File, File, Text), List)
+	;   source_file_property(PFile, includes(File, _Time)),
+	    atom_concat('swish://', StoreFile, File)
+	->  debug(trace(break), 'Pengine included source ~p', [StoreFile]),
+	    storage_file(StoreFile, IncludedText, _Meta),
+	    maplist(set_pengine_breakpoint(PFile, File, IncludedText), List)
+	;   debug(trace(break), 'Not in included source', [])
+	).
+
+set_pengine_breakpoint(Owner, File, Text, Line) :-
+	debug(trace(break), 'Try break at ~q:~d', [File, Line]),
 	line_start(Line, Text, Char),
-	(   set_breakpoint(File, Line, Char, Break)
+	(   set_breakpoint(Owner, File, Line, Char, Break)
 	->  !, debug(trace(break), 'Created breakpoint ~p', [Break])
 	;   print_message(warning, breakpoint(failed(File, Line, 0)))
 	).
@@ -438,44 +472,80 @@ line_start(N, Text, Start) :-
 	N0 is N - 2,
 	offset(N0, sub_string(Text, Start, _, _, '\n')), !.
 
-%%	current_breakpoints(-Pairs) is det.
+%%	update_breakpoints(+Breakpoints)
 %
-%	@arg Pairs is a list `Id-Line` for each defined breakpoint.
+%	Update the active breakpoint  by  comparing   with  the  set  of
+%	currently active breakpoints.
 
-current_breakpoints(Pairs) :-
+update_breakpoints(Breakpoints) :-
+	breakpoint_by_file(Breakpoints, NewBPS),
 	pengine_self(Pengine),
-	findall(Id-Line,
-		( pengine_property(Pengine, source(File, _Text)),
-		  breakpoint_property(Id, file(File)),
-		  breakpoint_property(Id, line_count(Line))
-		),
-		Pairs).
+	pengine_property(Pengine, source(PFile, Text)),
+	current_pengine_source_breakpoints(PFile, ByFile),
+	forall(( member(File-FBPS, ByFile),
+		 member(Id-Line, FBPS),
+		 \+ ( member(File-NFBPS, NewBPS),
+		      member(Line, NFBPS))),
+	       delete_breakpoint(Id)),
+	forall(( member(File-NFBPS, NewBPS),
+		 member(Line, NFBPS),
+		 \+ ( member(File-FBPS, ByFile),
+		      member(_-Line, FBPS))),
+	       add_breakpoint(PFile, File, Text, Line)).
+
+breakpoint_by_file(Breakpoints, NewBPS) :-
+	maplist(bp_by_file, Breakpoints, NewBPS).
+
+bp_by_file(Dict, File-Lines) :-
+	_{file:FileS, breakpoints:Lines} :< Dict,
+	atom_string(File, FileS).
+
+add_breakpoint(PFile, PFile, Text, Line) :- !,
+	set_pengine_breakpoint(PFile, PFile, Text, Line).
+add_breakpoint(PFile, File, _Text, Line) :-
+	atom_concat('swish://', Store, File), !,
+	storage_file(Store, Text, _Meta),
+	set_pengine_breakpoint(PFile, File, Text, Line).
+add_breakpoint(_, _, _, _Line).			% not in our files.
+
+%%	current_pengine_source_breakpoints(+PengineFile, -Pairs) is det.
+%
+%	Find the currently set breakpoints  for   the  Pengine  with the
+%	given source file PengineFile. Pairs is a list File-BreakPoints,
+%	where BreakPoints is a list of breakpoint-ID - Line pairs.
 
-%%	update_breakpoints(+Breakpoints)
+current_pengine_source_breakpoints(PFile, ByFile) :-
+	findall(Pair, current_pengine_breakpoint(PFile, Pair), Pairs0),
+	keysort(Pairs0, Pairs),
+	group_pairs_by_key(Pairs, ByFile).
 
-update_breakpoints(Breakpoints) :-
-	current_breakpoints(Pairs),
-	debug(trace(break), 'Current: ~p, Request: ~p', [Pairs, Breakpoints]),
-	forall((member(Id-Line, Pairs), \+memberchk(Line, Breakpoints)),
-	       delete_breakpoint(Id)),
-	forall((member(Line, Breakpoints), \+memberchk(_-Line, Pairs)),
-	       set_breakpoint(Line)).
+current_pengine_breakpoint(PFile, PFile-(Id-Line)) :-
+	breakpoint_property(Id, file(PFile)),
+	breakpoint_property(Id, line_count(Line)).
+current_pengine_breakpoint(PFile, File-(Id-Line)) :-
+	source_file_property(PFile, includes(File, _Time)),
+	breakpoint_property(Id, file(File)),
+	breakpoint_property(Id, line_count(Line)).
 
 
 %%	prolog_clause:open_source(+File, -Stream) is semidet.
 %
-%	Open the saved pengine source if applicable
+%	Open SWISH non-file sources.
 
 :- multifile prolog_clause:open_source/2.
 
 prolog_clause:open_source(File, Stream) :-
-	pengine_file(File), !,
+	sub_atom(File, 0, _, _, 'pengine://'), !,
 	(   pengine_self(Pengine)
 	->  true
 	;   debugging(trace(_))
 	),
 	pengine_property(Pengine, source(File, Source)),
 	open_string(Source, Stream).
+prolog_clause:open_source(File, Stream) :-
+	atom_concat('swish://', GittyFile, File), !,
+	storage_file(GittyFile, Data, _Meta),
+	open_string(Data, Stream).
 
 
 		 /*******************************