File: test.pl

package info (click to toggle)
swi-prolog 9.0.4%2Bdfsg-2
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 82,408 kB
  • sloc: ansic: 387,503; perl: 359,326; cpp: 6,613; lisp: 6,247; java: 5,540; sh: 3,147; javascript: 2,668; python: 1,900; ruby: 1,594; yacc: 845; makefile: 428; xml: 317; sed: 12; sql: 6
file content (149 lines) | stat: -rw-r--r-- 3,464 bytes parent folder | download | duplicates (4)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
:-module(term_table,
         [ bug/1,
           term/3,
           ci_term/4,
           plural/2,
           singular/2,
           find_term1/4,
           find_term/3,
           find_term_from_substring/3
         ]).

bug(R) :-
    compare_strings(aat_new, 'noot\u00e8one', 'noot\u00e8two', R).



:-dynamic stored_defs_handle/1.

user:file_search_path(foreign, Lib) :-
    feature(arch, Arch),
    concat('lib/', Arch, Lib).

:-use_module(library(table)).


:- initialization
    new_order_table(aat_new,
                    [ case_insensitive,
                      tag("("),
                      ignore("'`<>"),
                      break(" ,-:"),
                      32=95,        %map underscore to space
%                         45=95,
                      232=101,
                      233=101,
                      136=101       % OEM \^e --> e
                    ]).


find_database_file(DB,Type,File):-
    Path =.. [DB,'.'],
    absolute_file_name(Path,
                       [ file_type(directory),
                         access(read)
                       ],
                       AAT),
    ensure_slash(AAT, AATDir),
    atomic_list_concat([AATDir,DB,'_',Type, '.dat'], File).

ensure_slash(Name, Dir) :-
    concat(_, /, Name),
    !,
    Dir = Name.
ensure_slash(Name, Dir) :-
    concat(Name, /, Dir).


defs_table(Words):-
    stored_defs_handle(Words),
    !.
defs_table(Words):-
    %       find_database_file(aat,term,File),
    File = 'test.dat',
            new_table(File,
                      [  word(atom,[sorted(aat_new)]),
                         category(atom,[width(1)]),
                         index(integer,[width(8)])],
                      [ field_separator(0'!)],
                      Words),
            asserta(stored_defs_handle(Words)).


term(Word,Index,Category):-
    defs_table(DHandle),
    in_table(DHandle,
             [word(Word),
              category(Category),
              index(Index)],
              _RPos).


ci_term(Word,Term,Index,Category):-
    defs_table(DHandle),
    in_table(DHandle,
             [word(Word,=(aat_new)),
              category(Category),
              index(Index)],
              RPos),
    read_table_record(DHandle,RPos,_Next,
                      record(Term,_,_)).



find_term(Search_String,Term,Index):-
    defs_table(DHandle),
    in_table(DHandle,
             [word(Search_String,prefix(aat_new)),
                 index(Index)],
              _RPos),
    ident(Index,Term).

find_term_from_substring(Search_String,Term,Index):-
    defs_table(DHandle),
    in_table(DHandle,
             [word(Search_String,substring(aat_new)),
                 index(Index)],
              _RPos),
    ident(Index,Term).


find_term1(Search_String,Term,Index,Category):-
    defs_table(DHandle),
    in_table(DHandle,
             [word(Search_String,prefix(aat_new)),
              category(Category),
                 index(Index)],
              RPos),
%       ident(Index,Term),
    read_table_record(DHandle,RPos,_Next,
                      record(Term,_,_)).


plural(X,Y):-
    term(X,I,a),
    idterm(I,Y,m),
    !.

plural(X,Y):-
    term(X,I,q),
    find_term1(X,T1,I,a),
    idterm(I,Y,q),
    X \=Y,
    find_term1(Y,T2,I,m),
    T1 \= T2,
    !.

singular(X,Y):-
    term(X,I,m),
    idterm(I,Y,a),
    !.

singular(X,Y):-
    term(X,I,q),
    find_term1(X,T1,I,m),
    idterm(I,Y,q),
    X \=Y,
    find_term1(Y,T2,I,a),
    T1 \= T2,
    !.