90     INTEGER(INTG) :: 
VALUE    91     INTEGER(INTG) :: colour
    99     LOGICAL :: tree_finished
   100     INTEGER(INTG) :: insert_type
   101     INTEGER(INTG) :: number_in_tree
   193     INTEGER(INTG), 
INTENT(OUT) :: ERR
   197     enters(
"TREE_CREATE_FINISH",err,error,*998)
   199     IF(
ASSOCIATED(tree)) 
THEN   200       IF(tree%TREE_FINISHED) 
THEN   201         CALL flagerror(
"Tree is already finished",err,error,*998)
   204         ALLOCATE(tree%NIL,stat=err)
   205         IF(err/=0) 
CALL flagerror(
"Could not allocate NIL tree node",err,error,*999)
   207         tree%NIL%KEY=-99999999 
   208         tree%NIL%LEFT=>tree%NIL
   209         tree%NIL%RIGHT=>tree%NIL
   210         tree%NIL%PARENT=>tree%NIL
   214         tree%TREE_FINISHED=.true.
   217       CALL flagerror(
"Tree is not associated",err,error,*998)
   220     exits(
"TREE_CREATE_FINISH")
   223 998 errorsexits(
"TREE_CREATE_FINISH",err,error)
   236     INTEGER(INTG), 
INTENT(OUT) :: ERR
   240     enters(
"TREE_CREATE_START",err,error,*998)
   242     IF(
ASSOCIATED(tree)) 
THEN   243       CALL flagerror(
"Tree is already associated",err,error,*998)
   245       ALLOCATE(tree,stat=err)
   246       IF(err/=0) 
CALL flagerror(
"Could not allocate tree",err,error,*999)
   252     exits(
"TREE_CREATE_START")
   255 998 errorsexits(
"TREE_CREATE_START",err,error)
   268     INTEGER(INTG), 
INTENT(OUT) :: ERR
   272     enters(
"TREE_DESTROY",err,error,*999)
   274     IF(
ASSOCIATED(tree)) 
THEN   277       CALL flagerror(
"Tree is not associated",err,error,*999)
   280     exits(
"TREE_DESTROY")
   282 999 errorsexits(
"TREE_DESTROY",err,error)
   291   SUBROUTINE tree_detach(TREE,NUMBER_IN_TREE,TREE_VALUES,ERR,ERROR,*)
   295     INTEGER(INTG), 
INTENT(OUT) :: NUMBER_IN_TREE
   296     INTEGER(INTG), 
POINTER :: TREE_VALUES(:)
   297     INTEGER(INTG), 
INTENT(OUT) :: ERR
   301     enters(
"TREE_DETACH",err,error,*998)
   303     IF(
ASSOCIATED(tree)) 
THEN   304       IF(tree%TREE_FINISHED) 
THEN   305         IF(
ASSOCIATED(tree_values)) 
THEN   306           CALL flagerror(
"Tree values is already associated.",err,error,*998)
   309           ALLOCATE(tree_values(tree%NUMBER_IN_TREE),stat=err)
   310           IF(err/=0) 
CALL flagerror(
"Could not allocate tree values.",err,error,*999)
   315         CALL flagerror(
"Tree has not been finished.",err,error,*999)
   318       CALL flagerror(
"Tree is not associated.",err,error,*998)
   323 999 
IF(
ASSOCIATED(tree_values)) 
DEALLOCATE(tree_values)
   325 998 errorsexits(
"TREE_DETACH",err,error)
   338     INTEGER(INTG), 
INTENT(OUT) :: NUMBER_IN_TREE
   339     INTEGER(INTG), 
POINTER :: TREE_VALUES(:)
   340     INTEGER(INTG), 
INTENT(OUT) :: ERR
   344     enters(
"TREE_DETACH_AND_DESTROY",err,error,*998)
   346     IF(
ASSOCIATED(tree)) 
THEN   347       IF(tree%TREE_FINISHED) 
THEN   348         IF(
ASSOCIATED(tree_values)) 
THEN   349           CALL flagerror(
"Tree values is associated",err,error,*998)
   352           ALLOCATE(tree_values(tree%NUMBER_IN_TREE),stat=err)
   353           IF(err/=0) 
