1:- module(cgt,[load_cge/0,load_cgt/0]).    2:- use_module(library(cgt/cge/swi_apeal)).    3
    4cgt_data(F/A):- multifile(F/A), dynamic(F/A), discontiguous(F/A).
    5
    6:- cgt_data('<<'/2).    7:- cgt_data(c/3).    8:- cgt_data(concept_type/5).    9:- cgt_data(description/3).   10:- cgt_data(g/3).   11:- cgt_data(l/3).   12:- cgt_data(p/4).   13:- cgt_data(relation_type/5).   14
   15
   16/* COPYRIGHT ************************************************************
   17
   18Conceptual Graph Tools (CGT) - a partial implementation of Sowa's CS Theory
   19Copyright (C) 1990 Miguel Alexandre Wermelinger
   20
   21    This program is free software; you can redistribute it and/or modify
   22    it under the terms of the GNU General Public License as published by
   23    the Free Software Foundation; either version 2 of the License, or
   24    (at your option) any later version.
   25
   26    This program is distributed in the hope that it will be useful,
   27    but WITHOUT ANY WARRANTY; without even the implied warranty of
   28    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
   29    GNU General Public License for more details.
   30
   31    You should have received a copy of the GNU General Public License
   32    along with this program; if not, write to the Free Software
   33    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
   34
   35************************************************************************/
   36
   37/* AUTHOR(S) ************************************************************
   38
   39Michel Wermelinger
   40Dept. de Informatica, Univ. Nova de Lisboa, Quinta da Torre
   41P - 2825 Monte da Caparica, PORTUGAL
   42Phone: (+351) (1) 295 44 64 ext. 1360  Internet: mw@fct.unl.pt
   43
   44************************************************************************/
   45
   46/* GENERALITIES *********************************************************
   47 
   48File Name	: QXP.PL
   49Creation Date	: 90/11/19 	By: mw
   50Abbreviations	: mw - Michel Wermelinger 
   51Description	: Main file; for Quintus Prolog
   52 
   53************************************************************************/
   54
   55/* HISTORY **************************************************************
   56
   571.01	92/04/24  mw	created load_cgt/0 and load_cge/0 so that you only
   58				load what you want
   59			added comments
   601.02	92/05/05  mw	the 'lexicon' file is now loaded by portugues/0
   61
   62************************************************************************/
   63
   64/* CONTENTS *************************************************************
   65
   66not/1			the not operator (Quintus doesn't have it)
   67\=/2			the different operator (Quintus doesn't have it)
   68succ/2			the successor relation for integers
   69
   70load_cgt/0		loads the Conceptual Graph Tools
   71load_cge/0		loads the Conceptual Graph Editor
   72load_get/0		loads the Graph Editor and Tools
   73portugues/0		loads the Portuguese semantic interpreter
   74
   75get_back/0		returns to the Quintus X Prolog top level shell
   76snapshot/1		creates a widget to make screen dumps
   77
   78************************************************************************/
   79
   80/* IMPORTANT NOTES ******************************************************
   81
   82If you don't have X-Prolog please comment out all predicates where the
   83widget/2 infix operator occurs.
   84
   85If you're not using CGE please edit files 'misc.pl', 'sem_int.pl' and
   86'gramaux.pl'.
   87
   88************************************************************************/
   89
   90
   91%%% Some miscellaneous stuff
   92
   93:- use_module(library(logicmoo_common)).   94
   95/*
   96:- op(900, fy, not).
   97
   98not(X) :- X, !, fail.
   99not(X).
  100
  101:- op(700, xfx, \=).
  102
  103X \= Y :- not X = Y.
  104
  105*/
  106succ(X, Y) :-
  107    nonvar(X), !, Y is X + 1.
  108succ(X, Y) :-
  109    X is Y - 1.
  110
  111%:- unknown(X, fail).		% calls to undefined predicates simply fail
  112
  113%:- leash([call,redo]).		% leash call and redo ports only
  114%:- style_check(single_var).	% check for single occurrences of variables
  115
  116%%% Load Portuguese semantic interpreter
  117%%%
  118%%% load_cgt/0 (or load_get/0) must be called before portugues/0
  119%%%
  120%%% there will be some synax errors when compiling the 'syntax' file;
  121%%% please ignore them. I won't change the 'syntax' file as I'm not its author.
  122
  123portugues :- 
  124    no_style_check(single_var), % don't check for single occurrences of vars
  125    compile(syntax),		% compile the file with the Portuguese syntax
  126    [lexicon, sem_int], 	% load lexicon and the semantic interpreter
  127    style_check(single_var).	% enable checking again
  128
  129%%% Widget to make screen dumps
  130
  131/*snapshot(X) :- shell widget snapshot(ID), ID wproc window(X).
  132
  133shell widget snapshot(S) :-
  134	S= transientShell / [
  135		backgroundPixmap(0), width(100), height(100)].
  136*/
  137
  138%%% Load the Conceptual Graph Tools
  139
  140load_dir_file(Dir,[F]):-!, load_dir_file(Dir,F).
  141load_dir_file(Dir,F):- F\==[],!, reconsult(library(Dir/F)).
  142load_dir_file(_,_).
  143
  144
  145load_cgt :-
  146   maplist(load_dir_file(cgt),[
  147    [can_ops], 		% canonical formation rules
  148    [type_ops],		% operations on the type hierarchy
  149    [log_ops],		% propositional inference rules
  150    [misc], 		% DB management, referent expansions & contractions
  151    [gen_lin],		% generates the linear notation
  152    [rec_lin],		% reads the linear notation
  153    [gramaux],		% auxillary grammar rules (tokeniser)
  154    [list],		% list and set operations
  155    []]),
  156    start_cgp(canon).	% load the backup database
  157
  158%%% Load the Conceptual Graph Editor
  159
  160load_cge :-
  161   % load_set(xgraph),		% load the graph widget
  162   % language(L, [[unlp,wdl]|L]),% CGE is written in UNL Prolog and WDL
  163   maplist(load_dir_file('cgt/cge'), [
  164
  165    [wdl_ext],			% extensions to the Widget Description Language
  166    [cge_actions], 		% actions performed by the editor
  167    [cge_widgets],		% CGE's Window gadgets (editor's visual look)
  168    [dialog],			% widgets for several kinds of dialog boxes
  169    ['choice'],		% widgets for choice dialogs
  170    []]),
  171    %xt_display(D, D), 
  172    %xt_fetch_server_fonts(D),	% to display greek letters
  173    shell widget qxp_shell(G), 	% open a new top-level shell
  174    G = prolog,
  175    recorda(qxp_goal, G, _)	% remember the shell to make get_back possible
  176  %  !, G.			% start at the new shell
  177   .
  178
  179%%% get_back acts as an abort for CGE: it returns control to the top-level shell
  180
  181get_back :- recorded(qxp_goal, G, _), !, call(G).
  182get_back :- shell widget qxp_shell(G), recorda(qxp_goal, G, _), !, G.
  183
  184%%% Load the whole GET system
  185
  186load_get :- load_cgt, load_cge.
  187
  188
  189:- dynamic(defined/3).  190
  191
  192:- load_cgt.  193% :- load_cge.