Friday, September 28, 2012

AdaTutor - Advanced Topics (9)

Loose Ends and Pitfalls

This last section covers a few topics that were omitted earlier for simplicity.  We also mention some common errors made by Ada programmers.  Beginners aren't expected to understand every paragraph, so we won't ask questions here.

Some terminals and printers don't support the entire ASCII character set.  In an Ada program, the vertical bar | may be replaced with the exclamation mark !, as in when 3 ! 5 =>.  Also, a pair of sharp signs # may be replaced with a pair of colons :, as in 16:7C03:.  The quotation marks around a string constant may be replaced with percent signs if the string doesn't contain any quotation marks.  In that case, any percent signs within the string must be doubled.  For example, Put(%a 10%% increase%);.  These character replacements shouldn't be used in programs if the equipment will support the standard characters.

Section 4.9(2) of the Ada 95 RM gives a detailed definition of a static expression, but briefly, an expression is called static if it can be evaluated at compile time and isn't too complicated.  In almost every case where a constant normally appears, a static expression may also be used.  For example, an address representation clause normally takes a constant of type System.Address.  A static expression of this type is also acceptable, as in for Clock_Interrupt'Address use 16*16;.

The unary minus is always an operator and never part of a constant.  Thus -5 is actually a static expression and not a constant.  Normally, this doesn't concern the programmer, because, as we just said, static expressions can usually appear where a constant normally appears.  However, in a few special situations we can get into trouble.  For example, in Ada 83 we can write for I in 10 .. 20 loop and A : array(10 .. 20) of Float; but we can't omit the words Integer range in for I in Integer range -10 .. 10 loop and A : array(Integer range -10 .. 10) of Float;! (Ada 95 lets us write these without Integer range, however.)

Also, if a package P declares type Count is new Integer; then the unary minus operator for that type is part of the package.  If our program withs but doesn't use P, we can write A : P.Count := 1; but not B : P.Count := -1;.  We either have to use the package, rename P."-", or write B : P.Count := P."-"(1);.  Because we sometimes don't want to use the package except to avoid writing P."-"(1), Ada 95 lets us write

with P; use type P.Count;

This automatically uses only the infix operators belonging to the type P.Count.  Other operators belonging to P.Count, and other identifiers in the package P still require dot notation with the above use type clause.

The operators have precedence, so that 1 + 2 * 3 means 1 + (2 * 3).  The precedence of all the operators is given in section 4.5 of the Ada 95 RM.  A programmer should never have to look these up, because parentheses should be used for any cases that aren't obvious.  Unary minus has a low precedence, so -A mod B means -(A mod B).

If we write A, B : array(1 .. 5) of Float; then A and B have different anonymous types, and we can't write A := B;.  To fix this, write type Vector5 is array(1 .. 5) of Float; and then A, B : Vector5;, or write type Vector is array(Integer range <>) of Float; and A, B : Vector(1 .. 5);.

Ada 83 and Ada 95 will automatically convert from a universal type to a named type, but only Ada 95 will convert the other way.  For example,

   C1 : constant Integer := 1;  -- legal
   C2 : constant Integer := 2;  -- legal
   C3 : constant := C1 + C2;    -- legal only in Ada 95

When arrays are assigned, the subscripts don't have to match; only the lengths and types need match.  But in Ada 83 (not Ada 95), if a formal parameter ("dummy argument") of a subprogram is a constrained array, the subscripts in the call to the subprogram must match.  For example, the last line here will raise Constraint_Error in Ada 83:

   subtype Name is String(1 .. 30);
   John : Name;
   Line : String(1 .. 80);
   procedure Display(Person : in Name);
   ...
   John := Line(51 .. 80);   -- legal
   Display(Line( 1 .. 30));  -- legal
   Display(Line(51 .. 80));  -- Raises Constraint_Error in Ada 83

When a subprogram formal parameter is an unconstrained array, beginners often wrongly assume that the subscripts will start with one.  For example,

   Line : String(1 .. 80);
   procedure Display(S : in String) is
   begin
     for I in 1 .. S'Length loop
       ... S(I) ...
This will raise Constraint_Error if we call Display(Line(51 .. 80));.  The for statement should be changed to say for I in S'Range loop.

Remember that elaboration occurs at run time.  The following raises Program_Error by trying to activate a task before elaborating its body:

   task type T is ... end T;
   type P is access T;
   T1 : P := new T;
   task body T is ... end T;
The third line should be changed to T1 : P; and the statement T1 := new T; should be placed in the executable region.

Similarly, this procedure tries to activate a function before elaborating its body.  The initialization of J should be moved to the executable region:

   procedure Test is
   function X return Integer;
      J : Integer := X;  -- Raises Program_Error.
      function X return Integer is
      begin
         return 5;
      end X;
   begin
      null;
   end Test;

A return statement in a function is used with an object: return Answer;.  However, return may also appear without an object in a procedure; we simply write return;.  Normally, a procedure returns after executing its last statement, but an early return is possible by this method.  In the author's opinion, such early returns should be used rarely, if at all.

Many implementations of Ada allow us to insert machine code into a program. Ada 95 compilers that allow machine code insertions provide a package System.Machine_Code which usually contains a rather complex record definition representing the format of a machine instruction.  We can write a procedure or function that withs and uses that package.  In place of the usual Ada statements in the executable region, we write record aggregates, each one representing a machine code instruction.  Since the package System.Machine_Code varies greatly from one implementation to the next, you'll have to consult the compiler documentation.

Ada 83 compilers that allow machine code insertions sometimes provide a package Machine_Code and sometimes provide a pragma, such as pragma Native, which can be inserted in the middle of a procedure, function, etc.  Again, the details vary widely from one implementation to the next, and you'll have to consult the compiler documentation.

In the unusual case of a for loop index hiding an explicitly declared object of the same name, the explicitly declared object can be referenced inside the loop. Simply use dot notation with the name of the compilation unit (function, procedure, etc.) For example, the following is legal:

   procedure Main is
      Ix : Float;
      J  : Integer;
   begin
      Ix := 3.2;
      for Ix in 1 .. 10 loop
         Main.Ix := 6.0;
         J := Ix;
      end loop;
   end Main;
