Exported predicates: @export

create_dictionary/5 : this predicate loads a dictionary from the disk and sets up the memory structures accordingly delete_dictionary/1 : this predicate deletes a dictionary from the memory delete_all_dictionaries/0 : delete all the recorded dictionaries from the memory get_nb_dictionaries/1 : get the number of dictionaries currently in the memory get_handles_dictionaries/1 : get a list containing all the exiting handles of allocated dictionaries get_handles_nb_references_dictionaries/2 : get two lists associating the exiting handles of allocated dictionaries to the count other object references create_parse_options/2 : this predicate creates a parse options structure delete_parse_options/1 : this predicate deletes a parse options from the memory delete_all_parse_options/0 : delete all the recorded parse options from the memory set_parse_options/2 : set the options for a preexisting parse options structure get_parse_options/2 : get the options for a preexisting parse options structure get_nb_parse_options/2 : get the number of parse options currently in the memory get_handles_parse_options/1 : get a list containing all the exiting handles of allocated parse option objects get_handles_nb_references_parse_options/2 : get two lists associating the exiting handles of allocated parse options to the count other object references create_linkage_set/3 : this predicate creates a linkage set, gathering a sentence with its parse options delete_linkage_set/1 : this predicate deletes a linkage set from the memory delete_all_linkage_sets/0 : delete all the recorded linkage sets from the memory get_nb_linkage_sets/1 : get the number of linkage sets currently in the memory get_handles_linkage_sets/1 : get a list containing all the existing handles of allocated linkage set objects get_handles_nb_references_linkage_sets/2 : get two lists associating the exiting handles of allocated linkage sets to the count other object references get_num_linkages/2 : get the number of linkages available from a linkage set object get_parameters_for_linkage_set/2 : return a list containing all the handles and values associated to a linkage set object get_full_info_linkage_sets/1 : give the complete list of parameters for all the existing linkage sets create_sentence/3 : this predicate creates a sentence and tokenises it accordingly to a dictionary delete_sentence/1 : this predicate deletes a sentence object from the memory delete_all_sentences/0 : delete all the recorded sentences from the memory get_nb_sentences/1 : get the number of sentence objects currently in the memory get_handles_sentences/1 : get a list containing all the existing handles of allocated sentence objects get_handles_nb_references_sentences/2 : get two lists associating the exiting handles of allocated sentences to the count other object references get_max_sentence/1 : this predicate retrieves the value of MAX_SENTENCE inside the DLL enable_panic_on_parse_options/1 : this predicate activates panic mode on a parse options structure disable_panic_on_parse_options/1 : this predicate deactivates panic mode on a parse options structure get_linkage/2 : this is the foreign predicate making the link with the Link Grammar Parser's API **/

   42:- module(lgp,
   43	  [
   44	   create_dictionary/5,
   45	   delete_dictionary/1,
   46	   delete_all_dictionaries/0,
   47	   get_nb_dictionaries/1,
   48           get_handles_dictionaries/1,
   49	   get_handles_nb_references_dictionaries/2,
   50	   create_parse_options/2,
   51	   delete_parse_options/1,
   52	   delete_all_parse_options/0,
   53	   set_parse_options/2,
   54	   get_parse_options/2,
   55	   get_nb_parse_options/1,
   56           get_handles_parse_options/1,
   57           get_handles_nb_references_parse_options/2,
   58	   create_linkage_set/3,
   59	   delete_linkage_set/1,
   60	   delete_all_linkage_sets/0,
   61	   get_nb_linkage_sets/1,
   62           get_handles_linkage_sets/1,
   63	   get_handles_nb_references_linkage_sets/2,
   64	   get_num_linkages/2,
   65           get_parameters_for_linkage_set/2,
   66           get_full_info_linkage_sets/1,
   67	   create_sentence/3,
   68	   delete_sentence/1,
   69	   delete_all_sentences/0,
   70	   get_nb_sentences/1,
   71           get_handles_sentences/1,
   72	   get_handles_nb_references_sentences/2,
   73	   get_max_sentence/1,
   74	   enable_panic_on_parse_options/1,
   75	   disable_panic_on_parse_options/1,
   76	   get_linkage/2
   77	  ]).
   78
   79:- use_module(library(shlib)).
   80
   81:- initialization
   82   load_foreign_library(foreign(lgp), install_lgp).
@usage get_handles_dictionaries(Handles_list).

@description This predicate returns a list of all the currently valid dictionary handles **/

   95get_handles_dictionaries(Handles_list):-
   96	get_handles_nb_references_dictionaries(Handles_list, _).
@usage create_parse_options(Option_list, Parse_options_handle).

@description This predicate creates a new parse options object (using the Option_list or the default value if a property is not specified) and unifies Parse_options_handle with a handle on this new object **/

  109create_parse_options(Option_list, Parse_options_handle):-
  110	create_parse_options_(Parse_options_handle),
  111	set_parse_options(Parse_options_handle, Option_list).
