new from SWI
This commit is contained in:
parent
4f5a3469d6
commit
bd83674168
@ -19,7 +19,7 @@
|
||||
|
||||
You should have received a copy of the GNU Lesser General Public
|
||||
License along with this library; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
|
||||
|
||||
As a special exception, if you link this library with other files,
|
||||
compiled with a Free Software compiler, to produce an executable, this
|
||||
@ -32,6 +32,7 @@
|
||||
:- module((record),
|
||||
[ (record)/1, % +Record
|
||||
current_record/2, % ?Name, ?Term
|
||||
current_record_predicate/2, % ?Record, :PI
|
||||
op(1150, fx, record)
|
||||
]).
|
||||
:- use_module(library(error)).
|
||||
@ -59,7 +60,8 @@ _directive_. Here is a simple example declaration and some calls.
|
||||
*/
|
||||
|
||||
:- multifile
|
||||
error:has_type/2.
|
||||
error:has_type/2,
|
||||
prolog:generated_predicate/1.
|
||||
|
||||
error:has_type(record(M:Name), X) :-
|
||||
current_record(Name, M, _, X, IsX), !,
|
||||
@ -77,6 +79,7 @@ error:has_type(record(M:Name), X) :-
|
||||
% info the following predicates:
|
||||
%
|
||||
% * <constructor>_<name>(Record, Value)
|
||||
% * <constructor>_data(?Name, ?Record, ?Value)
|
||||
% * default_<constructor>(-Record)
|
||||
% * is_<constructor>(@Term)
|
||||
% * make_<constructor>(+Fields, -Record)
|
||||
@ -120,12 +123,14 @@ compile_record(RecordDef) -->
|
||||
defaults(Args, Defs, TypedArgs),
|
||||
types(TypedArgs, Names, Types),
|
||||
atom_concat(default_, Constructor, DefName),
|
||||
atom_concat(Constructor, '_data', DataName),
|
||||
DefRecord =.. [Constructor|Defs],
|
||||
DefClause =.. [DefName,DefRecord],
|
||||
length(Names, Arity)
|
||||
},
|
||||
[ DefClause ],
|
||||
access_predicates(Names, 1, Arity, Constructor),
|
||||
data_predicate(Names, 1, Arity, Constructor, DataName),
|
||||
set_predicates(Names, 1, Arity, Types, Constructor),
|
||||
set_field_predicates(Names, 1, Arity, Types, Constructor),
|
||||
make_predicate(Constructor),
|
||||
@ -133,7 +138,8 @@ compile_record(RecordDef) -->
|
||||
current_clause(RecordDef).
|
||||
|
||||
:- meta_predicate
|
||||
current_record(:).
|
||||
current_record(?, :),
|
||||
current_record_predicate(?, :).
|
||||
:- multifile
|
||||
current_record/5. % Name, Module, Term, X, IsX
|
||||
|
||||
@ -156,6 +162,56 @@ current_clause(RecordDef) -->
|
||||
].
|
||||
|
||||
|
||||
%% current_record_predicate(?Record, ?PI) is nondet.
|
||||
%
|
||||
% True if PI is the predicate indicator for an access predicate to
|
||||
% Record. This predicate is intended to support cross-referencer
|
||||
% tools.
|
||||
|
||||
current_record_predicate(Record, M:PI) :-
|
||||
( ground(PI)
|
||||
-> Det = true
|
||||
; true
|
||||
),
|
||||
current_record(Record, M:RecordDef),
|
||||
( general_record_pred(Record, M:PI)
|
||||
; RecordDef =.. [_|Args],
|
||||
defaults(Args, _Defs, TypedArgs),
|
||||
types(TypedArgs, Names, _Types),
|
||||
member(Field, Names),
|
||||
field_record_pred(Record, Field, M:PI)
|
||||
),
|
||||
( Det == true
|
||||
-> !
|
||||
; true
|
||||
).
|
||||
|
||||
general_record_pred(Record, _:Name/1) :-
|
||||
atom_concat(is_, Record, Name).
|
||||
general_record_pred(Record, _:Name/1) :-
|
||||
atom_concat(default_, Record, Name).
|
||||
general_record_pred(Record, _:Name/A) :-
|
||||
member(A, [2,3]),
|
||||
atom_concat(make_, Record, Name).
|
||||
general_record_pred(Record, _:Name/3) :-
|
||||
atom_concat(Record, '_data', Name).
|
||||
general_record_pred(Record, _:Name/A) :-
|
||||
member(A, [3,4]),
|
||||
atomic_list_concat([set_, Record, '_fields'], Name).
|
||||
general_record_pred(Record, _:Name/3) :-
|
||||
atomic_list_concat([set_, Record, '_field'], Name).
|
||||
|
||||
field_record_pred(Record, Field, _:Name/2) :-
|
||||
atomic_list_concat([Record, '_', Field], Name).
|
||||
field_record_pred(Record, Field, _:Name/A) :-
|
||||
member(A, [2,3]),
|
||||
atomic_list_concat([set_, Field, '_of_', Record], Name).
|
||||
field_record_pred(Record, Field, _:Name/2) :-
|
||||
atomic_list_concat([nb_set_, Field, '_of_', Record], Name).
|
||||
|
||||
prolog:generated_predicate(P) :-
|
||||
current_record_predicate(_, P).
|
||||
|
||||
%% make_predicate(+Constructor)// is det.
|
||||
%
|
||||
% Creates the make_<constructor>(+Fields, -Record) predicate. This
|
||||
@ -286,6 +342,22 @@ access_predicates([Name|NT], I, Arity, Constructor) -->
|
||||
access_predicates(NT, I2, Arity, Constructor).
|
||||
|
||||
|
||||
%% data_predicate(+Names, +Idx0, +Arity, +Constructor, +DataName)// is det.
|
||||
%
|
||||
% Create the <constructor>_data(Name, Record, Value) predicate.
|
||||
|
||||
data_predicate([], _, _, _, _) -->
|
||||
[].
|
||||
data_predicate([Name|NT], I, Arity, Constructor, DataName) -->
|
||||
{ functor(Record, Constructor, Arity),
|
||||
arg(I, Record, Value),
|
||||
Clause =.. [DataName, Name, Record, Value],
|
||||
I2 is I + 1
|
||||
},
|
||||
[Clause],
|
||||
data_predicate(NT, I2, Arity, Constructor, DataName).
|
||||
|
||||
|
||||
%% set_predicates(+Names, +Idx0, +Arity, +Types, +Constructor)// is det.
|
||||
%
|
||||
% Create the clauses
|
||||
|
Reference in New Issue
Block a user