Inside the loop, Ix refers to the loop index, and the explicitly declared object can be referenced by writing Main.IxOutside the loop, Ix refers to the explicitly declared object, and the loop index doesn't exist.

In the rare case of an aggregate containing just one element, we must use named notation rather than positional notation.  For example, the last line is illegal in the following program segment, because the right hand side is a Float rather than an array of one Float.

   type Vector is array(Integer range <>) of Float;
   A : Vector(1 .. 1);
   ...
   A := (1 => 2.3);  -- legal
   A := (2.3);  -- illegal

Of course, it's OK to use positional notation in calls to subprograms with only one parameter, for example, Put_Line("Hello");.

Annexes C through H of the Ada 95 RM describe optional features of Ada 95.  An Ada 95 compiler may implement any, all, or none of these.  Consult your compiler documentation for details.  The optional Ada 95 features are as follows:

  • ANNEX C. Systems Programming: Access to machine operations, interrupt support, shared variable control, task identification, etc.
  • ANNEX D. Real-Time Systems: Dynamic task priorities, scheduling, dispatching, queueing, monotonic time, etc.  An implementation that provides this must provide Systems Programming as well.
  • ANNEX E. Distributed Systems: Multiple partitions of an Ada program executing concurrently.
  • ANNEX F. Information Systems: Decimal types for handling monetary values. "Picture" strings to simplify output of monetary amounts.
  • ANNEX G. Numerics: Complex numbers, improved accuracy requirements for floating-point arithmetic, random number generation, etc.
  • ANNEX H. Safety and Security: Adds requirements on compilers for safety-critical systems.

Well, we haven't covered all there is to know about Ada, but this has been a very thorough course.  If you've come this far and completed the six Outside Assignments, you should be an excellent Ada programmer.  To continue learning, start doing all your casual programming in Ada.  If you need a simple program to balance your checkbook, write it in Ada!  At this point, switching to Ada for all your programming will do you much more good than further instruction from a tutorial program.

The best way to answer any remaining questions about Ada is to "ask the compiler" by writing a brief test program, especially if your compiler is validated.  You can also look in the Ada 95 RM, which, by definition, does cover all of the Ada language.  However, the RM isn't easy reading!

The best way to debug a short program is often to execute it by hand, with pencil and paper.  You can also add extra statements to the program to display intermediate results, and remove them later.

We wish you success with Ada, and welcome your comments and suggestions!

< prev

Wednesday, September 26, 2012

AdaTutor - Advanced Topics (8)

Pragmas

A pragma is a message to the compiler.  The pragmas that are predefined by Ada are all referenced in Annex L of the Ada 95 RM; we'll discuss the most important ones here.  A particular implementation of Ada need not honor all the predefined pragmas, and it may add some of its own.  (One implementation of Ada adds a pragma Time_Slice, used with tasking.)  Unlike representation clauses, unimplemented predefined pragmas do not cause error messages; the compiler simply ignores them.  This enhances program portability.  Any additional pragmas added by a particular implementation of Ada will be explained in the compiler documentation.  The most important predefined pragmas are these:

The statements pragma List(On); and pragma List(Off); turn on and off the compiler listing.  Also, pragma Page; will cause the compiler listing to start a new page, if the listing is turned on.  These pragmas are allowed almost anywhere in the program.

Within the declarative region we can write pragma Optimize(Time); or pragma Optimize(Space); to ask the compiler to optimize the program for minimum execution time or minimum memory usage.

We can write pragma Inline(...); with the name of a subprogram to ask the compiler to write inline code in place of every call to the subprogram.  Even implementations of Ada that honor this pragma will ignore it if the subprogram is recursive.

We can call a subprogram or reference an object written in another langauge with the Ada 95 pragma Import.  This pragma takes three parameters: the name of the language, the Ada name of the subprogram or object, and an optional external linker name for the subprogram or object.  Similarly, a program written in another language can call an Ada program with the Ada 95 pragma Export, taking the same three parameters.  The Ada 95 pragma Convention specifies that objects of a type should be stored using the conventions of another language.  Pragma Convention takes two parameters: the name of the language and the Ada name of the type whose storage convention is being specified.

Ada 83 provides only a pragma Interface.  It is similar to the Ada 95 pragma Import, but is useful only to call a subprogram written in another language, not to reference an object.  Pragma Interface takes only two parameters: the name of the language and the subprogram name.

We can ask the compiler to minimize memory occupied by a record or array by writing, after the type declaration, pragma Pack(...); with the name of the type.  Note that the specification for package Standard (in Annex A.1 of the Ada 95 RM) contains pragma Pack(String); after the definition of type String.

Package System defines a subtype of Integer called Priority.  We can assign a priority to a task by writing, in the specification, pragma Priority(...); with a parameter of subtype System.Priority.  Higher numbers denote greater urgency.

The pragma Suppress can be used to ask the compiler to turn off certain checks, such as Constraint_Error.  It's dangerous and shouldn't be used unless absolutely necessary because of time or memory constraints.

Question

In the author's opinion, which one of these is not dangerous?
  1. Ada.Unchecked_Deallocation
  2. pragma Pack
  3. pragma Suppress

< prev   next >

AdaTutor - Advanced Topics (7)

Unchecked Conversion and Unchecked Deallocation

