Interface predicates to commonly used R functions. This library allows Prolog users to do same simple tasks in R with out writing any R code or call any R functions explicitly.
Dependancies
date(Y,M,D)).
?- b_real_version( Vers, Date ). Vers = 1:0:0, Date = date(2023, 9, 1).
?- c25( C25 ), colours_pie( C25 ).
up_down(Up,Down)
of DeReg3 = up_down(Up,Level,Down)
Colours for up and down (de) regulation.
?- colour_de_reg( up_down(Up,Down) ), colours_pie( [Up,Down] ).
c(c11,cl2,c3). This should be digestable by real as an
input to a named argument. Requires library(real).
Opts
 ?- lib(b_real:c25/1).
 ?- c25(C25), colours_pie( C25 ).
 ?- lib(b_real:colour_cb/1).
 ?- colour_cb(Cb), colours_pie( Cb ).
 ?- lib(real).
 ?- <- library("RColorBrewer").
 ?- Set1 <- brewer.pal(9,"Set1"), colours_pie( Set1, main(main) ).
 ?- colfunc <- colorRampPalette(c("white", "blue")),Ten <- colfunc(10),colours_pie(Ten).
 ?- lib(r("colorspace")).
 ?- Pal <- diverge_hcl(7), colours_pie( Pal ).
 ?- Pal <- sequential_hcl(7), colours_pie( Pal ). % gives you shades of blue
 ?- R <- rainbow_hcl( 4 ), colours_pie( R ).
 ?- colours_pie( ["#008000","#CC0000"], weights(c(1,2)) ).
 ?- colours_pie( ["#008000","#CC0000"], [weights(c(1,2)),prefix(false)] ).
 ?- colours_pie( ["#008000","#CC0000"], [weights(c(1,1)),labels([a,b])] ).
?- lib(b_real:colours_pie/1).
?- colour_cb(Cb), colours_pie(Cb).
Cb = c("#999999", "#E69F00", "#56B4E9", "#009E73", "#F0E442", "#0072B2", "#D55E00", "#CC79A7").
?- lib(real).
?- colour_cb(Cb), <- svg("clr_cb.svg"), colours_pie(Cb), r_devoff.
Produces file: clr_cb.svg
?- lib(b_real:colours_pie/1).
?- colour_cbb(Cbb), colours_pie(Cbb).
Cbb = c("#000000", "#E69F00", "#56B4E9", "#009E73", "#F0E442", "#0072B2", "#D55E00", "#CC79A7").
Note that standard version of aheatmap() has a bug
when breaks and colours are given: https://github.com/renozao/NMF/issues/12
2014/08/12
Opts
aheatmap() call additional parameters given in Name(Value) syntax
?- Mpg <- mtcars$mpg, aheatmap( Mpg, [rowV(false),colV(false)]  ).
?- Mpg <- mtcars$mpg, x <- [Mpg], colnames(x) <- rownames(mtcars),
   aheatmap( x, [cellheight=32,scale(false),rowV(false)]  ).
?-
   Mtc <- as.list(mtcars), memberchk(hp=HP,Mtc), memberchk(disp=Disp,Mtc),
   x <- [HP, Disp], rownames(x) <- c("horsepower","displacement"),
   colnames(x) <- rownames(mtcars),
   aheatmap(x).
