1:- module( pepl, [
    2                   fam/1,
    3                   sload_pe/1,
    4                   sload_pe/2,
    5                   ssave/1,
    6                   switch_dbg/1,  % should we be using debug/1 ?
    7                   dbg_pepl/1,
    8                   pepl_citation/2,
    9                   pepl_version/2,
   10                   sls/0,
   11                   sample/1,
   12                   sample/5,
   13                   scall/1,
   14                   scall/2,
   15                   scall/5,
   16                   scall_findall/2,
   17                   scall_sum/2,
   18                   seed_pe/0,
   19                   % all_path/2,
   20                   op( 600, xfy, :: )
   21                 ] ).   22
   23:- ensure_loaded('../src/sload_pe').  % trick the system
   24
   25:- dynamic(dbg_flag/1).   26
   27:- license(mit).   28
   29% :- switch_dbg( off ).
   30% :- switch_dbg( on ).
   31
   32there_exists_mem_slp_with_datafile( DataFile ) :-
   33     ( bb_get( current_slp, Cslp ) -> 
   34          true
   35          ;
   36          pepl_warn( nothing_in_memory )
   37     ),
   38     ( file_name_extension(Stem,slp,Cslp) -> true; Stem=Cslp ),
   39     % fname_stem( Cslp, ".slp", Stem, _FullExt ),
   40     atom_concat( Stem, '_data', DataFile ).
   41     % atom_codes( Stem, StemCs ),
   42     % append( StemCs, "_data", DataFileCs ),
   43     % atom_codes( DataFile, DataFileCs ).
   44     
   45frequencies_to_top_goal( [H-_Hocc|T], Goal ) :-
   46     H =.. [Name|Args], 
   47     mold_vars_list( Args, Vars ),
   48     Goal =.. [Name|Vars],
   49     frequencies_to_top_goal_1( T, Goal ).
   50
   51frequencies_to_top_goal_1( [], _Goal ).
   52frequencies_to_top_goal_1( [H-_Hocc|T], Goal ) :-
   53     ( \+ \+ Goal = H -> 
   54          true
   55          ;
   56          pepl_warn( skipping_datum(Goal,H) )
   57     ),
   58     frequencies_to_top_goal_1( T, Goal ).
   59
   60check_data( Data ) :-
   61     ( is_list(Data) ->
   62          ( Data == [] ->
   63               Inner = empty_list
   64               ;
   65               ( check_data_1(Data) ->
   66                    Inner = []
   67                    ;
   68                    Inner = list_is_not_pairs(Data)
   69               )
   70          )
   71          ;
   72          Inner = not_a_list(Data)
   73     ),
   74     ( Inner == [] ->
   75          true
   76          ;
   77          pepl_warn( data_format_error(Inner) )
   78     ).
   79
   80check_data_1( [] ).
   81check_data_1( [_G-_F|T] ) :-
   82     !,
   83     check_data_1( T ).
   84
   85sload_in_fam_options( [], [] ).
   86sload_in_fam_options( [H|T], SldOpts ) :-
   87     ( \+ memberchk( H, [keep_pl(_)] ) ->
   88          SldOpts = TSldOpts
   89          ;
   90          SldOpts = [H|TSldOpts]
   91     ),
   92     sload_in_fam_options( T, TSldOpts ).
 ssave(+File)
Save the stochastic program currently in memory to a file.
   98ssave( InFile ) :-
   99     ( InFile == user -> 
  100          bb_get( directives, Directvs ),
  101          portray_sdirectives( Directvs ), nl,
  102          bb_get( all_slp_clauses, AllClauses ),
  103          bb_get( pp, PPs ),
  104          portray_sclauses( AllClauses, PPs )
  105          ;
  106          ( file_name_extension(_Base,slp,InFile) ->
  107               File = InFile
  108               ;
  109               file_name_extension( InFile, slp, File )
  110          ),
  111          current_output( Co ),
  112          open( File, write, Stream ),
  113          ( ( set_output( Stream ),
  114               % DefMod = (write( (:- module( slp, [])) ), nl, nl),
  115               % pl( swi(_), DefMod ), 
  116               write( '% Generated by ssave/1.' ), nl, nl,
  117               bb_get( directives, Directvs ),
  118               portray_sdirectives( Directvs ), nl,
  119               bb_get( all_slp_clauses, AllClauses ),
  120               bb_get( pp, PPs ),
  121               portray_sclauses( AllClauses, PPs ),
  122               set_output( Co ),
  123               write( 'program saved in: ' ), write( File ), nl, !
  124               )
  125               ;
  126               set_output( Co ),
  127               write( 'failure while trying to save in: ' ), write( File ), nl
  128          ),
  129          close( Stream ),
  130          set_output( Co )
  131     ).
 sls
Listing of the stochastic program currently in memory.
  137sls :-
  138     % bb_get( all_transformed_clauses, TrsClauses ),
  139     % sprint_list( TrsClauses ).
  140     ssave( user ).
  141
  142dbg_flag( off ).
  143
  144:- ensure_loaded( library(write_list_with_line_numbers) ).
 switch_dbg(Switch)
Switch debugging of fam/1 to either on or off.
  150switch_dbg( Flag ) :-
  151     ( (Flag == on;Flag == off) -> 
  152          retractall( dbg_flag(_) ),
  153          assert( (dbg_flag(Flag):- !) )
  154          ;
  155          G = switch_dbg( Flag ), T=[off,on],
  156          print_message( error, type_error(G,1,T,Flag) )
  157     ).
 dbg_pepl(+Goal)
Call Goal iff in (pepl) debugging.
  163dbg_pepl( Goal ) :- 
  164     ( dbg_flag(on) -> 
  165          call( Goal )
  166          ; 
  167          true
  168     ).
  169
  170dbg_ls_pepl( Header, List ) :-
  171     ( dbg_flag(on) -> 
  172          write( Header ), nl,
  173          write_list_with_line_numbers( List, 1, 4 ), nl
  174          ;
  175          true
  176     )