1/* * module * 
    2% All modules are declared here so that this next lines dont have to be pasted into every file.
    3% Since this list will need at least 160 entries to cover the obj classes rooms and commands, 
    4% we add the modules here to not waste 160^2 lines of text and having to not 
    5% update 160+ files whenever a new module is used
    6%
    7% Logicmoo Project PrologMUD: A MUD server written in Prolog
    8% Maintainer: Douglas Miles
    9% Dec 13, 2035
   10%
   11*/
   12
   13% :- nop('$set_source_module'( baseKB)).
   14
   15% :- include(logicmoo(mpred/'mpred_header.pi')).
   16
   17% :- '$current_source_module'(M),once(M==baseKB;on_x_log_cont(add_import_module(baseKB,M,end))).
   18:- use_module(library(pfc_lib)).   19
   20%:- kb_shared(get_session_id/1).
   21:- 
   22 current_prolog_flag(access_level,Was),
   23 set_prolog_flag(access_level,system),
   24 op(1190,xfx,('::::')),
   25 op(1180,xfx,('==>')),
   26 op(1170,xfx,'<==>'),  
   27 op(1160,xfx,('<-')),
   28 op(1150,xfx,'=>'),
   29 op(1140,xfx,'<='),
   30 op(1130,xfx,'<=>'), 
   31 op(600,yfx,'&'), 
   32 op(600,yfx,'v'),
   33 op(350,xfx,'xor'),
   34 op(300,fx,'~'),
   35 op(300,fx,'-'),
   36 op(1199,fx,('==>')),
   37 set_prolog_flag(access_level,Was).   38
   39:- style_check(-discontiguous).   40:- enable_mpred_expansion.   41:- expects_dialect(pfc).