1/* @(#)chat.pl 24.1 2/23/88 */ 2% load.pl : Load Chat-80, for Quintus Prolog 3 4/* 5 _________________________________________________________________________ 6| Copyright (C) 1982 | 7| | 8| David Warren, | 9| SRI International, 333 Ravenswood Ave., Menlo Park, | 10| California 94025, USA; | 11| | 12| Fernando Pereira, | 13| Dept. of Architecture, University of Edinburgh, | 14| 20 Chambers St., Edinburgh EH1 1JZ, Scotland | 15| | 16| This program may be used, copied, altered or included in other | 17| programs only for academic purposes and provided that the | 18| authorship of the initial program is aknowledged. | 19| Use for commercial purposes without the previous written | 20| agreement of the authors is forbidden. | 21|_________________________________________________________________________| 22 23*/ 24 25/* 26 Copyright 1986, Fernando C.N. Pereira and David H.D. Warren, 27 28 All Rights Reserved 29*/ 30 31% This file compiles all of Chat-80 32 33/* SWI-Prolog modifications: 34 35 - include library Quintus for enhanced compatibility 36 - put discontiguous between brackets 37 - rename plus/3 and index/1 to be ix_plus; my_index 38 - remove last/2: system predicate with equivalent definition. 39*/ 40 41:- use_module(library(quintus), [no_style_check/1]). 42:- op(1150, fx, [(mode), (public)]). 43 44:- no_style_check(single_var). 45:- no_style_check((discontiguous)). 46 47ttynl:- format('~N'),flush_output. 48 49:- user:ensure_loaded((.. / parser_sharing)). % misc 50 51 52%:- ensure_loaded(als_chat). % misc 53:- op(400, xfy, '&'). 54:- op(400, xfy, '--'). 55 56:- consult(chatops). 57 58:- consult(readin). % sentence input, ASCII VERSION 59:- consult(ptree). % print trees 60:- consult(xgrun). % XG runtimes 61 62:- consult(xgproc). % XG generator 63 64:- load_plus_xg_file(chat80,'chat80/clone.xg'). 65:- load_plus_xg_file(chat80,'chat80/lex.xg'). 66 67% :- compile_xg_clauses. 68% :- consult(newg). % clone + lex 69 70 71:- consult(clotab). % attachment tables 72:- consult(newdic). % syntactic dictionary 73:- consult(slots). % fits arguments into predicates 74:- consult(scopes). % quantification and scoping 75:- consult(templa). % semantic dictionary 76:- consult(qplan). % query planning 77:- consult(talkr). % query evaluation 78:- consult(ndtabl). % relation info. 79:- consult(aggreg). % aggregation operators 80:- consult(world0). % geographic data base 81:- consult(rivers). 82:- consult(cities). 83:- consult(countr). 84:- consult(contai). 85:- consult(border). 86:- consult(chattop). % top level control 87 88 89save_chat :- 90 qsave_program(chat, [goal(hi)])