The Ciao library browser

Author(s): Angel Fernandez Pineda, Isabel Garcia Contreras.

The librowser library provides a set of predicates wich enable the user to interactively find Ciao libraries and/or any predicate exported by them.

This is a simple example:

?- apropos(aggregates:'.*find.*').

aggregates:findnsols/5
aggregates:findnsols/4
aggregates:findall/4
aggregates:findall/3

yes
?- 

librowser is specially useful when inside GNU Emacs: just place the cursor over a librowser response and press C-cTAB in order to get help on the related predicate. Refer to the "Using Ciao inside GNU Emacs" chapter for further information.

Usage and interface

  • Library usage:
    It is not necesary to use this library at user programs. It is designed to be used at the Ciao toplevel shell: ciaosh. In order to do so, just make use of use_module/1 as follows:

    use_module(library(librowser)).

    Then, the library interface must be read. This is automatically done when calling any predicate at librowser, and the entire process will take a little moment.So, you should want to perform such a process after loading the Ciao toplevel:

    Ciao 0.9 #75: Fri Apr 30 19:04:24 MEST 1999
    ?- use_module(library(librowser)).
    
    yes
    ?- update.
    
    

    Whether you want this process to be automatically performed when loading ciaosh, you may include those lines in your .ciaorc personal initialization file.

  • Exports:
  • Imports:

Documentation on exports

PREDICATE
This predicate will scan the Ciao system libraries for predicate definitions. This may be done once time before calling any other predicate at this library.

update/0 will also be automatically called (once) when calling any other predicate at librowser.

Usage:

Creates an internal database of modules at Ciao system libraries.

    PREDICATE
    This predicate is fully reversible, and is provided to inspect concrete predicate specifications. For example:
    ?- browse(M,findall/A).
    
    A = 3,
    M = conc_aggregates ? ;
    
    A = 4,
    M = aggregates ? ;
    
    A = 3,
    M = aggregates ? ;
    
    no
    ?-
    

    Usage:browse(Module,Spec)

    Asocciates the given Spec predicate specification with the Module which exports it.

    • The following properties should hold at call time:
      (librowser:module_name/1)Module is a module name (an atom)
      (librowser:pred_spec/1)Spec is a Functor/Arity predicate specification

    PREDICATE
    This predicate will print at the screen the module needed in order to import a given predicate specification. For example:
    ?- where(findall/A).
    findall/3 exported at module conc_aggregates
    findall/4 exported at module aggregates
    findall/3 exported at module aggregates
    
    yes
    ?-
    

    Usage:where(Spec)

    Display what module to load in order to import the given Spec.

    • The following properties should hold at call time:
      (librowser:pred_spec/1)Spec is a Functor/Arity predicate specification

    PREDICATE
    This one is used to find out which predicates were exported by a given module. Very usefull when you know the library, but not the concrete predicate. For example:
    ?- describe(librowser).
    Predicates at library librowser :
    
    apropos/1
    system_lib/1
    describe/1
    where/1
    browse/2
    update/0
    
    yes
    ?-
    

    Usage:describe(Module)

    Display a list of exported predicates at the given Module

    • The following properties should hold at call time:
      (librowser:module_name/1)Module is a module name (an atom)

    PREDICATE
    It retrieves on backtracking all Ciao system libraries stored in the internal database. Certainly, those which were scanned at update/0 calling.

    Usage:system_lib(Module)

    Module variable will be successively instantiated to the system libaries stored in the internal database.

    • The following properties should hold at call time:
      (librowser:module_name/1)Module is a module name (an atom)

    PREDICATE
    This tool makes use of regular expresions in order to find predicate specifications. It is very usefull whether you can't remember the full name of a predicate. Regular expresions take the same format as described in library patterns. Example:
    ?- apropos('write.').
    
    write:writeq/1
    write:writeq/2
    
    yes
    ?- apropos('write.*'/2).
    
    dht_misc:write_pr/2
    profiler_auto_conf:write_cc_assertions/2
    mtree:write_mforest/2
    transaction_concurrency:write_lock/2
    transaction_logging:write/2
    provrml_io:write_vrml_file/2
    provrml_io:write_terms_file/2
    unittest_base:write_data/2
    write:write_canonical/2
    write:writeq/2
    write:write/2
    write:write_term/2
    strings:write_string/2
    res_exectime_hlm_gen:write_hlm_indep_each/2
    res_exectime_hlm_gen:write_hlm_indep_2/2
    res_exectime_hlm_gen:write_hlm_dep/2
    oracle_calibration:write_conf/2
    bshare_utils:write_string/2
    bshare_utils:write_string_list/2
    bshare_utils:write_length/2
    bshare_utils:write_neg_db_stream/2
    bshare_utils:write_neg_db/2
    bshare_utils:write_pos_db/2
    
    yes
    
    When no predicates are found with the exact search, this predicate will perform a fuzzy search which will find predicates at a distance of one edit, swap, deletion or insertion.

    ?- apropos('wirte').
    Predicate wirte not found. Similar predicates:
    
    transaction_logging:write/2
    write:write/1
    write:write/2
    
    yes
    ?- apropos(apend).
    Predicate apend not found. Similar predicates:
    
    hprolog:append/2
    lists:append/3
    llists:append/2
    
    yes
    ?- 
    
    

    Usage:apropos(RegSpec)

    This will search any predicate specification Spec which matches the given RegSpec incomplete predicate specification.

    • The following properties should hold at call time:
      (librowser:apropos_spec/1)RegSpec is a predicate specification Pattern, Pattern/Arity, Module:Pattern, Module:Pattern/Arity.

    Documentation on internals

    REGTYPE
    Defined as:
    apropos_spec(Pattern) :-
            atm(Pattern).
    apropos_spec(Pattern/Arity) :-
            atm(Pattern),
            int(Arity).
    apropos_spec(Module:Pattern/Arity) :-
            atm(Pattern),
            atm(Module),
            int(Arity).
    apropos_spec(Module:Pattern) :-
            atm(Pattern),
            atm(Module).
    

    Usage:apropos_spec(S)

    S is a predicate specification Pattern, Pattern/Arity, Module:Pattern, Module:Pattern/Arity.