1:- set_module(class(development)).    2:- '$set_source_module'(baseKB).    3:- use_module(library(pfc_lib)).    4:- mpred_unload_file.    5:- ensure_abox(baseKB).    6:- file_begin(pfc).    7:- set_fileAssertMt(baseKB).    8% ensure this file does not get unloaded with mpred_reset
    9:- prolog_load_context(file,F), ain(mpred_unload_option(F,never)).   10
   11
   12
   13pfcControlled(if_missing(ftAskable,ftAssertable)).
   14
   15% this should have been ok
   16% (if_missing(Missing,Create) ==> ((\+ Missing/(Missing\==Create), \+ Create , \+ ~(Create)) ==> Create)).
   17if_missing(Missing,Create) ==> 
   18 ( ( \+ (Missing/(Missing\=@=Create))) ==> Create).
   19
   20:- if(baseKB:startup_option(datalog,sanity);baseKB:startup_option(clif,sanity)).   21
   22:- ensure_loaded(pack(logicmoo_base/t/examples/pfc/'sanity_foob.pfc')).   23
   24:- endif.