]> git.evergreen-ils.org Git - working/Evergreen.git/blob - Open-ILS/src/sql/Pg/upgrade/XXXX.schema.symspell.sql
LP#1893997: mention new settings in the release notes
[working/Evergreen.git] / Open-ILS / src / sql / Pg / upgrade / XXXX.schema.symspell.sql
1 BEGIN;
2
3 CREATE EXTENSION IF NOT EXISTS fuzzystrmatch;
4 CREATE EXTENSION IF NOT EXISTS pg_trgm;
5
6 INSERT INTO config.internal_flag (name, value, enabled) VALUES ('symspell.prefix_length', '6', TRUE);
7 INSERT INTO config.internal_flag (name, value, enabled) VALUES ('symspell.max_edit_distance', '3', TRUE);
8
9 INSERT into config.org_unit_setting_type
10 ( name, grp, label, description, datatype )
11 VALUES
12 ( 'opac.did_you_mean.max_suggestions', 'opac',
13    oils_i18n_gettext(
14      'opac.did_you_mean.max_suggestions',
15      'Maximum number of spelling suggestions that may be offered',
16      'coust', 'label'),
17    oils_i18n_gettext(
18      'opac.did_you_mean.max_suggestions',
19      'If set to -1, provide "best" suggestion if mispelled; if set higher than 0, the maximum suggestions that can be provided; if set to 0, disable suggestions.',
20      'coust', 'description'),
21    'integer' );
22
23 INSERT into config.org_unit_setting_type
24 ( name, grp, label, description, datatype )
25 VALUES
26 ( 'opac.did_you_mean.low_result_threshold', 'opac',
27    oils_i18n_gettext(
28      'opac.did_you_mean.low_result_threshold',
29      'Maximum search result count at which spelling suggestions may be offered',
30      'coust', 'label'),
31    oils_i18n_gettext(
32      'opac.did_you_mean.low_result_threshold',
33      'If a search results in this number or fewer results, and there are correctable spelling mistakes, a suggested search may be provided.',
34      'coust', 'description'),
35    'integer' );
36
37 INSERT into config.org_unit_setting_type
38 ( name, grp, label, description, datatype )
39 VALUES
40 ( 'search.symspell.min_suggestion_use_threshold', 'opac',
41    oils_i18n_gettext(
42      'search.symspell.min_suggestion_use_threshold',
43      'Minimum required uses of a spelling suggestions that may be offered',
44      'coust', 'label'),
45    oils_i18n_gettext(
46      'search.symspell.min_suggestion_use_threshold',
47      'The number of bibliographic records (more or less) that a spelling suggestion must appear in to be considered before offering it to a user. Defaults to 1 (must appear in the bib data).',
48      'coust', 'description'),
49    'integer' );
50
51 INSERT into config.org_unit_setting_type
52 ( name, grp, label, description, datatype )
53 VALUES
54 ( 'search.symspell.soundex.weight', 'opac',
55    oils_i18n_gettext(
56      'search.symspell.soundex.weight',
57      'Soundex score weighting in OPAC spelling suggestions.',
58      'coust', 'label'),
59    oils_i18n_gettext(
60      'search.symspell.soundex.weight',
61      'Soundex, trgm, and keyboard distance similarity measures can be combined to form a secondary ordering parameter for spelling suggestions. This controls the relative weight of the scaled soundex component. Defaults to 0 for "off".',
62      'coust', 'description'),
63    'integer' );
64
65 INSERT into config.org_unit_setting_type
66 ( name, grp, label, description, datatype )
67 VALUES
68 ( 'search.symspell.pg_trgm.weight', 'opac',
69    oils_i18n_gettext(
70      'search.symspell.pg_trgm.weight',
71      'Pg_trgm score weighting in OPAC spelling suggestions.',
72      'coust', 'label'),
73    oils_i18n_gettext(
74      'search.symspell.pg_trgm.weight',
75      'Soundex, pg_trgm, and keyboard distance similarity measures can be combined to form a secondary ordering parameter for spelling suggestions. This controls the relative weight of the scaled pg_trgm component. Defaults to 0 for "off".',
76      'coust', 'description'),
77    'integer' );
78
79 INSERT into config.org_unit_setting_type
80 ( name, grp, label, description, datatype )
81 VALUES
82 ( 'search.symspell.keyboard_distance.weight', 'opac',
83    oils_i18n_gettext(
84      'search.symspell.keyboard_distance.weight',
85      'Keyboard distance score weighting in OPAC spelling suggestions.',
86      'coust', 'label'),
87    oils_i18n_gettext(
88      'search.symspell.keyboard_distance.weight',
89      'Soundex, trgm, and keyboard distance similarity measures can be combined to form a secondary ordering parameter for spelling suggestions. This controls the relative weight of the scaled keyboard distance component. Defaults to 0 for "off".',
90      'coust', 'description'),
91    'integer' );
92
93 CREATE OR REPLACE FUNCTION evergreen.uppercase( TEXT ) RETURNS TEXT AS $$
94     return uc(shift);
95 $$ LANGUAGE PLPERLU STRICT IMMUTABLE;
96
97 CREATE OR REPLACE FUNCTION evergreen.text_array_merge_unique (
98     TEXT[], TEXT[]
99 ) RETURNS TEXT[] AS $F$
100     SELECT NULLIF(ARRAY(
101         SELECT * FROM UNNEST($1) x WHERE x IS NOT NULL
102             UNION
103         SELECT * FROM UNNEST($2) y WHERE y IS NOT NULL
104     ),'{}');
105 $F$ LANGUAGE SQL;
106
107 CREATE OR REPLACE FUNCTION evergreen.qwerty_keyboard_distance ( a TEXT, b TEXT ) RETURNS NUMERIC AS $F$
108 use String::KeyboardDistance qw(:all);
109 return qwerty_keyboard_distance(@_);
110 $F$ LANGUAGE PLPERLU STRICT IMMUTABLE;
111
112 CREATE OR REPLACE FUNCTION evergreen.qwerty_keyboard_distance_match ( a TEXT, b TEXT ) RETURNS NUMERIC AS $F$
113 use String::KeyboardDistance qw(:all);
114 return qwerty_keyboard_distance_match(@_);
115 $F$ LANGUAGE PLPERLU STRICT IMMUTABLE;
116
117 CREATE OR REPLACE FUNCTION evergreen.levenshtein_damerau_edistance ( a TEXT, b TEXT, INT ) RETURNS NUMERIC AS $F$
118 use Text::Levenshtein::Damerau::XS qw/xs_edistance/;
119 return xs_edistance(@_);
120 $F$ LANGUAGE PLPERLU STRICT IMMUTABLE;
121
122 CREATE TABLE search.symspell_dictionary (
123     keyword_count           INT     NOT NULL DEFAULT 0,
124     title_count             INT     NOT NULL DEFAULT 0,
125     author_count            INT     NOT NULL DEFAULT 0,
126     subject_count           INT     NOT NULL DEFAULT 0,
127     series_count            INT     NOT NULL DEFAULT 0,
128     identifier_count        INT     NOT NULL DEFAULT 0,
129
130     prefix_key              TEXT    PRIMARY KEY,
131
132     keyword_suggestions     TEXT[],
133     title_suggestions       TEXT[],
134     author_suggestions      TEXT[],
135     subject_suggestions     TEXT[],
136     series_suggestions      TEXT[],
137     identifier_suggestions  TEXT[]
138 ) WITH (fillfactor = 80);
139
140 CREATE OR REPLACE FUNCTION search.symspell_parse_words ( phrase TEXT )
141 RETURNS SETOF TEXT AS $F$
142     SELECT UNNEST(x) FROM regexp_matches($1, '([[:alnum:]]+''*[[:alnum:]]*)', 'g') x;
143 $F$ LANGUAGE SQL STRICT IMMUTABLE;
144
145 -- This version does not preserve input word order!
146 CREATE OR REPLACE FUNCTION search.symspell_parse_words_distinct ( phrase TEXT )
147 RETURNS SETOF TEXT AS $F$
148     SELECT DISTINCT UNNEST(x) FROM regexp_matches($1, '([[:alnum:]]+''*[[:alnum:]]*)', 'g') x;
149 $F$ LANGUAGE SQL STRICT IMMUTABLE;
150
151 CREATE OR REPLACE FUNCTION search.symspell_transfer_casing ( withCase TEXT, withoutCase TEXT )
152 RETURNS TEXT AS $F$
153 DECLARE
154     woChars TEXT[];
155     curr    TEXT;
156     ind     INT := 1;
157 BEGIN
158     woChars := regexp_split_to_array(withoutCase,'');
159     FOR curr IN SELECT x FROM regexp_split_to_table(withCase, '') x LOOP
160         IF curr = evergreen.uppercase(curr) THEN
161             woChars[ind] := evergreen.uppercase(woChars[ind]);
162         END IF;
163         ind := ind + 1;
164     END LOOP;
165     RETURN ARRAY_TO_STRING(woChars,'');
166 END;
167 $F$ LANGUAGE PLPGSQL STRICT IMMUTABLE;
168
169 CREATE OR REPLACE FUNCTION search.symspell_generate_edits (
170     raw_word    TEXT,
171     dist        INT DEFAULT 1,
172     maxED       INT DEFAULT 3
173 ) RETURNS TEXT[] AS $F$
174 DECLARE
175     item    TEXT;
176     list    TEXT[] := '{}';
177     sublist TEXT[] := '{}';
178 BEGIN
179     FOR I IN 1 .. CHARACTER_LENGTH(raw_word) LOOP
180         item := SUBSTRING(raw_word FROM 1 FOR I - 1) || SUBSTRING(raw_word FROM I + 1);
181         IF NOT list @> ARRAY[item] THEN
182             list := item || list;
183             IF dist < maxED AND CHARACTER_LENGTH(raw_word) > dist + 1 THEN
184                 sublist := search.symspell_generate_edits(item, dist + 1, maxED) || sublist;
185             END IF;
186         END IF;
187     END LOOP;
188
189     IF dist = 1 THEN
190         RETURN evergreen.text_array_merge_unique(list, sublist);
191     ELSE
192         RETURN list || sublist;
193     END IF;
194 END;
195 $F$ LANGUAGE PLPGSQL STRICT IMMUTABLE;
196
197 -- DROP TYPE search.symspell_lookup_output CASCADE;
198 CREATE TYPE search.symspell_lookup_output AS (
199     suggestion          TEXT,
200     suggestion_count    INT,
201     lev_distance        INT,
202     pg_trgm_sim         NUMERIC,
203     qwerty_kb_match     NUMERIC,
204     soundex_sim         NUMERIC,
205     input               TEXT,
206     norm_input          TEXT,
207     prefix_key          TEXT,
208     prefix_key_count    INT,
209     word_pos            INT
210 );
211
212 CREATE OR REPLACE FUNCTION search.symspell_lookup (
213     raw_input       TEXT,
214     search_class    TEXT,
215     verbosity       INT DEFAULT 2,
216     xfer_case       BOOL DEFAULT FALSE,
217     count_threshold INT DEFAULT 1,
218     soundex_weight  INT DEFAULT 0,
219     pg_trgm_weight  INT DEFAULT 0,
220     kbdist_weight   INT DEFAULT 0
221 ) RETURNS SETOF search.symspell_lookup_output AS $F$
222 DECLARE
223     prefix_length INT;
224     maxED         INT;
225     word_list   TEXT[];
226     edit_list   TEXT[] := '{}';
227     seen_list   TEXT[] := '{}';
228     output      search.symspell_lookup_output;
229     output_list search.symspell_lookup_output[];
230     entry       RECORD;
231     entry_key   TEXT;
232     prefix_key  TEXT;
233     sugg        TEXT;
234     input       TEXT;
235     word        TEXT;
236     w_pos       INT := -1;
237     smallest_ed INT := -1;
238     global_ed   INT;
239 BEGIN
240     SELECT value::INT INTO prefix_length FROM config.internal_flag WHERE name = 'symspell.prefix_length' AND enabled;
241     prefix_length := COALESCE(prefix_length, 6);
242
243     SELECT value::INT INTO maxED FROM config.internal_flag WHERE name = 'symspell.max_edit_distance' AND enabled;
244     maxED := COALESCE(maxED, 3);
245
246     word_list := ARRAY_AGG(x) FROM search.symspell_parse_words(raw_input) x;
247
248     -- Common case exact match test for preformance
249     IF verbosity = 0 AND CARDINALITY(word_list) = 1 AND CHARACTER_LENGTH(word_list[1]) <= prefix_length THEN
250         EXECUTE
251           'SELECT  '||search_class||'_suggestions AS suggestions,
252                    '||search_class||'_count AS count,
253                    prefix_key
254              FROM  search.symspell_dictionary
255              WHERE prefix_key = $1
256                    AND '||search_class||'_count >= $2 
257                    AND '||search_class||'_suggestions @> ARRAY[$1]' 
258           INTO entry USING evergreen.lowercase(word_list[1]), COALESCE(count_threshold,1);
259         IF entry.prefix_key IS NOT NULL THEN
260             output.lev_distance := 0; -- definitionally
261             output.prefix_key := entry.prefix_key;
262             output.prefix_key_count := entry.count;
263             output.suggestion_count := entry.count;
264             output.input := word_list[1];
265             IF xfer_case THEN
266                 output.suggestion := search.symspell_transfer_casing(output.input, entry.prefix_key);
267             ELSE
268                 output.suggestion := entry.prefix_key;
269             END IF;
270             output.norm_input := entry.prefix_key;
271             output.qwerty_kb_match := 1;
272             output.pg_trgm_sim := 1;
273             output.soundex_sim := 1;
274             RETURN NEXT output;
275             RETURN;
276         END IF;
277     END IF;
278
279     <<word_loop>>
280     FOREACH word IN ARRAY word_list LOOP
281         w_pos := w_pos + 1;
282         input := evergreen.lowercase(word);
283
284         IF CHARACTER_LENGTH(input) > prefix_length THEN
285             prefix_key := SUBSTRING(input FROM 1 FOR prefix_length);
286             edit_list := ARRAY[input,prefix_key] || search.symspell_generate_edits(prefix_key, 1, maxED);
287         ELSE
288             edit_list := input || search.symspell_generate_edits(input, 1, maxED);
289         END IF;
290
291         SELECT ARRAY_AGG(x ORDER BY CHARACTER_LENGTH(x) DESC) INTO edit_list FROM UNNEST(edit_list) x;
292
293         output_list := '{}';
294         seen_list := '{}';
295         global_ed := NULL;
296
297         <<entry_key_loop>>
298         FOREACH entry_key IN ARRAY edit_list LOOP
299             smallest_ed := -1;
300             IF global_ed IS NOT NULL THEN
301                 smallest_ed := global_ed;
302             END IF;
303             FOR entry IN EXECUTE
304                 'SELECT  '||search_class||'_suggestions AS suggestions,
305                          '||search_class||'_count AS count,
306                          prefix_key
307                    FROM  search.symspell_dictionary
308                    WHERE prefix_key = $1
309                          AND '||search_class||'_suggestions IS NOT NULL' 
310                 USING entry_key
311             LOOP
312                 FOREACH sugg IN ARRAY entry.suggestions LOOP
313                     IF NOT seen_list @> ARRAY[sugg] THEN
314                         seen_list := seen_list || sugg;
315                         IF input = sugg THEN -- exact match, no need to spend time on a call
316                             output.lev_distance := 0;
317                             output.suggestion_count = entry.count;
318                         ELSIF ABS(CHARACTER_LENGTH(input) - CHARACTER_LENGTH(sugg)) > maxED THEN
319                             -- They are definitionally too different to consider, just move on.
320                             CONTINUE;
321                         ELSE
322                             --output.lev_distance := levenshtein_less_equal(
323                             output.lev_distance := evergreen.levenshtein_damerau_edistance(
324                                 input,
325                                 sugg,
326                                 maxED
327                             );
328                             IF output.lev_distance < 0 THEN
329                                 -- The Perl module returns -1 for "more distant than max".
330                                 output.lev_distance := maxED + 1;
331                                 -- This short-circuit's the count test below for speed, bypassing
332                                 -- a couple useless tests.
333                                 output.suggestion_count := -1;
334                             ELSE
335                                 EXECUTE 'SELECT '||search_class||'_count FROM search.symspell_dictionary WHERE prefix_key = $1'
336                                     INTO output.suggestion_count USING sugg;
337                             END IF;
338                         END IF;
339
340                         -- The caller passes a minimum suggestion count threshold (or uses
341                         -- the default of 0) and if the suggestion has that many or less uses
342                         -- then we move on to the next suggestion, since this one is too rare.
343                         CONTINUE WHEN output.suggestion_count < COALESCE(count_threshold,1);
344
345                         -- Track the smallest edit distance among suggestions from this prefix key.
346                         IF smallest_ed = -1 OR output.lev_distance < smallest_ed THEN
347                             smallest_ed := output.lev_distance;
348                         END IF;
349
350                         -- Track the smallest edit distance for all prefix keys for this word.
351                         IF global_ed IS NULL OR smallest_ed < global_ed THEN
352                             global_ed = smallest_ed;
353                         END IF;
354
355                         -- Only proceed if the edit distance is <= the max for the dictionary.
356                         IF output.lev_distance <= maxED THEN
357                             IF output.lev_distance > global_ed AND verbosity <= 1 THEN
358                                 -- Lev distance is our main similarity measure. While
359                                 -- trgm or soundex similarity could be the main filter,
360                                 -- Lev is both language agnostic and faster.
361                                 --
362                                 -- Here we will skip suggestions that have a longer edit distance
363                                 -- than the shortest we've already found. This is simply an
364                                 -- optimization that allows us to avoid further processing
365                                 -- of this entry. It would be filtered out later.
366
367                                 CONTINUE;
368                             END IF;
369
370                             -- If we have an exact match on the suggestion key we can also avoid
371                             -- some function calls.
372                             IF output.lev_distance = 0 THEN
373                                 output.qwerty_kb_match := 1;
374                                 output.pg_trgm_sim := 1;
375                                 output.soundex_sim := 1;
376                             ELSE
377                                 output.qwerty_kb_match := evergreen.qwerty_keyboard_distance_match(input, sugg);
378                                 output.pg_trgm_sim := similarity(input, sugg);
379                                 output.soundex_sim := difference(input, sugg) / 4.0;
380                             END IF;
381
382                             -- Fill in some fields
383                             IF xfer_case THEN
384                                 output.suggestion := search.symspell_transfer_casing(word, sugg);
385                             ELSE
386                                 output.suggestion := sugg;
387                             END IF;
388                             output.prefix_key := entry.prefix_key;
389                             output.prefix_key_count := entry.count;
390                             output.input := word;
391                             output.norm_input := input;
392                             output.word_pos := w_pos;
393
394                             -- We can't "cache" a set of generated records directly, so
395                             -- here we build up an array of search.symspell_lookup_output
396                             -- records that we can revivicate later as a table using UNNEST().
397                             output_list := output_list || output;
398
399                             EXIT entry_key_loop WHEN smallest_ed = 0 AND verbosity = 0; -- exact match early exit
400                             CONTINUE entry_key_loop WHEN smallest_ed = 0 AND verbosity = 1; -- exact match early jump to the next key
401                         END IF; -- maxED test
402                     END IF; -- suggestion not seen test
403                 END LOOP; -- loop over suggestions
404             END LOOP; -- loop over entries
405         END LOOP; -- loop over entry_keys
406
407         -- Now we're done examining this word
408         IF verbosity = 0 THEN
409             -- Return the "best" suggestion from the smallest edit
410             -- distance group.  We define best based on the weighting
411             -- of the non-lev similarity measures and use the suggestion
412             -- use count to break ties.
413             RETURN QUERY
414                 SELECT * FROM UNNEST(output_list)
415                     ORDER BY lev_distance,
416                         (soundex_sim * COALESCE(soundex_weight,0))
417                             + (pg_trgm_sim * COALESCE(pg_trgm_weight,0))
418                             + (qwerty_kb_match * COALESCE(kbdist_weight,0)) DESC,
419                         suggestion_count DESC
420                         LIMIT 1;
421         ELSIF verbosity = 1 THEN
422             -- Return all suggestions from the smallest
423             -- edit distance group.
424             RETURN QUERY
425                 SELECT * FROM UNNEST(output_list) WHERE lev_distance = smallest_ed
426                     ORDER BY (soundex_sim * COALESCE(soundex_weight,0))
427                             + (pg_trgm_sim * COALESCE(pg_trgm_weight,0))
428                             + (qwerty_kb_match * COALESCE(kbdist_weight,0)) DESC,
429                         suggestion_count DESC;
430         ELSIF verbosity = 2 THEN
431             -- Return everything we find, along with relevant stats
432             RETURN QUERY
433                 SELECT * FROM UNNEST(output_list)
434                     ORDER BY lev_distance,
435                         (soundex_sim * COALESCE(soundex_weight,0))
436                             + (pg_trgm_sim * COALESCE(pg_trgm_weight,0))
437                             + (qwerty_kb_match * COALESCE(kbdist_weight,0)) DESC,
438                         suggestion_count DESC;
439         ELSIF verbosity = 3 THEN
440             -- Return everything we find from the two smallest edit distance groups
441             RETURN QUERY
442                 SELECT * FROM UNNEST(output_list)
443                     WHERE lev_distance IN (SELECT DISTINCT lev_distance FROM UNNEST(output_list) ORDER BY 1 LIMIT 2)
444                     ORDER BY lev_distance,
445                         (soundex_sim * COALESCE(soundex_weight,0))
446                             + (pg_trgm_sim * COALESCE(pg_trgm_weight,0))
447                             + (qwerty_kb_match * COALESCE(kbdist_weight,0)) DESC,
448                         suggestion_count DESC;
449         ELSIF verbosity = 4 THEN
450             -- Return everything we find from the two smallest edit distance groups that are NOT 0 distance
451             RETURN QUERY
452                 SELECT * FROM UNNEST(output_list)
453                     WHERE lev_distance IN (SELECT DISTINCT lev_distance FROM UNNEST(output_list) WHERE lev_distance > 0 ORDER BY 1 LIMIT 2)
454                     ORDER BY lev_distance,
455                         (soundex_sim * COALESCE(soundex_weight,0))
456                             + (pg_trgm_sim * COALESCE(pg_trgm_weight,0))
457                             + (qwerty_kb_match * COALESCE(kbdist_weight,0)) DESC,
458                         suggestion_count DESC;
459         END IF;
460     END LOOP; -- loop over words
461 END;
462 $F$ LANGUAGE PLPGSQL;
463
464 CREATE OR REPLACE FUNCTION search.symspell_build_raw_entry (
465     raw_input       TEXT,
466     source_class    TEXT,
467     no_limit        BOOL DEFAULT FALSE,
468     prefix_length   INT DEFAULT 6,
469     maxED           INT DEFAULT 3
470 ) RETURNS SETOF search.symspell_dictionary AS $F$
471 DECLARE
472     key         TEXT;
473     del_key     TEXT;
474     key_list    TEXT[];
475     entry       search.symspell_dictionary%ROWTYPE;
476 BEGIN
477     key := raw_input;
478
479     IF NOT no_limit AND CHARACTER_LENGTH(raw_input) > prefix_length THEN
480         key := SUBSTRING(key FROM 1 FOR prefix_length);
481         key_list := ARRAY[raw_input, key];
482     ELSE
483         key_list := ARRAY[key];
484     END IF;
485
486     FOREACH del_key IN ARRAY key_list LOOP
487         entry.prefix_key := del_key;
488
489         entry.keyword_count := 0;
490         entry.title_count := 0;
491         entry.author_count := 0;
492         entry.subject_count := 0;
493         entry.series_count := 0;
494         entry.identifier_count := 0;
495
496         entry.keyword_suggestions := '{}';
497         entry.title_suggestions := '{}';
498         entry.author_suggestions := '{}';
499         entry.subject_suggestions := '{}';
500         entry.series_suggestions := '{}';
501         entry.identifier_suggestions := '{}';
502
503         IF source_class = 'keyword' THEN entry.keyword_suggestions := ARRAY[raw_input]; END IF;
504         IF source_class = 'title' THEN entry.title_suggestions := ARRAY[raw_input]; END IF;
505         IF source_class = 'author' THEN entry.author_suggestions := ARRAY[raw_input]; END IF;
506         IF source_class = 'subject' THEN entry.subject_suggestions := ARRAY[raw_input]; END IF;
507         IF source_class = 'series' THEN entry.series_suggestions := ARRAY[raw_input]; END IF;
508         IF source_class = 'identifier' THEN entry.identifier_suggestions := ARRAY[raw_input]; END IF;
509         IF source_class = 'keyword' THEN entry.keyword_suggestions := ARRAY[raw_input]; END IF;
510
511         IF del_key = raw_input THEN
512             IF source_class = 'keyword' THEN entry.keyword_count := 1; END IF;
513             IF source_class = 'title' THEN entry.title_count := 1; END IF;
514             IF source_class = 'author' THEN entry.author_count := 1; END IF;
515             IF source_class = 'subject' THEN entry.subject_count := 1; END IF;
516             IF source_class = 'series' THEN entry.series_count := 1; END IF;
517             IF source_class = 'identifier' THEN entry.identifier_count := 1; END IF;
518         END IF;
519
520         RETURN NEXT entry;
521     END LOOP;
522
523     FOR del_key IN SELECT x FROM UNNEST(search.symspell_generate_edits(key, 1, maxED)) x LOOP
524
525         entry.keyword_suggestions := '{}';
526         entry.title_suggestions := '{}';
527         entry.author_suggestions := '{}';
528         entry.subject_suggestions := '{}';
529         entry.series_suggestions := '{}';
530         entry.identifier_suggestions := '{}';
531
532         IF source_class = 'keyword' THEN entry.keyword_count := 0; END IF;
533         IF source_class = 'title' THEN entry.title_count := 0; END IF;
534         IF source_class = 'author' THEN entry.author_count := 0; END IF;
535         IF source_class = 'subject' THEN entry.subject_count := 0; END IF;
536         IF source_class = 'series' THEN entry.series_count := 0; END IF;
537         IF source_class = 'identifier' THEN entry.identifier_count := 0; END IF;
538
539         entry.prefix_key := del_key;
540
541         IF source_class = 'keyword' THEN entry.keyword_suggestions := ARRAY[raw_input]; END IF;
542         IF source_class = 'title' THEN entry.title_suggestions := ARRAY[raw_input]; END IF;
543         IF source_class = 'author' THEN entry.author_suggestions := ARRAY[raw_input]; END IF;
544         IF source_class = 'subject' THEN entry.subject_suggestions := ARRAY[raw_input]; END IF;
545         IF source_class = 'series' THEN entry.series_suggestions := ARRAY[raw_input]; END IF;
546         IF source_class = 'identifier' THEN entry.identifier_suggestions := ARRAY[raw_input]; END IF;
547         IF source_class = 'keyword' THEN entry.keyword_suggestions := ARRAY[raw_input]; END IF;
548
549         RETURN NEXT entry;
550     END LOOP;
551
552 END;
553 $F$ LANGUAGE PLPGSQL STRICT IMMUTABLE;
554
555 CREATE OR REPLACE FUNCTION search.symspell_build_entries (
556     full_input      TEXT,
557     source_class    TEXT,
558     old_input       TEXT DEFAULT NULL,
559     include_phrases BOOL DEFAULT FALSE
560 ) RETURNS SETOF search.symspell_dictionary AS $F$
561 DECLARE
562     prefix_length   INT;
563     maxED           INT;
564     word_list   TEXT[];
565     input       TEXT;
566     word        TEXT;
567     entry       search.symspell_dictionary;
568 BEGIN
569     IF full_input IS NOT NULL THEN
570         SELECT value::INT INTO prefix_length FROM config.internal_flag WHERE name = 'symspell.prefix_length' AND enabled;
571         prefix_length := COALESCE(prefix_length, 6);
572
573         SELECT value::INT INTO maxED FROM config.internal_flag WHERE name = 'symspell.max_edit_distance' AND enabled;
574         maxED := COALESCE(maxED, 3);
575
576         input := evergreen.lowercase(full_input);
577         word_list := ARRAY_AGG(x) FROM search.symspell_parse_words_distinct(input) x;
578     
579         IF CARDINALITY(word_list) > 1 AND include_phrases THEN
580             RETURN QUERY SELECT * FROM search.symspell_build_raw_entry(input, source_class, TRUE, prefix_length, maxED);
581         END IF;
582
583         FOREACH word IN ARRAY word_list LOOP
584             RETURN QUERY SELECT * FROM search.symspell_build_raw_entry(word, source_class, FALSE, prefix_length, maxED);
585         END LOOP;
586     END IF;
587
588     IF old_input IS NOT NULL THEN
589         input := evergreen.lowercase(old_input);
590
591         FOR word IN SELECT x FROM search.symspell_parse_words_distinct(input) x LOOP
592             entry.prefix_key := word;
593
594             entry.keyword_count := 0;
595             entry.title_count := 0;
596             entry.author_count := 0;
597             entry.subject_count := 0;
598             entry.series_count := 0;
599             entry.identifier_count := 0;
600
601             entry.keyword_suggestions := '{}';
602             entry.title_suggestions := '{}';
603             entry.author_suggestions := '{}';
604             entry.subject_suggestions := '{}';
605             entry.series_suggestions := '{}';
606             entry.identifier_suggestions := '{}';
607
608             IF source_class = 'keyword' THEN entry.keyword_count := -1; END IF;
609             IF source_class = 'title' THEN entry.title_count := -1; END IF;
610             IF source_class = 'author' THEN entry.author_count := -1; END IF;
611             IF source_class = 'subject' THEN entry.subject_count := -1; END IF;
612             IF source_class = 'series' THEN entry.series_count := -1; END IF;
613             IF source_class = 'identifier' THEN entry.identifier_count := -1; END IF;
614
615             RETURN NEXT entry;
616         END LOOP;
617     END IF;
618 END;
619 $F$ LANGUAGE PLPGSQL;
620
621 CREATE OR REPLACE FUNCTION search.symspell_build_and_merge_entries (
622     full_input      TEXT,
623     source_class    TEXT,
624     old_input       TEXT DEFAULT NULL,
625     include_phrases BOOL DEFAULT FALSE
626 ) RETURNS SETOF search.symspell_dictionary AS $F$
627 DECLARE
628     new_entry       RECORD;
629     conflict_entry  RECORD;
630 BEGIN
631
632     IF full_input = old_input THEN -- neither NULL, and are the same
633         RETURN;
634     END IF;
635
636     FOR new_entry IN EXECUTE $q$
637         SELECT  count,
638                 prefix_key,
639                 evergreen.text_array_merge_unique(s,'{}') suggestions
640           FROM  (SELECT prefix_key,
641                         ARRAY_AGG($q$ || source_class || $q$_suggestions[1]) s,
642                         SUM($q$ || source_class || $q$_count) count
643                   FROM  search.symspell_build_entries($1, $2, $3, $4)
644                   GROUP BY 1) x
645         $q$ USING full_input, source_class, old_input, include_phrases
646     LOOP
647         EXECUTE $q$
648             SELECT  prefix_key,
649                     $q$ || source_class || $q$_suggestions suggestions,
650                     $q$ || source_class || $q$_count count
651               FROM  search.symspell_dictionary
652               WHERE prefix_key = $1 $q$
653             INTO conflict_entry
654             USING new_entry.prefix_key;
655
656         IF new_entry.count <> 0 THEN -- Real word, and count changed
657             IF conflict_entry.prefix_key IS NOT NULL THEN -- we'll be updating
658                 IF conflict_entry.count > 0 THEN -- it's a real word
659                     RETURN QUERY EXECUTE $q$
660                         UPDATE  search.symspell_dictionary
661                            SET  $q$ || source_class || $q$_count = $2
662                           WHERE prefix_key = $1
663                           RETURNING * $q$
664                         USING new_entry.prefix_key, GREATEST(0, new_entry.count + conflict_entry.count);
665                 ELSE -- it was a prefix key or delete-emptied word before
666                     IF conflict_entry.suggestions @> new_entry.suggestions THEN -- already have all suggestions here...
667                         RETURN QUERY EXECUTE $q$
668                             UPDATE  search.symspell_dictionary
669                                SET  $q$ || source_class || $q$_count = $2
670                               WHERE prefix_key = $1
671                               RETURNING * $q$
672                             USING new_entry.prefix_key, GREATEST(0, new_entry.count);
673                     ELSE -- new suggestion!
674                         RETURN QUERY EXECUTE $q$
675                             UPDATE  search.symspell_dictionary
676                                SET  $q$ || source_class || $q$_count = $2,
677                                     $q$ || source_class || $q$_suggestions = $3
678                               WHERE prefix_key = $1
679                               RETURNING * $q$
680                             USING new_entry.prefix_key, GREATEST(0, new_entry.count), evergreen.text_array_merge_unique(conflict_entry.suggestions,new_entry.suggestions);
681                     END IF;
682                 END IF;
683             ELSE
684                 -- We keep the on-conflict clause just in case...
685                 RETURN QUERY EXECUTE $q$
686                     INSERT INTO search.symspell_dictionary AS d (
687                         $q$ || source_class || $q$_count,
688                         prefix_key,
689                         $q$ || source_class || $q$_suggestions
690                     ) VALUES ( $1, $2, $3 ) ON CONFLICT (prefix_key) DO
691                         UPDATE SET  $q$ || source_class || $q$_count = d.$q$ || source_class || $q$_count + EXCLUDED.$q$ || source_class || $q$_count,
692                                     $q$ || source_class || $q$_suggestions = evergreen.text_array_merge_unique(d.$q$ || source_class || $q$_suggestions, EXCLUDED.$q$ || source_class || $q$_suggestions)
693                         RETURNING * $q$
694                     USING new_entry.count, new_entry.prefix_key, new_entry.suggestions;
695             END IF;
696         ELSE -- key only, or no change
697             IF conflict_entry.prefix_key IS NOT NULL THEN -- we'll be updating
698                 IF NOT conflict_entry.suggestions @> new_entry.suggestions THEN -- There are new suggestions
699                     RETURN QUERY EXECUTE $q$
700                         UPDATE  search.symspell_dictionary
701                            SET  $q$ || source_class || $q$_suggestions = $2
702                           WHERE prefix_key = $1
703                           RETURNING * $q$
704                         USING new_entry.prefix_key, evergreen.text_array_merge_unique(conflict_entry.suggestions,new_entry.suggestions);
705                 END IF;
706             ELSE
707                 RETURN QUERY EXECUTE $q$
708                     INSERT INTO search.symspell_dictionary AS d (
709                         $q$ || source_class || $q$_count,
710                         prefix_key,
711                         $q$ || source_class || $q$_suggestions
712                     ) VALUES ( $1, $2, $3 ) ON CONFLICT (prefix_key) DO -- key exists, suggestions may be added due to this entry
713                         UPDATE SET  $q$ || source_class || $q$_suggestions = evergreen.text_array_merge_unique(d.$q$ || source_class || $q$_suggestions, EXCLUDED.$q$ || source_class || $q$_suggestions)
714                     RETURNING * $q$
715                     USING new_entry.count, new_entry.prefix_key, new_entry.suggestions;
716             END IF;
717         END IF;
718     END LOOP;
719 END;
720 $F$ LANGUAGE PLPGSQL;
721
722 CREATE OR REPLACE FUNCTION search.symspell_maintain_entries () RETURNS TRIGGER AS $f$
723 DECLARE
724     search_class    TEXT;
725     new_value       TEXT := NULL;
726     old_value       TEXT := NULL;
727 BEGIN
728     search_class := COALESCE(TG_ARGV[0], SPLIT_PART(TG_TABLE_NAME,'_',1));
729
730     IF TG_OP IN ('INSERT', 'UPDATE') THEN
731         new_value := NEW.value;
732     END IF;
733
734     IF TG_OP IN ('DELETE', 'UPDATE') THEN
735         old_value := OLD.value;
736     END IF;
737
738     PERFORM * FROM search.symspell_build_and_merge_entries(new_value, search_class, old_value);
739
740     RETURN NULL; -- always fired AFTER
741 END;
742 $f$ LANGUAGE PLPGSQL;
743
744 CREATE TRIGGER maintain_symspell_entries_tgr
745     AFTER INSERT OR UPDATE OR DELETE ON metabib.title_field_entry
746     FOR EACH ROW EXECUTE PROCEDURE search.symspell_maintain_entries();
747
748 CREATE TRIGGER maintain_symspell_entries_tgr
749     AFTER INSERT OR UPDATE OR DELETE ON metabib.author_field_entry
750     FOR EACH ROW EXECUTE PROCEDURE search.symspell_maintain_entries();
751
752 CREATE TRIGGER maintain_symspell_entries_tgr
753     AFTER INSERT OR UPDATE OR DELETE ON metabib.subject_field_entry
754     FOR EACH ROW EXECUTE PROCEDURE search.symspell_maintain_entries();
755
756 CREATE TRIGGER maintain_symspell_entries_tgr
757     AFTER INSERT OR UPDATE OR DELETE ON metabib.series_field_entry
758     FOR EACH ROW EXECUTE PROCEDURE search.symspell_maintain_entries();
759
760 CREATE TRIGGER maintain_symspell_entries_tgr
761     AFTER INSERT OR UPDATE OR DELETE ON metabib.keyword_field_entry
762     FOR EACH ROW EXECUTE PROCEDURE search.symspell_maintain_entries();
763
764 CREATE TRIGGER maintain_symspell_entries_tgr
765     AFTER INSERT OR UPDATE OR DELETE ON metabib.identifier_field_entry
766     FOR EACH ROW EXECUTE PROCEDURE search.symspell_maintain_entries();
767
768 COMMIT;
769
770 /* This will generate the queries needed to generate the /file/ that can
771  * be used to populate the dictionary table.
772
773 select $z$select $y$select $y$||x.id||$y$, '$z$||x.x||$z$', count(*) from search.symspell_build_and_merge_entries($x$$y$ || x.value||$y$$x$, '$z$||x||$z$');$y$ from metabib.$z$||x||$z$_field_entry x;$z$ from (select 'keyword'::text x union select 'title' union select 'author' union select 'subject' union select 'series' union select 'identifier') x;
774
775 */
776
777 \qecho ''
778 \qecho 'The following should be run at the end of the upgrade before any'
779 \qecho 'reingest occurs.  Because new triggers are installed already,'
780 \qecho 'updates to indexed strings will cause zero-count dictionary entries'
781 \qecho 'to be recorded which will require updating every row again (or'
782 \qecho 'starting from scratch) so best to do this before other batch'
783 \qecho 'changes.  A later reingest that does not significantly change'
784 \qecho 'indexed strings will /not/ cause table bloat here, and will be'
785 \qecho 'as fast as normal.  A copy of the SQL in a ready-to-use, non-escaped'
786 \qecho 'form is available inside a comment at the end of this upgrade sub-'
787 \qecho 'script so you do not need to copy this comment from the psql ouptut.'
788 \qecho ''
789 \qecho '\\a'
790 \qecho '\\t'
791 \qecho ''
792 \qecho '\\o title'
793 \qecho 'select value from metabib.title_field_entry;'
794 \qecho '\\o author'
795 \qecho 'select value from metabib.author_field_entry;'
796 \qecho '\\o subject'
797 \qecho 'select value from metabib.subject_field_entry;'
798 \qecho '\\o series'
799 \qecho 'select value from metabib.series_field_entry;'
800 \qecho '\\o identifier'
801 \qecho 'select value from metabib.identifier_field_entry;'
802 \qecho '\\o keyword'
803 \qecho 'select value from metabib.keyword_field_entry;'
804 \qecho ''
805 \qecho '\\o'
806 \qecho '\\a'
807 \qecho '\\t'
808 \qecho ''
809 \qecho '// Then, at the command line:'
810 \qecho ''
811 \qecho '$ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl title > title.sql'
812 \qecho '$ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl author > author.sql'
813 \qecho '$ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl subject > subject.sql'
814 \qecho '$ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl series > series.sql'
815 \qecho '$ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl identifier > identifier.sql'
816 \qecho '$ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl keyword > keyword.sql'
817 \qecho ''
818 \qecho '// And, back in psql'
819 \qecho ''
820 \qecho 'ALTER TABLE search.symspell_dictionary SET UNLOGGED;'
821 \qecho 'TRUNCATE search.symspell_dictionary;'
822 \qecho ''
823 \qecho '\\i identifier.sql'
824 \qecho '\\i author.sql'
825 \qecho '\\i title.sql'
826 \qecho '\\i subject.sql'
827 \qecho '\\i series.sql'
828 \qecho '\\i keyword.sql'
829 \qecho ''
830 \qecho 'CLUSTER search.symspell_dictionary USING symspell_dictionary_pkey;'
831 \qecho 'REINDEX TABLE search.symspell_dictionary;'
832 \qecho 'ALTER TABLE search.symspell_dictionary SET LOGGED;'
833 \qecho 'VACUUM ANALYZE search.symspell_dictionary;'
834 \qecho ''
835 \qecho 'DROP TABLE search.symspell_dictionary_partial_title;'
836 \qecho 'DROP TABLE search.symspell_dictionary_partial_author;'
837 \qecho 'DROP TABLE search.symspell_dictionary_partial_subject;'
838 \qecho 'DROP TABLE search.symspell_dictionary_partial_series;'
839 \qecho 'DROP TABLE search.symspell_dictionary_partial_identifier;'
840 \qecho 'DROP TABLE search.symspell_dictionary_partial_keyword;'
841
842 /* To run by hand:
843
844 \a
845 \t
846
847 \o title
848 select value from metabib.title_field_entry;
849
850 \o author
851 select value from metabib.author_field_entry;
852
853 \o subject
854 select value from metabib.subject_field_entry;
855
856 \o series
857 select value from metabib.series_field_entry;
858
859 \o identifier
860 select value from metabib.identifier_field_entry;
861
862 \o keyword
863 select value from metabib.keyword_field_entry;
864
865 \o
866 \a
867 \t
868
869 // Then, at the command line:
870
871 $ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl title > title.sql
872 $ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl author > author.sql
873 $ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl subject > subject.sql
874 $ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl series > series.sql
875 $ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl identifier > identifier.sql
876 $ ~/EG-src-path/Open-ILS/src/support-scripts/symspell-sideload.pl keyword > keyword.sql
877
878 // To the extent your hardware allows, the above commands can be run in 
879 // in parallel, in different shells.  Each will use a full CPU, and RAM
880 // may be a limiting resource, so keep an eye on that with `top`.
881
882
883 // And, back in psql
884
885 ALTER TABLE search.symspell_dictionary SET UNLOGGED;
886 TRUNCATE search.symspell_dictionary;
887
888 \i identifier.sql
889 \i author.sql
890 \i title.sql
891 \i subject.sql
892 \i series.sql
893 \i keyword.sql
894
895 CLUSTER search.symspell_dictionary USING symspell_dictionary_pkey;
896 REINDEX TABLE search.symspell_dictionary;
897 ALTER TABLE search.symspell_dictionary SET LOGGED;
898 VACUUM ANALYZE search.symspell_dictionary;
899
900 DROP TABLE search.symspell_dictionary_partial_title;
901 DROP TABLE search.symspell_dictionary_partial_author;
902 DROP TABLE search.symspell_dictionary_partial_subject;
903 DROP TABLE search.symspell_dictionary_partial_series;
904 DROP TABLE search.symspell_dictionary_partial_identifier;
905 DROP TABLE search.symspell_dictionary_partial_keyword;
906
907 */
908