1:- module( lib, [ 2 op( 200, fy, & ), 3 lib/1, lib/2 % +Repo[, +Opts] 4 ] ). 5 % lib_suggests/1, % fixme: feature() 6 % lib_promise/2, 7 % lib_expects/1+2, 8 % lib_init/1 9 10:- ensure_loaded(library(apply)). % exclude/3, ... 11:- ensure_loaded(library(lists)). % append/3, ... 12:- ensure_loaded(library(debug)). % debug/1+3, ? 13:- ensure_loaded(library(filesex)). % directory_file_path/3,... 14:- ensure_loaded(library(prolog_pack)). % query_pack_server/3 15 16:- ensure_loaded('../src/lib_init'). 17:- ensure_loaded('../src/lib_load'). 18:- ensure_loaded('../src/lib_type'). 19:- ensure_loaded('../src/lib_auxil'). 20:- ensure_loaded('../src/lib_attach'). 21:- ensure_loaded('../src/lib_homonyms'). 22:- ensure_loaded('../src/lib_suggests'). 23:- ensure_loaded('../src/lib_expects'). 24:- ensure_loaded('../src/lib_promise'). 25:- ensure_loaded('../src/lib_message'). 26:- ensure_loaded('../src/lib_pack_install'). 27 28:- dynamic(lib_tables:lib_repo/4). % +Repo, +Type, +Root, +Load 29:- dynamic(lib_tables:lib_repo_index/2). % +Repo, +IdxFile 30:- dynamic(lib_tables:lib_repo_homonyms/2). % +Repo, +SrcDir 31:- dynamic(lib_tables:lib_context/2). % +Ctx, +Root 32:- dynamic(lib_tables:lib_index/4). % +Pa, +Pn, +Repo, +File. records loaded indices 33:- dynamic(lib_tables:lib_promise/2). % +Pids, +Cxt, +Load. hot swap Pid with loading Load 34:- dynamic(lib_tables:lib_homonym/3). % +Stem, +Repo, +File. record loaded homonym 35:- dynamic(lib_tables:lib_loaded_index/2). % +Repo, +File. tracks loaded index files 36:- dynamic(lib_tables:lib_loaded_homonyms/2). % 37:- dynamic(lib_tables:lib_attached_indices/2). % +Ctx, Repo 38:- dynamic(lib_tables:lib_attached_homonyms/2).% +Ctx, Repo 39:- dynamic(lib_tables:lib_lazy/1). % +Repo 40:- dynamic(lib_tables:lib_full/2). % +Repo 41:- dynamic(lib_tables:lib_packs_at/2). % +Repo, +Dir 42:- dynamic(lib_tables:lib_skeleton_only/1). % +Pack 43 44:- multifile(user:lib_code_loader/3 ). 45 46userlib_code_loader(bioc, lib, lib_bioc). 47userlib_code_loader(r, lib, lib_r). 48 49% values: auto, allow option to override if set to true; false: never warn; true: always warn; install: install if missing 50:- Opts = [access(read_write),type(atom),keep(true)], 51 create_prolog_flag(lib_suggests_warns, auto, Opts). 52 53lib_bioc( Rlib, Opts ) :- 54 lib_r( Rlib, [bioc(true)|Opts] ). 55 56lib_r( Rlib, Opts ) :- 57 string( Rlib ), 58 !, 59 atom_string( RlibAtm, Rlib ), 60 lib_r( RlibAtm, Opts ). 61lib_r( Rlib, _Opts ) :- 62 getenv( 'R_LIB_REAL', RlibRealPath ), 63 atomic_list_concat( RlibDirs, ':', RlibRealPath ), 64 member( Rdir, RlibDirs ), 65 member( Ext, ['','r','R'] ), 66 file_name_extension( Rlib, Ext, Rbase ), 67 directory_file_path( Rdir, Rbase, Rfile ), 68 exists_file( Rfile ), 69 !, 70 r_call( source(+Rfile), [] ). 71lib_r( Rlib, Opts ) :- 72 memberchk( suggest(Sugg), Opts ), 73 current_prolog_flag( lib_suggests_warns, SuggFlag ), 74 (Sugg == true ; SuggFlag == debug; SuggFlag == install), 75 !, 76 ( current_predicate(real:r_call/2) -> 77 true 78 ; 79 catch(use_module(library(real)),_,true) 80 ), 81 ( current_predicate(real:r_call/2) -> 82 real:r_call(rownames('installed.packages'()), [rvar(Rlibs)]), 83 ( memberchk(Rlib,Rlibs) -> 84 ( (debugging(lib);SuggFlag==debug) -> 85 Mess = 'Loading installed R library: ~w', 86 lib_message_report( Mess, [Rlib], informational ) 87 ; 88 true 89 ), 90 r_lib_sys( Rlib ) 91 ; 92 % not-installed Rlib... 93 % fixme: clarify logic of warnings... 94 ( memberchk(suggests_warns(false),Opts) -> 95 true % no warning, successed 96 ; 97 ( (SuggFlag==install ; SuggFlag==debug) -> 98 ( prolog_pack:confirm( contact_r_server(Rlib), yes, [] ) -> 99 ( memberchk(bioc(true),Opts) -> 100 real:r_call( requireNamespace("BiocManager",quietly='TRUE'), [rvar(BiocX)] ), 101 (BiocX == true -> true; real:r_call('install.packages'("BiocManager"),[])), 102 real:r_call('BiocManager::install'(+ Rlib), []), 103 real:r_call(library(Rlib), []) 104 ; 105 real:r_call('install.packages'(+ Rlib), []), 106 real:r_call(library(Rlib), []) 107 ) 108 ; 109 true 110 ) 111 ) 112 ; 113 fail 114 ) 115 ) 116 ; % if it is still not installed 117 Mess1 = 'You need to install SWI-Prolog lib Real before you can lib/1-load R library: ~w', 118 lib_message_report( Mess1, [Rlib], informational ) 119 ). 120lib_r( Rlib, _Opts ) :- 121 r_lib_sys( Rlib ). 122 123r_lib_sys( Rlib ) :- 124 current_prolog_flag( real_suppress_lib_messages, false ), 125 !, 126 r_library_codes( Rlib, '', '', Rcodes ), % fixme to atom 127 atom_codes( R, Rcodes ), 128 real:r_send(R). 129r_lib_sys( Rlib ) :- 130 Pre = 'suppressPackageStartupMessages(', 131 r_lib_codes( Rlib, Pre, ')', Rcodes ), 132 atom_codes( R, Rcodes ), 133 real:r_send( R ). 134r_lib_codes( Rlib, Pre, Post, Rcodes ) :- 135 ( is_list(Rlib) -> Rlib=Rlibs; Rlibs = [Rlib] ), 136 atomic_list_concat( Rlibs, ',', RlibsAtm ), 137 atomic_list_concat( [Pre,'library(',RlibsAtm,')',Post], RlibCallAtm ), 138 atom_codes( RlibCallAtm, Rcodes ). 139 140% fixme: user defined ones 141lib_src_sub_dir(src). 142lib_src_sub_dir('src/lib'). 143lib_src_sub_dir('src/auxil' ).
445lib_defaults( pack, [load(true),index(true),homonym(true),type(pack),mode(self)] ). 446lib_defaults( lib, [load(false),index(true),homonym(true),type(lib),mode(self)] ). 447lib_defaults( [suggest(true)] ).
When Repo homonym(Repository)
then only the homonims of local dir
(adjusted for pack dir structure) are added to as coming from Repository.
Opts
The defaults depend on whether Repo is a pack or a lib.
[load(true),index(true),homonym(false),type(pack)]
[load(false),index(true),homonym(true),type(lib)]
When invoked with code attaching operands (SysLibrary, Pack or Lib)
the predicate will first load anything that needs to be loaded in their native module
and then import predicates from that module. Attaching a lib or pack means that the
predicates pointed to by indices and by file name from the target pack/lib become
available to the importee. Option index(Idx)
controls whether LibIndex.pl
based indices are attahced whereas homonym(Hmns)
control the attachment of
the file names from within the filesystem of the target.
For example to only import the interface predicates of pack ex1
use
?- lib(ex1, [type(pack),load(true),index(false),homonym(false)]).
Assume that ex1 is a pack that is not installed on your Prolog installation, but you have its sources
unpacked on local dir /tmp/ex1/
you can load it interface predicates with:
For example to only import the interface predicates of pack ex1
use
?- lib('/tmp/ex1', [type(pack),load(true),index(false),homonym(false)]).
Assume there is a file src/lib/foo.pl
in ex1
defining predicate foo/1, then you can load its code with
?- lib('/tmp/ex1', [type(pack),load(true),index(false),homonym(true)]). ?- lib(foo/1).
The above will first load foo.pl
(by means of matching its filename to the predicate name) into ex1:
and then assuming that this loaded foo/1 it will import it into current context (here this is =user+).
Assuming foo.pl
also defines predicate bar/2 and there is a file src/LibIndex.pl
within ex1
containing the
line
lib_index( bar, 2, swipl(_), user, 'lib/foo.pl' ).
Then the code for foo_bar/2 can be loaded with
?- lib('/tmp/ex1', [type(pack),load(true),index(true),homonym(false)]). ?- lib(bar/2).
Pack lib can be used to create and access skeleton packs. These packs, may load very little interface code but their code base can be loaded on demand and piece-meal. That is if a specific non-interface predicate is required, it will be located and loaded along with all its dependencies.
An example of such a pack is stoics_lib
.
The following commands: 1. load the minimal interface,,
2, load the code for a specific non-interface predicate.
?- lib(stoics_lib). ?- lib(kv_decompose/3).
The above two directives can be shortened to:
?- lib(stoics_lib:kv_decompose/3).
Current version can be found by:
?- lib( version(Vers,Date) ). Vers = 2:10:0, Date = date(2022, 12, 29).
573lib( Repo ) :- 574 % fixme: add alias() command 575 lib( Repo, [] ). 576 577lib( Repo, ArgS ) :- 578 lib_loading_context( Cxt ), 579 lib_en_list( ArgS, Args ), 580 lib_defaults( Defs ), 581 append( Args, Defs, Opts ), 582 lib( Repo, Cxt, Opts ). 583 584lib( Lib, Cxt, Args ) :- 585 debug( lib, 'lib directive: ~w, in context: ~w, with opts: ~w', [Lib,Cxt,Args] ), 586 fail. 587lib( Pn/Pa, Cxt, Args ) :- 588 !, 589 lib_load( Cxt, Pn, Pa, Args ). 590lib( Repo:Pn/Pa, Cxt, Args ) :- 591 !, 592 lib_explicit( Repo, Pn, Pa, Cxt, Args ). 593lib( External, Cxt, Opts ) :- 594 compound( External ), 595 External =.. [Alias,Lib], 596 user:lib_code_loader( Alias, Mod, Pname ), 597 !, 598 Goal =.. [Pname,Lib,Opts], 599 ( catch(Mod:Goal,_,fail) -> 600 true 601 ; 602 memberchk( suggest(Sugg), Opts ), 603 lib_missing( Sugg, Lib, Cxt, Opts, true ) 604 ). 605 606lib( homonyms(Repo), _, _Args ) :- 607 % load local homonyms as coming from Repo. can be added to 608 % pack to indicate that LibIndex is incomplete or missing 609 % by default packs do not load their homonyms 610 !, 611 lib_homonyms( Repo ). 612lib( source(Src), _Cxt, Opts ) :- 613 !, 614 lib_source( Src, Opts ). 615lib( end(Src), _Cxt, Opts ) :- 616 lib_source_end( Src, Opts ). 617 618% lib( alias(Alias), Cxt, Opts ) :- 619 % !, 620 % lib_alias( Alias, Cxt, Opts ). 621lib( version(V,D), _, _Args ) :- 622 !, 623 V = 2:10:0, D = date(2022,12,29). 624lib( suggests(Lib), _, _Args ) :- 625 !, 626 lib_suggests( Lib ). 627lib( suggests(Lib,SgOptS), _, _Args ) :- 628 !, 629 lib_en_list( SgOptS, SgOpts ), 630 lib_suggests( Lib, SgOpts ). 631lib( promise(PidS,Load), Cxt, _Args ) :- 632 !, 633 lib_promise( PidS, Cxt, Load ). 634lib( expects(Lib,Mess), _, _Opts ) :- 635 !, 636 lib_expects( Lib, Mess ). 637lib( expects(Lib,Mess,Goal), _, _Opts ) :- % fixme: add note() option 638 !, 639 lib_expects( Lib, Mess, Goal ). 640lib( init(Lib), Cxt, _Opts ) :- 641 !, 642 lib_init( Lib, Cxt ). 643lib( sys(SysLib), Cxt, _Opts ) :- 644 !, 645 % AbsOpts = [access(read),file_errors(fail),file_type(prolog)], 646 % absolute_file_name(library(SysLib), AbsLib, AbsOpts ), 647 absolute_file_name(library(SysLib), AbsLib ), 648 % fixme: need map from SysLib -> Repo 649 lib_retract_lazy( SysLib, WasLazy ), 650 lib_sys_lazy( WasLazy, SysLib, AbsLib, ', expected,', Cxt ). 651% testing: lib( & (bio_db(hs)) ). % which contains hgnc 652% map_hgnc_hgnc_symb(H,'LMTK3'). 653lib( @(Pack), Cxt, _Opts ) :- 654 atomic( Pack ), 655 absolute_file_name( pack(Pack), PackD, [file_type(directory),access(exist)] ), 656 !, 657 ( lib_tables:lib_skeleton_only(Pack) -> % fixme: shall we check it is the first one ? 658 true 659 ; 660 directory_file_path( PackD, cell, CellsD ), 661 ( exists_directory(CellsD) -> 662 directory_files( CellsD, AllOses ), 663 findall( Os, (member(Os,AllOses),file_name_extension(_,pl,Os)), Oses ), 664 debug( lib, 'Loading of all cells found pl files: ~w', [Oses] ), 665 findall( Os, ( member(Os,Oses), directory_file_path(CellsD,Os,CellF), 666 %fixme: this: assumes module is same as pack ... 667 debug( lib, 'Loading of cells is loading: ~w', [CellF] ), 668 Pack:ensure_loaded(CellF), 669 directory_file_path(Pack,cell,RelCellP), 670 directory_file_path(RelCellP,Os,RelOs), 671 lib_export_cell(Pack,RelOs,Cxt) 672 ), 673 _OsesDash 674 ) 675 ; 676 % fixme: print warning ? 677 debug( lib, 'Loading directory only as cells cannot be located for: ~w', Pack ) 678 ) 679 ). 680lib( &(Pack), Cxt, _Opts ) :- 681 atomic( Pack ), 682 % absolute_file_name( pack(Pack), PackD, [file_type(directory),access(exist)] ), 683 !, 684 asserta( lib_tables:lib_skeleton_only(Pack) ), 685 debug( lib, 'Loading of ampersand pack with: ~w', [Cxt:use_module(library(Pack))] ), 686 Cxt:use_module( library(Pack) ), 687 once( retract(lib_tables:lib_skeleton_only(Pack)) ). 688 689lib( &(CellIn), Cxt, Opts ) :- 690 !, 691 lib_cell( CellIn, Main, Cell, Opts ), 692 % Cxt:use_module( library(Main) ), 693 asserta( lib_tables:lib_skeleton_only(Main) ), 694 debug( lib, 'Loading of ampersand cell (~w) with: ~w', [CellIn,Cxt:use_module(library(Main))] ), 695 Cxt:use_module( library(Main) ), 696 once( retract(lib_tables:lib_skeleton_only(Main)) ), 697 698 atomic_list_concat( [Main,Cell], '/', Full ), 699 Main:ensure_loaded( pack(Full) ), 700 lib_export_cell( Main, Full, Cxt ). 701lib( Repo, Cxt, Opts ) :- 702 lib_tables:lib_lazy( Repo ), 703 !, 704 lib_lazy_no_more( Repo, Cxt, Opts ). 705lib( Repo, Cxt, _Args ) :- 706 lib_tables:lib_packs_at( Cxt, PrivPacksD ), 707 directory_file_path( PrivPacksD, Repo, PackRoot ), 708 directory_file_path( PackRoot, prolog, PackPrologD ), 709 directory_file_path( PackPrologD, Repo, PrologStem ), 710 file_name_extension( PrologStem, pl, PlF ), 711 exists_file( PlF ), 712 !, 713 debug( lib, 'Loading from private pack with entry point: ~p', PlF ), 714 % ensure_loaded( PlF ). 715 lib_defaults( pack, PackLoadDefs ), 716 lib( Repo, PackRoot, PlF, Cxt, PackLoadDefs ). 717lib( Repo, Cxt, Args ) :- 718 lib_type( Repo, RepoType, RepoMod, RepoRoot, RepoLoad ), 719 !, 720 lib_reg_repo( RepoMod, RepoType, RepoRoot, RepoLoad, Exists ), 721 MsId = 'Identified repo: ~w as: ~w, loading in: ~w, with root: ~w', 722 debug( lib, MsId, [Repo,RepoType,RepoMod,RepoRoot] ), 723 lib_defaults( RepoType, Defs ), 724 append( Args, Defs, Opts ), 725 lib( Exists, RepoMod, RepoRoot, RepoLoad, Cxt, Opts ). 726lib( SysLib, Cxt, _Args ) :- 727 AbsOpts = [access(read),file_errors(fail),file_type(prolog)], 728 absolute_file_name(library(SysLib), AbsLib, AbsOpts ), 729 lib_retract_lazy( SysLib, WasLazy ), 730 lib_sys_lazy( WasLazy, SysLib, AbsLib, '', Cxt ), 731 !. % fixme: is this too late in the body? 732 733 /* 734 Assert = asserta( lib_tables:lib_full(SysLib,AbsLib) ), 735 Goal = Cxt:use_module(library(SysLib)), 736 Retract = retract(lib_tables:lib_full(SysLib,AbsLib) ), 737 setup_call_cleanup(Assert, Goal, Retract), 738 % catch( Cxt:use_module(library(SysLib)), _, fail ), 739 !, 740 debug( lib, 'System library: ~w, loaded in: ~w', [SysLib,Cxt] ). 741 */ 742lib( Repo, Cxt, Args ) :- 743 lib_tables:lib_repo(Repo,Type,Root,Load), 744 !, 745 lib_repo( Repo, Type, Root, Load, Cxt, Args ). 746lib( Root, Cxt, Args ) :- 747 lib_tables:lib_repo(Repo,Type,Root,Load), 748 !, 749 lib_repo( Repo, Type, Root, Load, Cxt, Args ). 750lib( Pack, Cxt, Opts ) :- 751 memberchk( suggest(Sugg), Opts ), 752 lib_missing( Sugg, Pack, Cxt, Opts, true ), 753 !. 754lib( Repo, Cxt, Opts ) :- 755 compound( Repo ), 756 lib( &(Repo), Cxt, Opts ), 757 !. 758lib( Repo, Cxt, Opts ) :- 759 memberchk( mode(Mode), Opts ), 760 lib_not_found( Mode, Repo, Cxt ). 761 762lib_cell( CellIn, Main, Cell, _Opts ) :- 763 compound( CellIn ), 764 !, 765 lib_term_dir( CellIn, true, Main, Cell ). 766lib_cell( CellIn, Pack, Cell, Opts ) :- 767 % options( pack(Pack), Opts ), 768 memberchk( pack(Pack), Opts ), 769 !, 770 lib_term_dir( CellIn, false, Pack, Cell ). 771 % lib_cell_pack( Pack, CellIn, Main, Cell, Opts ). 772lib_cell( CellIn, _Main, _Cell, Opts ) :- 773 throw( cannot_locate_cell_with_options(CellIn,Opts) ). 774 775lib_retract_lazy( SysLib, WasLazy ) :- 776 lib_tables:lib_lazy(SysLib), 777 !, 778 WasLazy = true. 779lib_retract_lazy( _SysLib, false ). 780 781lib_sys_lazy( _, SysLib, AbsLib, ExplicitTkn, Cxt ) :- 782 lib_sys( SysLib, AbsLib, ExplicitTkn, Cxt ), 783 !. % don't need to reassert it as it is now fully loaded 784lib_sys_lazy( true, SysLib, _AbsLib, _ExplicitTkn, _Cxt ) :- 785 asserta( lib_tables:lib_lazy(SysLib) ), 786 fail. 787 788lib_sys( SysLib, AbsLib, ExplicitTkn, Cxt ) :- 789 Assert = asserta( lib_tables:lib_full(SysLib,AbsLib) ), 790 Goal = Cxt:use_module(library(SysLib)), 791 Retract = retract(lib_tables:lib_full(SysLib,AbsLib) ), 792 setup_call_cleanup(Assert, Goal, Retract), 793 debug( lib, 'System~w library: ~w, loaded in: ~w', [ExplicitTkn,SysLib,Cxt] ). 794 795lib_not_found( self, Repo, _Cxt ) :- 796 Mess = 'Failed to locate library:~w, (no local lib, local pack or remote pack)', 797 lib_message_report( Mess, [Repo], informational ). 798lib_not_found( suggests, Repo, _Cxt ) :- 799 Mess = 'Failed to locate suggested library:~w, (no local lib, local pack or remote pack)', 800 lib_message_report( Mess, [Repo], informational ). 801 802lib_explicit( Repo, Pn, Pa, Cxt, _Opts ) :- 803 lib_tables:lib_full(Repo,_), 804 !, % this should be able to cope with cyclic dependencies? 805 % check with options 806 Cxt:import( Repo:Pn/Pa ). 807lib_explicit( Repo, Pn, Pa, Cxt, _Opts ) :- 808 current_predicate( Repo:Pn/Pa ), 809 !, 810 lib_import_existing( Repo, Pn/Pa, Cxt ). 811lib_explicit( Repo, Pn, Pa, Cxt, Opts ) :- 812 lib_type( Repo, Type, Rmod, Root, Load ), 813 lib_repo_lazy_assert( Rmod ), 814 lib_explicit_repo( Type, Repo, Rmod, Root, Load, Pn, Pa, Cxt, Opts ), 815 !. 816lib_explicit( Repo, Pn, Pa, Cxt, Opts ) :- 817 memberchk( suggest(Sugg), Opts ), 818 lib_missing( Sugg, Repo, Cxt, Opts, false ), 819 !, 820 lib_explicit( Repo, Pn, Pa, Cxt, Opts ). 821lib_explicit( Repo, Pn, Pa, Cxt, _Args ) :- 822 % 17.03.24; the following 2 lines create a cycle 823 % lib( Repo, Cxt, Args ), 824 % lib( Pn/Pa, Cxt, [repo(Repo)|Args] ). 825 Mess = 'Failed to locate: ~w within explicit repository:~w, within context: ~w', 826 lib_message_report( Mess, [Pn/Pa,Repo,Cxt], error ). 827 828lib_explicit_repo( pack, Repo, Rmod, Root, Load, Pn, Pa, Cxt, Opts ) :- 829 file_name_extension( LoadStem, pl, Load ), 830 atomic_concat( LoadStem, '_lazy', LazyStem ), 831 file_name_extension( LazyStem, pl, LazyF ), 832 ( exists_file(LazyF) -> 833 true 834 ; 835 Mess = 'Lazy loading file: ~w does not exist (context: ~w)', 836 lib_message_report( Mess, [LazyF,Cxt], informational), 837 fail 838 ), 839 lib_defaults( pack, Defs ), 840 append( Opts, Defs, All ), 841 lib( Rmod, Root, LazyF, Cxt, All ), 842 % ensure_loaded( Rmod:LazyF ), 843 % lib_reg_repo( Repo, pack, Root, LazyF ), 844 lib( Pn/Pa, Cxt, [repo(Repo)|Opts] ). 845 846lib_repo_lazy_assert( Repo ) :- 847 lib_tables:lib_lazy( Repo ), 848 !. 849lib_repo_lazy_assert( Repo ) :- 850 asserta( lib_tables:lib_lazy(Repo) ). 851 852lib_missing( false, Pack, Cxt, Opts, _Load ) :- 853 memberchk( mode(Mode), Opts ), 854 Mode == suggests, 855 !, 856 current_prolog_flag( lib_suggests_warns, WarnFlag ), 857 lib_missing_suggested( WarnFlag, Pack, Cxt, Opts ). 858lib_missing( false, Pack, Cxt, _Args, _Load ) :- 859 debug( lib, 'Instructed to skip contacting server for:~w and context:~w', [Pack,Cxt] ). 860lib_missing( true, Pack, Cxt, Args, Load ) :- 861 prolog_pack:confirm( contact_server(Pack), yes, [] ), 862 G = query_pack_server(search(Pack), Result, [] ), 863 catch( prolog_pack:G, _Ball, fail ), 864 Result \== false, 865 lib_defaults( lib, LibDefs ), 866 append( Args, LibDefs, Opts ), 867 memberchk( mode(Mode), Opts ), 868 catch( prolog_pack:pack_list(Pack), _, fail ), 869 prolog_pack:confirm( pack_on_server(Mode,Pack), yes, [] ), 870 !, 871 lib_pack_install( Pack ), 872 lib_missing_load( Load, Cxt, Pack ). 873 874lib_missing_suggested( WarnFlag, Pack, Cxt, Opts ) :- 875 memberchk( WarnFlag, [auto,debug,false,install,true] ), 876 !, 877 lib_missing_suggested_known( WarnFlag, Pack, Cxt, Opts ). 878lib_missing_suggested( WarnFlag, _Pack, _Cxt, _Opts ) :- 879 throw( incorrect_value_for_flag(lib_suggests_warns(WarnFlag)) ). 880 881lib_missing_suggested_known( auto, Pack, Cxt, Opts ) :- 882 memberchk( suggests_warns(WarnsOpt), Opts ), 883 ( memberchk(WarnsOpt,[true,false]) -> true; throw(incorrent_option_value_for_option(suggest_warns(WarnsOpt))) ), 884 lib_missing_suggested_known( WarnsOpt, Pack, Cxt, Opts ). 885lib_missing_suggested_known( debug, Pack, Cxt, Opts ) :- 886 lib_missing_suggested_known( true, Pack, Cxt, Opts ). 887lib_missing_suggested_known( false, Pack, Cxt, _Opts ) :- 888 debug( lib, 'Silently ignoring suggested, and missing library: ~w, in context: ~w', [Pack,Cxt] ). 889lib_missing_suggested_known( true, Pack, Cxt, _Opts ) :- 890 Mess = 'Failed to load suggested library:~w, in context: ~w', 891 lib_message_report( Mess, [Pack,Cxt], informational ). 892 893lib_missing_load( true, Cxt, Pack ) :- 894 Cxt:use_module( library(Pack) ). 895lib_missing_load( false, _Cxt, _Pack ). 896 897lib_import_existing( Repo, Pn/Pa, Cxt ) :- 898 functor( Phead, Pn, Pa ), 899 predicate_property(Repo:Phead,exported), 900 !, 901 debug( lib, 'Importing from existing : ~w, into: ~w', [Repo:Pn/Pa,Cxt] ), 902 Cxt:import( Repo:Pn/Pa ). 903lib_import_existing( Repo, Pn/Pa, Cxt ) :- 904 functor( Phead, Pn, Pa ), 905 predicate_property(Repo:Phead,imported_from(Mod)), 906 !, 907 debug( lib, 'Importing from parent: ~w, via: ~w, pred: ~w, and context: ~w', [Mod,Repo:Pn/Pa,Cxt] ), 908 Mod:import(Repo:Pn/Pa). 909lib_import_existing( Repo, Pn/Pa, Cxt ) :- 910 debug( lib, 'Exporting on: ~w and then importing:~w, into: ~w', [Repo,Pn/Pa,Cxt] ), 911 export( Repo:Pn/Pa ), 912 Cxt:import( Repo:Pn/Pa ). 913 914lib_lazy_no_more( Repo, Cxt, Opts ) :- 915 % use_module( Repo:library(Repo) ). 916 lib_type( Repo, Type, _RepoMod, _RepoRoot, RepoLoad ), 917 open( RepoLoad, read, In ), 918 read( In, ModuleDfn ), 919 ModuleDfn = (:- module(Repo,Exports) ), 920 lib_defaults( Type, Defs ), 921 append( Opts, Defs, All ), 922 maplist( lib_explicit_exports(Repo,Cxt,All), Exports ), 923 close( In ), 924 !. 925lib_lazy_no_more( Repo, Cxt, Opts ) :- 926 throw( failed_to_unset_lazy_mode_for(Repo,Cxt,Opts) ). 927 928lib_explicit_exports( Repo, Cxt, Opts, Pn/Pa) :- 929 lib_explicit( Repo, Pn, Pa, Cxt, Opts ). 930 931% lib_alias( Alias, Cxt, Opts ) :- 932 % !, 933 % absolute_file_name( Alias, Dir, [access(exist)] ), 934 % lib( Dir, Cxt, Opts ). 935% lib_alias( Alias, _Cxt, _Opts ) :- 936 % throw( alias_does_not_correspont_to_lib(Alias) ). 937 938lib( Repo, Root, Load, Cxt, Opts ) :- 939 lib( false, Repo, Root, Load, Cxt, Opts ). 940 941% testing: 18.11.22: 942/* 943lib( true, Repo, Root, _Load, Cxt, _Opts ) :- 944 Mess = 'lib/4, not loading anything for lib that already existed. Cxt: ~w, repo: ~w, root:~w', 945 debug( lib, Mess, [Cxt,Repo,Root] ), 946 !. 947 */ 948lib( _, Repo, Root, Load, Cxt, Opts ) :- 949 ( catch(lib_load_repo_root_index_file(Repo,Root), _, true ) -> true; true ), 950 Setup = asserta( lib_tables:lib_context(Repo,Root) ), 951 Goal = lib_load_file( Load, Repo, Opts ), 952 Clean = ( once(retract(lib_tables:lib_context(Repo,Root))) ), 953 debug( lib, 'lib/4: ~w', setup_call_cleanup(Setup, Goal, Clean) ), 954 setup_call_cleanup(Setup, Goal, Clean), 955 findall( _, 956 ( predicate_property(Repo:Ph,exported), 957 functor(Ph,Pn,Pa), 958 Cxt:import(Repo:Pn/Pa) 959 ) 960 , 961 _ ), 962 memberchk( index(IdxB), Opts ), 963 lib_attach_indices( IdxB, Root, Repo, Cxt ), 964 memberchk( homonym(LocB), Opts ), 965 lib_attach_filenames( LocB, Root, Repo, Cxt ). 966 967lib_repo( Repo, Type, Root, Load, Cxt, Args ) :- 968 Mess = 'Located in memory repo:~w of type: ~w, loading in: ~w, with root: ~w', 969 debug( lib, Mess, [Repo,Type,Repo,Root] ), 970 lib_defaults( Type, Defs ), 971 append( Args, Defs, Opts ), 972 lib( Repo, Root, Load, Cxt, Opts ), 973 findall( _, (predicate_property(Repo:Phead,exported),functor(Phead,Pn,Pa),Cxt:import(Repo:Pn/Pa)), _ ). 974 975lib_source( Repo, Opts ) :- 976 prolog_load_context( directory, Base ), 977 directory_file_path( Root, prolog, Base ), 978 !, 979 % next N lines accommodate for private packs... 980 directory_file_path( Root, src, Srot ), 981 directory_file_path( Srot, packs, PrivP ), 982 ( exists_directory(PrivP) -> assert( lib_tables:lib_packs_at(Repo,PrivP) ); true ), 983 % end of N lines 984 asserta( lib_tables:lib_context(Repo,Root) ), 985 ( memberchk(index(Idx),Opts) -> true; Idx = false ), 986 lib_source_index( Idx, Root, Repo ), 987 ( memberchk(homonyms(Hmns),Opts) -> true; Hmns = false ), 988 lib_source_homonyms( Hmns, Repo ). 989lib_source( Repo, Opts ) :- 990 compound( Repo ), 991 % we are within a cell of a pack... 992 Repo =.. [Pack,Cell], % fixme: allow for more complex terms 993 prolog_load_context( directory, Base ), 994 % directory_file_path( Base, src, Srot ), 995 atomic_list_concat( [Pack,Cell], '_', Mod ), 996 asserta( lib_tables:lib_context(Mod,Base) ), 997 ( memberchk(index(Idx),Opts) -> true; Idx = false ), 998 lib_source_index( Idx, Base, Mod ), 999 ( memberchk(homonyms(Hmns),Opts) -> true; Hmns = false ), 1000 lib_source_homonyms( Hmns, Repo ). 1001 1002lib_source_index( true, Root, Repo ) :- 1003 lib_src_sub_dir( Sub ), 1004 directory_file_path( Root, Sub, AbsSrc ), 1005 directory_file_path( AbsSrc, 'LibIndex.pl', LibIndex ), 1006 exists_file( LibIndex ), 1007 !, 1008 lib_load_index_file( LibIndex, Repo ). 1009lib_source_index( false, _Root, _Repo ). 1010 1011lib_source_homonyms( true, Repo ) :- 1012 % :- dynamic( lib_tables:lib_loaded_homonyms/2 ). % 1013 lib_homonyms( Repo ), 1014 !. 1015lib_source_homonyms( false, _Repo ). 1016 1017lib_source_end( Repo, _Opts ) :- 1018 compound( Repo ), 1019 % then we are within a cell of a pack 1020 !, 1021 Repo =.. [Pack,Cell], % fixme: allow for more complex terms 1022 atomic_list_concat( [Pack,Cell], '_', Mod ), 1023 retractall( lib_tables:lib_context(Mod,_Root1) ), 1024 retractall( lib_tables:lib_packs_at(Mod,_) ). 1025lib_source_end( Repo, _Opts ) :- 1026 retractall( lib_tables:lib_context(Repo,_Root1) ), 1027 retractall( lib_tables:lib_packs_at(Repo,_) ). 1028 1029lib_term_dir( DirIn, _Top, _Main, Dir ) :- 1030 atomic( DirIn ), 1031 !, 1032 DirIn = Dir. 1033lib_term_dir( LeftIn/Leaf, Top, Main, Dir ) :- 1034 !, 1035 lib_term_dir( LeftIn, Top, Main, Left ), 1036 atomic_list_concat( [Left,Leaf], '/', Dir ). 1037lib_term_dir( DirIn, Top, Main, Dir ) :- 1038 functor( DirIn, TNm, 1 ), 1039 !, 1040 arg( 1, DirIn, SubIn ), 1041 lib_term_dir( SubIn, false, Main, Sub ), 1042 ( Top == true -> TNm = Main, 1043 atomic_list_concat( [cell,Sub], '/', Dir ) 1044 ; atomic_list_concat( [TNm,Sub], '/', Dir ) 1045 ). 1046lib_term_dir( DirIn, Top, _Main, _Dir ) :- 1047 throw( cannot_de_term_dir(DirIn,Top) ). 1048 1049% import all predicates that are defined by RelCell into module defined by pack Main. 1050lib_export_cell( Main, RelCell, Cxt ) :- 1051 lib_pack_module( Main, Cxt, Mod ), 1052 lib_cell_module( Mod, RelCell, Cod ), 1053 findall( Pid, ( 1054 ( 1055 predicate_property(Mod:Pid,imported_from(Cod)) 1056 ; 1057 ( predicate_property(Cod:Pid,imported_from(Common)), 1058 predicate_property(Mod:Pid,imported_from(Common)) 1059 ) 1060 ), 1061 \+ predicate_property(Cxt:Pid,_), 1062 functor( Pid, Pnm, Par ), 1063 % export(Mod:Pid), 1064 % Cxt:import(Mod:Pid) 1065 Cxt:import(Cod:Pnm/Par), 1066 Cxt:export(Cxt:Pnm/Par) 1067 ), Pids ), 1068 debug( lib, 'lib imported in context: ~w, from mod: ~w, having cell, ~w, the predicates: ~w', [Cxt,Main,RelCell,Pids] ). 1069 1070% finds the module defined by a loaded pack file... 1071lib_pack_module( Main, Cxt, Mod ) :- 1072 absolute_file_name( pack(Main), PackMain ), 1073 directory_file_path( PackMain, prolog, PrologMain ), 1074 directory_file_path( PrologMain, Main, MainF ), 1075 file_name_extension( MainF, pl, PlF ), 1076 exists_file( PlF ), 1077 lib_pack_file_module( PlF, Main, Cxt, Mod ), 1078 !. 1079lib_pack_module( Main, Cxt, Mod ) :- 1080 throw( cannot_locate_loaded_module_for(Main,Cxt,Mod) ). 1081 1082lib_pack_file_module( PlF, Main, Cxt, Mod ) :- 1083 predicate_property( Cxt:Pred, file(PlF) ), 1084 predicate_property( Cxt:Pred, imported_from(Mod) ), 1085 !, 1086 debug( lib, 'Commiting to mod: ~w, for main pack: ~w in context: ~w', [Mod,Main,Cxt] ). 1087% fixme: we need this for ?- lib(bio_db). use_module(library(bio_db)) works fine because of initialization delay ? 1088lib_pack_file_module( PlF, _Main, _Cxt, Mod ) :- 1089 exists_file( PlF ), 1090 open( PlF, read, In ), 1091 read( In, Term ), 1092 close( In ), 1093 Term = ( :- module(Mod,_) ). 1094 1095lib_cell_module( Mod, Rel, Cod ) :- 1096 absolute_file_name( pack(Rel), PlF, [file_type(prolog),access(read)] ), 1097 predicate_property( Mod:Pid, file(PlF) ), 1098 predicate_property( Mod:Pid, imported_from(Cod) ), 1099 !, 1100 debug( lib, 'Commiting to cell mod: ~w, for main mod: ~w and relative : ~w', [Cod,Mod,Rel] ). 1101lib_cell_module( Mod, Rel, Cod ) :- 1102 throw( cannot_locate_loaded_module_cell(Mod,Rel,Cod) )
Predicate based code development.
This pack implements methods for loading code into SWI Prolog programs.
Main innovations
Lazy loading
One of the major innovations the library introduces, is that of progressive, lazy loading of packs. That is, if only a specific predicate is (lazily) required from a
pack(lib)-aware
pack, only that and its dependent code will be loaded.That is, your code can load things like
and only the relevant parts of the
pack(stoics_lib)
will be loaded.If later on your code decides to do a
The remainder of the library loads up quietly and politely.
Please note that this is, at top level at least, orthogonal to any other loading.
You can still do
and get the whole thing into memory.
A good example of how to create a lazy pack is
pack(stoics_lib)
, http://stoics.org.uk/~nicos/sware/stoics_lib v0.3. An example of how to lazy load things from stoics_lib is the latestpack(debug_call)
http://stoics.org.uk/~nicos/sware/debug_call v0.4.Cells
As of version 2.0 the pack supports hierarchical module de-composition.
A cell compose pack, is build by a skeleton module that all cells depend on and then a number of independent cells that can be loaded independently as well as in combination.
There are at least 2 reasons why one would like decomposable modules: (a) resources, and (b) clarity of interface. Only loading parts of a module can result in smaller memory consumption as irrelevant bits are not loaded. Also, if modules have long lists of defined predicates, like bio_db v2.0, then loading only conceptually clear sub-set of a module allows programmer to focus on the predicates that are relevant to a specific task.
pack(bio_db)
was the driving force for developing cell based packs and it provides natural cell units. At the top level there are two cells, hs for human biological data and mouse for mouse data. Each cell is further broken to a number of cells each corresponding to the source database where data is converted from. For instance hs contains sub-cells: ense, gont, hgnc, ncbi, pros, strg and unip.See
pack(bio_db/cell/hs.pl)
andpack(bio_db/cell/mouse.pl)
.Cell based pack can still be viewed and loaded as normal module files. For instance,
Loads the whole interface (all cells), without the user needing to be aware of anything. The only difference is that the user will not be able to see all the module predicates at the first line of file
pack(bio_db/prolog/bio_db.pl)
).Also loads everything.
Loads the skeleton of the module (cells usually load the module dependencies like this). That is, file
pack(prolog/bio_db.pl)
, but not the cell files inpack(cell/ * )
.Loads hs cell, which in this case comprises of number of sub-cells.
Loads hs cell (and skeleton). hs comprises of a number of sub-cells.
Loads the hs/hgnc primary cell (and the skeleton).
Loads all sub-cells of a library.
Will load everything even if cell based loading ahs taken place. (
use_module(library(bio_db))
would work.)Suggested code
The library supports suggested loading and code execution. These operations are meant for fringe features that are not, by default reported if missing. Reporting in form of warnings can be turned on by either setting flag lib_suggests_warns to true (globally controlled), or passing option (local, controlled by developer).
Prolog lag lib_suggests_warns can take values:
suggests_warns(true)
Other features
General points
Pack(lib) plays reasonably well with the documentation server. Bar, the normal limitations of the server. By convention and to help locating the module docs, lazy packs should define (Pack)/0 predicate in same file as the mods docs. Searching for that on doc server, should make it easy enough to get to it.
Although this library,
pack(lib)
, contains a number of involved features it can also be used as a straight forward shorthand, replacement foruse_module(library(Lib))
.is equivelant to
use_module(library(Atomic))
if Atomic is a system library or an installed Pack, while it will interogate the SWI pack server for matching packs if Atomic is atomic and not an installed pack.In addition the library allows for loading with initializations turned off.
Repositories
Code is managed in repositories (also repo) that can be either packs or libs (ie local directories).
A pack is a unit of programs as managed by built-in SWI package manager (
library(prolog_pack)
). A lib (library) is a directory containing a number of program files.pack(lib)
supports a number of ways to organise your code and load it, but it comes to its own when code s organised as predicate-in-a-file fashion. In this mode of development a predicate such as kv_decompose/3 would be defined on filekv_decompose.pl
which will only containing code for defining this predicate, with the possible exception of helper predicates that are too specific to be of outside interest.Lib code is considered as coming from the special pack user.
Code-tables
Associated with each repository are 2 types of code-tables: (code-)_indices_ and (file-)_locators_.
A code-index maps a predicate identifier along with its source repo to an absolute file name of the source that defines it. Indices are of the form:
File locators store all filenames in a repository. These can be named matched predicate names that need to be loaded.
pack(lib)
can be directed to assume that files from a specific repository exhibit this homonyms property. Locators are of the form:For each index file loaded for a repository, the following is asserted:
and for each locator
When loading a repository the user can choose whether to load indices and locators independently.
Loading source code
During the process of loading code into memory, lib/1 and /2 directives are used to locate code to which the specific code depends.
There are three main categories of operations:
These operations are all specific to the loading context. This is achieved by creating meta-predicates that identify which part of the repository base each context has access to.
Attachment of repository is registered via
lib_tables:lib_attached_indices(To,PackIG)
andlib_tables:lib_attached_homonyms(To,PackFG)
.attaches the indices but not the file locators.
Since all code from directory-libs load to a single module (user), loading code has either access to all such code, or to none.
Conventions
Packs are expected to have matching top directories and main files. The main file of a pack should be within top directory prolog/. (The directory convention is set by library(prolog_pack)). For example for pack bims the following file should exist in packs directory:
For packs the main code directory is src/. Additionally src/lib and src/auxil are treated as code directories.
Internals
Variables
Predicate names
Pack info
This is a complete re-write of
pack(requires)
v1.1.Listens to
debug(lib)
.lib(version(V,D))
suggests()
, lib/2,promise()
via hot-swapping, private packssuggests_warns(false)
, logic needs further work*/