@usage set_parse_options(Parse_options_handle, Option_list).

@description This predciate sets the options in the Parse_options_handle object, accordingly to the Option_list **/

  124set_parse_options(Parse_options_handle, Option_list):-
  125	(   memberchk(linkage_limit=Linkage_limit, Option_list),
  126	    nonvar(Linkage_limit),
  127	    integer(Linkage_limit)
  128	->  po_set_linkage_limit_(Parse_options_handle, Linkage_limit)
  129	;   true
  130	),
  131	(   memberchk(disjunct_cost=Disjunct_cost, Option_list),
  132	    nonvar(Disjunct_cost),
  133	    integer(Disjunct_cost)
  134	->  po_set_disjunct_cost_(Parse_options_handle, Disjunct_cost)
  135	;   true
  136	),
  137	(   memberchk(min_null_count=Min_null_count, Option_list),
  138	    nonvar(Min_null_count),
  139	    integer(Min_null_count)
  140	->  po_set_min_null_count_(Parse_options_handle, Min_null_count)
  141	;   true
  142	),
  143	(   memberchk(max_null_count=Max_null_count, Option_list),
  144	    nonvar(Max_null_count),
  145	    integer(Max_null_count)
  146	->  po_set_max_null_count_(Parse_options_handle, Max_null_count)
  147	;   true
  148	),
  149	(   memberchk(null_block=Null_block, Option_list),
  150	    nonvar(Null_block),
  151	    integer(Null_block)
  152	->  po_set_null_block_(Parse_options_handle, Null_block)
  153	;   true
  154	),
  155	(   memberchk(islands_ok=Islands_ok, Option_list),
  156	    nonvar(Islands_ok)
  157	->  (   Islands_ok=true
  158	    ->	po_set_islands_ok_(Parse_options_handle, true)
  159	    ;	po_set_islands_ok_(Parse_options_handle, false)
  160	    )
  161	;   true
  162	),
  163	(   memberchk(short_length=Short_length, Option_list),
  164	    nonvar(Short_length),
  165	    integer(Short_length)
  166	->  po_set_short_length_(Parse_options_handle, Short_length)
  167	;   true
  168	),
  169	(   memberchk(all_short_connectors=All_short_connectors, Option_list),
  170	    nonvar(All_short_connectors)
  171	->  (   All_short_connectors=true
  172	    ->	po_set_all_short_connectors_(Parse_options_handle, true)
  173	    ;	po_set_all_short_connectors_(Parse_options_handle, false)
  174	    )
  175	;   true
  176	),
  177	(   memberchk(max_parse_time=Max_parse_time, Option_list),
  178	    nonvar(Max_parse_time),
  179	    integer(Max_parse_time)
  180	->  po_set_max_parse_time_(Parse_options_handle, Max_parse_time)
  181	;   true
  182	),
  183	(   memberchk(max_memory=Max_memory, Option_list),
  184	    nonvar(Max_memory),
  185	    integer(Max_memory)
  186	->  po_set_max_memory_(Parse_options_handle, Max_memory)
  187	;   true
  188	),
  189	(   memberchk(max_sentence_length=Max_sentence_length, Option_list),
  190	    nonvar(Max_sentence_length),
  191	    integer(Max_sentence_length)
  192	->  po_set_max_sentence_length_(Parse_options_handle, Max_sentence_length)
  193	;   true
  194	),
  195	(   memberchk(batch_mode=Batch_mode, Option_list),
  196	    nonvar(Batch_mode)
  197	->  (   Batch_mode=true
  198	    ->	po_set_batch_mode_(Parse_options_handle, true)
  199	    ;	po_set_batch_mode_(Parse_options_handle, false)
  200	    )
  201	;   true
  202	),
  203	(   memberchk(panic_mode=Panic_mode, Option_list),
  204	    nonvar(Panic_mode)
  205	->  (   Panic_mode=true
  206	    ->	po_set_panic_mode_(Parse_options_handle, true)
  207	    ;	po_set_panic_mode_(Parse_options_handle, false)
  208	    )
  209	;   true
  210	),
  211	(   memberchk(allow_null=Allow_null, Option_list),
  212	    nonvar(Allow_null)
  213	->  (   Allow_null=true
  214	    ->	po_set_allow_null_(Parse_options_handle, true)
  215	    ;	po_set_allow_null_(Parse_options_handle, false)
  216	    )
  217	;   true
  218	).
@usage set_parse_options(Parse_options_handle, Option_list).

