--- /dev/null
+sweep_link.pl
\ No newline at end of file
swipl_plugin(
sweep-module
C_SOURCES sweep.c
- C_INCLUDE_DIR ${EMACS_INCLUDE_DIR})
+ C_INCLUDE_DIR ${EMACS_INCLUDE_DIR}
+ PL_LIBS sweep_link.pl)
pkg_doc(
sweep
),
Index).
+:- if(exists_source(library(sweep_link))).
+:- use_module(library(sweep_link), [write_sweep_module_location/0]).
+:- else.
write_sweep_module_location :-
+ format('V ~w~n', 1),
absolute_file_name(foreign('sweep-module'),
Path,
[file_type(executable), access(read)]),
( current_prolog_flag(executable_format, elf)
-> current_prolog_flag(libswipl, Libpath),
- writeln(Libpath)
+ format('L ~w~n', Libpath)
; true
),
- writeln(Path).
+ format('M ~w~n', Path).
+:- endif.
sweep_top_level_server(_, Port) :-
tcp_socket(ServerSocket),
--- /dev/null
+/*
+ Author: Eshel Yaron
+ E-mail: eshel@swi-prolog.org
+ Copyright (c) 2022, SWI-Prolog Solutions b.v.
+ All rights reserved.
+
+ Redistribution and use in source and binary forms, with or without
+ modification, are permitted provided that the following conditions
+ are met:
+
+ 1. Redistributions of source code must retain the above copyright
+ notice, this list of conditions and the following disclaimer.
+
+ 2. Redistributions in binary form must reproduce the above copyright
+ notice, this list of conditions and the following disclaimer in
+ the documentation and/or other materials provided with the
+ distribution.
+
+ THIS SOFTWARE IS PROVIDED BY THE COPYRIGHT HOLDERS AND CONTRIBUTORS
+ "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT
+ LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS
+ FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE
+ COPYRIGHT OWNER OR CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT,
+ INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING,
+ BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES;
+ LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER
+ CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
+ LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN
+ ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE
+ POSSIBILITY OF SUCH DAMAGE.
+*/
+
+:- module(sweep_link,
+ [ write_sweep_module_location/0
+ ]).
+
+/** <module> Information for dynamically linking to GNU Emacs
+*/
+
+sweep_link_version(1).
+
+write_sweep_module_location :-
+ sweep_link_version(V),
+ format('V ~w~n', V),
+ absolute_file_name(foreign('sweep-module'),
+ Path,
+ [file_type(executable), access(read)]),
+ ( current_prolog_flag(executable_format, elf)
+ -> current_prolog_flag(libswipl, Libpath),
+ format('L ~w~n', Libpath)
+ ; true
+ ),
+ format('M ~w~n', Path).
(declare-function sweeprolog-close-query "sweep-module")
(declare-function sweeprolog-cleanup "sweep-module")
+(defun sweeprolog--load-module (line)
+ (save-match-data
+ (when (string-match (rx bos
+ (or "L" "M")
+ (one-or-more whitespace)
+ (group-n 1 (one-or-more not-newline))
+ eos)
+ line)
+ (load (match-string 1 line)))))
+
(defun sweeprolog--ensure-module ()
"Locate and load `sweep-module', unless already loaded."
(unless (featurep 'sweep-module)
- (if-let ((paths (save-match-data
+ (if-let ((lines (save-match-data
(split-string
(with-output-to-string
(with-current-buffer standard-output
"sweep.pl"
(file-name-directory load-file-name)))))
"\n" t))))
- (mapc #'load paths)
+ (mapc #'sweeprolog--load-module lines)
(error (concat "Failed to locate `sweep-module'. "
"Make sure SWI-Prolog is installed "
"and up to date")))))
(sweeprolog-open-query "user" "sweep" "sweep_path_module" (buffer-file-name))
(let ((sol (sweeprolog-next-solution)))
(sweeprolog-close-query)
- (when (sweeprolog-true-p sol)
- (setq sweeprolog-buffer-module (cdr sol)))))
+ (setq sweeprolog-buffer-module
+ (if (sweeprolog-true-p sol)
+ (cdr sol)
+ "user"))))
;;;###autoload
(defun sweeprolog-find-module (mod)
(when sweeprolog--diagnostics-report-fn
(funcall sweeprolog--diagnostics-report-fn sweeprolog--diagnostics)
(setq sweeprolog--diagnostics-report-fn nil))
+ (sweeprolog--set-buffer-module)
sol))))
(defun sweeprolog-colourise-some-terms (beg0 end0 &optional _verbose)