CALL flagerror(
"Could not allocate tree values",err,error,*999)
   359         CALL flagerror(
"Tree has not been finished",err,error,*999)
   362       CALL flagerror(
"Tree is not associated",err,error,*998)
   365     exits(
"TREE_DETACH_AND_DESTROY")
   367 999 
IF(
ASSOCIATED(tree_values)) 
DEALLOCATE(tree_values)
   369 998 errorsexits(
"TREE_DETACH_AND_DESTROY",err,error)
   383     INTEGER(INTG), 
INTENT(INOUT) :: COUNT
   384     INTEGER(INTG), 
INTENT(INOUT) :: TREE_VALUES(:)
   385     INTEGER(INTG), 
INTENT(OUT) :: ERR
   390     enters(
"TREE_DETACH_IN_ORDER",err,error,*999)
   392     IF(
ASSOCIATED(tree)) 
THEN   393       IF(.NOT.
ASSOCIATED(x,tree%NIL)) 
THEN   396         IF(count<=
SIZE(tree_values,1)) 
THEN   397           tree_values(count)=x%VALUE
   399           local_error=
"The current count of the tree values ("//
trim(
number_to_vstring(count,
"*",err,error))// &
   400             & 
") is greater than the size of the tree values array ("// &
   402           CALL flagerror(local_error,err,error,*999)
   407       CALL flagerror(
"Tree is not associated",err,error,*999)
   410     exits(
"TREE_DETACH_IN_ORDER")
   412 999 errorsexits(
"TREE_DETACH_IN_ORDER",err,error)
   425     INTEGER(INTG), 
INTENT(OUT) :: ERR
   429     enters(
"TREE_FINALISE",err,error,*999)
   431     IF(
ASSOCIATED(tree)) 
THEN   433       IF(
ASSOCIATED(tree%NIL)) 
DEALLOCATE(tree%NIL)
   437     exits(
"TREE_FINALISE")
   439 999 errorsexits(
"TREE_FINALISE",err,error)
   452     INTEGER(INTG), 
INTENT(OUT) :: ERR
   456     enters(
"TREE_INITIALISE",err,error,*999)
   458     IF(
ASSOCIATED(tree)) 
THEN   459       tree%TREE_FINISHED=.false.
   461       tree%NUMBER_IN_TREE=0
   465       CALL flagerror(
"Tree is not associated",err,error,*999)
   468     exits(
"TREE_INITIALISE")
   470 999 errorsexits(
"TREE_INITIALISE",err,error)
   483     INTEGER(INTG), 
INTENT(IN) :: INSERT_TYPE
   484     INTEGER(INTG), 
INTENT(OUT) :: ERR
   489     enters(
"TREE_INSERT_TYPE_SET",err,error,*999)
   491     IF(
ASSOCIATED(tree)) 
THEN   492       IF(tree%TREE_FINISHED) 
THEN   493         CALL flagerror(
"Tree has been finished",err,error,*999)
   495         SELECT CASE(insert_type)
   502           CALL flagerror(local_error,err,error,*999)
   506       CALL flagerror(
"Tree is not associated",err,error,*999)
   509     exits(
"TREE_INSERT_TYPE_SET")
   511 999 errorsexits(
"TREE_INSERT_TYPE_SET",err,error)
   524     INTEGER(INTG), 
INTENT(IN) :: KEY
   525     INTEGER(INTG), 
INTENT(OUT) :: ERR
   528     INTEGER(INTG) :: COMPARE_VALUE
   532     enters(
"TREE_ITEM_DELETE",err,error,*999)
   534     IF(
ASSOCIATED(tree)) 
THEN   535       IF(tree%TREE_FINISHED) 
THEN   538         IF(.NOT.
ASSOCIATED(z,tree%NIL)) 
THEN   539           compare_value=z%KEY-key
   540           DO WHILE(compare_value/=0)
   541             IF(compare_value>0) 