Ada comes with a generic function Ada.Unchecked_Conversion and a generic procedure Ada.Unchecked_Deallocation.  (In Ada 83, the names don't contain Ada., and Ada 95 accepts the shorter names for compatibility.)  They can be instantiated for any type.  Both are somewhat dangerous to use, but we'll describe them briefly.  Their specifications (slightly simplified) are below; the Ada 83 specifications don't have (<>).

   generic
      type Source(<>) is limited private;
      type Target(<>) is limited private;
   function Ada.Unchecked_Conversion(S : Source) return Target;

   generic
      type Object(<>) is limited private;
      type Name       is access Object;
   procedure Ada.Unchecked_Deallocation(X : in out Name);

Ada.Unchecked_Conversion "converts" from one type to another without doing any arithmetic or bit manipulation, letting us look at an object of one type as if it were of another type.  (This is similar to using EQUIVALENCE in Fortran.)

The results of using Ada.Unchecked_Conversion may be unpredictable if the two types don't occupy the same amount of storage.

One use of Ada.Unchecked_Conversion might be to allow us to and two Integers.  (Ada 95 allows us to and two objects of a modular type, but not two Integers.) Some Ada compilers come with a package that enables us to and two Integers, but many compilers have no such package.  Suppose that types Integer and Boolean occupy the same amount of storage.  If our program says with Ada.Unchecked_Conversion; we could write

function Int_To_Bool is new Ada.Unchecked_Conversion(Integer, Boolean);
function Bool_To_Int is new Ada.Unchecked_Conversion(Boolean, Integer);
function "and"(Left, Right : in Integer) return Integer is
begin
   return Bool_To_Int(Int_To_Bool(Left) and Int_To_Bool(Right));
end "and";

Using Ada.Unchecked_Conversion usually destroys program portability.

Ada.Unchecked_Deallocation allows us to free the memory occupied by an object accessed through an access type.  Some systems automatically reclaim memory when it's needed.  However, the execution time for that so-called garbage collection tends to be long and unpredictable.  Suppose we have type P is access Link; and Ptr : P;.  Also suppose that we no longer need the object accessed by Ptr and we're sure that no other objects access the same object as Ptr.  If our program says with Ada.Unchecked_Deallocation; we can write

procedure Free is new Ada.Unchecked_Deallocation(Link, P);
...
Free(Ptr);
This will release the memory occupied by the object accessed by Ptr, and then set Ptr to null.  But there's a danger.  If there's another object that accessed what Ptr accessed, it now accesses released memory.  A reference through such an object will have unpredictable results.  In general, it's best to let the system handle the reclaiming of memory.  That way there's no danger of dangling references.

< prev   next >

AdaTutor - Advanced Topics (6)

Representation Clauses and System

Ada normally represents an enumeration type internally with successive integers starting at zero.  For example, if we write

type Command is (Left, Right, Forward, Back);
the compiler will normally represent Left with 0, Right with 1, etc.  Usually this doesn't concern the programmer.  However, after the above declaration, we can specify the internal representation with a representation clause like this:
for Command use (Left => 1, Right => 2, Forward => 4, Back => 8);
We might want to do that if, for example, we're sending a value of type Command to some hardware which will interpret the bit patterns.  The values must be assigned in increasing order with no duplications, but gaps are permitted.  The attributes 'Succ, 'Pred, 'Pos, and 'Val are not affected. Thus Command'Pos(Back) is still 3.

Ada lets us specify the Size, in bits, of the objects of a given type:

   type Num is range 0 .. 100;
   for Num'Size use 8;
Similarly, we can specify the attribute 'Small for a fixed point type:
   type Voltage is delta 0.01 range -20.0 .. 20.0;
   for Voltage'Small use 1.0/128.0;
These attributes can also be read:
   I : Integer := Num'Size;
   F : Float := Voltage'Small;

Before discussing the remaining types of representation clauses, we must briefly mention the package System that comes with Ada.  System contains implementation dependent specifications.

A brief outline of package System is in section 13.7 of the Ada 95 RM.  However, the full package specification should appear in the documentation that came with your compiler.  Of interest here is the type Address.  In our examples, we'll assume that System.Address is some integer type.  (On some PC implementations of Ada, type System.Address is a bit more complicated.)

We can specify the absolute address of a variable, a constant, a task entry, a procedure, or a package, with a constant of type System.Address.  In Ada 83 the program must with System.  This is useful for memory-mapped I/O, interrupt handlers, etc.  For example:

   Modem_Control : Integer;
   for Modem_Control'Address use 16#7C00#;
   task Interrupt_Handler is
      entry Clock_Interrupt;
      for Clock_Interrupt'Address use 16#100#;
   end Interrupt_Handler;
   procedure Keystroke;
   for Keystroke'Address use 16#200#;

In Ada 83, the syntax is for Keystroke use 16#200#, and Ada 95 accepts this older syntax for compatibility.

Finally, we can specify how records are stored.  This example forces A and B to be stored in bits 0 .. 3 and 4 .. 7 of byte 0 of the record, and C and D to be packed into byte 1.  The optional clause for Packed'Alignment use 2; specifies that all records of type Packed will begin at even addresses:

   type Nibble is range 0 .. 15;
   type Packed is record
       A, B, C, D : Nibble;
   end record;
   for Packed'Alignment use 2;
   for Packed use record
      A at 0 range 0 .. 3;
      B at 0 range 4 .. 7;
      C at 1 range 0 .. 3;
      D at 1 range 4 .. 7;
   end record;

In Ada 83, we use the clause record at mod 2; after for Packed use, rather than saying for Packed'Alignment use 2; before for Packed use:

   type Nibble is range 0 .. 15;
   type Packed is record
      A, B, C, D : Nibble;
   end record;
   for Packed use record at mod 2;
      A at 0 range 0 .. 3;
      B at 0 range 4 .. 7;
      C at 1 range 0 .. 3;
      D at 1 range 4 .. 7;
   end record;

Again, Ada 95 accepts this older syntax for compatibility.

An implementation of Ada need not accept most representation clauses to meet the standard.  If any clause is rejected, an error message will be displayed.

Question

   type Answer is (Yes, No, Maybe);
   for Answer use (Yes => 1, No => 2, Maybe => 4);
What is Answer'Val(20)?
  1. Answer'Val(2) is No.
  2. Answer'Val(2) is Maybe.

< prev   next >

Tuesday, September 25, 2012

AdaTutor - Advanced Topics (5)

Subprogram Parameters with Generics

The generic part of a subprogram or package can specify a dummy subprogram as well as a dummy type or object.  This is similar to using subprograms as parameters in Algol and Pascal, and to using the little-known keyword EXTERNAL in Fortran.  In Ada, we simply precede the dummy subprogram specification with the keyword with in the generic part.  This use of the word with has nothing to do with context clauses.  Here's the specification of a generic function that has one dummy function specification in the generic part:

generic
   with function Dummy(X : in Float) return Float;
function Definite_Integral(Lower_Limit, Upper_Limit : in Float)
   return Float;

If we instantiate Ada.Numerics.Generic_Elementary_Functions for type Float, and use that instantiation, we get functions like Cos for type Float.  We could then instantiate Definite_Integral for Cos, and make use of it as follows:

 Answer : Float;
 function Definite_Integral_Of_Cos is new Definite_Integral(Cos);
 ...
 Answer := Definite_Integral_Of_Cos(Lower_Limit => 0.0,
                                    Upper_Limit => 1.5708);

generic
   with function Dummy(X : in Float) return Float;
function Definite_Integral(Lower_Limit, Upper_Limit : in Float)
   return Float;

function Definite_Integral(Lower_Limit, Upper_Limit : in Float)
   return Float is
   Mult : array(0 .. 6) of Float := (1.0, 4.0, 2.0, 4.0,
                                     2.0, 4.0, 1.0);
   Sum  : Float := 0.0;
   X    : Float;  -- the independent variable
begin
   for I in 0 .. 6 loop
      X   := Lower_Limit
             + (Float(I) / 6.0) * (Upper_Limit - Lower_Limit);
      Sum := Sum + Mult(I) * Dummy(X);
   end loop;
   return Sum * (Upper_Limit - Lower_Limit) / 18.0;
end Definite_Integral;
This is one possible body for the generic function Definite_Integral.  (We've repeated the specification above the body for reference.)  This function integrates the function Dummy between the two limits by evaluating Dummy at seven points and using Simpson's rule.  (Definite_Integral could be improved by making the number of points a generic parameter, instead of fixing it at seven.)

< prev   next >

AdaTutor - Advanced Topics (4)

Renaming

A subprogram can be renamed in Ada.  This allows us to avoid the dot notation without a use clause.  For example, if our program withs Ada.Text_IO, we can write:

procedure Print(Object : in String) renames Ada.Text_IO.Put_Line;

We can now call Print instead of Ada.Text_IO.Put_Line.  The old name is still available.  Note that renaming can change the names of the formal parameters ("dummy arguments").  Renaming can also add, delete, or change default values.  When used in a package in Ada 83, a renaming declaration like the above must appear in the specification, not the body.  In Ada 95, the specification can say simply procedure Print(Object : in String);, and the renames declaration above may appear in the body.

We can also rename task entries as procedures.  This is the only way to avoid the dot notation when calling a task entry.

A function can be renamed as an infix operator, if it has the right number and types of parameters.  Also, an infix operator can be renamed as a function.  For example, earlier we defined type Vector and wrote:

function "*"(Left, Right : in Vector) return Float;
This could be renamed as follows:
function Dot_Product(X, Y : in Vector) return Float renames "*";

Renaming can get around the restriction that library subprograms can't be infix operators.  We can use a normal function name for the library, and rename it as an infix operator for our program.  Similarly, we can get around the rule that library subprograms can't overload each other.  We can give subprograms distinct names in the library, and rename them in our program to overload each other.

An attribute that takes a parameter, such as 'Pred and 'Succ, can be renamed as a function.  For example,

function Next(M : in Month_Type) return Month_Type
   renames Month_Type'Succ;

Record components can be renamed.  If D is of type Date, we can write

Y : Integer renames D.Year;

Exceptions can also be renamed.  For example,

No_Such_File : exception renames Ada.Text_IO.Name_Error;
The ability to rename exceptions is used by Ada.Text_IO, Ada.Sequential_IO, Ada.Direct_IO, etc.  Earlier, when we gave a simplified specification of Ada.Text_IO, we pretended that the exceptions Status_Error, Mode_Error, End_Error, etc. were defined in that package.  Actually, they're defined in a package Ada.IO_Exceptions.  Ada.Text_IO withs that package, and declares
Status_Error : exception renames IO_Exceptions.Status_Error;
Mode_Error   : exception renames IO_Exceptions.Mode_Error;
etc.  Other packages like Ada.Direct_IO and Ada.Sequential_IO do exactly the same thing.  Suppose Random_IO is an instantiation of Ada.Direct_IO.  Then Ada.Text_IO.File_Type and Random_IO.File_Type are two different types, but Ada.Text_IO.Status_Error and Random_IO.Status_Error are the same exception, because they both rename Ada.IO_Exceptions.Status_Error.

A subtype can be used to achieve the effect of renaming a type.  For example,

subtype File is Ada.Text_IO.File_Type;

< prev   next >

Thursday, September 20, 2012

Ref: Change Your Forgotten Windows Password with the Linux System Rescue CD

Ref: Change Your Forgotten Windows Password with the Linux System Rescue CD In summary
  • boot with system rescue CD
  • mount windows partition with ntfs-3g
  • cd Windows/System32/config under your windows partion
  • use chntpw –l SAM to list user
  • chntpw –u username SAM to clear or reset password
  • unmount windows partion and reboot

Wednesday, September 19, 2012

AdaTutor - Advanced Topics (3)

Ada.Sequential_IO, Ada.Direct_IO, and Ada.Streams.Stream_IO

Ada.Text_IO creates, reads and writes text files that can be typed on the screen or printed.  Ada also provides generic packages Ada.Sequential_IO and Ada.Direct_IO, which create, read, and write binary files.  (In Ada 83, the names don't contain Ada., and Ada 95 accepts the shorter names for compatibility.)

Binary files usually can't be typed or printed, but they tend to be more efficient than text files, because the computer doesn't have to convert numbers between its internal representation and text to read and write binary files.

The full specifications of Ada.Sequential_IO and Ada.Direct_IO are in Annex A.8.1 and A.8.4 of the Ada 95 RM.  They begin as follows:

   ...
   generic
      -- "(<>)" is omitted in Ada 83.
      type Element_Type(<>) is private;
   -- "Ada." is omitted in Ada 83.
   package Ada.Sequential_IO is
     ...

   ...
   generic
      type Element_Type is private;
   -- "Ada." is omitted in Ada 83.
   package Ada.Direct_IO is
      ...

Like Ada.Text_IO, both packages have procedures to Create, Open, and Close files, but the I/O procedures are called Read and Write, rather than Get, Put, Get_Line, and Put_Line.  The first parameter is an object of type File_Type; the second is the item being read or written.  Ada.Sequential_IO always reads and writes sequentially, but Ada.Direct_IO is capable of random access.  In Ada.Direct_IO, an optional third parameter in Read and Write tells the procedure the position in the file to read From or write To; this parameter is sometimes referred to as the "index."  The start of the file is position 1.

Both Ada.Sequential_IO and Ada.Direct_IO can be instantiated for any non-limited type.  In Ada 95, Ada.Sequential_IO can be instantiated for class-wide types.  This means that a file created by Ada.Sequential_IO can be heterogeneous, containing objects of different types belonging to the same class.  However, Ada.Direct_IO can't be instantiated for class-wide types.  Files created by Ada.Direct_IO must be homogeneous (containing objects of one type only), because of the ability to use an index.  (We'll discuss Ada.Streams.Stream_IO shortly.)

Ada.Direct_IO provides a File_Mode of Inout_File as well as the usual In_File and Out_File.  In Ada 95, Ada.Sequential_IO, like Ada.Text_IO, provides an additional File_Mode, Append_File, not present in Ada 83.  Note that Ada.Text_IO and instantiations of Ada.Sequential_IO and Ada.Direct_IO each define their own File_Type, so we can't open a file with one package and then do I/O on it with another.

If you like, you can examine the file ADATU400.ADA for an example of the use of Direct_IO.  (This file is written to compile with either Ada 83 or Ada 95, so it uses the name Direct_IO rather than Ada.Direct_IO.)  AdaTutor creates a subtype for a block of characters and then instantiates Direct_IO for that subtype.  It then opens ADATUTOR.DAT with mode In_File so that it can read blocks of characters by random access.  This enables AdaTutor to find and display any screen quickly.  The preliminary comments in ADATU400.ADA describe the format of the data file ADATUTOR.DAT in detail.

You may also want to examine the files DAT2TXT.ADA and TXT2DAT.ADA, which are much simpler than ADATU400.ADA.  Again, these were written to compile with either Ada 83 or Ada 95.  These two programs are used when installing AdaTutor on non-PC computers.  Their use is described on pages 41-42 of your printed course notes.  They with both Text_IO and Direct_IO, because they access a text file as well as a binary file.  However, to avoid confusion between the two packages, they use neither Text_IO nor the instantiation of Direct_IO.  Dot notation is used instead.

DAT2TXT.ADA and TXT2DAT.ADA could have used Sequential_IO instead of Direct_IO, because they don't do random access.  (In contrast, ADATU400.ADA does random access and requires Direct_IO).  However, the file written by TXT2DAT.ADA is meant to be read by ADATU400.ADA, using an instantiation of Direct_IO, on a non-PC computer.  To avoid any possible incompatibilities between different file types on an unknown system, TXT2DAT.ADA produces the file with an instantiation of Direct_IO, because ADATU400.ADA will use a similar instantiation of Direct_IO to read the file.

Question

Which commented line is illegal?
   with Ada.Text_IO, Ada.Sequential_IO; --
   use Ada.Text_IO, Ada.Sequential_IO;  -- 1
   procedure IO is
      subtype Line is String(1 .. 80);
      type Screen is array(1 .. 24) of Line;
      package Line_IO is new Ada.Sequential_IO(Line); --
      use Line_IO;                                    -- 2
      package Screen_IO is new Ada.Sequential_IO(Screen); --
      use Screen_IO;                                      -- 3
   begin
      null;
   end IO;

The specification of the Ada 95 package Ada.Streams.Stream_IO is in Annex A.12.1 of the Ada 95 RM.  This package enables us to create a truly heterogenous file.  It's not generic, so all the files it creates are of the same type.  The file modes available are In_File, Out_File, and Append_File.

Suppose we define type Date as before, and we want to create a file containing dates and random-length strings.  We Create a file in the same way as with Ada.Text_IO.  To write an object of a constrained type like Date to the file, we give the name of the type followed by the attribute 'Write.  (Similarly, to read, we use the attribute 'Read.)  The first parameter is of type Stream_Access; the second is the object being read or written.  The first parameter is obtained from the following function in Ada.Streams.Stream_IO:

   function Stream(File : in File_Type) return Stream_Access;

For example if we with and use Ada.Streams.Stream_IO and we have F : File_Type; and D : Date;, we can Create a file with F and then write

   Date'Write(Stream(F), D);

If we use 'Write or 'Read with an unconstrained type, the constraint information is not read or written.  So with unconstrained types, we should use the attributes 'Output and 'Input instead of 'Write and 'Read.  For example, if we want to write the string "Hello" to our file F, we would say

   String'Output(Stream(F), "Hello");

This would first store the string bounds (1 and 5), and then store the five characters of the string.

We can write our own procedures to be called by 'Read, 'Write, 'Input, and 'Output if we want to.  Our procedures can do anything they want - they don't even have to do I/O!  For example:

procedure My_Date_Write(
     Stream : access Ada.Streams.Root_Stream_Type'Class;
     D      : in Date);
  for Date'Write use My_Date_Write;

However, overwriting the standard attributes is normally not recommended.

Here's a program that stores a String, a Date, another String, and another Date in a heterogeneous file:

   with Ada.Streams.Stream_IO; use Ada.Streams.Stream_IO;
   procedure Test is
      type Date is ...
      F : File_Type;
   begin
      Create(F, Out_File, "STREAM.DAT");
      String'Output(Stream(F), "Ada");
      Date'Write(Stream(F), (12, Dec, 1815));
      String'Output(Stream(F), "United States");
      Date'Write(Stream(F), ( 4, Jul, 1776));
      Close(F);
   end Test;

After executing the above, we could Open the file in mode In_File, and then use 'Input, 'Read, 'Input, and 'Read in that order to read the four items back.

Ada.Streams.Stream_IO can do random as well as sequential access.  We can call

   procedure Set_Index(File : in File_Type; To : in Positive_Count);
in Ada.Streams.Stream_IO to set the index before using any of the four attributes mentioned above.  The index of the first byte of the file is 1.

However, we have to know where to set the index, and that can vary from one implementation of Ada 95 to the next.  For example, when we ran the above program Test on a particular Ada 95 system, it created a 50-byte file.  That's because the Ada compiler that we used allows four bytes for each Integer, one byte for each object of an enumeration type like Month_Type, and of course one byte for each Character.  Recall that two Integers are stored before each String (the bounds).

With that particular Ada 95 compiler we could retrieve the second Date stored by adding D : Date; to our declarations and executing

   Open(F, In_File, "STREAM.DAT");
   Set_Index(F, 42);
   Date'Read(Stream(F), D);
   Close(F);

However, with Ada 95 compilers that use a different size for Integer, the call to Set_Index would have to be changed.

In contrast, when we instantiate Ada.Direct_IO for type Date, for example, the first Date in the file is always at position 1, the second Date is always at position 2, etc., regardless of the number of bytes per Date.  In this case, the difference between position 1 and position 2 is the length of a Date, not one byte.  If our instantiation of Ada.Direct_IO is called Date_IO, and we declare D : Date; and F : Date_IO.File_Type;, we can write

   Date_IO.Read(File => F, Item => D, From => 2);
and be certain that we have read the second Date in the file.

Thus, using an instantiation of Ada.Direct_IO instead of using Ada.Streams.Stream_IO makes our program more portable, at the expense of requiring the file to be homogeneous.  Ada.Direct_IO has another advantage: mode Inout_File is available with Ada.Direct_IO, but not with Ada.Streams.Stream_IO.

< prev   next >

AdaTutor - Advanced Topics (2)

More Attributes

Ada provides many attributes, all described in Annex K of the Ada 95 RM.  The most important ones that we haven't yet discussed are these:

For any real type or subtype (floating or fixed), 'Small and 'Large are the smallest and largest positive model numbers.  Thus Float'Small is the difference between zero and the next larger number in type Float.  Also, for any floating point (sub)type, 'Model_Epsilon is the difference between one and the next larger number.  (In Ada 83, 'Model_Epsilon is simply called 'Epsilon.)  We'll use 'Epsilon in an Ada 83 generic function in a moment.

For a floating point (sub)type, 'Digits returns the value given for digits in the declaration, and for a fixed point (sub)type, 'Delta returns the value given for delta in the declaration.  These attributes may not seem too useful, because the programmer already knows what he or she wrote in the declarations.  However, they're useful in generic packages and subprograms.  For example, if the generic part says type Dummy is delta <>;, the body can use Dummy'Delta.

Ada 95 has 'Max and 'Min, both of which take two scalar parameters.  For example, if we have I : Integer := 1; and J : Integer := 2;, then Integer'Max(I, J) is 2.

For any discrete (sub)type, 'Width gives the maximum length that the attribute 'Image can produce.  Boolean'Width is 5 because “False” has length 5.  With our earlier definition of Rainbow_Color, Rainbow_Color'Width is 6.  For versions of Ada using 16-bit Integers, Integer'Width is also 6, the length of &lduqo;-32768”.

'Count is used with the name of a task entry.  It returns the number of calls presently queued on the entry.  'Terminated is of type Boolean.  It's used with a task name, and tells if the task is terminated.

Ada 95 has a package Ada.Numerics.Generic_Elementary_Functions containing a square root (Sqrt) function, but Ada 83 doesn't have this package.  As an exercise, let's write a generic Ada 83 function to compute the square root for any floating point type, using Newton-Raphson iteration.

Let's suppose that G is our guess of the square root of X.  If our guess is correct, then X/G equals G.  If our guess is too low, then X/G is larger than G, and if our guess is too high, then X/G is smaller than G.  The Newton- -Raphson method simply says that our next guess is the average of G and X/G (one of which is too high, and the other of which is too low).  For example, if we want to compute the square root of 9.0 and our first guess is 9.0, successive guesses are 5.0, 3.4, 3.02352941, 3.00009155, 3.00000000.  Note that convergence is very rapid.

However, the problem in writing a program like this is knowing when to stop the iteration.  We'll use the Ada 83 attribute 'Epsilon (called 'Model_Epsilon in Ada 95).  Since G*G/X should be 1.0, we'll quit when the absolute value of the difference between G*G/X and 1.0 is less than or equal to 3.0 times Epsilon.  Recall that Dummy'Epsilon is the difference between 1.0 and the next higher number for type Dummy.  If we use 1.0 times Epsilon, the loop might never terminate, and if we use 10.0 times Epsilon, we might not get full precision.  So we'll use 3.0 times Epsilon.  Here's our function:

   generic
      type Dummy is digits <>;
   function Sqrt(X :in Dummy) return Dummy;
   function Sqrt(X :in Dummy) return Dummy is
      Guess : Dummy := X;
   begin
      if X < 0.0 then
         raise Constraint_Error;
      end if;
      while X /= 0.0 and then abs(Guess*Guess/X - 1.0)
                               > 3.0*Dummy'Epsilon loop
         Guess := (X/Guess + Guess) * 0.5;
      end loop;
      return Guess;
   end Sqrt;

We tested our Sqrt with an implementation of Ada 83 having types Float, Long_Float, and Long_Long_Float.  The last gives at least 33 decimal digits of precision.  Sqrt was instantiated for all three floating point types, as was Float_IO to display the results.  When tested with the three types, all displayed digits of the answers were correct.

< prev   next >

AdaTutor - Advanced Topics

Packages Standard and Ada.Characters.Latin_1

Ada comes with a package Standard.  However, unlike all the other packages, Standard is needed by every Ada compilation unit.  Therefore, Standard is automatically withed and used in every compilation.  It need not be mentioned in a context clause.  Standard contains the definitions built into the Ada language, such as type Boolean is (False, True);.  A listing of the package specification is in Annex A.1 of the Ada 95 RM.  Thus, the full name for the type Boolean is Standard.Boolean, the full name for Integer is Standard.Integer, etc.  Naturally, this normally need not concern the programmer.  The dot notation is automatic because Standard is automatically used in every compilation.

Ada 95 has a package Ada.Characters.Latin_1, defined in Annex A.3.3 of the Ada 95 RM.  This package gives names to all of the unprintable 8-bit characters, and some of the printable ones.  For example, the unprintable "bell" character is named BEL.  If our program withs and uses this package and Ada.Text_IO, then Put(BEL); will beep the terminal.

Ada 83 doesn't have Ada.Characters.Latin_1, but it has a package ASCII inside package Standard.  This package gives names to all of the unprintable ASCII characters and some of the printable ones.  (The ASCII characters are the first 128 of the 256 8-bit characters.)  Ada 95 also has package ASCII for compatibility, but with Ada 95 it's better to use Ada.Characters.Latin_1.

Since ASCII is inside Standard, we never have to write a with clause for it.  But ASCII isn't automatically used.  If we want the dot notation for ASCII to be automatic, we have to provide a use clause.

For example, either of these Ada 83 programs will beep the terminal:

   with Text_IO; use Text_IO;    with Text_IO; use Text_IO;
   procedure Beep is             procedure Beep is
   begin                           use ASCII;
     Put(ASCII.BEL);             begin
   end Beep;                       Put(BEL);
                                 end Beep;

Note the placement of use ASCII; in the second example.  It's similar to the placement of use My_Int_IO; in ADD.ADA, which we discussed early in the course.

An Alternative to Infix Notation, and Use Type

Earlier we learned to define and use infix operators like

   type Vector is array(Integer range <>) of Float;
   function "*"(Left, Right : in Vector) return Float;
   A, B : Vector(1 .. 10);
   F    : Float;
   ...
   F := A * B;

An alternative notation equivalent to F := A * B; is F := "*"(A, B);.  Why would anyone want to use this clumsier notation?  If our function is in a package Math that the calling program withs but for some reason doesn't use, we could use dot notation and write F := Math."*"(A, B);.  But we couldn't use dot notation directly with infix operators, as in F := A Math.* B; or even F := A Math."*" B;.  Both of those are illegal.  The alternative notation can also be used to emphasize that an operator comes from package Standard.  For example, if I, J, and K are Integers, we could write I := Standard."*"(J, K);, which is equivalent to I := J * K;.

In Ada 95, a context clause can say use type, followed by the name of a type or subtype in a package.  This makes the dot notation automatic only for infix operators for that type or subtype.   For example, if we have a package Math containing the definition of a type Vector and a * operator for Vectors, as above, we can write

    with Math; use type Math.Vector;
    ...
      A, B : Math.Vector(1 .. 10);
      F    : Float;
    ...
      F := A * B;

Here we were able to write F := A * B; instead of F := "*"(A, B); or F := Math."*"(A, B); because we said use type Math.Vector; and the * here is an infix operator for that type.  However, in declaring A and B, we still had to write Math.Vector, because use type applies only to infix operators for the type or subtype named.

Question

Assuming X, Y, and Z have been declared Float, which one of the following is illegal?
  1. X := Y / Z;
  2. X := Y Standard."/" Z;
  3. X := Standard."/"(Y, Z);

< prev   next >

Tuesday, September 18, 2012

AdaTutor - More Records and Types (4)

Fixed Point, Modular, and Universal Types

The only fixed point type defined in package Standard is Duration.  However, Ada lets us define our own fixed point types.  We specify the accuracy with the reserved word delta, and a range constraint is required.  For example,

   type Voltage is delta 0.01 range -20.0 .. 20.0;

This guarantees that the objects of type Voltage will be represented with at least an accuracy of 1/100.  Since the computer is binary, Ada will choose an internal representation at least as accurate as 1/128.  It might use even greater accuracy, for example, 1/256.  In any event, it's guaranteed that the accuracy is at least as good as that requested.

It's possible to make a request that a particular implementation of Ada can't handle.  For example, if we write

   type Voltage is delta 1.0E-10 range 0.0 .. 1.0E9;
the Ada compiler that we're using may have to report that it has no internal representation that satisfies this requirement.  (Almost any delta would be unreasonable if Ada didn't require range constraints on all fixed point types.)

The set of numbers that can be represented exactly by any implementation of Ada that accepts a type definition like the above is called the model numbers of that type.  This applies to floating types as well as fixed, for example,

   type W is digits 5 range 0.0 .. 100.0;

A particular implementation may represent additional numbers exactly; these are called safe numbers.  The safe numbers are a superset of the model numbers; their range usually is a little larger.

We can add and subtract objects of a fixed point type.  However, if we multiply or divide them in Ada 83, we must immediately convert the result to the same or another numeric type before we can store it.  For example,

   V1, V2, V3 : Voltage;
   ...
   V1 := V2+V3;  -- legal
   V1 := V2*V3;  -- illegal in Ada 83, legal in Ada 95
   V1 := Voltage(V2*V3);  -- legal

In Ada 95, we can multiply two numbers of a fixed point type without an explicit type conversion if the type of the multiply is uniquely determined.  In the previous example, the multiplication is legal in Ada 95 because storing the result into V1 uniquely determines the type of the product of V2 and V3.

Note that V1 := V1*V2*V3 is illegal even in Ada 95, because the intermediate result has no uniquely determined type.

Also note that if we have procedure Display(V : in Voltage); then in Ada 95 we can write

   Display(V2*V3);
because the type of V2*V3 is uniquely determined by the procedure call.

Ada.Text_IO contains a generic package Fixed_IO for I/O of fixed point types.

Ada 95 also provides modular types.  These are unsigned integers, and the arithmetic is performed modulo a specified number so that overflow can never occur.  For example, in Ada 95 we can write:

   type Unsigned_Byte is mod 256;

The modulus doesn't have to be a power of two, but it often is.  If we now declare A : Unsigned_Byte := 100; and B : Unsigned_Byte := 200; then the result of A + B will be 300 mod 256, or 44.

In Ada 95, the package Interfaces is supplied, and it defines a modular type for each signed integer type.  For example, an implementation of Ada 95 might define the types Unsigned_8, Unsigned_16, and Unsigned_32.  Type Unsigned_8 corresponds to the example Unsigned_Byte above.

When we declare a variable in Ada, we give its type.  But when we declare a constant, we may or may not give its type.  For example,

   L  : constant Integer := 30;
   M  : constant := 1000;
   E  : constant Float := 2.718281828;
   Pi : constant := 3.141592654;

Also, when we write a number, such as 3.0 or 29_999, we usually don't qualify it with a type (for example, we usually don't write Float'(3.0)).

Suppose an implementation of Ada provides types Integer, Long_Integer, Float, and Long_Float.  How can Ada determine the types of M, Pi, 3.0, and 29_999?  M and 29_999 are said to be of type universal_integer; they can assume any integer type as required.  Pi and 3.0 are said to be of type universal_real and can assume any floating or fixed point type as required.

We can't explicitly declare objects to be of universal types.  However, we can write

   M  : constant := 1000;
   Pi : constant := 3.141592654;
   I  : Integer;
   LI : Long_Integer;
   F  : Float;
   LF : Long_Float;
   ...
   I := M;       LI := M;
   I := 29_999;  LI := 29_999;
   F := Pi;      LF := Pi;
   F := 3.0;     LF := 3.0;
and in each case the constant assumes the correct type.  The result of multiplying or dividing two numbers of a fixed point type is said to be of type universal_fixed.  As we pointed out, this result must be converted to some numeric type before it can be stored.

Most of the attributes that produce integer results, like Pos, are of type universal_integer.  For example, with the declarations above, we could write

   I  := Character'Pos('A');
   LI := Character'Pos('A');

Question

Which one of the following declarations is illegal?
  1. type Rate is digits 6
  2. type Distance is digits 6 range 0.0 .. 1.0E6;
  3. type Current is delta 0.1;
  4. type Temp is delta 0.05 range -200.0 .. 450.0;

< prev   next >

AdaTutor - More Records and Types (3)

Abstract Types and Abstract Subprograms

   package P is
      type Abstract_Date is abstract tagged null record;
      procedure Display(Ad : in Abstract_Date) is abstract;
   end P;

In this example for Ada 95 only, type Abstract_Date is an abstract type.  We can't declare objects of that type, but we can derive other types from it.  For example, we can derive type Date by adding three fields, and then derive type Complete_Date from type Date by adding one more field.

The abstract procedure does not have a body, only a specification.  However, it lets us write procedures built around types derived from the abstract type.  For example, we could write overloaded procedures Display for types Date and Complete_Date (these procedures will have bodies as well as specifications).  Also, by declaring an access type to type Abstract_Date, we could again make use of dynamic dispatching to our overloaded versions of Display:

   package P is
      type Abstract_Date is abstract tagged null record;
      procedure Display(Ad : in Abstract_Date) is abstract;
   end P;

   with P; use P;
   package Q is
      ...
      type Ptr is access Abstract_Date;
      type Date is new Abstract_Date
         with record ... -- Day, Month, Year
      type Complete_Date is new Date
         with record ... -- Day_Of_Week
      procedure Display(D : in Date);
      procedure Display(Cd : in Complete_Date);
   end Q;

The advantage of this is that we can write package P, with all its abstract procedures, before we write the code in package Q detailing what the derived types (Date and Complete_Date) look like.

Controlled Types

Ada 95 has Controlled Types, which cause the program automatically to call special procedures whenever an object of a controlled type is created, assigned, or destroyed.  The Ada 95 package Ada.Finalization contains abstract tagged private types Controlled and Limited_Controlled.  We'll discuss type Controlled first.  The package also contains procedures Initialize, Adjust, and Finalize, but they're null and do nothing.  We'll see shortly how we can override the null procedures with our own procedures when we need to.

We can create our own controlled types by extending the type Ada.Finalization.Controlled.  Whenever an object of a controlled type is created, the procedure Initialize is automatically called, with the object as the single in out parameter of Initialize. Whenever an object of a controlled type is destroyed, Finalize is automatically called.  When an object of a controlled type is stored into, first Finalize is automatically called for the object stored into, then the assignment is done, and then Adjust is automatically called for the object stored into.

Controlled types must be declared at the library level, so they're usually declared in a package specification.  In this example, we create a controlled type Special with a single field containing one Integer:

   with Ada.Finalization; use Ada.Finalization;
   package Demo_Controlled is
      type Special is new Controlled with record
         I : Integer;
      end record;
      procedure Initialize(Int : in out Special);
      procedure Adjust(Int : in out Special);
      procedure Finalize(Int : in out Special);
      procedure Set(Target : out Special; To : in Integer);
   end Demo_Controlled;

We don't have to write our own versions of all three procedures, Initialize, Adjust, and Finalize if we don't need them; for any we don't write, the null procedures in Ada.Finalization will be called.  Here we chose to write all three as an example.  We also wrote a procedure Set to set an object of type Special to an Integer.

In our example, Initialize, Adjust, and Finalize will merely print messages so we can see when they're called.  Here's the package body:

   with Ada.Text_IO; use Ada.Text_IO;
   package body Demo_Controlled is
      procedure Initialize(Int : in out Special) is
      begin
         Put_Line("Initialize was called.");
      end Initialize;
     
      procedure Adjust(Int : in out Special) is
      begin
         Put_Line("Adjust was called.");
      end Adjust;

      procedure Finalize(Int : in out Special) is
      begin
         Put_Line("Finalize was called.");
      end Finalize;

      procedure Set(Target : out Special; To : in Integer) is
      begin
         Target.I := To;
      end Set;
   end Demo_Controlled;

The main program below creates two objects of type Special, calls Set for one of them, and assigns one object of type Special to another.  Below the main program, we show the program output with some explanation:

   with Demo_Controlled, Ada.Text_IO;
   use Demo_Controlled, Ada.Text_IO;
   procedure Test is
      A, B : Special;
   begin
      Put_Line("I'm about to call Set.");
      Set(Target => A, To => 3);
      Put_Line("Set returned.");
      B := A;
   end Test;

Initialize was called.      \  A and B came into existence when the declarative
Initialize was called. /  region of the main program was elaborated.
I'm about to call Set. \  Set didn't create, assign, or destroy controlled
Set returned. /  objects, so nothing was called automatically.
Finalize was called. -  B was "finalized" before being overwritten.
Adjust was called. -  B was "adjusted" after receiving a new value.
Finalize was called. \  A and B went out of existence at
Finalize was called. /  the end of the main program.

The type Limited_Controlled in Ada.Finalization is the same as the type Controlled, except that it's an abstract tagged limited private type.  Because we can't assign objects of a limited type, only procedures Initialize and Finalize are available for that type.  There's no procedure Adjust for type Limited_Controlled.

< prev   next >