Pval is the anova p.value of Clm2 ~ Clm1, Coef is the coefficient of the regression, R2 is R squared (coefficient of determination). See options.
Opts
?- mtx_data( mtcars, Mt ), lm_plot( mpg, disp, mtx(Mt) ). ?- assert( lm_mtx( [row(a,b,c),row(1,2,3),row(2,3,4),row(3,4,5)] ) ). ?- lm_mtx( Mtx ), lm_plot( a, b, C, R2, P, mtx(Mtx) ). C = 1.0, P = 0.0. ?- lm_mtx(Mtx), lm_plot(Mtx,a,b,C,R2,P,true,). C = 1.0, P = 0.0. ?- ls. what.png ?- use_module( library(by_unix) ). ?- @ eog(what.png).
Opts is a combination of options controlling the predicate as per normal Prolog convention, and term structures that translate to '+' ggplot2 terms.
Originally this only supported lists at the value part of Pairs. Now single values make the predicate plot a non-grouped barplot.
Opts
scale_fill_manual() term, true use def. colours, else give list of coloursgeom_bar() termggplot2() one). only works for Clrs \== falsepdf("myfile.pdf")?- Pairs = [a-[1,2,3],b-[2,4,6]], gg_bar_plot( Pairs, true ). ?- FClrs = ["gold1", "#E31A1C", "blue1"], BoldTitle = theme(plot.title(element_text(face(+"bold")))), Pairs = [a-[1,2,3],b-[2,4,6]], gg_bar_plot( Pairs, [debug(true), geom_bar_draw_colour(black), labels(x,y,main), fill_colours(FClrs), gg_terms(BoldTitle),legend_title(leeg)] ). ?- FClrs = ["gold1", "#E31A1C","blue1","darkolivegreen"], Pairs = [a-1,b-2,c-3,d-4], gg_bar_plot( Pairs, [flip(false),geom_bar(empty),fill_colours(FClrs)] ). ?- Pairs = [a-1,b-2,c-3,d-4], gg_bar_plot( Pairs, [flip(false),geom_bar(empty),fill_colours(true),df_rvar_rmv(false)] ).
Since v0.5 it is possible to pass colour names recognised by colour_hex/2. This examples also shows how to use the predicate for displaying up and downregulation data from biological experiments.
?- Pairs = [a-[12,-22],b-[14,-5]], Fcs = [cadmiumred,brandeisblue], gg_bar_plot( Pairs, [fill_colours(Fcs),output(svg("dereg_bar_plot.svg"))] ).
Produces file: dereg_bar_plot.svg
Currently the expected format for Data is Label-Value KVPairs.
Opts
strict for not flipping and not turning, or a number (such as 90) for the actual degrees.ggplot() callfalse displays according to ggplot2
reverse reverses it
true keeps the order of labels in Data as is.
size order in descending size of the numerical values in Data, and
size_reverse orders elements in ascending size of the numerical values in Datalolli if flip(true) is given in Opts.Examples
?- gg_lollipop([a-2,b-5,c-1,d-3], true).
Options are passed to gg_outputs/2.
?- gg_lollipop([a-2,b-5,c-1,d-3], outputs(svg)).
Produces file: gg_lollipop.svg
Change basic parameters of the plot
?- gg_lollipop([a-2,b-5,c-1,d-3], [clr_point("red"),clr_stem("green"),theme(false)] ).
?- gg_lollipop( [a-2,b-5,c-1,d-3], theme(blank) ).
Change the labels
?- gg_lollipop([a-2,b-5,c-1,d-3], labels(doom,gloom,all_around)).
Inject arbitrary ggplot2 terms
?- gg_lollipop( [a-2,b-5,c-1,d-3], theme(false) ). ?- gg_lollipop( [a-2,b-5,c-1,d-3], [theme(false),g_terms(theme_light())] ).
Adjust angle of tick labels, when not flipping
?- gg_lollipop([a-2,b-5,c-1,d-3], flip(45) ).
"ordering" can be counter-intuitive. By Order=true we mean keep the order as in the given list.
By default, ggplot2 presents the categorical variable in lexicographical order.
?- gg_lollipop([b-5,a-2,d-3,c-1], true ). ?- gg_lollipop([b-5,a-2,d-3,c-1], order(false) ). ?- gg_lollipop([b-5,a-2,d-3,c-1], order(reverse) ).
The plot can also be ordered by the numerical values in the Data.
?- gg_lollipop([a-2,b-5,c-1,d-3], order(size) ). ?- gg_lollipop([a-2,b-5,c-1,d-3], order(size_reverse) ).
Can keep the R variables around for later use with
?- gg_lollipop([a-2,b-5,c-1,d-3], rvar_rmv(false)). ?- lib(real). ?- <- ls(). ?- <- print(ls()). [1] "glp_df" "glp_gp" true. ?- DF <- glp_df. DF = [x=[1, 2, 3, 4], y=[2, 5, 1, 3]]. ?- <- summary(glp_gp). data: x, y [4x2] mapping: x = ~x, y = ~y ...
ggsave().
Ggplot should be an R variable holding a ggplot2 plot. In addition to be called directly by users, this predicate is also used in a number of Prolog library predicates that interface to ggplot2 plots.
Opts
ggsave() goalExamples
?- lib(real), lib(r(ggplot2)). ?- ddf <- 'data.frame'(x='LETTERS'[1:26], y=abs(rnorm(26)) ). ?- ggp <- ggplot(ddf, aes(x=x, y=y)) + geom_segment(aes(x=x,xend=x,y=0,yend=y)) + geom_point(size=4,alpha=0.6). ?- gg_outputs(ggp,[]).
?- lib(real), lib(r(ggplot2)). ?- ddf <- 'data.frame'(x='LETTERS'[1:26], y=abs(rnorm(26)) ). ?- ggp <- ggplot(ddf, aes(x=x, y=y)) + geom_segment(aes(x=x,xend=x,y=0,yend=y)) + geom_point(size=4,alpha=0.6). ?- gg_outputs( ggp, outputs(png(file="abc.svg")) ).
Produces file: abc.svg
Width, Height and Stem can be overridden by = options within Outs.
In the example below, the pdf gets Width 8, from the plot_width parameter, while the png gets Width 9.
?- lib(real), lib(r(ggplot2)). ?- ddf <- 'data.frame'(x='LETTERS'[1:26], y=abs(rnorm(26)) ). ?- ggp <- ggplot(ddf, aes(x=x, y=y)) + geom_segment(aes(x=x,xend=x,y=0,yend=y)) + geom_point(size=4,alpha=0.6). ?- gg_outputs( ggp, [plot_width(8),outputs([pdf,png(file="abc.png",width=9)]),debug(true)] ). % Sending to Real: ggsave(plot=ggp,width=8,height=7,file= +gg_output.pdf) % Sending to Real: ggsave(plot=ggp,height=7,file=abc.png,width=9)
Panel
?- Pairs = [a-[1,2,3],b-[2,4,6]], gg_bar_plot( Pairs, true ).
    % shows a plot with grid lines and axis lines