THEN    546             IF(
ASSOCIATED(z,tree%NIL)) 
THEN   549               compare_value=z%KEY-key
   552           IF(compare_value==0) 
THEN   554             IF(
ASSOCIATED(z%LEFT,tree%NIL).OR.
ASSOCIATED(z%RIGHT,tree%NIL)) 
THEN   560             IF(.NOT.
ASSOCIATED(y%LEFT,tree%NIL)) 
THEN   566             IF(
ASSOCIATED(y%PARENT,tree%NIL)) 
THEN   569               IF(
ASSOCIATED(y,y%PARENT%LEFT)) 
THEN   580                 IF(
ASSOCIATED(x,x%PARENT%LEFT)) 
THEN   589                     IF(.NOT.
ASSOCIATED(v%LEFT,tree%NIL)) v%LEFT%PARENT=>u
   591                     IF(
ASSOCIATED(u%PARENT,tree%NIL)) 
THEN   594                       IF(
ASSOCIATED(u,u%PARENT%LEFT)) 
THEN   615                       IF(.NOT.
ASSOCIATED(v%RIGHT,tree%NIL)) v%RIGHT%PARENT=>u
   617                       IF(
ASSOCIATED(v%PARENT,tree%NIL)) 
THEN   620                         IF(
ASSOCIATED(u,u%PARENT%RIGHT)) 
THEN   630                     w%COLOUR=x%PARENT%COLOUR
   637                     IF(.NOT.
ASSOCIATED(v%LEFT,tree%NIL)) v%LEFT%PARENT=>u
   639                     IF(
ASSOCIATED(u%PARENT,tree%NIL)) 
THEN   642                       IF(
ASSOCIATED(u,u%PARENT%LEFT)) 
THEN   661                     IF(.NOT.
ASSOCIATED(v%RIGHT,tree%NIL)) v%RIGHT%PARENT=>u
   663                     IF(
ASSOCIATED(v%PARENT,tree%NIL)) 
THEN   666                       IF(
ASSOCIATED(u,u%PARENT%RIGHT)) 
THEN   687                       IF(.NOT.
ASSOCIATED(v%LEFT,tree%NIL)) v%LEFT%PARENT=>u
   689                       IF(
ASSOCIATED(u%PARENT,tree%NIL)) 
THEN   692                         IF(
ASSOCIATED(u,u%PARENT%LEFT)) 
THEN   702                     w%COLOUR=x%PARENT%COLOUR
   709                     IF(.NOT.
ASSOCIATED(v%RIGHT,tree%NIL)) v%RIGHT%PARENT=>u
   711                     IF(
ASSOCIATED(v%PARENT,tree%NIL)) 
THEN   714                       IF(
ASSOCIATED(u,u%PARENT%RIGHT)) 
THEN   728             IF(.NOT.
ASSOCIATED(y,z)) 
THEN   735               IF(
ASSOCIATED(z,z%PARENT%LEFT)) 
THEN   742             tree%NUMBER_IN_TREE=tree%NUMBER_IN_TREE-1
   745             CALL flagerror(local_error,err,error,*999)
   748           CALL flagerror(
"The tree root is NIL. Can not delete the key",err,error,*999)
   751         CALL flagerror(
"The tree has not been finished",err,error,*999)
   754       CALL flagerror(
"Tree is not associated",err,error,*999)
   757     exits(
"TREE_ITEM_DELETE")
   759 999 errorsexits(
"TREE_ITEM_DELETE",err,error)
   772     INTEGER(INTG), 
INTENT(IN) :: KEY
   773     INTEGER(INTG), 
INTENT(IN) :: 
VALUE   774     INTEGER(INTG), 
INTENT(OUT) :: INSERT_STATUS
   775     INTEGER(INTG), 