@description This predciate gets the options in the Parse_options_handle object and unifies them with Option_list **/

  231get_parse_options(Parse_options_handle, Option_list):-
  232	!,
  233	(   po_get_linkage_limit_(Parse_options_handle, Linkage_limit)
  234	->  Linkage_limit_property=(linkage_limit=Linkage_limit)
  235	;   Linkage_limit_property=pl_skip_element
  236	),
  237	(   po_get_disjunct_cost_(Parse_options_handle, Disjunct_cost)
  238	->  Disjunct_cost_property=(disjunct_cost=Disjunct_cost)
  239	;   Disjunct_cost_property=pl_skip_element
  240	),
  241	(   po_get_min_null_count_(Parse_options_handle, Min_null_count)
  242	->  Min_null_count_property=(min_null_count=Min_null_count)
  243	;   Min_null_count_property=pl_skip_element
  244	),
  245	(   po_get_max_null_count_(Parse_options_handle, Max_null_count)
  246	->  Max_null_count_property=(max_null_count=Max_null_count)
  247	;   Max_null_count_property=pl_skip_element
  248	),
  249	(   po_get_null_block_(Parse_options_handle, Null_block)
  250	->  Null_block_property=(null_block=Null_block)
  251	;   Null_block_property=pl_skip_element
  252	),
  253	(   po_get_islands_ok_(Parse_options_handle, Islands_ok)
  254	->  Islands_ok_property=(islands_ok=Islands_ok)
  255	;   Islands_ok_property=pl_skip_element
  256	),
  257	(   po_get_short_length_(Parse_options_handle, Short_length)
  258	->  Short_length_property=(short_length=Short_length)
  259	;   Short_length_property=pl_skip_element
  260	),
  261	(   po_get_all_short_connectors_(Parse_options_handle, All_short_connectors)
  262	->  All_short_connectors_property=(all_short_connectors=All_short_connectors)
  263	;   All_short_connectors_property=pl_skip_element
  264	),
  265	(   po_get_max_parse_time_(Parse_options_handle, Max_parse_time)
  266	->  Max_parse_time_property=(max_parse_time=Max_parse_time)
  267	;   Max_parse_time_property=pl_skip_element
  268	),
  269	(   po_get_max_memory_(Parse_options_handle, Max_memory)
  270	->  Max_memory_property=(max_memory=Max_memory)
  271	;   Max_memory_property=pl_skip_element
  272	),
  273	(   po_get_max_sentence_length_(Parse_options_handle, Max_sentence_length)
  274	->  Max_sentence_length_property=(max_sentence_length=Max_sentence_length)
  275	;   Max_sentence_length_property=pl_skip_element
  276	),
  277	(   po_get_batch_mode_(Parse_options_handle, Batch_mode)
  278	->  Batch_mode_property=(batch_mode=Batch_mode)	
  279	;   Batch_mode_property=pl_skip_element
  280	),
  281	(   po_get_panic_mode_(Parse_options_handle, Panic_mode)
  282	->  Panic_mode_property=(panic_mode=Panic_mode)
  283	;   Panic_mode_property=pl_skip_element
  284	),
  285	(   po_get_allow_null_(Parse_options_handle, Allow_null)
  286	->  Allow_null_property=(allow_null=Allow_null)
  287	;   Allow_null_property=pl_skip_element
  288	),
  289	Option_list_tmp=[Linkage_limit_property, Disjunct_cost_property, Min_null_count_property,
  290			 Max_null_count_property, Null_block_property, Islands_ok_property,
  291			 Short_length_property, All_short_connectors_property, Max_parse_time_property,
  292			 Max_memory_property, Max_sentence_length_property, Batch_mode_property,
  293			 Panic_mode_property, Allow_null_property],
  294	tools:clean_nested_list(Option_list_tmp, Option_list).
@usage get_handles_parse_options(Handles_list).

@description This predicate returns a list of all the currently valid parse options handles **/

  307get_handles_parse_options(Handles_list):-
  308	get_handles_nb_references_parse_options(Handles_list, _).
@usage get_full_info_linkage_sets(Information_list).

@description This predicate will return in Information_list, a list containing the details of all existing linkage set objects **/

  321get_full_info_linkage_sets(Information_list):-
  322	get_handles_linkage_sets(Handle_list),
  323	get_full_info_linkage_sets_(Handle_list, Information_list).
  324get_full_info_linkage_sets_([Head_handle|Tail_Handle_list], [Head_information|Tail_information_list]):-
  325	get_parameters_for_linkage_set(Head_handle, Information_for_handle),
  326	Head_information=[handle=Head_handle|Information_for_handle],
  327	get_full_info_linkage_sets_(Tail_Handle_list, Tail_information_list).
  328get_full_info_linkage_sets_([], []).
@usage get_handles_linkage_sets(Handles_list).

@description This predicate returns a list of all the currently valid linkage sets handles **/

  341get_handles_linkage_sets(Handles_list):-
  342	get_handles_nb_references_linkage_sets(Handles_list, _).
@usage get_handles_sentences(Handles_list).

@description This predicate returns a list of all the currently valid sentence handles **/

  355get_handles_sentences(Handles_list):-
  356	get_handles_nb_references_sentences(Handles_list, _)