34
35:- module(i18n_file_utils,
36 [current_po_file/3,
37 edit_po_file/3,
38 edit_po_file/2,
39 edit_po_files/2,
40 edit_po_files/1,
41 expand_pot_files/0,
42 expand_pot_file/1, 43 clean/3,
44 sort_po/3,
45 expand/3,
46 compact/2,
47 read_po_file/2, 48 save_to_po_file/2,
49 arrange_po_files/1,
50 subtract_po_file/2]). 51
52:- use_module(library(lists)). 53:- use_module(library(pairs)). 54:- use_module(library(readutil)). 55:- use_module(library(ref_changes)). 56:- use_module(library(term_info)). 57:- use_module(library(clambda)). 58:- use_module(library(i18n/i18n_parser)). 59:- use_module(library(i18n/i18n_support)). 60:- init_expansors. 61
62current_po_file(M, Lang, PoFile) :-
63 current_pot_file(M, PotFile),
64 get_lang_file(PotFile, Lang, PoWildcard),
65 expand_file_name(PoWildcard, PoFiles),
66 member(PoFile, PoFiles).
67
68read_po_file(File, Entries) :-
69 ( ( pending_change(_, File, Codes)
70 ->true
71 ; access_file(File, read) ->
72 read_file_to_codes(File, Codes, [])
73 )
74 ->parse_po_entries(Entries, Codes, [])
75 ; Entries = []
76 ).
81subtract_po_file(PoFile1, PoFile2) :-
82 read_po_file(PoFile1, Entries1),
83 read_po_file(PoFile2, Entries2),
84 subtract(Entries1, Entries2, Entries),
85 save_to_po_file(Entries, PoFile1).
86
90
91clean(PoFile, ML, Codes) :-
92 i18n_tmpl_entries(ML, TmplEntries),
93 read_po_file(PoFile, Entries1),
94 Entry = entry(_, _, Ref, _, MsgId, _),
95 findall(Entry,
96 ( member(Entry, Entries1),
97 member(entry(_, _, Ref, _, MsgId, _), TmplEntries)
98 ), Entries),
99 parse_po_entries(Entries, Codes, []).
100
101sort_po(PoFile, _, Codes) :-
102 read_po_file(PoFile, EntriesU),
103 sort(EntriesU, Entries),
104 parse_po_entries(Entries, Codes, []).
110expand(PoFile, ML, Codes) :-
111 read_po_file(PoFile, Entries1),
112 i18n_tmpl_entries(ML, TmplEntries),
113 Entry = entry(_, _, Ref, _, MsgId, _),
114 findall(Entry, ( member(Entry, TmplEntries),
115 \+ member(entry(_, _, Ref, _, MsgId, _), Entries1)
116 ), Entries, Entries1),
117 parse_po_entries(Entries, Codes, []).
122compact(PoFile, Codes) :-
123 read_po_file(PoFile, Entries1),
124 findall(Entry,
125 ( member(Entry, Entries1),
126 Entry \= entry(_, _, _, _, _, [""])
127 ), Entries),
128 parse_po_entries(Entries, Codes, []).
129
131:- meta_predicate edit_po_file(2,+,+). 132edit_po_file(Command, M, Lang) :-
133 findall(PoFile-Codes,
134 ( current_po_file(M, Lang, PoFile),
135 call(Command, PoFile, [M], Codes)
136 ), FileCodes),
137 save_changes(FileCodes).
138
139:- meta_predicate edit_po_file(2,+). 140edit_po_file(Command, M) :-
141 edit_po_file(Command, M, '??').
142
143:- meta_predicate edit_po_files(2,+). 144edit_po_files(Command, Lang) :-
145 findall(PoFile-M, current_po_file(M, Lang, PoFile), Pairs),
146 keysort(Pairs, Sorted),
147 group_pairs_by_key(Sorted, Grouped),
148 forall(member(PoFile-ML, Grouped),
149 call(Command, PoFile, ML)).
150
151:- meta_predicate edit_po_files(2). 152edit_po_files(Command) :- edit_po_files(Command, '??').
153
154expand_pot_file(M) :-
155 findall(PotFile-Codes,
156 ( current_pot_file(M, PotFile),
157 i18n_tmpl_entries_module(M, EntriesU),
158 sort(EntriesU, Entries),
159 parse_po_entries(Entries, Codes, [])
160 ),
161 FileChanges),
162 save_changes(FileChanges).
163
164expand_pot_files :-
165 findall(PotFile-M, current_pot_file(M, PotFile), Pairs),
166 keysort(Pairs, Sorted),
167 group_pairs_by_key(Sorted, Grouped),
168 findall(PotFile-Codes,
169 ( member(PotFile-ML, Grouped),
170 i18n_tmpl_entries(ML, EntriesU),
171 sort(EntriesU, Entries),
172 parse_po_entries(Entries, Codes, [])
173 ),
174 FileChanges),
175 save_changes(FileChanges).
176
177read_entries(FL, Lang, TEntriesL) :-
178 findall(PotFile, current_pot_file(_, PotFile), FL1),
179 sort(FL1, FL2),
180 read_entries(FL2, [], FL, Lang, TEntriesL).
181
182read_time_entries(PotFile, Lang, Time-Entries) :-
183 get_lang_file(PotFile, Lang, PoFile),
184 read_po_file(PoFile, Entries),
185 Entries \= [],
186 time_file(PoFile, Time).
187
188read_entries([], FL, FL, _, []) :- !.
189read_entries(FD1, FL1, FL, Lang, TEntriesL) :-
190 findall(TEntries,
191 ( member(PotFile, FD1),
192 read_time_entries(PotFile, Lang, TEntries)
193 ),
194 TEntriesL, TEntriesT),
195 append(FL1, FD1, FL2),
196 findall(PotFile, ( TEntriesT = [], 197 member(_-Entries, TEntriesL),
198 member(Entry, Entries),
199 determine_module(Entry, M),
200 current_pot_file(M, PotFile),
201 \+ memberchk(PotFile, FL2)
202 ), FD2),
203 sort(FD2, FD3),
204 read_entries(FD3, FL2, FL, Lang, TEntriesT).
205
208merge_entries_list([], TEntries, TEntries).
209merge_entries_list([Time-EntriesL|TEntriesL], TEntries1, TEntries) :-
210 merge_entries(EntriesL, Time, TEntries1, TEntries2),
211 merge_entries_list(TEntriesL, TEntries2, TEntries).
212
213merge_entries([], _, TEntries, TEntries).
214merge_entries([Entry1|Entries], Time1, TEntries1, TEntries) :-
215 Entry1 = entry(_, _, Ref, _, MsgId, _),
216 ( select(Time2-entry(_, _, Ref, _, MsgId, _), TEntries1, TEntries2)
217 -> 218 ( Time2 < Time1
219 ->TEntries3 = [Time1-Entry1|TEntries2] 220 ; TEntries3 = TEntries1 221 )
222 ; TEntries3 = [Time1-Entry1|TEntries1]
223 ),
224 merge_entries(Entries, Time1, TEntries3, TEntries).
225
226save_to_po_file(Entries, PoFile) :-
227 parse_po_entries(Entries, Codes, []),
228 save_changes([PoFile-Codes]).
229
230arrange_po_files(Lang) :-
231 read_entries(FL, Lang, TEntriesL),
232 merge_entries_list(TEntriesL, [], TEntries),
233 pairs_values(TEntries, Entries),
234 maplist(\Entry^(F-Entry)^ ( determine_module(Entry, M),
235 once(current_pot_file(M, F))
236 ),
237 Entries, UFEntries),
238 keysort(UFEntries, FEntries),
239 group_pairs_by_key(FEntries, GFEntries),
240 pairs_keys(GFEntries, UF),
241 subtract(FL, UF, EFL),
242 maplist(\F^(F-[])^true, EFL, EFEntries),
243 append(GFEntries, EFEntries, AFEntries),
244 maplist([Lang] +\ (F-UE)^(PoFile-Codes)^
245 ( sort(UE, E),
246 get_lang_file(F, Lang, PoFile),
247 parse_po_entries(E, Codes, [])
248 ), AFEntries, FileChanges),
249 save_changes(FileChanges).
250
251determine_module(entry(_, _, Ref, _, _, _), M) :-
252 reference(M, Ref).
253
255
256:- dynamic i18n_po_tmpl/2. 257
258assert_entry_tmpl((~), M, MsgId, [""]) :- !,
259 reference(M, Ref),
260 Entry = entry([], [], Ref, [], MsgId, [""]),
261 ( i18n_po_tmpl(Entry, M) -> true
262 ; assertz(i18n_po_tmpl(Entry, M))
263 ).
264assert_entry_tmpl((~~), _, _, [""]). 265
266collect_i18n_term(M, (:- resourceterm(Term))) :-
267 i18n_process_term(assert_entry_tmpl((~)), M, Term, _),
268 !.
269collect_i18n_term(M, Term) :-
270 expand_i18n_term(assert_entry_tmpl, M, Term, _).
271
272i18n_tmpl_entries(ML, Entries) :-
273 collect_i18n_entries_by_module,
274 findall(Entry,
275 ( member(M, ML),
276 retract(i18n_po_tmpl(Entry, M))
277 ), Entries).
278
279i18n_tmpl_entries_module(M, Entries) :-
280 collect_i18n_entries_by_module,
281 findall(Entry, retract(i18n_po_tmpl(Entry, M)), Entries).
282
283get_term_info(M, Pattern, Options) :-
284 get_term_info(M, Pattern, Term, \_^true, _, Options),
285 Term = Pattern.
286
287collect_i18n_entries_by_module :-
288 retractall(i18n_po_tmpl(_, _)),
289 ( i18n_support:current_i18n_module(M),
290 get_term_info(M, RawTerm, []),
291 collect_i18n_term(M, RawTerm),
292 fail
293 ; true
294 )