1/*
    2Registration dataset, it contains information about participants in a recent
    3Seminar on Data Mining.
    4We would like to find out what type of people attend the parties at the seminar.
    5From
    6L. De Raedt, H. Blockeel, L. Dehaspe, and W. Van Laer. Three companions for data mining in first order logic. In S. Dzeroski and N. Lavrac, editors, Relational Data Mining, pages 105-139.  Springer-Verlag, 2001.
    7
    8See also The ACE Data Mining System User's Manual
    9http://dtai.cs.kuleuven.be/ACE/doc/ACEuser-1.2.16.pdf
   10
   11Downloaded from
   12http://dtai.cs.kuleuven.be/static/ACE/doc/
   13*/

?- induce_par([rand_train],P),test(P,[rand_test],LL,AUCROC,ROC,AUCPR,PR). ?- in(P),test(P,[all],LL,AUCROC,ROC,AUCPR,PR). ?- induce([all],P),test(P,[all],LL,AUCROC,ROC,AUCPR,PR). */

   21:-use_module(library(slipcover)).   22
   23:- if(current_predicate(use_rendering/1)).   24:- use_rendering(c3).   25:- use_rendering(lpad).   26:- endif.   27
   28:-sc.   29
   30:- set_sc(depth_bound,false).   31:- set_sc(neg_ex,given).   32:- set_sc(megaex_bottom,7).   33%:- set_sc(max_iter,2).
   34%:- set_sc(max_iter_structure,5).
   35:- set_sc(verbosity,1).   36
   37:- begin_bg.   38company_info(jvt,commercial).
   39company_info(scuf,university).
   40company_info(ucro,university).
   41course(cso,2,introductory).
   42course(erm,3,introductory).
   43course(so2,4,introductory).
   44course(srw,3,advanced).
   45
   46
   47
   48job(J):-
   49	participant(J, _, _, _).
   50company(C):-
   51	participant(_, C, _, _).
   52
   53party_yes :- party(yes).
   54party_no :- party(no).
   55
   56company_type(T):-
   57	company(C),
   58	company_info(C, T).
   59
   60not_company_type(commercial):-
   61  \+ company_type(commercial).
   62
   63not_company_type(university):-
   64  \+ company_type(university).
   65
   66course_len(C, L):-
   67	course(C, L, _).
   68
   69course_type(C, T):-
   70	course(C, _, T).
   71
   72:- end_bg.   73
   74:- begin_in.   75party(yes):0.5:-
   76  company_type(commercial).
   77
   78party(no):0.5:-
   79  subscription(A),
   80  course_len(A,4),
   81  \+ company_type(commercial).
   82:- end_in.   83
   84fold(all,F):-
   85  findall(I,int(I),F).
   86
   87fold(test,[adams,scott]).
   88fold(train,[blake, king, miller, turner]).
   89
   90output(party/1).
   91
   92input_cw(job/1).
   93input_cw(not_company_type/1).
   94input_cw(company_type/1).
   95input_cw(subscription/1).
   96input_cw(course_len/2).
   97input_cw(course_type/2).
   98input_cw(company/1).
   99input_cw(company_info/2).
  100input_cw(participant/4).
  101input_cw(course/3).
  102
  103determination(party/1,job/1).
  104determination(party/1,not_company_type/1).
  105determination(party/1,company_type/1).
  106determination(party/1,subscription/1).
  107determination(party/1,course_len/2).
  108determination(party/1,course_type/2).
  109
  110%modeh(*,[party(yes),party(no)],
  111%  [party(yes),party(no)],
  112%  [job/1,company_type/1,subscription/1,course_len/2,course_type/2]).
  113
  114
  115modeh(*,party(yes)).
  116modeh(*,party(no)).
  117
  118modeb(*,job(-#job)).
  119modeb(*,company_type(-#ctype)).
  120modeb(*,not_company_type(-#ctype)).
  121modeb(*,subscription(-sub)).
  122modeb(*,course_len(+sub,-#cl)).
  123modeb(*,course_type(+sub,-#ct)).
  124
  125neg(party(M,yes)):- party(M,no).
  126neg(party(M,no)):- party(M,yes).
  127
  128party(M,P):-
  129  participant(M,_, _, P, _).
  130
  131
  132begin(model(adams)).
  133participant(researcher,scuf,no,23).
  134subscription(erm).
  135subscription(so2).
  136subscription(srw).
  137end(model(adams)).
  138
  139begin(model(blake)).
  140participant(president,jvt,yes,5).
  141subscription(cso).
  142subscription(erm).
  143end(model(blake)).
  144
  145begin(model(king)).
  146participant(manager,ucro,no,78).
  147subscription(cso).
  148subscription(erm).
  149subscription(so2).
  150subscription(srw).
  151end(model(king)).
  152
  153begin(model(miller)).
  154participant(manager,jvt,yes,14).
  155subscription(so2).
  156end(model(miller)).
  157
  158begin(model(scott)).
  159participant(researcher,scuf,yes,94).
  160subscription(erm).
  161subscription(srw).
  162end(model(scott)).
  163
  164begin(model(turner)).
  165participant(researcher,ucro,no,81).
  166subscription(so2).
  167subscription(srw).
  168end(model(turner)).
  169
  170:- fold(all,F),
  171   sample(4,F,FTr,FTe),
  172   assert(fold(rand_train,FTr)),
  173   assert(fold(rand_test,FTe)).