This module make R available to SWISH using the
Rserve R package. The module r_serve.pl
implements a SWI-Prolog wrapper around the Rserve C++ client to realise
the communication with the R server.
The Prolog view at R is inspired by
real from Nicos Angelopoulos.
It consists of the following two predicates:
- Var <- Expression
Assign the result of evaluating the given R Expression to Var. Var
can be a Prolog variable or an R expression.
- <- Expression
Evaluate expression, discarding the result. Possible console output
is captured.
In addition, the quasi quotation r
is defined. The quasi quotation
takes Prolog variables as arguments and an R expression as content.
Arguments (Prolog variable names) that match R identifiers cause the
temporary of an R variable with that name bound to the translated Prolog
value. R quasi quotations can be used as isolated goals, as well as as
right-hand arguments to <-/2 and <-/1. The example below calls the R
plot()
function on the given Prolog list.
?- numlist(1,10,Data),
{|r(Data)||plot(Data)|}.
Images created by the R session are transferred as SVG and sent to the
SWISH console using pengine_output/1.
- r_call(+Fun, +Options)
- Construct and possibly call an R function. Fun can be an atom or
a compound, eg plot, or
plot(width=3)
. The predicate also
supports multiple output destinations. Options processed:
- call(Bool)
- If
false
(default true
), do not call the result.
- fcall(-Term)
- Term is unified with the constructed call
- rvar(Var)
- Variable for the output
- Compatibility
- - This is a partial implementation of the corresponding
real predicate.
- r_console(+Stream, ?Term)[multifile]
- Hook console interaction. Currently only used for <-/1 to emit
the captured output. In this cases, Stream is
stdout
and Term
is a list of strings, each representing a line of output. The
list can be empty. If the hook fails, maplist(writeln, Term)
is
called to write the output to current_output
.
- r_execute(+Assignments, +Command, -Result) is det
- Execute the R command Command after binding the variables in
Assignments and unify the result with Result.
- Arguments:
-
Assignments | - is a list of Name=Value, where Name must be a
valid R indentifier. |
Command | - is a string holding the R command to execute |
- r(+Content, +Vars, +VarDict, -Goal) is det
- Parse {|r(Arg,...||R-code|} into a the expression below. This
expression may be passed to <-/2 and <-/1 as well as used
directly as a goal, calling r_execute/3.
r_execute(Assignments, Command, Result)
- See also
- - https://cran.r-project.org/doc/manuals/r-release/R-lang.html#Parser
- To be done
- - Verify more of the R syntax.
- rserve:r_open_hook(+Name, -R)[multifile]
- Called for lazy creation to the Rserve server. Connections are
per-thread. The destination depends on settings:
- Unix domain socket
-
If
rserve:socket
is defined and not empty, it is taken
as the path to a Unix domain socket to connect to.
- TCP/IP socket
-
Else, if
rserve:port
and rserve:host
is defined, we
connect to the indicated host and port.
After the connection is established, the session can be
configured using the hook r_init_session/1. The default calls
r_setup_graphics/2 to setup graphics output to send SVG files.
- r_init_session(+RConn) is semidet[multifile]
- Multifile hook that is called after the Rserve server has handed
us a new connection. If this hook fails, r_setup_graphics/2 is
called to setup capturing graphics as SVG files.
- r_setup_graphics(+Rconn, +Format) is det
- Setup graphics output using files. Currently only supports
Format = svg
.
- r_display_images(+Images:list)[multifile]
- Hook to display images.
- Arguments:
-
Images | - is a list of images. Each image is of the form
Format(String), where Format is the file extension. Currently
only uses svg . If not defined, print_message/2 is called
with the term r_images(Images) . |
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- Arg1 <- Arg2
- <-(Arg1)