1% Simple illustration of interactive construction of tree-based models
    2% within Aleph
    3% To run do the following:
    4%       a. Load Aleph
    5%       b. read_all(animals).
    6%       c. induce_tree.

?- induce_tree(T). % try with this input 1. */

   13%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   14% specify tree type
   15
   16:- use_module(library(aleph)).   17:- aleph.   18:- if(current_predicate(use_rendering/1)).   19:- use_rendering(prolog).   20:- endif.   21
   22:- aleph_set(tree_type,classification).   23:- aleph_set(classes,[mammal,nmammal]).   24:- aleph_set(minpos,2).       % minimum examples in leaf for splitting
   25:- aleph_set(prune_tree,true).   26:- aleph_set(confidence,0.25).% pruning conf parameter used by C4.5
   27:- aleph_set(evalfn,entropy).   28:- aleph_set(dependent,2).	% second argument of class/2 is the one to predict
   29:- aleph_set(interactive,true).   30
   31%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   32% Mode declarations
   33
   34:- modeh(1,class(+animal,-class)).   35:- modeb(1,has_gills(+animal)).   36:- modeb(1,has_covering(+animal,#covering)).
   37:- modeb(1,has_legs(+animal,#nat)).
   38:- modeb(1,homeothermic(+animal)).   39:- modeb(1,has_eggs(+animal)).   40:- modeb(1,not(has_gills(+animal))).   41:- modeb(1,nhas_gills(+animal)).   42:- modeb(*,habitat(+animal,#habitat)).
   43:- modeb(1,has_milk(+animal)).   44
   45:-determination(class/2,has_gills/1).   46:-determination(class/2,has_covering/2).   47:-determination(class/2,has_legs/2).   48:-determination(class/2,momeotermic/1).   49:-determination(class/2,has_egss/1).   50:-determination(class/2,nhas_gills/1).   51:-determination(class/2,habitat/2).   52:-determination(class/2,has_milk/1).   53
   54%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   55% Types
   56:-begin_bg.   57animal(dog).  animal(dolphin).  animal(platypus).  animal(bat).
   58animal(trout).  animal(herring).  animal(shark). animal(eel).
   59animal(lizard).  animal(crocodile).  animal(t_rex).  animal(turtle).
   60animal(snake).  animal(eagle).  animal(ostrich).  animal(penguin).
   61animal(cat). animal(dragon).  animal(girl).  animal(boy).
   62
   63
   64class(mammal).  class(fish).  class(reptile).  class(bird).
   65
   66covering(hair).  covering(none).  covering(scales).  covering(feathers).
   67
   68habitat(land).  habitat(water).  habitat(air).  habitat(caves).
   69
   70%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   71
   72%%%%%%%%%%%%%%%%%%%%%%%%%%%%
   73% Background knowledge
   74
   75has_covering(dog,hair).
   76has_covering(dolphin,none).
   77has_covering(platypus,hair).
   78has_covering(bat,hair).
   79has_covering(trout,scales).
   80has_covering(herring,scales).
   81has_covering(shark,none).
   82has_covering(eel,none).
   83has_covering(lizard,scales).
   84has_covering(crocodile,scales).
   85has_covering(t_rex,scales).
   86has_covering(snake,scales).
   87has_covering(turtle,scales).
   88has_covering(eagle,feathers).
   89has_covering(ostrich,feathers).
   90has_covering(penguin,feathers).
   91
   92has_legs(dog,4).
   93has_legs(dolphin,0).
   94has_legs(platypus,2).
   95has_legs(bat,2).
   96has_legs(trout,0).
   97has_legs(herring,0).
   98has_legs(shark,0).
   99has_legs(eel,0).
  100has_legs(lizard,4).
  101has_legs(crocodile,4).
  102has_legs(t_rex,4).
  103has_legs(snake,0).
  104has_legs(turtle,4).
  105has_legs(eagle,2).
  106has_legs(ostrich,2).
  107has_legs(penguin,2).
  108
  109has_milk(dog).
  110has_milk(cat).
  111has_milk(dolphin).
  112has_milk(bat).
  113has_milk(platypus).
  114
  115
  116homeothermic(dog).
  117homeothermic(cat).
  118homeothermic(dolphin).
  119homeothermic(platypus).
  120homeothermic(bat).
  121homeothermic(eagle).
  122homeothermic(ostrich).
  123homeothermic(penguin).
  124
  125
  126habitat(dog,land).
  127habitat(dolphin,water).
  128habitat(platypus,water).
  129habitat(bat,air).
  130habitat(bat,caves).
  131habitat(trout,water).
  132habitat(herring,water).
  133habitat(shark,water).
  134habitat(eel,water).
  135habitat(lizard,land).
  136habitat(crocodile,water).
  137habitat(crocodile,land).
  138habitat(t_rex,land).
  139habitat(snake,land).
  140habitat(turtle,water).
  141habitat(eagle,air).
  142habitat(eagle,land).
  143habitat(ostrich,land).
  144habitat(penguin,water).
  145
  146has_eggs(platypus).
  147has_eggs(trout).
  148has_eggs(herring).
  149has_eggs(shark).
  150has_eggs(eel).
  151has_eggs(lizard).
  152has_eggs(crocodile).
  153has_eggs(t_rex).
  154has_eggs(snake).
  155has_eggs(turtle).
  156has_eggs(eagle).
  157has_eggs(ostrich).
  158has_eggs(penguin).
  159
  160has_gills(trout).
  161has_gills(herring).
  162has_gills(shark).
  163has_gills(eel).
  164
  165nhas_gills(X) :- animal(X), not(has_gills(X)).
  166:-end_bg.  167
  168:-begin_in_pos.  169
  170class(bat,mammal).
  171class(dog,mammal).
  172class(bat,mammal).
  173class(bat,mammal).
  174class(dog,mammal).
  175class(platypus,mammal).
  176
  177
  178class(eagle,nmammal).
  179class(eagle,nmammal).
  180class(ostrich,nmammal).
  181class(shark,nmammal).
  182class(crocodile,nmammal).
  183class(shark,nmammal).
  184class(penguin,nmammal).
  185class(shark,nmammal).
  186class(crocodile,nmammal).
  187class(crocodile,nmammal).
  188class(shark,nmammal).
  189class(snake,nmammal).
  190class(t_rex,nmammal).
  191class(crocodile,nmammal).
  192
  193:-end_in_pos.