INTENT(OUT) :: ERR
   778     LOGICAL :: DUPLICATE_KEY
   781     NULLIFY(new_tree_node)
   783     enters(
"TREE_ITEM_INSERT",err,error,*998)
   785     IF(
ASSOCIATED(tree)) 
THEN   786       IF(tree%TREE_FINISHED) 
THEN   790         duplicate_key=.false.
   791         DO WHILE(.NOT.
ASSOCIATED(x,tree%NIL))
   794           IF(duplicate_key) 
THEN   796           ELSE IF(key<x%KEY) 
THEN   802         IF(duplicate_key) 
THEN   806           ALLOCATE(new_tree_node,stat=err)
   807           IF(err/=0) 
CALL flagerror(
"Could not allocate new tree node",err,error,*999)
   809           new_tree_node%KEY=key
   810           new_tree_node%VALUE=
VALUE   813           new_tree_node%LEFT=>tree%NIL
   814           new_tree_node%RIGHT=>tree%NIL
   815           new_tree_node%PARENT=>y
   816           IF(
ASSOCIATED(y,tree%NIL)) 
THEN   817             tree%ROOT=>new_tree_node
   819             IF(new_tree_node%KEY<y%KEY) 
THEN   820               y%LEFT=>new_tree_node
   822               y%RIGHT=>new_tree_node
   830             IF(
ASSOCIATED(z%PARENT,z%PARENT%PARENT%LEFT)) 
THEN   831               y=>z%PARENT%PARENT%RIGHT
   838                 IF(
ASSOCIATED(z,z%PARENT%RIGHT)) 
THEN   844                   IF(.NOT.
ASSOCIATED(y%LEFT,tree%NIL)) y%LEFT%PARENT=>x
   846                   IF(
ASSOCIATED(x%PARENT,tree%NIL)) 
THEN   849                     IF(
ASSOCIATED(x,x%PARENT%LEFT)) 
THEN   864                 IF(.NOT.
ASSOCIATED(y%RIGHT,tree%NIL)) y%RIGHT%PARENT=>x
   866                 IF(
ASSOCIATED(x%PARENT,tree%NIL)) 
THEN   869                   IF(
ASSOCIATED(x,x%PARENT%RIGHT)) 
THEN   879               y=>z%PARENT%PARENT%LEFT
   886                 IF(
ASSOCIATED(z,z%PARENT%LEFT)) 
THEN   892                   IF(.NOT.
ASSOCIATED(y%RIGHT,tree%NIL)) y%RIGHT%PARENT=>x
   894                   IF(
ASSOCIATED(x%PARENT,tree%NIL)) 
THEN   897                     IF(
ASSOCIATED(x,x%PARENT%RIGHT)) 
THEN   912                 IF(.NOT.
ASSOCIATED(y%LEFT,tree%NIL)) y%LEFT%PARENT=>x
   914                 IF(
ASSOCIATED(x%PARENT,tree%NIL)) 
THEN   917                   IF(
ASSOCIATED(x,x%PARENT%LEFT)) 
THEN   930           tree%NUMBER_IN_TREE=tree%NUMBER_IN_TREE+1
   934         CALL flagerror(
"The tree has not been finished",err,error,*998)
   937       CALL flagerror(
"Tree is not associated",err,error,*998)
   940     exits(
"TREE_ITEM_INSERT")
   942 999 
IF(
ASSOCIATED(new_tree_node)) 
DEALLOCATE(new_tree_node)
   943 998 errorsexits(
"TREE_ITEM_INSERT",err,error)
   957     INTEGER(INTG), 
INTENT(OUT) :: ERR
   961     enters(
"TREE_NODE_FINALISE",err,error,*999)
   963     IF(
ASSOCIATED(tree)) 
THEN   964       IF(.NOT.
ASSOCIATED(tree_node,tree%NIL)) 
THEN   967         DEALLOCATE(tree_node)
   970       CALL flagerror(
"Tree is not associated",err,error,*999)
   973     exits(
"TREE_NODE_FINALISE")
   975 999 errorsexits(
"TREE_NODE_FINALISE",err,error)
   989     INTEGER(INTG), 