?- Pairs = [a-[1,2,3],b-[2,4,6]], gg_bar_plot( Pairs, theme(blank) ).
    % shows a plot with neither grid lines and axis lines
?- Pairs = [a-[1,2,3],b-[2,4,6]], gg_bar_plot( Pairs, theme(axes) ).
    % shows a plot with no-background colour and no grid lines, but with lines on both axes
Opts
Mtx = [  row(v,x,y,z),
         row(1,0,0,a),
         row(0,0,1,a),
            row(0,1,1,b),
            row(1,1,1,b),
            row(0,1,0,c)
      ],
assert( ex1(Mtx) ).
?- ex1(Mtx), vectors_subed_gg_bar_plot( [v,x,y], 1, z, mtx(Mtx) ).
[[1,1,0],[0,2,1],[1,2,0]]
Opts are passed to
pheatmap() from omonymous package.
See mtx_column_pheatmap/3. Here we print vertically though.
Opts
pheatmap() R callPredicate uses r_call/2 which takes its own options.
Dependencies
?- pack_install( real ). ?- use_module( library(real) ). ?- <- install.packages( "pheatmap" ).
Examples
?- use_module( library(real) ). ?- <- write.csv( mtcars, "mtcars.csv" ). % mtcars is an example dataset in R ?- csv_read_file( 'mtcars.csv', Mt ), assert( mt(Mt) ). ?- mt(Mt), mtx_pheatmap( Mt, [names(1),scale="column"] ). ?- mt(Mt), mtx_pheatmap( Mt, [names(1),scale="column",debug(true)] ).
This is mainly constructed as a demonstration of using R's pheatmap function from the omonymous library (http://cran.r-project.org/web/packages/pheatmap/pheatmap.pdf).
Opts
atomic_list_concat([Cnm,phmap],'_',Stem).Ropt
privates(true)?- use_module( library(real) ). ?- <- write.csv( mtcars, "mtcars.csv" ). % mtcars is an example dataset in R ?- csv_read_file( 'mtcars.csv', Mt ), mtx_column_pheatmap( Mt, 2, [] ). ?- csv_read_file( 'mtcars.csv', Mt ), mtx_column_pheatmap( Mt, 2, [names(1)] ). ?- csv_read_file( 'mtcars.csv', Mt ), mtx_column_pheatmap( Mt, 2, [names(1),legend='TRUE'] ). ?- csv_read_file( 'mtcars.csv', Mt ), mtx_column_pheatmap( Mt, 2, [names(1),outputs(pdf),stem(mtcars_c2)] ). ?- shell( 'ls -l mtcars_c2.pdf' ). -rw------- 1 user user 4212 Jan 13 13:56 mtcars_c2.pdf
rvar_rmv(true) is in Opts.
The rationale is to make rvar_rmv(_) a commonly occured option in b_real predicates.
?- x <- 1. ?- <- x. [1] 1 true. ?- options_rvar_rmv( x, [rvar_rmv(true)] ). ?- <- x. % Error in print(x) : object 'x' not found % ERROR: R was unable to digest your statement, either syntax or existance error ?- x <- 1. ?- options_rvar_rmv( x, [rvar_rmv(false),debug(true)] ). % Keeping R variable: x true. ?- y <- 2. ?- options_rvar_rmv( [x,y], [rvar_rmv(true)] ). true. ?- <- x. ERROR: R was unable to digest your statement, either syntax or existance error.
Through Options you can also control max and min values. As of version 0.6 option value Multi can be used to channel lists of vectors.
Recognisable represenation are:
memberchk(mtx(MTx),Opts) and mtx_column(Mtx, Cid, Vect)Opts
true it allows input of a list of representations and canonicalsk(Kid) is not present
Currently, k() and v() are inompatible to max() and min().
?- pl_vector( [1,2,3], V, true ). V = [1, 2, 3]. ?- mtx_data( mtcars, Mc ), pl_vector( 1, Vect, [mtx(Mc),cnm(Cnm)] ), max_list( Vect, Max ). Mc = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, 6.0|...], Vect = [21.0, 21.0, 22.8, 21.4, 18.7, 18.1, 14.3, 24.4, 22.8|...], Cnm = mpg, Max = 33.9. ?- mtx_data( mtcars, Mc ), pl_vector( 1, Vect, [mtx(Mc),cnm(Cnm),max(30)] ), max_list( Vect, Max ). Mc = [row(mpg, cyl, disp, hp, drat, wt, qsec, vs, am, gear, carb), row(21.0, 6.0|...], Vect = [21.0, 21.0, 22.8, 21.4, 18.7, 18.1, 14.3, 24.4, 22.8|...], Cnm = mpg, Max = 30.
As of v0.5
?- mtx_data( mtcars, Mc ), pl_vector( 1:Mc, Vect, true ), max_list( Vect, Max ). ... Vect = [21.0, 21.0, 22.8, 21.4, 18.7, 18.1, 14.3, 24.4, 22.8|...], Max = 33.9. ?- mtx_data( mtcars, Mc ), pl_vector( mpg:Mc, Vect, cps(MpgPos) ), max_list( Vect, Max ). ... MpgPos = 1, ...
As of v0.6
?- pl_vector( [1,2,3], V, multi(true) ). ERROR: Unhandled exception: Unknown message: cannot_identify_pl_values_for_vector(1) ?- pl_vector( [[1,2,3]], V, multi(true) ). V = [[1, 2, 3]].
pack(real)) understands as a LHS to <- assignment.
That is, if it is a Prolog variable, it will be instantiated to the vector as a list,
or a ground term, will translate that to an R expression (typically an R variable) to which
the scaled vector is assigned to.
For details on VectSpec, see pl_vector/3 and options affecting this.
Opts
See R's scale().
?- Mtc <- as.vector( mtcars[*,3] ), Mean <- mean(Mtc), vector_scale( Mtc, Sca, [scale(true)] ), ScaMean <- mean(Sca), ScaVrc <- var(Sca). Mtc = ... Mean = 230.721875, Sca = ... ScaMean = -9.084936579070724e-17, ScaVrc = [[1.0]]. ?- Mtc <- as.vector( mtcars[*,3] ), Mean <- mean(Mtc), vector_scale( Mtc, Sca, [scale(centre)] ), ScaMean <- mean(Sca), ScaVrc <- var(Sca). Mtc = ... Mean = 230.721875, Sca = ... ScaMean = -1.199040866595169e-14, ScaVrc = [[15360.799828629033]].
?- pl_plot_on( <- plot(c(1,2,3)), plot_on(x11()) ). ?- pl_plot_on( <- plot(c(1,2,3)), plot_on(pdf(+ex.pdf)) ). ?- shell( 'evince ex.pdf' ). ?- pl_plot_on( <- plot(c(1,2,3)), plot_on(x11(width=14)) ).
Opts
?- mtx_data( mtcars, Mt ), r_mtx( rv, Mt, [debug(true),rownames(1)] ).
If DfIn, is an R variable, and Df is atomic it is assumed to be a data frame and Df <- DfIn, is called (this can be elaborated upon later), whereas if Df is variable then Df = DfIn is called.
If DfIn is not an R variable, it is passed through mtx/2 and the result is passed through mtx_df/2. When Df is a variable in this context, a unique variable is generated that looks like tmp.df.N where N is an integer.
?- r_unique( df.data, Uniq ). Uniq = df.data.1. ?- r_unique( df.data, Uniq ). Uniq = df.data.2.
Opts
main() optionCfx=true else Stem is passed.
If Stem='' and Cfx=true (defaults) Cid is passed as r_hist/2 stem().
If Stem='' and Cfx=false then class is passed.
The predicate options are also passed to r_hist/2 (with debug_r_hist() renamed to debug()).
Examples
?- use_module(library(mtx)), mtx_data( iris, Iris ) r_mtx_class_distros(Iris,[]). ?- ls(). Petal.Length.svg Petal.Width.svg plots/ Sepal.Length.svg Sepal.Width.svg
As above, but cuts Y max values to 2 and minimum of 0.
?- use_module(library(mtx)), mtx_data( iris, Iris ), r_mtx_class_distros(Iris,[dir(plots),ylim=c(0,2)]).
The predicate uses r_hist/2 and with default values it will create .svg versions of the plots in sub-directory plots.
Opts
Cfx=true else Stem is passed.
If Stem='' and Cfx=true (defaults) Cid is passed as r_hist/2 stem().
If Stem='' and Cfx=false then class is passed.
The predicate options are also passed to r_hist/2 (with debug_r_hist() renamed to debug()).
Examples
?- use_module(library(mtx)), mtx_data( iris, Iris ) r_mtx_columns_hist(Iris,[]). ?- ls(plots). Petal.Length.svg Petal.Width.svg plots/ Sepal.Length.svg Sepal.Width.svg
As above, but cuts Y max values to 2 and minimum of 0.
?- use_module(library(mtx)), mtx_data( iris, Iris ), r_mtx_class_distros(Iris,[dir(plots),ylim=c(0,2)]).
VectSpec should be as that recognised by the 1st argument of pl_vector/3. A list is the simplest representation of a vector.
Displaying is via r_call/2, so Opts can influence that call.
Opts
true VectSpec should be a list of
vector specs. Currently only with AsDense=trueAsDense=true)
?- lib(real).
?- Mtc <- as.matrix(mtcars), r_hist( 2, mtx(Mtc) ).
?- rns <- rnorm(1000).
?- Rns <- rns, r_hist( Rns, name("rnorm") ).
?- Rns <- rns, r_hist( Rns, [name("rnorm"),main="Main Title",outputs(svg),stem(rh1)] ).
Produces file: rh1.svg
?- lib(real).
?- rnsm <- rnorm(10000), r_hist( rnsm, true ).
?- r_hist( rnsm, as_density(true) ).
?- pl_vector( rnsm, Rnsm, if_rvar(prolog) ), r_hist( Rnsm, name(+true) ).
?- r_hist( rnsm, [as_density(true),transparent(false)] ).
?- r_hist( rnsm, [as_density(true),transparency_colour("lightgreen"),outputs(svg),stem(rh2)] ).
Produces file: rh2.svg
?- lib(real).
?- rnsm <- rnorm(1000), r_hist( rnsm, true ).
?- rnsm2 <- rnorm(1000,2), r_hist(rnsm2, true).
?- r_hist([rnsm2,rnsm],[multi(true),as_density(true),transparency_colour(["lightgreen","lightblue"])]).
?-
     Fulls = [ multi(true), as_density(true), transparency_colour(["lightgreen","lightblue"]),
               xlab="x_lab",ylab="y_lab",main="main", ylim=c(0,0.3)
             ],
     r_hist([rnsm2,rnsm],Fulls).
