GDB for GNAT

[This document is based on "GDB for GNAT, Draft 1.10," by Paul N. Hilfinger, December 1995. Hilfinger prepared the first version of gdb modifications for Ada sysntax. His text has been minimally modified for inclusion here, mostly by adding HTML tags.]


Introduction

Ada Language Files

Ada Expression Syntax

Arrays

Selected Names

Overloading

Miscellaneous

A Note on Implementation Philosophy

Future Directions

Final Comments

Example: Arrays

Example: User-defined Operators


Introduction

This document describes changes to GDB -- as seen by its users -- for use with Ada95 programs compiled with GNAT. This draft describes the version denoted 4.15.1.gnat.1.10, a modification of GDB version 4.15.1. For purposes of distinguishing this new version from officially-released GDB, I'll refer to it in this document as "AdaGDB." This version runs with GNAT version 2.07.

The philosophy of AdaGDB is pragmatic. It does not reproduce the entire semantics of Ada, but rather a sufficient subset to cover typical debugging needs. Since this subset includes function calls, the programmer can link in a package of auxiliary debugging routines and call them from AdaGDB to produce fancier effects. Likewise, AdaGDB will take no notice of tasking and exceptions, assuming that routines in the runtime support, again callable from AdaGDB, will provide the necessary support.

Ada Language Files

GDB selects a syntax for expressions depending on its "current language," which by default is selected automatically based on the name of the source file containing the function attached to the currently-selected frame. Also by default, when the program is not executing, the current language is that of the main program. Programmers may also use the "set language" command to set the current language by hand.

AdaGDB adds "ada" as a possible value of the current language, and selects it automatically for files with extensions .ads or .adb. By means of a heuristic check, it can usually determine when the main program is written in Ada, and thus start in Ada mode.

Ada Expression Syntax

When the current language is "ada," AdaGDB accepts expressions written in an "extended subset" of Ada95 syntax. Currently, this subset includes

Arrays

AdaGDB understands both GNAT arrays with static constraints and GNAT arrays that are represented using array descriptors. It can index either, as well as printing them. This also applies to strings.

Not all dynamic arrays, however, have actual descriptors. For example, AdaGDB cannot properly handle a local variable declared

    X: STRING(1..N);

because the current version of GNAT provides insufficient information about where to find the uppper bound N). In those cases where an actual descriptor ("fat pointer") is used---as in an unconstrained array parameter---AdaGDB is able to recover the bounds. Use C syntax for printing arrays.

Selected Names

GNAT has a convention for "mangling" the expanded names of subprograms and objects declared within packages and nested packages, converting the dots into sequences of two underscores, suffixing the names with an additional integer to get unique names for overloaded subprograms declared in the same scope, and distinguishing the name of the main program with a special prefix. AdaGDB converts the names of symbols from files whose language is Ada into the standard Ada syntax for expanded names. In addition, when matching against Ada symbols, AdaGDB ignores case. In addition, AdaGDB provides, in effect, with and use clauses for all packages in a program, so that the programmer is free to call subprograms or to access package variables at the library level at any point, using only as much of the suffix of the expanded name as is needed. For example, a function Utilities.Math.sin may also be referred to as sin or Math.sin, if ambiguity does not intervene. While this is nothing like Ada semantics, we hypothesize that it is convenient from the point of view of the GDB-user. In particular, it is essentially the convention used by GDB for C programs.

Overloading

AdaGDB will detect and attempt to resolve calls on overloaded subprograms. Specifically, it employs a simple heuristic in which the types and number of the actual parameters of a call are used to select one of several candidates. Unlike full Ada, AdaGDB does not use return types, and because its visibility rules differ, it generally sees more candidate resolutions. If its heuristics don't work, it will prompt the user to make a choice. Users may call user-defined functions either with prefix syntax, as in

    C := "+"(A,B);
    C := Math."+"(A,B);

or with infix syntax, as in

    C := A+B;

There are limitations: one cannot refer to built-in operators with prefix syntax and one cannot refer to user-defined operators with infix syntax if there is a conflict with a built-in operator. Overloading resolution is the same as for ordinary functions. GDB's existing support for C++ only provides overloading of class member functions. In contrast, AdaGDB is able to handle all overloaded subprograms, not just primitive subprograms (the analogues of C++ member functions).

Miscellaneous

Somewhat experimentally, AdaGDB includes a modification of GDB that, when in Ada mode, causes all unrecognized commands to be treated as subprogram calls. For example, the command

    (gdb) printTree(T)