INTENT(OUT) :: ERR
   993     enters(
"TREE_NODE_INITIALISE",err,error,*999)
   995     IF(
ASSOCIATED(tree)) 
THEN   996       IF(
ASSOCIATED(tree_node)) 
THEN  1000         NULLIFY(tree_node%LEFT)
  1001         NULLIFY(tree_node%RIGHT)
  1002         NULLIFY(tree_node%PARENT)
  1004         CALL flagerror(
"Tree node is not associated",err,error,*999)
  1007       CALL flagerror(
"Tree is not associated",err,error,*999)
  1010     exits(
"TREE_NODE_INITIALISE")
  1012 999 errorsexits(
"TREE_NODE_INITIALISE",err,error)
  1026     INTEGER(INTG), 
INTENT(OUT) :: KEY
  1027     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1031     enters(
"TREE_NODE_KEY_GET",err,error,*999)
  1033     IF(
ASSOCIATED(tree)) 
THEN  1034       IF(tree%TREE_FINISHED) 
THEN  1035         IF(
ASSOCIATED(tree_node)) 
THEN  1038           CALL flagerror(
"Tree node is not associated",err,error,*999)
  1041         CALL flagerror(
"Tree has not been finished",err,error,*999)
  1044       CALL flagerror(
"Tree is not associated",err,error,*999)
  1047     exits(
"TREE_NODE_KEY_GET")
  1049 999 errorsexits(
"TREE_NODE_KEY_GET",err,error)
  1063     INTEGER(INTG), 
INTENT(OUT) :: 
VALUE  1064     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1068     enters(
"TREE_NODE_VALUE_GET",err,error,*999)
  1070     IF(
ASSOCIATED(tree)) 
THEN  1071       IF(tree%TREE_FINISHED) 
THEN  1072         IF(
ASSOCIATED(tree_node)) 
THEN  1073           VALUE=tree_node%VALUE
  1075           CALL flagerror(
"Tree node is not associated",err,error,*999)
  1078         CALL flagerror(
"Tree has not been finished",err,error,*999)
  1081       CALL flagerror(
"Tree is not associated",err,error,*999)
  1084     exits(
"TREE_NODE_VALUE_GET")
  1086 999 errorsexits(
"TREE_NODE_VALUE_GET",err,error)
  1100     INTEGER(INTG), 
INTENT(IN) :: 
VALUE  1101     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1105     enters(
"TREE_NODE_VALUE_SET",err,error,*999)
  1107     IF(
ASSOCIATED(tree)) 
THEN  1108       IF(tree%TREE_FINISHED) 
THEN  1109         IF(
ASSOCIATED(tree_node)) 
THEN  1110           tree_node%VALUE=
VALUE  1112           CALL flagerror(
"Tree node is not associated",err,error,*999)
  1115         CALL flagerror(
"Tree has not been finished",err,error,*999)
  1118       CALL flagerror(
"Tree is not associated",err,error,*999)
  1121     exits(
"TREE_NODE_VALUE_SET")
  1123 999 errorsexits(
"TREE_NODE_VALUE_SET",err,error)
  1135     INTEGER(INTG), 
INTENT(IN) :: ID
  1137     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1141     enters(
"TREE_OUTPUT",err,error,*999)
  1143     IF(
ASSOCIATED(tree)) 
THEN  1144       IF(tree%TREE_FINISHED) 
THEN  1146         CALL write_string_value(id,
"Number of tree nodes = ",tree%NUMBER_IN_TREE,err,error,*999)
  1150         CALL flagerror(
"The tree has not been finished",err,error,*999)
  1153       CALL flagerror(
"Tree is not associated",err,error,*999)
  1156     exits(
"TREE_OUTPUT")
  1158 999 errorsexits(
"TREE_OUTPUT",err,error)
  1170     INTEGER(INTG), 
