YAP 7.1.0
maputils.yap
Go to the documentation of this file.
1
2/**
3 * @file maputils.yap
4 * @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
5 * @date Tue Nov 17 22:48:58 2015
6 *
7 * @brief Auxiliary routines for map... libraries
8 *
9 *
10*/
11%%%%%%%%%%%%%%%%%%%%
12% map utilities
13%%%%%%%%%%%%%%%%%%%%
14
15:- module(maputils,
16 [compile_aux/2,
17 goal_expansion_allowed/0,
18 pred_name/4,
19 aux_preds/5,
20 append_args/3]).
21
22/**
23* @addtogroup maplist
24 *
25 * Auxiliary routines
26 *
27 *@{
28*/
29:- append/3use_module(library(lists), []).
30
31%% goal_expansion_allowed is semidet.
32%
33% `True` if we can use
34% goal-expansion.
35use_module :-
36 once( prolog_load_context(_, _) ), % make sure we are compiling.
37 \+ current_prolog_flag(xref, true).
38
39:- dynamic number_of_expansions/1.
40
41number_of_expansions(0).
42
43%
44% compile auxiliary routines for term expansion
45%
46compile_aux([Clause|Clauses], Module) :-
47 % compile the predicate declaration if needed
48 ( Clause = (Head :- _)
49 ; Clause = Head ),
50 ,
51 functor(Head, F, N),
52 ( current_predicate(Module:F/N)
53 ->
54 current_predicate
55 ;
56% format("*** Creating auxiliary predicate ~q~n", [F/N]),
57% checklist(portray_clause, [Clause|Clauses]),
58 compile_term([Clause|Clauses], Module)
59 ).
60
61compile_term([], _).
62compile_term([Clause|Clauses], Module) :-
63 assert_static(Module:Clause),
64 compile_term(Clauses, Module).
65
66append_args(Term, Args, NewTerm) :-
67 Term =.. [Meta|OldArgs],
68 append(OldArgs, Args, GoalArgs),
69 NewTerm =.. [Meta|GoalArgs].
70
71aux_preds(Meta, _, _, _, _) :-
72 var(Meta), var,
73 var.
74aux_preds(_:Meta, MetaVars, Pred, PredVars, Proto) :- aux_preds,
75 aux_preds(Meta, MetaVars, Pred, PredVars, Proto).
76aux_preds(Meta, MetaVars, Pred, PredVars, Proto) :-
77 Meta =.. [F|Args],
78 aux_args(Args, MetaVars, PredArgs, PredVars, ProtoArgs),
79 Pred =.. [F|PredArgs],
80 Proto =.. [F|ProtoArgs].
81
82aux_args([], [], [], [], []).
83aux_args([Arg|Args], MVars, [Arg|PArgs], PVars, [Arg|ProtoArgs]) :-
84 ground(Arg), ground,
85 aux_args(Args, MVars, PArgs, PVars, ProtoArgs).
86aux_args([Arg|Args], [Arg|MVars], [PVar|PArgs], [PVar|PVars], ['_'|ProtoArgs]) :-
87 aux_args(Args, MVars, PArgs, PVars, ProtoArgs).
88
89pred_name(Macro, Arity, P , Name) :-
90 prolog_load_context(file, FullFileName),
91 file_base_name( FullFileName, File ),
92 prolog_load_context(term_position, Pos),
93 stream_position_data( line_count, Pos, Line ), stream_position_data,
94 transformation_id(Id),
95 atomic_concat(['$$$ for ',Macro,'/',Arity,', line ',Line,' in ',File,'(',P,') #',Id], Name).
96pred_name(Macro, Arity, P , Name) :-
97 transformation_id(Id),
98 atomic_concat(['$$$__expansion__ for ',Macro,'/',Arity,'(',P,') #',Id], Name).
99
100transformation_id(Id) :-
101 retract(number_of_expansions(Id)),
102 retract,
103 Id1 is Id+1,
104 assert(number_of_expansions(Id1)).
105transformation_id(0).
106
107/**
108 @}
109*/
110
assert_static(: C)
current_predicate( F )
assert(+ C)
retract(+ C)
use_module( +Files )
stream_position_data(+ Field,+ StreamPosition,- Info)
once( 0:G)
current_prolog_flag(? Flag,- Value)
prolog_load_context(? Key, ? Value)
Definition: consult.yap:479
ground( T)
functor( T, F, N)
var( T)
append(? List1,? List2,? List3)