1:- module(
    2  tree,
    3  [
    4    depth/2,   % +Tree, ?Depth
    5    shortest/2 % +Trees, ?Tree
    6  ]
    7).

Tree data structure support

Support library for working with tree data structures.

A tree is represented by a compound term with the following components:

Here are some examples of tree terms:

tree(leaf, 'Electra', [])

tree(father,
     'Agamemnon',
     [tree(leaf, 'Electra', []),
      tree(leaf, 'Orestes', [])])

tree('Modus ponens',
     'Socrates is mortal',
     [tree(premise, 'Sorcrates is a man', []),
      tree(premise, 'Men are mortal', [])])
author
- Wouter Beek
version
- 2021-03-18 /
   40:- use_module(library(aggregate)).   41:- use_module(library(lists)).
 depth(+Tree:compound, +Depth:nonneg) is semidet
depth(+Tree:compound, -Depth:nonneg) is det
Succeeds for the Depth of the Tree.

The depth of a tree is defined inductively:

   54depth(tree(_,_,[]), 0).
   55depth(tree(_,_,Trees), Depth) :-
   56  aggregate_all(
   57    max(Depth),
   58    (
   59      member(Tree, Trees),
   60      depth(Tree, Depth)
   61    ),
   62    Depth
   63  ).
 shortest(+Trees:list(compound), +Tree:compound) is semidet
shortest(+Trees:list(compound), -Tree:compound) is det
Succeeds if Tree is the shotests of Trees.
   72shortest(Trees, Tree) :-
   73  aggregate_all(
   74    min(Depth0,Tree0),
   75    (
   76      member(Tree0, Trees),
   77      depth(Tree0, Depth0)
   78    ),
   79    min(_, Tree)
   80  )