INTENT(IN) :: ID
  1173     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1177     enters(
"TREE_OUTPUT_IN_ORDER",err,error,*999)
  1179     IF(
ASSOCIATED(tree)) 
THEN  1180       IF(.NOT.
ASSOCIATED(x,tree%NIL)) 
THEN  1188         IF(
ASSOCIATED(x%LEFT,tree%NIL)) 
THEN  1193         IF(
ASSOCIATED(x%RIGHT,tree%NIL)) 
THEN  1194           CALL write_string(id,
"    Right Key = NIL",err,error,*999)
  1198         IF(
ASSOCIATED(x%PARENT,tree%NIL)) 
THEN  1199           CALL write_string(id,
"    Parent Key = NIL",err,error,*999)
  1207       CALL flagerror(
"Tree is not associated",err,error,*999)
  1210     exits(
"TREE_OUTPUT_IN_ORDER")
  1212 999 errorsexits(
"TREE_OUTPUT_IN_ORDER",err,error)
  1226     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1233     NULLIFY(tree_predecessor)
  1235     enters(
"TREE_PREDECESSOR",err,error,*999)
  1237     IF(
ASSOCIATED(tree)) 
THEN  1238       IF(
ASSOCIATED(x)) 
THEN  1240         IF(
ASSOCIATED(y,tree%NIL)) 
THEN  1241           DO WHILE(.NOT.
ASSOCIATED(y%RIGHT,tree%NIL))
  1247           DO WHILE(
ASSOCIATED(x,y%LEFT))
  1248             IF(
ASSOCIATED(y,tree%ROOT)) 
THEN  1249               tree_predecessor=>tree%NIL
  1256           IF(.NOT.
ASSOCIATED(tree_predecessor)) tree_predecessor=>y
  1259         CALL flagerror(
"Tree node X is not associated",err,error,*999)
  1262       CALL flagerror(
"Tree is not associated",err,error,*999)
  1265     exits(
"TREE_PREDECESSOR")
  1267 999 errorsexits(
"TREE_PREDECESSOR",err,error)
  1280     INTEGER(INTG), 
INTENT(IN) :: KEY
  1282     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1285     INTEGER(INTG) :: COMPARE_VALUE
  1288     enters(
"TREE_SEARCH",err,error,*999)
  1290     IF(
ASSOCIATED(tree)) 
THEN  1291       IF(tree%TREE_FINISHED) 
THEN  1292         IF(
ASSOCIATED(x)) 
THEN  1293           CALL flagerror(
"The tree node X is already associated",err,error,*999)
  1297           IF(.NOT.
ASSOCIATED(y,tree%NIL)) 
THEN  1298             compare_value=y%KEY-key
  1299             DO WHILE(compare_value/=0)
  1300               IF(compare_value>0) 
THEN   1305               IF(
ASSOCIATED(y,tree%NIL)) 
THEN  1308                 compare_value=y%KEY-key
  1311             IF(compare_value==0) x=>y
  1315         CALL flagerror(
"The tree has not been finished",err,error,*999)
  1318       CALL flagerror(
"Tree is not associated",err,error,*999)
  1321     exits(
"TREE_SEARCH")
  1323 999 errorsexits(
"TREE_SEARCH",err,error)
  1337     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1344     NULLIFY(tree_successor)
  1346     enters(
"TREE_SUCCESSOR",err,error,*999)
  1348     IF(
ASSOCIATED(tree)) 
THEN  1349       IF(
ASSOCIATED(x)) 
THEN  1351         IF(
ASSOCIATED(y,tree%NIL)) 
THEN  1352           DO WHILE(.NOT.
ASSOCIATED(y%LEFT,tree%NIL))
  1359           DO WHILE(
ASSOCIATED(x,y%RIGHT))
  1363           IF(
ASSOCIATED(y,tree%ROOT)) 
THEN  1364             tree_successor=>tree%NIL
  1370         CALL flagerror(
"Tree node X is not associated",err,error,*999)
  1373       CALL flagerror(
"Tree is not associated",err,error,*999)
  1376     exits(
"TREE_SUCCESSOR")
  1378 999 errorsexits(
"TREE_SUCCESSOR",err,error)
 integer(intg), parameter, public tree_duplicates_allowed_type
