1% This file is part of the Attempto Parsing Engine (APE).
    2% Copyright 2008-2013, Attempto Group, University of Zurich (see http://attempto.ifi.uzh.ch).
    3%
    4% The Attempto Parsing Engine (APE) is free software: you can redistribute it and/or modify it
    5% under the terms of the GNU Lesser General Public License as published by the Free Software
    6% Foundation, either version 3 of the License, or (at your option) any later version.
    7%
    8% The Attempto Parsing Engine (APE) is distributed in the hope that it will be useful, but WITHOUT
    9% ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR
   10% PURPOSE. See the GNU Lesser General Public License for more details.
   11%
   12% You should have received a copy of the GNU Lesser General Public License along with the Attempto
   13% Parsing Engine (APE). If not, see http://www.gnu.org/licenses/.
   14
   15
   16:- module(clex, [
   17		clex_switch/1,     % ?Switch
   18		set_clex_switch/1  % +Switch
   19	]).   20:- use_module(library(error)).

Common Lexicon Interface

This module contains the predicates for the management of the common lexicon that is compiled into the executable.

author
- Tobias Kuhn
version
- 2008-07-17 */
 clex_file(-ClexFile)
This predicate defines the clex-file that is loaded and compiled into the executable. In order to change this, you have to edit the source code and recompile.
   37clex_file(clex_lexicon).
   38%clex_file(clex_lexicon_small).
   39%clex_file('').
   40
   41
   42% The predicates for the lexicon entries are declared dynamic. In this way, they don't fail if
   43% no entry exists.
   44
   45:- dynamic adv/2.   46:- dynamic adv_comp/2.   47:- dynamic adv_sup/2.   48:- dynamic adj_itr/2.   49:- dynamic adj_itr_comp/2.   50:- dynamic adj_itr_sup/2.   51:- dynamic adj_tr/3.   52:- dynamic adj_tr_comp/3.   53:- dynamic adj_tr_sup/3.   54:- dynamic noun_sg/3.   55:- dynamic noun_pl/3.   56:- dynamic noun_mass/3.   57:- dynamic mn_sg/2.   58:- dynamic mn_pl/2.   59:- dynamic pn_sg/3.   60:- dynamic pn_pl/3.   61:- dynamic pndef_sg/3.   62:- dynamic pndef_pl/3.   63:- dynamic iv_finsg/2.   64:- dynamic iv_infpl/2.   65:- dynamic tv_finsg/2.   66:- dynamic tv_infpl/2.   67:- dynamic tv_pp/2.   68:- dynamic dv_finsg/3.   69:- dynamic dv_infpl/3.   70:- dynamic dv_pp/3.   71:- dynamic prep/2.   72
   73
   74% Load the clex-file
   75:- style_check(-discontiguous).   76:- clex_file(ClexFile), ( ClexFile == '' ; load_files(ClexFile, [encoding(utf8)]) ).   77:- style_check(+discontiguous).
 clex_switch(?Switch)
This predicate returns 'on' if clex is switched on, or 'off' otherwise.
   84:- dynamic(clex_switch/1).   85
   86clex_switch(on).
 set_clex_switch(+Switch)
This predicate switches clex on (Switch='on') or off (Switch='off').
   93set_clex_switch(Switch) :-
   94    must_be(oneof([on,off]), Switch),
   95    retractall(clex_switch(_)),
   96    assert(clex_switch(Switch))