34
35:- module(text_properties, []). 36:- use_module(library(dcg/basics)). 37:- use_module(library(semweb/rdf_db)). 38:- use_module(library(semweb/rdf_litindex)). 39
40:- multifile
41 sparql:functional_property/2,
42 sparql:current_functional_property/3. 43
44:- rdf_register_prefix(tpf, 'http://cliopatria.swi-prolog.org/pf/text#'). 45
46term_expansion((sparql:functional_property(S, NS:Term0) :- Body),
47 [ (sparql:functional_property(S, Term) :- Body),
48 sparql:current_functional_property(P, P, Argc)
49 ]) :-
50 Term0 =.. [Name|Args],
51 length(Args, Argc),
52 rdf_global_id(NS:Name, P),
53 Term =.. [P|Args].
54
55
56
66sparql:functional_property(S, tpf:match(P, Pattern)) :-
67 compile_pattern(Pattern, Spec, LV),
68 search(S, P, Spec, LV).
69sparql:functional_property(S, tpf:match(P, Pattern, literal(Found))) :-
70 compile_pattern(Pattern, Spec, Found),
71 search(S, P, Spec, Found).
72
73search(S, P, prefix0(Prefix), Literal) :-
74 !,
75 rdf_has(S, P, literal(prefix(Prefix), Literal)).
76search(S, P, Pattern, Literal) :-
77 rdf_find_literal(Pattern, Plain),
78 rdf_has(S, P, literal(exact(Plain), Literal)).
79
80compile_pattern(Literal, Spec, LitValue) :-
81 text_of(Literal, Pattern, Lang, LitValue),
82 atom_codes(Pattern, PatternCodes),
83 phrase(compile_pattern(Spec, Lang), PatternCodes).
84
85text_of(literal(lang(Lang, Pattern)), Pattern, Lang, lang(Lang,_)) :- !.
86text_of(literal(Pattern), Pattern, _, _).
87
88compile_pattern(Spec, _) -->
89 "^", !, rest(Prefix),
90 { Spec = prefix0(Prefix) }.
91compile_pattern(Spec, Lang) -->
92 blanks, "(", compile_pattern(Spec, Lang), ")",
93 !.
94compile_pattern(Spec, Lang) -->
95 blanks,
96 simple_pattern(Left, Lang),
97 ( and
98 -> compile_pattern(Right, Lang),
99 { Spec = and(Left,Right) }
100 ; or
101 -> compile_pattern(Right, Lang),
102 { Spec = or(Left,Right) }
103 ; compile_pattern(Right, Lang)
104 -> { Spec = and(Left,Right) }
105 ; blanks
106 -> { Spec = Left }
107 ).
108
109and --> blanks, "AND", blank, !, blanks.
110or --> blanks, "OR", blank, !, blanks.
111
112simple_pattern(not(Spec), Lang) -->
113 "-",
114 !,
115 token_pattern(Spec, Lang).
116simple_pattern(Spec, Lang) -->
117 token_pattern(Spec, Lang).
118
119token_pattern(Spec, Lang) -->
120 word(Word),
121 !,
122 modifiers(Word, Lang, Spec).
123token_pattern(Spec, _) -->
124 number(N1),
125 ( "..",
126 number(N2)
127 -> { Spec = between(N1, N2) }
128 ; { Spec = N1 }
129 ).
130token_pattern(ge(N), _) -->
131 ">=", number(N),
132 !.
133token_pattern(le(N), _) -->
134 "<=", number(N),
135 !.
136token_pattern(le(N), _) -->
137 "=<", number(N),
138 !.
139
140modifiers(Word, _, case(Word)) --> "/i", !.
141modifiers(Word, _, prefix(Word)) --> "*", !.
142modifiers(Word, L, stem(Word,L)) --> "/s", {nonvar(L)}, !.
143modifiers(Word, _, stem(Word)) --> "/s", !.
144modifiers(Word, _, sounds(Word)) --> "/S", !.
145modifiers(Word, _, Word) --> "".
152word(Word) -->
153 alpha(First),
154 alphas(Alphas),
155 { atom_codes(Word, [First|Alphas])
156 }.
157
158alphas([H|T]) -->
159 alpha(H),
160 !,
161 alphas(T).
162alphas([]) --> [].
163
164alpha(H) -->
165 [H],
166 { code_type(H, alpha) }.
167
168rest(Atom, Codes, []) :-
169 atom_codes(Atom, Codes)