?-
     Fulls = [ multi(true), as_density(true), transparency_colour(["lightgreen","lightblue"]),
               xlab="x_lab",ylab="y_lab",main="main", ylim=c(0,0.3), outputs(svg)
             ],
     r_hist([rnsm2,rnsm],Fulls).
Opts
?- cd( '/usr/local/users/nicos/work/2015/15.11.04-hmrn/Exploristics/data' ). ?- columns_fisher_test( hmrn_muts_t10.csv, inters, odds, Lods, [plot(true),plot_on(x11()),plot_on(pdf())] ).
Note that at_con/3 is used so '' is handled differently to atomic_list_concat/3.
?- dot( tmp, rv, Dot ). Dot = tmp.rv. ?- dot( [tmp,rv], phase1, Dot ). Dot = tmp.rv.phase1. ?- dot( '', x, Dot ). Dot = x. ?- dot( x, ['',x], Dot ). Dot = x.x.
Opts
?- mtx_df( [row(a,b,c),row(1,2,3),row(4,5,6)], df1 ), <- df1, csv_df( Csv1, df1 ). $a [1] 1 4 $b [1] 2 5 $c [1] 3 6 Csv1 = [row(a, b, c), row(1, 2, 3), row(4, 5, 6)].
This seems to get stuck for very large matrices, (>130,000).
See implementation in r_sqlite_load.pl .
length(Q) distinct elements spliting the list ot Length(Q)-1 quantiles.
The predicate would always replace the same value in List to the same Q element. Thus the quantiles
might be imbalanced in lengths.
Strictly speaking quantiles are the cut points but this predicate produces the rank of the elements. The purpose is to discretise vector of continuous values or to crate a vector of fewer factor values for a discrete vector.
?- quantiles( [6,5,4,3,2,1], [0,1], BinV ). BinV = [1, 1, 1, 0, 0, 0]. ?- quantiles( [6,6,6,2,2,2], [0,1], BinV ). BinV = [1, 1, 1, 0, 0, 0]. ?- quantiles( [6,6,6,6,6,2], [0,1], BinV ). BinV = [1, 1, 1, 1, 1, 0]. ?- quantiles( [6,6,6,6,6,6], [0,1], BinV ). BinV = [0, 0, 0, 0, 0, 0].
We need to modernise this and add it is an alternative to wgraph_plot. Modernise by dealing with widths within the predicate and letting SymbG be a wgraph.
See string_symboled_display/4.
Used to have 2 more args, Stem & Title; 4+5, which are now in Opts.
Opts
?- assert( g([a-b,b-c,c-a]) ), assert ns([a,b,c]). ?- g(G), ns(Ns), symboled_graph_display( G, Ns, [], Ns, [] ). ?- g(G), ns(Ns), symboled_graph_display( G, Ns, [], Ns, [output(svg)] ). ?- @ eog( abc.svg ).
Opts