Duplicate keys allowed tree type. 
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code. 
subroutine, public tree_insert_type_set(TREE, INSERT_TYPE, ERR, ERROR,)
Sets/changes the insert type for a tree. 
Converts a number to its equivalent varying string representation. 
Implements trees of base types. 
integer(intg), parameter, public tree_node_insert_sucessful
Successful insert status. 
subroutine, public tree_search(TREE, KEY, X, ERR, ERROR,)
Searches a tree to see if it contains a key. 
This module contains all string manipulation and transformation routines. 
subroutine tree_node_initialise(TREE, TREE_NODE, ERR, ERROR,)
Initialises a tree node. 
subroutine, public tree_detach_and_destroy(TREE, NUMBER_IN_TREE, TREE_VALUES, ERR, ERROR,)
Detaches the tree values and returns them as a pointer to the an array and then destroys the tree...
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
subroutine, public tree_output(ID, TREE, ERR, ERROR,)
Outputs a tree to the specified output stream ID. 
recursive subroutine tree_output_in_order(ID, TREE, X, ERR, ERROR,)
Outputs a tree in order to the specified output stream ID from the specified tree node...
subroutine, public exits(NAME)
Records the exit out of the named procedure. 
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
subroutine, public tree_item_delete(TREE, KEY, ERR, ERROR,)
Deletes a tree node specified by a key from a tree. 
type(tree_node_type) function, pointer tree_successor(TREE, X, ERR, ERROR)
Returns the successor of a tree at a specified tree node. 
integer(intg), parameter, public tree_node_duplicate_key
Duplicate key found for those trees that do not allow duplicate keys. 
subroutine, public tree_create_finish(TREE, ERR, ERROR,)
Finishes the creation of a tree created with TREE_CREATE_START. 
subroutine, public tree_detach(TREE, NUMBER_IN_TREE, TREE_VALUES, ERR, ERROR,)
Detaches the tree values and returns them as a pointer to the an array. 
integer(intg), parameter, public tree_no_duplicates_allowed
No duplicate keys allowed tree type. 
subroutine, public tree_node_key_get(TREE, TREE_NODE, KEY, ERR, ERROR,)
Gets the key at a specified tree node. 
subroutine, public tree_destroy(TREE, ERR, ERROR,)
Destroys a tree. 
recursive subroutine tree_detach_in_order(TREE, X, COUNT, TREE_VALUES, ERR, ERROR,)
Detaches the tree values in order from the specified tree node and adds them to the tree values array...
subroutine, public tree_item_insert(TREE, KEY, VALUE, INSERT_STATUS, ERR, ERROR,)
Inserts a tree node into a red-black tree. 
subroutine, public tree_node_value_set(TREE, TREE_NODE, VALUE, ERR, ERROR,)
Sets the value at a specified tree node. 
subroutine, public tree_node_value_get(TREE, TREE_NODE, VALUE, ERR, ERROR,)
Gets the value at a specified tree node. 
type(tree_node_type) function, pointer tree_predecessor(TREE, X, ERR, ERROR)
Returns the predeccessor of a tree at a specified tree node. 
recursive subroutine tree_node_finalise(TREE, TREE_NODE, ERR, ERROR,)
Finalises a tree node and deallocates all memory. 
integer(intg), parameter tree_red_node
The red colour type for a tree node. 
Flags an error condition. 
integer(intg), parameter tree_black_node
The black colour type for a tree node. 
subroutine, public tree_create_start(TREE, ERR, ERROR,)
Starts the creation of a tree and returns a pointer to the created tree. 
subroutine tree_initialise(TREE, ERR, ERROR,)
Initialises a tree. 
This module contains all kind definitions. 
subroutine tree_finalise(TREE, ERR, ERROR,)
Finalises a tree and deallocates all memory.