1 /****************************************************************/
2 /* OCaml Linkgrammar module                                     */
3 /*                                                              */
4 /* Interfacing OCaml API to LinkGrammar C API                   */
5 /*                                                              */
6 /* Author: Ramu Ramamurthy ramu_ramamurthy at yahoo dot com     */
7 /* (C) 2006                                                     */
8 /*                                                              */
9 /* This is released under the BSD license                       */
10 /****************************************************************/
11 /*
12 #include <stdio.h>
13 /********************************************/
14 /* Caml Includes                            */
15 /********************************************/
16 #include <caml/mlvalues.h>
17 #include <caml/memory.h>
18 #include <caml/alloc.h>
19 #include <caml/custom.h>
20 /********************************************/
21 /* Link Grammar Includes                    */
22 /********************************************/
23 #include "link-grammar/link-includes.h"
24 
25 
26 #define Po_val(v) (*((Parse_Options *)Data_custom_val(v)))
27 #define Dict_val(v) (*((Dictionary *)Data_custom_val(v)))
28 #define Sent_val(v) (*((Sentence *)Data_custom_val(v)))
29 #define Linkage_val(v) (*((Linkage *)Data_custom_val(v)))
30 
31 #define CAML_GC_ALLOC_USED (1)
32 #define CAML_GC_ALLOC_MAX (10)
33 
34 static struct custom_operations custom_default_ops = {
35   "linkgrammar",
36   custom_finalize_default,
37   custom_compare_default,
38   custom_hash_default,
39   custom_serialize_default,
40   custom_deserialize_default
41 };
42 
43 
44 /* following are the caml interface funcs */
45 
46 /* start of operations on parse options */
po_create(value nothing)47 value po_create(value nothing) {
48   CAMLparam1(nothing);
49   CAMLlocal1(block);
50   block = alloc_custom(&custom_default_ops, sizeof(Parse_Options),
51 		       CAML_GC_ALLOC_USED, CAML_GC_ALLOC_MAX);
52   Po_val(block) = parse_options_create();
53   CAMLreturn(block);
54 }
55 
free_po(value l)56 value free_po(value l) {
57   Parse_Options po = Po_val(l);
58   /*printf("**************free po\n");fflush(stdout);*/
59   parse_options_delete(po);
60   return Val_unit;
61 }
62 
po_get_verbosity(value po)63 value po_get_verbosity(value po) {
64   CAMLparam1(po);
65   Parse_Options opts = Po_val(po);
66   int val = parse_options_get_verbosity(opts);
67   return Val_long(val);
68 }
69 
po_set_verbosity(value po,value lim)70 value po_set_verbosity(value po, value lim) {
71   CAMLparam2(po,lim);
72   Parse_Options opts = Po_val(po);
73   parse_options_set_verbosity(opts, Long_val(lim));
74   CAMLreturn(Val_unit);
75 }
76 
77 
po_get_linkage_limit(value po)78 value po_get_linkage_limit(value po) {
79   CAMLparam1(po);
80   Parse_Options opts = Po_val(po);
81   int val = parse_options_get_linkage_limit(opts);
82   return Val_long(val);
83 }
84 
po_set_linkage_limit(value po,value lim)85 value po_set_linkage_limit(value po, value lim) {
86   CAMLparam2(po,lim);
87   Parse_Options opts = Po_val(po);
88   parse_options_set_linkage_limit(opts, Long_val(lim));
89   CAMLreturn(Val_unit);
90 }
91 
po_get_disjunct_cost(value po)92 value po_get_disjunct_cost(value po) {
93   CAMLparam1(po);
94   Parse_Options opts = Po_val(po);
95   int val = parse_options_get_disjunct_cost(opts);
96   return Val_long(val);
97 }
98 
po_set_disjunct_cost(value po,value cost)99 value po_set_disjunct_cost(value po, value cost) {
100   CAMLparam2(po,cost);
101   Parse_Options opts = Po_val(po);
102   parse_options_set_disjunct_cost(opts, Long_val(cost));
103   CAMLreturn(Val_unit);
104 }
105 
po_get_min_null_count(value po)106 value po_get_min_null_count(value po) {
107   CAMLparam1(po);
108   Parse_Options opts = Po_val(po);
109   int val = parse_options_get_min_null_count(opts);
110   CAMLreturn(Val_long(val));
111 }
112 
po_set_min_null_count(value po,value count)113 value po_set_min_null_count(value po, value count) {
114   CAMLparam2(po,count);
115   Parse_Options opts = Po_val(po);
116   parse_options_set_min_null_count(opts, Long_val(count));
117   CAMLreturn(Val_unit);
118 }
119 
po_get_max_null_count(value po)120 value po_get_max_null_count(value po) {
121   CAMLparam1(po);
122   Parse_Options opts = Po_val(po);
123   int val = parse_options_get_max_null_count(opts);
124   CAMLreturn(Val_long(val));
125 }
126 
po_set_max_null_count(value po,value count)127 value po_set_max_null_count(value po, value count) {
128   CAMLparam2(po,count);
129   Parse_Options opts = Po_val(po);
130   parse_options_set_max_null_count(opts, Long_val(count));
131   CAMLreturn(Val_unit);
132 }
133 
po_get_null_block(value po)134 value po_get_null_block(value po) {
135   CAMLparam1(po);
136   Parse_Options opts = Po_val(po);
137   int val = parse_options_get_null_block(opts);
138   CAMLreturn(Val_long(val));
139 }
140 
po_set_null_block(value po,value count)141 value po_set_null_block(value po, value count) {
142   CAMLparam2(po,count);
143   Parse_Options opts = Po_val(po);
144   parse_options_set_null_block(opts, Long_val(count));
145   CAMLreturn(Val_unit);
146 }
147 
po_get_short_length(value po)148 value po_get_short_length(value po) {
149   CAMLparam1(po);
150   Parse_Options opts = Po_val(po);
151   int val = parse_options_get_short_length(opts);
152   CAMLreturn(Val_long(val));
153 }
154 
po_set_short_length(value po,value count)155 value po_set_short_length(value po, value count) {
156   CAMLparam2(po,count);
157   Parse_Options opts = Po_val(po);
158   parse_options_set_short_length(opts, Long_val(count));
159   CAMLreturn(Val_unit);
160 }
161 
po_get_islands_ok(value po)162 value po_get_islands_ok(value po) {
163   CAMLparam1(po);
164   Parse_Options opts = Po_val(po);
165   int val = parse_options_get_islands_ok(opts);
166   CAMLreturn(Val_long(val));
167 }
168 
po_set_islands_ok(value po,value count)169 value po_set_islands_ok(value po, value count) {
170   CAMLparam2(po,count);
171   Parse_Options opts = Po_val(po);
172   parse_options_set_islands_ok(opts, Long_val(count));
173   CAMLreturn(Val_unit);
174 }
175 
po_get_max_parse_time(value po)176 value po_get_max_parse_time(value po) {
177   CAMLparam1(po);
178   Parse_Options opts = Po_val(po);
179   int val = parse_options_get_max_parse_time(opts);
180   CAMLreturn(Val_long(val));
181 }
182 
po_set_max_parse_time(value po,value count)183 value po_set_max_parse_time(value po, value count) {
184   CAMLparam2(po,count);
185   Parse_Options opts = Po_val(po);
186   parse_options_set_max_parse_time(opts, Long_val(count));
187   CAMLreturn(Val_unit);
188 }
189 
po_get_timer_expired(value po)190 value po_get_timer_expired(value po) {
191   CAMLparam1(po);
192   Parse_Options opts = Po_val(po);
193   int val = parse_options_timer_expired(opts);
194   CAMLreturn(Val_long(val));
195 }
196 
po_reset_resources(value po)197 value po_reset_resources(value po) {
198   CAMLparam1(po);
199   Parse_Options opts = Po_val(po);
200   parse_options_reset_resources(opts);
201   CAMLreturn(Val_unit);
202 }
203 
204 
po_get_allow_null(value po)205 value po_get_allow_null(value po) {
206   CAMLparam1(po);
207   Parse_Options opts = Po_val(po);
208   int val = parse_options_get_allow_null(opts);
209   CAMLreturn(Val_long(val));
210 }
211 
po_set_allow_null(value po,value count)212 value po_set_allow_null(value po, value count) {
213   CAMLparam2(po,count);
214   Parse_Options opts = Po_val(po);
215   parse_options_set_allow_null(opts, Long_val(count));
216   CAMLreturn(Val_unit);
217 }
218 
po_get_all_short_connectors(value po)219 value po_get_all_short_connectors(value po) {
220   CAMLparam1(po);
221   Parse_Options opts = Po_val(po);
222   int val = parse_options_get_all_short_connectors(opts);
223   CAMLreturn(Val_long(val));
224 }
225 
po_set_all_short_connectors(value po,value count)226 value po_set_all_short_connectors(value po, value count) {
227   CAMLparam2(po,count);
228   Parse_Options opts = Po_val(po);
229   parse_options_set_all_short_connectors(opts, Long_val(count));
230   CAMLreturn(Val_unit);
231 }
232 /* end of operations on parse_options */
233 
234 /* start of operations on dictionary */
dict_create(value lang)235 value dict_create(value lang) {
236   CAMLparam1(lang);
237   CAMLlocal1(block);
238   char *lang_str = String_val(lang);
239 
240   Dictionary dict = dictionary_create_lang(lang_str);
241 
242   if (!dict) {
243     printf("Cant open Dictionary!\n"); fflush(stdout);
244     raise_not_found();
245   }
246 
247   block = alloc_custom(&custom_default_ops, sizeof(Dictionary),
248 		       CAML_GC_ALLOC_USED, CAML_GC_ALLOC_MAX);
249   Dict_val(block) = dict;
250 
251   CAMLreturn(block);
252 }
253 
free_dict(value l)254 value free_dict(value l) {
255   Dictionary dict = Dict_val(l);
256   /*printf("*****************free dict %x\n",(unsigned int)dict);fflush(stdout);*/
257   dictionary_delete(dict);
258   return Val_unit;
259 }
260 
261 
262 /* end of operation on dictionary */
263 
264 
265 /* start of operations on sentences */
sent_create(value str,value dic)266 value sent_create(value str, value dic) {
267   CAMLparam2(str,dic);
268   CAMLlocal1(block);
269   char *sent_str = String_val(str);
270   Dictionary dict = Dict_val(dic);
271   Sentence sent = sentence_create(sent_str, dict);
272   if (!sent) {
273     /* throw an exception here */
274     /* possibly later throw a user defined exception */
275     printf("NOTTTT  FOUND\n");fflush(stdout);
276     raise_not_found();
277   } else {
278 
279     block = alloc_custom(&custom_default_ops, sizeof(Sentence),
280 			 CAML_GC_ALLOC_USED, CAML_GC_ALLOC_MAX);
281     Sent_val(block) = sent;
282     CAMLreturn(block);
283   }
284 }
285 
free_sentence(value l)286 value free_sentence(value l) {
287   Sentence sent = Sent_val(l);
288   /*printf("***************free sent %x\n",(unsigned int)sent);fflush(stdout);*/
289   sentence_delete(sent);
290   return Val_unit;
291 }
292 
293 
sent_parse(value sentence,value po)294 value sent_parse(value sentence, value po) {
295   CAMLparam2(sentence,po);
296   Sentence sent = Sent_val(sentence);
297   Parse_Options opts = Po_val(po);
298   int ret_val = sentence_parse(sent, opts);
299   /* printf("parse done\n");fflush(stdout); */
300   CAMLreturn(Val_long(ret_val));
301 }
302 
sent_length(value sentence)303 value sent_length(value sentence) {
304   CAMLparam1(sentence);
305   Sentence sent = Sent_val(sentence);
306   int val = sentence_length(sent);
307   CAMLreturn(Val_long(val));
308 }
309 
sent_get_word(value sentence,value ith)310 value sent_get_word(value sentence, value ith) {
311   CAMLparam2(sentence,ith);
312   Sentence sent = Sent_val(sentence);
313   char *str = sentence_get_word(sent, Long_val(ith));
314   value block = copy_string(str);
315   string_delete(str);
316   CAMLreturn(block);
317 }
318 
sent_null_count(value sentence)319 value sent_null_count(value sentence) {
320   CAMLparam1(sentence);
321   Sentence sent = Sent_val(sentence);
322   int val = sentence_null_count(sent);
323   CAMLreturn(Val_long(val));
324 }
325 
sent_num_linkages_found(value sentence)326 value sent_num_linkages_found(value sentence) {
327   CAMLparam1(sentence);
328   Sentence sent = Sent_val(sentence);
329   int val = sentence_num_linkages_found(sent);
330   CAMLreturn(Val_long(val));
331 }
332 
sent_num_valid_linkages(value sentence)333 value sent_num_valid_linkages(value sentence) {
334   CAMLparam1(sentence);
335   Sentence sent = Sent_val(sentence);
336   int val = sentence_num_valid_linkages(sent);
337   CAMLreturn(Val_long(val));
338 }
339 
sent_num_linkages_post_processed(value sentence)340 value sent_num_linkages_post_processed(value sentence) {
341   CAMLparam1(sentence);
342   Sentence sent = Sent_val(sentence);
343   int val = sentence_num_linkages_post_processed(sent);
344   CAMLreturn(Val_long(val));
345 }
346 
sent_num_violations(value sentence,value ith)347 value sent_num_violations(value sentence, value ith) {
348   CAMLparam2(sentence,ith);
349   Sentence sent = Sent_val(sentence);
350   int val = sentence_num_violations(sent, Long_val(ith));
351   CAMLreturn(Val_long(val));
352 }
353 
sent_disjunct_cost(value sentence,value ith)354 value sent_disjunct_cost(value sentence, value ith) {
355   CAMLparam2(sentence,ith);
356   Sentence sent = Sent_val(sentence);
357   int val = sentence_disjunct_cost(sent, Long_val(ith));
358   CAMLreturn(Val_long(val));
359 }
360 /* end of operation on sentences */
361 
362 
363 /* start of operations on linkages */
link_create(value s,value ith,value po)364 value link_create(value s, value ith, value po) {
365   CAMLparam3(s, ith, po);
366   CAMLlocal1(block);
367 
368   Sentence sent = Sent_val(s);
369   Parse_Options opts = Po_val(po);
370   Linkage link = linkage_create(Long_val(ith),sent,opts);
371   if (!link) {
372     /* throw an exception here */
373     /* possibly later throw a user defined exception */
374     raise_not_found();
375   } else {
376 
377     block = alloc_custom(&custom_default_ops, sizeof(Linkage),
378 			 CAML_GC_ALLOC_USED, CAML_GC_ALLOC_MAX);
379     Linkage_val(block) = link;
380     CAMLreturn(block);
381   }
382 }
383 
free_linkage(value l)384 value free_linkage(value l) {
385   Linkage link = Linkage_val(l);
386   /*printf("*************free linkage %x\n", (unsigned int)link);fflush(stdout);*/
387   linkage_delete(link);
388   return Val_unit;
389 }
390 
391 
link_get_num_words(value l)392 value link_get_num_words(value l) {
393   CAMLparam1(l);
394   Linkage link = Linkage_val(l);
395   int val = linkage_get_num_words(link);
396   CAMLreturn(Val_long(val));
397 }
398 
link_get_num_links(value l)399 value link_get_num_links(value l) {
400   CAMLparam1(l);
401   Linkage link = Linkage_val(l);
402   int val = linkage_get_num_links(link);
403   CAMLreturn(Val_long(val));
404 }
405 
link_get_link_length(value l,value index)406 value link_get_link_length(value l, value index) {
407   CAMLparam2(l,index);
408   Linkage link = Linkage_val(l);
409   int val = linkage_get_link_length(link,Long_val(index));
410   CAMLreturn(Val_long(val));
411 }
412 
link_get_link_lword(value l,value index)413 value link_get_link_lword(value l, value index) {
414   CAMLparam2(l,index);
415   Linkage link = Linkage_val(l);
416   int val = linkage_get_link_lword(link,Long_val(index));
417   CAMLreturn(Val_long(val));
418 }
419 
link_get_link_rword(value l,value index)420 value link_get_link_rword(value l, value index) {
421   CAMLparam2(l,index);
422   Linkage link = Linkage_val(l);
423   int val = linkage_get_link_rword(link,Long_val(index));
424   CAMLreturn(Val_long(val));
425 }
426 
link_print_diagram(value l)427 value link_print_diagram(value l) {
428   CAMLparam1(l);
429   CAMLlocal1(block);
430   Linkage link = Linkage_val(l);
431   char *str = linkage_print_diagram(link);
432   block = copy_string(str);
433   string_delete(str);
434   CAMLreturn(block);
435 }
436 
link_print_postscript(value l,value mode)437 value link_print_postscript(value l, value mode) {
438   CAMLparam2(l,mode);
439   CAMLlocal1(block);
440   Linkage link = Linkage_val(l);
441   char *str = linkage_print_postscript(link, Long_val(mode));
442   block = copy_string(str);
443   string_delete(str);
444   CAMLreturn(block);
445 }
446 
link_print_links_and_domains(value l)447 value link_print_links_and_domains(value l) {
448   CAMLparam1(l);
449   CAMLlocal1(block);
450   Linkage link = Linkage_val(l);
451   char *str = linkage_print_links_and_domains(link);
452   block = copy_string(str);
453   string_delete(str);
454   CAMLreturn(block);
455 }
456 
link_get_link_label(value l,value index)457 value link_get_link_label(value l, value index) {
458   CAMLparam2(l,index);
459   CAMLlocal1(block);
460   Linkage link = Linkage_val(l);
461   char *str = linkage_get_link_label(link, Long_val(index));
462   block = copy_string(str);
463   CAMLreturn(block);
464 }
465 
link_get_link_llabel(value l,value index)466 value link_get_link_llabel(value l, value index) {
467   CAMLparam2(l,index);
468   CAMLlocal1(block);
469   Linkage link = Linkage_val(l);
470   char *str = linkage_get_link_llabel(link, Long_val(index));
471   block = copy_string(str);
472   CAMLreturn(block);
473 }
474 
link_get_link_rlabel(value l,value index)475 value link_get_link_rlabel(value l, value index) {
476   CAMLparam2(l,index);
477   CAMLlocal1(block);
478   Linkage link = Linkage_val(l);
479   char *str = linkage_get_link_rlabel(link, Long_val(index));
480   block = copy_string(str);
481   CAMLreturn(block);
482 }
483 
link_get_link_num_domains(value l,value index)484 value link_get_link_num_domains(value l, value index) {
485   CAMLparam2(l,index);
486   Linkage link = Linkage_val(l);
487   int val = linkage_get_link_num_domains(link,Long_val(index));
488   CAMLreturn(Val_long(val));
489 }
490 
link_get_violation_name(value l)491 value link_get_violation_name(value l) {
492   CAMLparam1(l);
493   CAMLlocal1(block);
494   Linkage link = Linkage_val(l);
495   char *str = linkage_get_violation_name(link);
496   block = copy_string(str);
497   CAMLreturn(block);
498 }
499 
link_get_link_domain_name_i(value l,value index,value i)500 value link_get_link_domain_name_i(value l, value index, value i) {
501   CAMLparam3(l, index, i);
502   CAMLlocal1(block);
503   Linkage link = Linkage_val(l);
504   char **names = linkage_get_link_domain_names(link, Long_val(index));
505   char *str = names[Long_val(i)];
506   block = copy_string(str);
507   CAMLreturn(block);
508 }
509 
link_get_word(value l,value index)510 value link_get_word(value l, value index) {
511   CAMLparam2(l,index);
512   CAMLlocal1(block);
513   Linkage link = Linkage_val(l);
514   char *str = linkage_get_word(link, Long_val(index));
515   block = copy_string(str);
516   CAMLreturn(block);
517 }
518 
link_unused_word_cost(value l)519 value link_unused_word_cost(value l) {
520   CAMLparam1(l);
521   Linkage link = Linkage_val(l);
522   int val = linkage_unused_word_cost(link);
523   CAMLreturn(Val_long(val));
524 }
525 
link_disjunct_cost(value l)526 value link_disjunct_cost(value l) {
527   CAMLparam1(l);
528   Linkage link = Linkage_val(l);
529   int val = linkage_disjunct_cost(link);
530   CAMLreturn(Val_long(val));
531 }
532 
link_link_cost(value l)533 value link_link_cost(value l) {
534   CAMLparam1(l);
535   Linkage link = Linkage_val(l);
536   int val = linkage_link_cost(link);
537   CAMLreturn(Val_long(val));
538 }
539 /* end of operations on linkages */
540