1% ===================================================================
    2% File 'logicmoo_util_library.pl'
    3% Purpose: To load the logicmoo libraries as needed
    4% Maintainers: Douglas Miles/Annie Ogborn/Kino Coursey
    5% Contact: $Author: dmiles $@users.sourceforge.net ;
    6% Version: 'logicmoo_util_library.pl' 1.0.0
    7% Revision:  $Revision: 1.7 $
    8% Revised At:   $Date: 2002/07/11 21:57:28 $
    9% ===================================================================
   10:-module(logicmoo_util_library,[dynamic_transparent/1,
   11         upcase_atom_safe/2,
   12         concat_atom_safe/3,
   13         string_to_atom_safe/2,
   14         atom_concat_safe/3,
   15         exists_file_safe/1,
   16         exists_directory_safe/1,
   17         time_file_safe/2,
   18         throw_safe/1,
   19         maplist_safe/2,
   20         maplist_safe/3,
   21         list_to_set_safe/2,
   22   multi_transparent/1]).   23
   24dynamic_transparent([]):-!.
   25dynamic_transparent([X]):-dynamic_transparent(X),!.
   26dynamic_transparent([X|Xs]):-!,dynamic_transparent(X),dynamic_transparent(Xs),!.
   27dynamic_transparent(M:F/A):-!, module_transparent(M:F/A),dynamic(M:F/A).
   28dynamic_transparent(F/A):-!,multi_transparent(user:F/A).
   29dynamic_transparent(X):-functor(X,F,A),dynamic_transparent(F/A),!.
   30
   31multi_transparent([]):-!.
   32multi_transparent([X]):-multi_transparent(X),!.
   33multi_transparent([X|Xs]):-!,multi_transparent(X),multi_transparent(Xs),!.
   34multi_transparent(M:F/A):-!, module_transparent(M:F/A),dynamic(M:F/A),multifile(M:F/A).
   35multi_transparent(F/A):-!,multi_transparent(user:F/A).
   36multi_transparent(X):-functor(X,F,A),multi_transparent(F/A),!.
   37
   38:- module_transparent(library_directory/1).   39
   40throw_safe(Exc):-trace,throw(Exc).
   41string_to_atom_safe(ISO,LISTO):-LISTO==[],!,string_to_atom(ISO,'').
   42string_to_atom_safe(ISO,LISTO):-string_to_atom(ISO,LISTO).
   43atom_concat_safe(L,R,A):- ((atom(A),(atom(L);atom(R))) ; ((atom(L),atom(R)))), !, atom_concat(L,R,A),!.
   44exists_file_safe(File):-prolog_must(atomic(File)),exists_file(File).
   45exists_directory_safe(File):-prolog_must(atomic(File)),exists_directory(File).
   46concat_atom_safe(List,Sep,[Atom]):-atom(Atom),!,concat_atom(List,Sep,Atom),!.
   47concat_atom_safe(List,Sep,Atom):-atom(Atom),!,concat_atom(ListM,Sep,Atom),!,List = ListM.
   48concat_atom_safe(List,Sep,Atom):- concat_atom(List,Sep,Atom),!.
   49upcase_atom_safe(A,B):-atom(A),upcase_atom(A,B),!.
   50time_file_safe(F,INNER_XML):-exists_file_safe(F),time_file(F,INNER_XML).
   51list_to_set_safe(A,A):-(var(A);atomic(A)),!.
   52list_to_set_safe([A|AA],BB):- (not(not(lastMember(A,AA))) -> list_to_set_safe(AA,BB) ; (list_to_set_safe(AA,NB),BB=[A|NB])),!.
   53
   54
   55%================================================================
   56% maplist/[2,3]
   57% this must succeed  maplist_safe(=,[X,X,X],[1,2,3]).
   58% well if its not "maplist" what shall we call it?
   59%================================================================
   60% so far only the findall version works .. the other runs out of local stack!?
   61
   62maplist_safe(_Pred,[]):-!.
   63maplist_safe(Pred,LIST):-findall(E,(member(E,LIST),debugOnFailure(apply(Pred,[E]))),LISTO),!, ignore(LIST=LISTO),!.
   66maplist_safe(_Pred,[],[]):-!.
   67maplist_safe(Pred,LISTIN, LIST):-!, findall(EE, ((member(E,LISTIN),debugOnFailure(apply(Pred,[E,EE])))), LISTO),  ignore(LIST=LISTO),!.
   71:- dynamic(buggerDir/1).   72:- abolish(buggerDir/1),prolog_load_context(directory,D),asserta(buggerDir(D)).   73:- dynamic(buggerFile/1).   74:- abolish(buggerFile/1),prolog_load_context(source,D),asserta(buggerFile(D)).   75
   76
   77hasLibrarySupport :- absolute_file_name(library('logicmoo/logicmoo_util_library.pl'),File),exists_file(File).
   78
   79throwNoLib:- trace,absolute_file_name('.',Here), buggerFile(BuggerFile), listing(library_directory), throw(error(existence_error(url, BuggerFile), context(_, status(404, [BuggerFile, from( Here) ])))).
   80
   81addLibraryDir :- buggerDir(Here),atom_concat(Here,'/..',UpOne), absolute_file_name(UpOne,AUpOne),asserta(user:library_directory(AUpOne)).
   82
   83% if not has library suport, add this direcotry as a library directory
   84:-not(hasLibrarySupport) -> addLibraryDir ; true .   85
   86:-hasLibrarySupport->true;throwNoLib.   87
   88% TODO remove this next line
   89% :-ensure_loaded(library('logicmoo/logicmoo_util_bugger.pl')).
   90% and replace with...