would normally cause an error. In AdaGDB, it is treated as

    (gdb) call printTree(T)

The utility of this feature is not certain. It was inspired by the observation that interactions between AdaGDB and complex Ada features---notably tasking and exceptions---will generally take the form of calls on special run-time library procedures. These calls function, in the user's mind, as additional GDB commands, so it makes sense to have the syntax encourage that notion.

A Note on Implementation Philosophy

Implementing the Ada language requires a number of decisions about run-time representations. Designers have considerable choice in how to represent discriminated records, record variants, tagged types, arrays with run-time bounds information, and so forth. While it would certainly be possible explicitly to encompass all of these possibilities within a single debugging format, we have taken a different course that offers distinct engineering advantages. AdaGDB required no changes to the internal interface to the debugging data, and no changes to the format itself. Instead, there are naming conventions by which the compiler communicates to AdaGDB information that is unique to the GNAT implementation of Ada. Thus, selected names are encoded with their '.'s replaced by underscores, and with numeric suffixes used to distinguish overloadings of a single subprogram name. Also, the debugger recognizes array descriptors from the distinctive names given their fields. Tagged types are recognizable from the name of the tag field. Indeed, the debugger can reconstruct a type hierarchy because each derived tagged type contains a field designating its parent's type. As a result, changes to GDB to support GNAT were largely localized to specific, new GNAT-related modules, and we were able to proceed independently of work on the debugging format. We are continuing with this philosophy in developing conventions for self-describing data structures (discriminated records in which discriminants constrain fields). When the GNAT compiler adopts them, AdaGDB will be able to handle such records.

Future Directions

Here is a list of planned or proposed changes and enhancements.

Final Comments

At the moment, AdaGDB provides almost all of the functionality of Ada that is allowed by the available debugging information. The few exceptions (see Future Directions ) are not difficult. AdaGDB is available through anonymous FTP from helen.cs.berkeley.edu in directory pub/gdb. Both source and SunOS 4.1.3 binaries are provided.


Example: Arrays

This simple example is not interesting computationally but provides an introduction to some of gdb's features for Ada. There are listings of three files, followed by a transcript of a gdb session:

    The file arrays1.ads
    The file arrays1.adb
    The file main1.adb
    Transcript: Arrays
 


The file arrays1.ads

package arrays1 is
   type Vector is array (INTEGER range <>) of INTEGER;
   subtype Vector10 is Vector(1..10);
 
   type Array2D is array (INTEGER range <>, INTEGER range <>) of INTEGER;
   subtype Array2D3_4 is Array2D(2..4, 3..6);
 
   procedure main(N: INTEGER);
   procedure f(X0: in out Vector; Y0: in out Vector10; 
               X1: Vector; Y1: Vector10);
   procedure g(A0: in out Array2D; B0: in out Array2D3_4; S: STRING);
end arrays1;
 


The file arrays1.adb

The file arrays1.adb

package body arrays1 is
    procedure main(N: INTEGER) is
        A,B: Vector10;
        C,D: Vector(1..N);
        E: Array2D(1..N, 3..N);
        H: Array2D3_4;
    begin
        for i in A'RANGE loop
            A(i) := -i; B(i) := -2 * i;
        end loop;
        for i in C'RANGE loop
            C(i) := 2*i+1; D(i) := 2*i;
        end loop;
        f(C, A, D, B);
 
        for i in E'RANGE(1) loop
           for j in E'RANGE(2) loop
              E(i,j) := 5*i + 7*j;
           end loop;
        end loop;
        for i in H'RANGE(1) loop
           for j in H'RANGE(2) loop
              H(i,j) := 2*i + 3*j;
           end loop;
        end loop;
        g(E, H, "Hello, world");
 
    end;
 
    procedure f(X0: in out Vector; Y0: in out Vector10; 
                X1: Vector; Y1: Vector10) is
    begin
        null;
    end;
 
   procedure g(A0: in out Array2D; B0: in out Array2D3_4; S: STRING) is
   begin
        null;
   end;
 
end arrays1;
 


The file main1.adb

with arrays1;
procedure main1 is
begin
    arrays1.main(8);
end;
 


Transcript: Arrays

The following is a terminal session for this rather unrepresentative program. The program was compiled using GNAT 2.07. Comments are preceded by "(gdb) #". When re-creating this demonstration, do not expect identical addresses.

