1:- module( bio_analytics, [
2 bio_analytics_version/2, % -Vers, -Date
3 bio_diffex/4, % +Exp, -DEs -NDEs, +Opts
4 bio_p_adjust/3, % +Obj, +AdjObj, +Opts
5 bio_symbols/3, % +Vect, -Symbs, +Opts
6 bio_volcano_plot/2, % +Mtx, Opts
7 exp_gene_family_string_graph/4, % +Exp, +Fam, -Graph, +Opts
8 exp_go_over/3, % +Exp, -GoOver, +Opts
9 exp_go_over_string_graphs/4, % +Exp, ?GoOver, ?Dir, +Opts
10 exp_go_over_string_graphs_multi/1,% +Opts
11 exp_reac_over/3, % +Exp, -ReOver, +Opts
12 gene_family/3, % +Alias, -Symbols, +Opts
13 go_org_symbol/3, % +Org, +GoT, -Symbol
14 go_org_symbols/3, % +Org, +GoT, -Symbols
15 go_over_plot/2, % +GovF, +Opts
16 go_string_graph/3, % +GoT, -Graph, +Opts
17 go_symbols_reach/3, % +GoT, -Symbs, +Opts
18 symbols_string_graph/3 % +Symbs, -Graph, +Opts
19 ] ).
?- bio_analytics_version(V,D). V = 0:7:0, D = date(2024,10,17).
*/
61bio_analytics_version( 0:7:0, date(2024,10,17) ). 62 63:- use_module(library(lists)). 64:- use_module(library(apply)). 65:- use_module(library(debug)). 66:- use_module(library(filesex)). 67:- use_module(library(lib)). 68 69:- lib(mtx). 70:- lib(real). 71:- lib(b_real). 72:- lib(bio_db). 73:- lib(os_lib). 74:- lib(options). 75:- lib(debug_call). 76:- lib(pack_errors). 77:- lib(promise(wgraph_plot/2,wgraph)). 78 79:- debug_call:debug(ba(info)). 80 81:- lib(source(bio_analytics), homonyms(true)). 82 83:- lib(gene_family/3). 84:- lib(go_org_symbols/3). 85:- lib(go_symbols_reach/3). 86:- lib(go_string_graph/3). 87:- lib(symbols_string_graph/3). 88:- lib(bio_diffex/4). 89:- lib(exp_gene_family_string_graph/4). 90:- lib(exp_go_over/3). 91:- lib(exp_go_over_string_graphs/4). 92:- lib(exp_go_over_string_graphs_multi/1). 93:- lib(bio_volcano_plot/2). 94:- lib(bio_symbols/3). 95:- lib(bio_org/0). 96:- lib(bio_p_adjust/3). 97:- lib(exp_reac_over/3). 98:- lib(go_over_plot/2). 99:- lib(end(bio_analytics), homonyms(true)). 100 101pack_errorsmessage( cannot_map_gids(Org,Gid,Gto) ) --> 102 ['Predicate org_gid_map/3 could not convert gids from: ~w to: ~w in organism: ~w.'-[Gid,Gto,Org]]
Computational biology data analytics.
Collects a number of biological data analytics tasks. This library provides tools for the bio_db served data, empowering downstream analyses of user's experimental data.
Installation and loading:
The library comes with one experimental dataset: data/silac/bt.csv which is used in the example files in directory examples/ .
*/