(gdb) break main1
Breakpoint 1 at 0x2ebc: file main1.adb, line 4.
(gdb) run
...
 
Breakpoint 1, main1 () at main1.adb:4
4           arrays1.main(8);
(gdb) step
arrays1.main (n=8) at arrays1.adb:2
2           procedure main(N: INTEGER) is
(gdb) break f
Breakpoint 2 at 0x2d00: file arrays1.adb, line 30.
(gdb) # Just 'f' works ....
(gdb) # But we are allowed to qualify:
(gdb) break arrays1.g
Breakpoint 3 at 0x2db8: file arrays1.adb, line 36.
(gdb) cont
Continuing.
 
Breakpoint 2, arrays1.f (x0=0xf7fff5e8, y0=0xf7fff750, x1=0xf7fff560, 
    y1=0xf7fff728) at arrays1.adb:30
30          procedure f(X0: in out Vector; Y0: in out Vector10; 
(gdb) # All array parameters are printed as pointers.  
(gdb) # AdaGDB allows them to be dereferenced.
(gdb) p x0.all
$1 = {3, 5, 7, 9, 11, 13, 15, 17}
(gdb) p y0.all
$2 = {-1, -2, -3, -4, -5, -6, -7, -8, -9, -10}
(gdb) p x1.all
$3 = {2, 4, 6, 8, 10, 12, 14, 16}
(gdb) p y1.all
$4 = {-2, -4, -6, -8, -10, -12, -14, -16, -18, -20}
(gdb) # Parameters x0 and x1 are represented by fat pointers.
(gdb) # We'll change temporarily to ordinary GDB and look at what they
(gdb) # really are.
(gdb) set language c
Warning: the current language does not match this frame.
(gdb) p x0
$5 = {P_ARRAY = 0xf7fff5e8, P_BOUNDS = 0xf7fff6e0}
(gdb) p x1
$6 = {P_ARRAY = 0xf7fff560, P_BOUNDS = 0xf7fff6d0}
(gdb) set language auto
(gdb) # Attributes of arrays
(gdb) p x0'first
$7 = 1
(gdb) p x0'last
$8 = 8
(gdb) # Indexing
(gdb) p x0(1)
$9 = 3
(gdb) cont
Continuing.
 
Breakpoint 3, arrays1.g (a0=0xf7fff438, b0=0xf7fff6f8, s=0x2608)
    at arrays1.adb:36
36         procedure g(A0: in out Array2D; B0: in out Array2D3_4; S: STRING) is
(gdb) p a0'first(1)
$10 = 1
(gdb) p a0'first(2)
$11 = 3
(gdb) # 2-D indexing
(gdb) p a0(1,3)
$12 = 26
(gdb) # A more complex expression (at the moment, no special treatment
(gdb) # for the Ada BOOLEAN type, so it prints as 1).
(gdb) p a0(a0'first(1), a0'first(2)) < 42 and then s(2) = 'e'
$13 = 1
(gdb) # Ranges
(gdb) p a0'last(1)
$14 = 8
(gdb) p 4 in a0'range(1)
$15 = 1
(gdb) p 4 not in a0'range(1)
$16 = 0
(gdb) p 0 in a0'range(1)
$17 = 0
(gdb) p 4 in a0'first .. a0'last
$18 = 1
(gdb) 
 



Example: User-defined Operators

This example is adapted from a program by Michael B. Feldman. The transcript is next; file listings follow.

    Transcript: Rationals
    The file rationals.ads
    The file rationals.adb
    The file rational_io.ads
    The file rational_io.adb
    The file testrat1.adb
 


Transcript: Rationals

(gdb) # Look up the function "/" in Rationals (just its address; don't call
(gdb) # it).
(gdb) p Rationals."/"'access
Multiple matches for Rationals."/"
[0] cancel
[1] rationals."/" at rationals.adb:45
[2] rationals."/" at rationals.adb:141
> 0
cancelled
(gdb) break testrat1
Breakpoint 1 at 0xbd14: file testrat1.adb, line 8.
(gdb) # File input0 contains 7/8 and 5/6 on two lines.
(gdb) run < input0
...
 
Breakpoint 1, testrat1 () at testrat1.adb:8
8         A: Rationals.Rational;
(gdb) next
9         B: Rationals.Rational;
(gdb) next
10        C: Rationals.Rational;
(gdb) next
11        D: Rationals.Rational;
(gdb) next
12        E: Rationals.Rational;
(gdb) next 
13        F: Rationals.Rational;
(gdb) next
17        A := Rationals."/"(1,3);
(gdb) next
18        B := Rationals."/"(2,-4);
(gdb) next
19        Text_IO.Put(Item => "A = ");
(gdb) p A
$1 = {numerator = 1, denominator = 3}
(gdb) p B
$2 = {numerator = -1, denominator = 2}
(gdb) p A+B -- User-defined operator
 
$3 = {numerator = -1, denominator = 6}
(gdb) p A*B
$5 = {numerator = -1, denominator = 6}
(gdb) p a/B
$6 = {numerator = -2, denominator = 3}
(gdb) p abs(a*b)
$7 = {numerator = 1, denominator = 6}
(gdb) p "/"(5,10)    -- This always calls a user-defined function
$8 = {numerator = 1, denominator = 2}
(gdb) p a<b
$9 = false
(gdb) p a>b
$10 = true
(gdb) p a<= b
$11 = false
(gdb) next
20        Rational_IO.Put(Item => A);
(gdb) next
21        Text_IO.New_Line;
(gdb) next
A = 1/3
22        Text_IO.Put(Item => "B = ");
(gdb) break 43
Breakpoint 2 at 0xbf70: file testrat1.adb, line 43.
(gdb) cont
Continuing.
B = -1/2
Enter rational number C > Enter rational number D > 
E = A + B is -1/6
F = C * D is 35/48
 
Breakpoint 2, testrat1 () at testrat1.adb:43
43        Text_IO.Put(Item => "A + E * F is ");
(gdb) next
44        Rational_IO.Put(Item => Rationals."+"(A, Rationals."*"(E,F)));
(gdb) step
rationals."*" (r1=0xf7fff7b0, r2=0xf7fff7a8) at rationals.adb:129
129         N := Numer(R1) * Numer(R2);
(gdb) # Here, record parameters show up as pointers, since 
(gdb) # this is the way they are passed internally.  
(gdb) # The user must dereference them.
(gdb) p r1.all
$12 = {numerator = -1, denominator = 6}
(gdb) p r2.all
$13 = {numerator = 35, denominator = 48}
(gdb) cont
Continuing.
A + E * F is 61/288
 
Program exited normally.
 


The file rationals.ads

PACKAGE Rationals IS
 
-- Specification of the abstract data type for representing
-- and manipulating rational numbers.
-- All rational quantities in this package are initialized
-- to 0/1.
 
  TYPE Rational IS PRIVATE;
 
--Operators   
 
  FUNCTION "/" (X : Integer; Y : Integer) RETURN Rational;
  -- constructor: returns a rational number in lowest terms
  -- Pre :   X and Y are defined
  -- Post:   returns a rational number
  --   If Y > 0, returns Reduce(X,Y)
  --   If Y < 0, returns Reduce(-X,-Y)
  -- Raises: ZeroDenominator if Y = 0
 
  ZeroDenominator: EXCEPTION;
  
  FUNCTION Numer (R : Rational) RETURN Integer;
  FUNCTION Denom (R : Rational) RETURN Positive;
  -- selectors:
  -- Pre: R is defined
  -- Post: Numer (Denom) returns the numerator (denominator) of R;
 
  FUNCTION "<" (R1 : Rational; R2 : Rational) RETURN Boolean;
  FUNCTION "<="(R1 : Rational; R2 : Rational) RETURN Boolean;
  FUNCTION ">" (R1 : Rational; R2 : Rational) RETURN Boolean;
  FUNCTION ">="(R1 : Rational; R2 : Rational) RETURN Boolean;
  -- inquiry operators: comparison of two rational numbers
  -- Pre : R1 and R2 are defined
 
  FUNCTION "+"(R: Rational)   RETURN Rational;
  FUNCTION "-"(R: Rational)   RETURN Rational;
  FUNCTION "ABS"(R: Rational) RETURN Rational;
  -- monadic arithmetic constructors:
  -- Pre:  R is defined
 
  FUNCTION "+"(R1 : Rational; R2 : Rational) RETURN Rational;
  FUNCTION "-"(R1 : Rational; R2 : Rational) RETURN Rational;
  FUNCTION "*"(R1 : Rational; R2 : Rational) RETURN Rational;
  FUNCTION "/"(R1 : Rational; R2 : Rational) RETURN Rational;
  -- dyadic arithmetic constructors:
  -- Pre : R1 and R2 are defined
 
PRIVATE
-- A record of type Rational consists of a pair of Integer values
-- such that the first number represents the numerator of a rational
-- number and the second number represents the denominator.
 
  TYPE Rational IS RECORD
    Numerator  : Integer  := 0;
    Denominator: Positive := 1;
  END RECORD; 
END Rationals;
 


The file rationals.adb

PACKAGE BODY Rationals IS
 
-- Body of the abstract data type for representing
-- and manipulating rational numbers.
 
-- local function GCD, not provided to clients
 
  FUNCTION GCD(M: Positive; N: Positive) RETURN Positive IS
 
  -- finds the greatest common divisor of M and N
  -- Pre: M and N are defined
  -- Post: returns the GCD of M and N, by Euclid's Algorithm
 
    TempM: Natural;
    TempN: Natural;
 
  BEGIN -- GCD
    
    TempM := M;
    TempN := N;
 
    WHILE TempM /= 0 and TempN /= 0 LOOP
      IF (TempM > TempN) THEN
        TempM := TempM REM TempN;
      ELSE 
        TempN := TempN REM TempM;
      END IF;
    END LOOP;
 
    RETURN TempN+TempM;
 
  END GCD;
 
 
  -- exported operators
 
  -- constructor
 
  FUNCTION "/" (X : Integer; Y : Integer) RETURN Rational IS
  
    G: Positive;
 
  BEGIN -- "/"
 
    IF Y = 0 THEN
      RAISE ZeroDenominator;
    END IF;
 
    IF X = 0 THEN
      RETURN (Numerator => 0, Denominator => 1);
    END IF;
 
    G := GCD(ABS X, ABS Y);
    IF Y > 0 THEN
      RETURN (Numerator => X/G, Denominator => Y/G);
    ELSE
      RETURN (Numerator => (-X)/G, Denominator => (-Y)/G);
    END IF;
 
  END "/";
 
 
  -- selectors
 
  FUNCTION Numer (R : Rational) RETURN Integer IS
  BEGIN -- Numer
    RETURN R.Numerator;
  END Numer;
  
  FUNCTION Denom (R : Rational) RETURN Positive IS
  BEGIN -- Denom
    RETURN R.Denominator;
  END Denom;
 
  -- inquiry operators for comparison of Rationals
 
  FUNCTION "<" (R1 : Rational; R2 : Rational) RETURN Boolean IS
  BEGIN
    RETURN Numer(R1) * Denom(R2) < Numer(R2) * Denom(R1);
  END "<";
 
  FUNCTION ">" (R1 : Rational; R2 : Rational) RETURN Boolean IS
  BEGIN
    RETURN R2 < R1;
  END ">";
 
  FUNCTION "<=" (R1 : Rational; R2 : Rational) RETURN Boolean IS
  BEGIN
    RETURN not (R2 < R1);
  END "<=";
 
  FUNCTION ">=" (R1 : Rational; R2 : Rational) RETURN Boolean IS
  BEGIN
    RETURN not (R1 < R2);
  END ">=";
 
  -- monadic arithmetic operators
 
  FUNCTION "+"(R : Rational) RETURN Rational IS
  BEGIN -- "+"
    RETURN R;
  END "+";
  
  FUNCTION "-"(R : Rational) RETURN Rational IS
  BEGIN -- "-"
    RETURN (-Numer(R)) / Denom(R);
  END "-";
 
  FUNCTION "ABS"(R : Rational) RETURN Rational IS
  BEGIN -- "ABS"
    RETURN (ABS Numer(R)) / Denom(R);
  END "ABS";
 
  -- dyadic arithmetic operators
 
  FUNCTION "+"(R1 : Rational; R2 : Rational) RETURN Rational IS
    N: Integer;
    D: Positive;
  BEGIN -- "+"
    N := Numer(R1) * Denom(R2) + Numer(R2) * Denom(R1);
    D := Denom(R1) * Denom(R2);
    RETURN N/D;  -- compiler will use fraction constructor here!
  END "+";
 
  FUNCTION "*"(R1 : Rational; R2 : Rational) RETURN Rational IS
    N: Integer;
    D: Positive;
  BEGIN
    N := Numer(R1) * Numer(R2);
    D := Denom(R1) * Denom(R2);
    RETURN N/D;  -- compiler will use fraction constructor here!
  END "*";
 
  FUNCTION "-"(R1 : Rational; R2 : Rational) RETURN Rational IS
  BEGIN 
    RETURN R1 + (-R2);
  END "-";
 
  FUNCTION "/"(R1 : Rational; R2 : Rational) RETURN Rational IS
  BEGIN -- stub
    RETURN (Numer(R1)*Denom(R2)) / (Numer(R2)*Denom(R1));
  END "/";
 
END Rationals;
 


The file rational_io.ads

WITH Rationals;
USE Rationals;
WITH Text_IO;
PACKAGE Rational_IO IS
 
-- Specification of the input/output package for Rationals
    
  -- input operations to read a Rational from terminal or file
 
  PROCEDURE Get (Item : OUT Rational);
  PROCEDURE Get (File: IN Text_IO.File_Type; Item : OUT Rational);
  -- Pre : File is open
  -- Post: The first integer number read is the numerator of Item;
  --       the second integer number is the denominator of Item.
  --       A "/" between the two numbers is optional.
  --       The Rational constructor "/" is called 
  --       to produce a rational in reduced form.
 
 
  -- output operations to display a Rational on terminal or 
  -- write it to an external file
 
  PROCEDURE Put (Item : IN Rational);
  PROCEDURE Put (File: IN Text_IO.File_Type; Item : IN Rational);
  -- Pre : Item is defined; File is open
  -- Post: displays or writes the numerator and denominator of Item.
 
END Rational_IO;
 


The file rational_io.adb

with Ada.Text_IO;
with Ada.Integer_Text_IO;
with Rationals; use Rationals;
package body Rational_IO is
 
-- Body of the input/output package for Rationals
 
  -- input procedures
 
  procedure Get (File: in Text_IO.File_Type; Item : out Rational) is
 
    N: Integer;
    D: Integer;
    Dummy: Character;  -- dummy character to hold the "/"
 
  begin -- Get
 
    Ada.Integer_Text_IO.Get(File => File, Item => N);
    Text_IO.Get  (File => File, Item => Dummy);
    Ada.Integer_Text_IO.Get(File => File, Item => D);
    Item := N/D;
 
  end Get;
 
  procedure Get (Item : out Rational) is
 
  begin -- Get
 
    Get(File => Text_IO.Standard_Input, Item => Item);
 
  end Get;
 
  -- output procedures
 
  procedure Put (File: in Text_IO.File_Type; Item : in Rational) is
 
  begin -- Put
 
    Ada.Integer_Text_IO.Put(File => File, Item => Numer(Item), Width => 1);
    Text_IO.Put(File => File, Item => '/');
    Ada.Integer_Text_IO.Put(File => File, Item => Denom(Item), Width => 1);
 
  end Put;
 
  procedure Put (Item : in Rational) is
 
  begin -- Put
 
    Put(File => Text_IO.Standard_Output, Item => Item);
 
  end Put;
 
end Rational_IO;
 


The file testrat1.adb

WITH Text_IO;
WITH Rationals;
WITH Rational_IO; 
PROCEDURE TestRat1 IS
 
-- Very rudimentary test of package Rationals
  
  A: Rationals.Rational;
  B: Rationals.Rational;
  C: Rationals.Rational;
  D: Rationals.Rational;
  E: Rationals.Rational;
  F: Rationals.Rational;
 
BEGIN -- TestRat1
 
  A := Rationals."/"(1,3);
  B := Rationals."/"(2,-4);
  Text_IO.Put(Item => "A = ");
  Rational_IO.Put(Item => A);
  Text_IO.New_Line;
  Text_IO.Put(Item => "B = ");
  Rational_IO.Put(Item => B);
  Text_IO.New_Line;
 
  -- Read in rational numbers C and D.   
  Text_IO.Put(Item => "Enter rational number C > ");
  Rational_IO.Get(Item => C);
  Text_IO.Put(Item => "Enter rational number D > ");
  Rational_IO.Get(Item => D);
  Text_IO.New_Line;
 
  E := Rationals."+"(A,B);                   -- form the sum   
  Text_IO.Put(Item => "E = A + B is ");
  Rational_IO.Put(Item => E);  
  Text_IO.New_Line;
 
  F := Rationals."*"(C,D);                   -- form the product
  Text_IO.Put(Item => "F = C * D is ");
  Rational_IO.Put(Item => F);  
  Text_IO.New_Line;
 
  Text_IO.Put(Item => "A + E * F is ");
  Rational_IO.Put(Item => Rationals."+"(A, Rationals."*"(E,F)));
  Text_IO.New_Line;
 
END TestRat1;