From extended Pascals to Ada

by G. de Montmollin, Switzerland.
Parts from Neil A Six.
Thanks to J.-P. Rosen (Adalog) for his careful reading and comments.

Here is a "brief" hypertext for helping people who, for some reason, are tempted to port programs from the various dialects of Pascal to Ada.

Contents:

  1. A *-Pascal to Ada porting guide
  2. Comparison Tables: benefits of the Ada standard even for using its own "extended Pascal" subset
  3. Web links

Introduction

The Pascal dialects abound. If you take the classic Pascal as reference and common denominator, they are (hopefully) far extensions of it. But Borland / Turbo Pascal 1,2,3,4,5,5.5,6,7, Delphi 1 to 6, TMT Pascal, GNU Pascal, Free Pascal, Virtual Pascal, UCSD Pascal, ST Pascal+, Code Warrior Pascal, Compaq-DEC Pascal, Pascal ISO-7185:1990 or Extended Pascal ISO-10206:1990 have profound differences that block portability even for pieces of code that should be completely reusable. To me - and to many other programmers, it appears - Ada (an ISO standard) is a relief.

Well, what is that Ada language ? For here, it suffices to write: a superset of Pascal with some syntactical differences. Or a Super-Pascal. Or, a Pascal on steroids. In fact it's a better, redesigned language strongly inspired by Pascal. You'll see what I mean in the examples.

A bit of history. The first Ada language version was created around 1980 by Jean Ichbiah and a handful of gurus, on the grounds of Pascal. It won a challenge of the US Dept. of Defence for designing an all-purpose language for its needs: real-time systems, numerics, databases... Such an ambitious language was a bit large for compiling on less than 100Mhz home computers, and DoD held fiercly the rights on what could be called "Ada". Compilers were very expensive. As a result, it almost disappeared (or didn't appear out of DoD). The real birth dates from around 1995: a newer standard with completed OOP and a convenient library, 100Mhz or faster PCs for compiling it and the free open-source GNAT compiler. Please follow the links (Adapower.com) for more history.

So, where is the "plus" with Ada ? Contrary to its ancestor Pascal, where "standard" means a theoretical, hardly usable set, the Ada standard is rich, detailed, useful. It contains all - and more - expressive power of any existing or dreamed Pascal dialect. The Ada standard also includes libraries for math, I/O, interfacing, text formatting etc. Their behaviour is precisely specified, so when you change compilers or platforms, the bad surprises are minimal. Ada is certainly the most predictable native-code compiled language. There are many ISO-compliant Ada compilers, certified against a huge validation suite. This allows cross-port of large parts of your sources without any change. Only for Windows and Unix you can download, for free two compilers! The excellent GNAT runs on Windows, Linux, MacOS, FreeBSD, OpenVMS and plenty of other systems and processors - even virtual platforms: the Java Virtual Machine or .NET. I have tested for you, the portability is completely stunning. In addition Ada brings simple, flexible and efficient things like unconstrained arrays or record types, while being still more strong-typed than Pascal!

I don't want to start any religious argument. Pascal was a genial idea of language design and surely revolutionary at its time in the early 1970s. I have had an enormous pleasure to program in Pascal (of course, in a couple of extended Pascals). However, there are annoying things.

  1. The common denominator in the Pascal language is very small. All you can program there are "Hello World"-type programs or basic exercices for the school:
    • one source file for the whole program (no modularity)
    • communication between the program and the oustide world only via a console text I/O
    • all types sizes fixed by constants.
    This is normal, Pascal was invented for teaching.
  2. Not convinced ? Try to compile your nice PC program on an OpenVMS server or on an Unix station: compilation will stop in the first lines. Same when you switch from a PC compiler to another one. The Pascals are just completely different!
    • they have not the same modularity :
      • "{$I Include.pas}" & "external" for the traditional, 1960s-style ones (like C/C++)
      • "unit", "interface",... (UCSD, Borland)
      • "module", "export",... (DEC / Compaq / HP, ISO-10206:1990)
    • they have different names for allocating memory for non-static sizes: "GetMem" vs "NewPtr" etc. (since every type in Pascal, except variant records, has dimensions fixed by static constants, some Pascals offer to cheat as a workaround. It is good for real programming, but breaks every type safety and is highly non-portable)
    • they have differnet ways to handle files:
      • to open a file: "assign(f,name); reset(f);" (Borland) "reset(f,name)" (the others)
      • to read a character: "Read(f,c)" (Borland and some) "c:= f^; Get(f);" (some others)
    • your funny identifiers like "_" or "__a2" will work on a system but won't pass the compilation on the next one
    • the syntax of initialized variables or unconstrained arrays changes
    • for Strings, you have not the same types, and different operators :
      • "concat" or "+"
      • "#123" (Borland) for "chr(123)" (classical)
      • strings enclosed in double quotes (normally single quotes) with C style character escapes (`\n', `\007' etc.)
    • there are different (or no) short-circuits for logical operators: $B- switch (Borland), &,| (Code Warrior), or "or_else","and_then" (ISO, DEC / Compaq) !
    • they have various acceptance of parameters in forwarded subprograms: some want the parameter part only on second appearance (body), some don't want them, some tolerate both
    • absent of a proper standard and a validation suite, Pascal compilers have syntactical bugs (they accept syntaxes obviously not intended by their authors) which users think they are features. This makes portability more difficult.
    • to complicate things (and in hope to simplify them), most Pascal compilers provide themselves several syntax variants, with switches for...
      • changing the nature of the "Integer" type
      • changing the nature of the "String" type
      • changing the existence or nature of floating-point types
      • changing (or not) the behaviour of logical operators (see above)
      • changing the acceptance and interpretation of parameters on forwarded subprograms (see above)
      • relaxing (or not) Pascal's fixed-sized typing for referencing Strings (and only them)
      • accepting functions as procedures (or not)
      • using constants as variables (or not)
      • checking types of pointers (or not)
      • nesting or allowing various comment styles: "{ ... }", "(* ... *)", Delphi's "// ..." or TMT's Ada-Style "-- ..."
      • changing the step value of Inc/Dec operations when appliying to pointers
    I let you the pleasure of estimating the number of possible syntax combinations and, in consequence, the probability that a program compiles on another Pascal compiler, and if it compiles, that the result will work as expected... Just as an example from real life, a Pascal code for decompressing data needs hundreds of lines conditional define like the following for compiling on a certain amount of OSes/Pascal compilers/CPUs:
    ...
    {$ifdef BP_DPMI}
       {$define Can_Use_DLL}
    {$endif}
    
    {$ifdef USE_STDCALL}
       {$ifndef __TMT__}
         {$define BY_NAME}
       {$endif}
    {$endif}
    
    {$ifdef Delphi32}
      {$H-}
      {$ifdef Linux}
         {$define kylix}
      {$endif}
      {$define OS_BigMem}
      {$ifdef kylix}
       {$undef __OS_DOS__}
       {$undef UseWin}
       {$undef MSWINDOWS}
       {$define NOCRT}
      {$else}
        {$define Win32}
      {$endif}
      {$undef assembler}
    {$endif}
    ...
    
    In Ada, for an unlimited amount of targets, it is:
    (empty!)
  3. Some observations specific to the Borland Pascal family (Delphi, FPC, TMT,...):
    • There are plenty of subtleties that make a simple program unportable, or requires lots of conditional defines to allow the compilation on targeted compilers. Just read sources files on the Net meant to be compiled by several of these compilers, or read their feature lists (links above). You can forget a "blind" portability or a even a reasonable parallel development with two compilers. Fortunately, Ada is there for the big synchronization!
    • Protected by its proprietary policy Borland has extended the language often with Intel 16-bit programming in mind or with unhappy choices. E.g., the scope of $B+/- (complete boolean evaluation) and $I+/- (I/O checking) switches can modify the program's behaviour till the end of the source file. A typed CONST is in fact an initialized variable whose value remains outside its block: a complete anti-Pascalism! As the versions evolved, the confusion of new reserved words that coincide with usable names has become crazy. Especially, the pseudo-procedures Exit (Ada's return keyword), Break (Ada's exit keyword), Continue act as goto's but can be masked by a procedure declaration with the same name!
    • In Borland Pascal, the "uses" clauses hide similar entries from the previous used units as new ones come; in Ada it becomes an ambiguity and the compilers require to make the reference explicit. E.g. if you have a variable integer X in interface (specification) of units A and B, "uses A,B" will have a completely different effect than "uses B,A", without any warning.
    • Borland has missed to provide a convincing compiler optimisation, except perhaps in late versions of Delphi. Since they have a quasi-monopoly on the Pascal market, it has become common that "optimise Pascal" means "write the code in assembler"! Alas, assembler is rigid, becomes difficult to modify. You lose the Pascal abstraction and portability. In addition, modern optimising compilers will most of the time outshadow your hard-worked assembler code... Another key element for optimisation is the possibility of inlining small subprograms, i.e. inserting the contents of a routine at the places where it is called. Ada has the pragma inline for that purpose and it often brings impressive speedups since the inserted code can be fully worked in its place by multi-level optimisers. This feature is still a wish for Delphi...
You find more on the topic in the Web links.

Ada brings unbeatable portability, a strong standard even for small I/O details, generic programming, polymorphism, overloadable subprogram names and operators, full OOP, tasking, portable but also efficient floating-point types. A few points in the migration are negative - I'll mark with a :-(. But they are really minor compared to the positive ones: you can read an implicit :-) everywhere else.

Well, I don't want to continue on a huge dissertation, the best is to see with examples, and make your own idea.



1. A *-Pascal to Ada porting guide

This part - more than others - is under construction! Write me for ideas, experiences, contestations, corrections and comments.

Don't be afraid: the global programming structure of Ada is exactly the brillant Pascal one, with its blocks. So, Ada will appear as a super-Pascal with minor syntactical changes :-).

Start

Let's start with a very simple program, the famous 'hello world'.
Hello world!
Pascal Ada
program Hello(input,output);
begin
  WriteLn( 'Hello world' )
end.
with Ada.Text_IO; use Ada.Text_IO;
procedure Hello is
begin
  Put_Line( "Hello world" );
end Hello; -- can be also just 'end;'
  1. The "with" clause imports packages (modules) or simple procedures. The "use" clause makes a package's contents visible without prefix: it opens visibility. Unlike Turbo Pascal, Ada detects possible confusions about comparable things coming from different packages but with the same name. You can close the visibility by suppressing the "use". You should write e.g. "Ada.Text_IO.Put_Line". It is useful in large programs where you begin to forget the origin of types, variables, etc.
    That being said, I find the always separate importation and visibility-opening clauses a bit long-winded :-(, especially for using packages like "Ada.Numerics.Elementary_functions" ! I would add to the Ada standard a "with and use" clause to make both things together, corresponding to the "uses" in UCSD or Turbo Pascal.
  2. The main program has also the keyword "procedure". As you guess, you can use it as subprogram elsewhere, just "with" it! The feature is very useful: in a commercial software with several programs using almost the same components, I was able to divide by 6 the total excecutable size. Just an extra mini shell Ada procedure having a "with P1,P2,P3,...;" and "case choice is when 1=> P1; when 2=> P2; ..." !

Declarations, parameters, instructions

Usual Pascal declarations have their equivalents in Ada, with slight differences. The same two deadly simple rules apply: what is outside and above a block is visible inside of it; within a block, what is above is visible to what is below. So, Pascal or Ada never handle undefined things as the 1960s predecessors of Pascal do: C, Fortran and their ++, OO, 95 etc. avatars. No flood of warnings where a few real problems are lost, no functions treated as implicit and wrongly coded!
Declarations
Pascal Ada
const a=1; b=2;
a: constant:= 1; b: constant:= 2;
type r = record x,y: integer; f: boolean end;
     a = array[1..10] of integer;
type r is record x,y: integer; f: boolean; end record;
type a is array(1..10) of integer;
var a: integer; b: real;
a: integer; b: real;
Ada (even the 1983 one) brings many nice things like unconstrained types (the way to combine the type safety of Pascal and the flexibility of C), subtypes, initialized variables, initialized types (--> constructors).

The parameter syntax is quite different. In Pascal you copy a value or you reference a variable (var). In Ada there are "in", "in out" and "out" modes. Shortly, in Pascal (or e.g. in C) you tell how you transmit your parameters; in Ada you tell what you want to do with your parameters.

For "in" mode you can pass a value (1.2345, "hello!", x, x+2,...) that can be used under the specified name; the "in" parameter is read-only, just like a constant. For "in out" mode, you pass a variable that you intend to use and modify. For "out", you decide the variable is write-only.
Now, how is it translated by the compiler ? The compilers are free to choose the actual mode (copy or reference). On the few compiler I know well, the parameters are almost always passed by reference, even for "in", which can seem surprising at first. But reference is possible for "in" precisely because the parameter is read-only and cannot be accidently rewritten. Only small objects like integers or pointers are usually copied when passed as "in" parameters, since it is faster to do so. Note that the optimal way may vary from a target architecture to another one. Since the compiler (well, at least a good one!) knows the timings of the various ways of passing, it will (or should!) always compile them at best. It is not the case for Pascal where you choose the "how". Another advantage on Pascal is that you avoid the blunder of passing a big object by copy, although you don't need to copy it! Maybe a point against Ada is that if you are curious about the "how", you see it only in an assembler listing. But you almost never need to care of it.

Parameters
Pascal Ada
procedure Do_it(i,j: integer; var k: integer);
{ values for i,j have been copied; they are local variables }
begin
...
  i:= i+1;
procedure Do_it(i,j: in integer; k: out integer) is -- "in" can be omitted
  ii: integer:= i; -- you copy here if you have to modify
begin
...
  ii:= ii+1;

Now, let's compare supercifially basic instructions, with a nonsense piece of code.

Instructions
Pascal Ada
...
var i  : integer;
    j,k: word;
begin
  j:= 100;
  k:= 100;
  if n>5 then
    for i:= a to b do
      begin
        j:= j + f(i);
        k:= k + g(i)
      end
  else
    if n=4 then
      begin
        j:= 0;
        k:= 0
      end
    else
      case m of
        1: s:= j;
        2: begin
             s:= k;
             t:= j+k
           end;
        else s:= 0;
        { ! else: Turbo only }
      end
end;
...
  j,k: unsigned_16:= 100;
begin
  if n>5 then
    for i in a .. b loop
      j:= j + f(i);
      k:= k + g(i);
    end loop;
  elsif n=4 then
    j:= 0;
    k:= 0;
  else
    case m is
      when 1=> s:= j;
      when 2=> s:= k;
               t:= j+k;
      when others => s:= 0;
    end case;
  end if;
end;


  1. The ";" terminates in Ada, separates in Pascal
  2. In Ada all loop, then/else branches etc. can contain several instructions (the real life!). It clears a lot of "begin" and "end" of Pascal or "{", "}" of C/C++ . It also spares lifes of debugging stupid mistakes like the "else" applying to the wrong level of "if", or an instruction block, looking like it by the indentation, where you forgot the "begin" - "end" pair (resp. the "{" - "}") to enclose it!
  3. The variable i is declared just for the loop, no need to declare it as variable

Advanced but simple Ada features that make things easier!

Here are examples of Ada features with no Pascal equivalent (or whose inclusion is still discussed for the next version of Delphi...). Note that all of them were already in the first 1983 standard!

Some nice Ada things you might never see fully in any Pascal variant
On-purpose declaration among instructions
if m>0 then
  declare
    temp: Integer:= Calc(m,n);
  begin
    u:= arr(temp,i);
    v:= arr(temp,j);
  end;
  ...
end if;
Exit from a function just when you have the answer, without a temporary variable, and without goto or loss of time
function Find_it(a: Structure) return Index is
begin
  for i in a.table'range(1) loop
    for j in a.table'range(2) loop
      if ... then
        for k in seek_range loop
          if ... then
            return Match( a.table(i,j), k );
          end if;
        end loop;
      end if;
    end loop;
  end loop;
  -- <-- Here Program_error will be raised:
  -- no answer, there should be one!
  -- Variant: return Index'first;
end Find_it;
Handy attributes to obtain everything from a variable
Put( my_enum'Image(e) );
e:= my_enum'Value(token);
i:= my_enum'Pos(e);
my_enum'Val(0)
o'Size
a'First
a'Length
a'Range
...
Array indexed by a scalar type, and initialised; loop through the values of this type
subtype Key_value is Natural range 0..127;
keyboard: array(Key_value) of Boolean:= (others=> false);
-- keyboard(i) <=> the key number i is pressed
...
for k in Key_value loop -- or: k in keyboard'Range
  ...
end loop;
Define a matrix type of whatever size, but safely strong-typed.
This is an unconstrained array type.
Same exists for records and these records can include other uncontrained types!
type Matrix is array(Integer range <>, Integer range <>) of Float;
type p_Matrix is access Matrix; -- pointer on Matrix
Declare a local variable of unconstrained type.
A: Matrix(100,100); -- on stack (small)
Define a "+" operator.
function "+"(A,B: Matrix) return Matrix;
Declare a pointer variable and initialize it; allocate without cheating or hacking with memory sizes.
B: p_Matrix:= New Matrix(10000,10000); -- on heap (a big one)
Named loops, exiting from several loops
tol_tries: for tol_try in 1..resizings loop

  for n in 1..nodes_count loop
    for i in 1..xgr loop
      ...
      exit tol_tries when attrib_gridnode = xgr*ygr;
    end loop;
  end loop;

  tx:= tx * factor;
  ty:= ty * factor;

end loop tol_tries;
Name overloading and default values
procedure FloodFill(x,y: Integer; border: Gr_colour;
                    d: Device_type:= current_device);
                    
procedure FloodFill(x,y: Float;   border: Gr_colour;
                    d: Device_type:= current_device);
Optional named parameter associations
package File_LZH is
           New LZH( Message_length_integer => Byte_IO.Count,
                    Read_a_byte    => Read_IO_byte,
                    Write_a_byte   => Write_IO_byte,
                    calling_latch  => 1024,
                    Feedback       => Display_progress );

------

if Matr_sym then                -- LtL (Cholesky), symmetric case
  DPBTRF( upper, N=> pMB.size,
          KD=> pMB.half_band - 1,
          AB=> pMB.val, LDAB=> pMB.multi_band );
else                            -- LU
  DGBTRF( M=> pMB.size, N=> pMB.size,
          KL=> pMB.half_band - 1, KU=> pMB.half_band - 1,
          AB=> pMB.val, LDAB=> pMB.multi_band,
          IPIV=> pivots.all );
end if;
Comment needed ?... Note the function calls in the definition
anisotrope_y: constant p_matrix:= New matrix ' ( 0.01 *
  ( 1=> (1=>1.0, 2=>0.0,   3=>0.0  ) ,
    2=> (1=>0.0, 2=>0.005, 3=>0.0  ) ,
    3=> (1=>0.0, 2=>0.0,   3=>1.0  ) )   );

angle_x: constant:= 0.3;

rota_x: constant matrix := (
  ( 1=> (1=> 1.0,           2=> 0.0,          3=>  0.0            ),
    2=> (1=> 0.0,           2=> cos(angle_x), 3=> -sin(angle_x)   ),
    3=> (1=> 0.0,           2=> sin(angle_x), 3=>  cos(angle_x)   )  )    );
  • A constant is such inside of its block and then not necessarily static.
  • An "in" parameter is considered as a constant.
  • You can define what you want much more dynamically than Pascal, but still with strict compile-time checks - indeed better than Pascal ones!
The cool thing is the ability to combine the above features together :-)

Modularity

Now, let's explain a bit of modularity.

Roughly, both Ada and Turbo Pascal inherit their modularity from UCSD Pascal (~1975). The units are called packages in Ada. This model with interface/specification and implementation/body parts allows a fully automatic build and (re-)compilation of a program and all depending units. Ironically, following the "first in, last out" rule in the programming language world, most programmers in the year 2000 are still obliged to do modularity with #include, #define and extern often spaghettized to death by tens of unknown programmers, construct complicated makefiles or projects...

Units, packages
UCSD,Turbo Pascal Ada
unit Files;
interface
  ...
  function Exist(name:String): Boolean;

implementation
  ...
  function Exist(name:String): Boolean;
    var f: Text;
  begin
    {$I-} { ! Turbo only }
    { ! Turbo only }
     Assign(f,name); Reset(f);
    { ! Standard Pascal }
     {Reset(f,name);}
    {$I+} { Scope for the rest of the text !! }
    if IOResult<>0 then
      Exist:= False
    else begin
      Exist:= True;
      Close(f)
    end
  end;
  ...
end.
package Files is
  ...
  function Exist(name:String) return Boolean;
end Files;


package body Files is
  ...
  function Exist(name:String) return Boolean is
    use Ada.Text_IO;
    f: File_Type;
  begin
    Open(f,in_file,name);
    Close(f);
    return True;
  exception
    when Name_Error => return False;
  end;
  ...
end Files;
  1. Specification (interface) and body (implementation) parts can be in two files. It allows multi-platform, separate programming. Some Ada compilers, like GNAT, require this separation, so it doubles the amount of files :-( !
  2. In Ada, you can define a structure of any sort inside of another one. For example, if you discover that a package is useful only inside another one, but want to keep its structure (e.g. for recycling it elsewhere), you can do it !

    Example of nested package
    package body SB_Driver is -- Driver for Sound Blaster, 32-bit protected mode
    ...
      package DMA is
        procedure Read_8bit_Single_Cycle( linearAddressOfBuffer: unsigned_32;
                                          length: integer );
        procedure Read_8bit_AutoInit( linearAddressOfBuffer: unsigned_32;
                                      length: integer );
      end DMA;
      package body DMA is
        generic
          dmaCommand: Unsigned_8;
        procedure Program_DMA( linearAddressOfBuffer: unsigned_32;
                               length: integer );
    ...
      end DMA;
    end SB_Driver;

  3. True modularity allows a full build with a single command or keystroke. The compilation system can easily figure out what is needed to be recompiled and what not. Here is examples of diverse equivalent commands on various system.

    Smart recompilation
      Turbo / Borland Pascal DEC / Compaq Ada GNAT Aonix ObjectAda
      IDE (turbo) command line (tpc) command line GPS, the GNAT Programming Studio command line AdaGIDE IDE command line
    Compile unit "xxx" only. Alt-F9 tpc xxx ada xxx Shift-F4 gcc -c xxx, or gnatmake -u xxx F2 Ctrl-F7 adacomp
    Compile unit "xxx", compile depending units, link. Only needed operation.s F9 tpc /m xxx acs comp xxx
    acs link xxx
    F4 gnatmake xxx F3 F7 adabuild
    Compile unit "xxx", compile depending units, link. (Re-)do all operations. Alt-C , B tpc /b xxx acs comp /recomp xxx
    acs link xxx
    Make / Compile all sources gnatmake -f xxx Build - force recompilations Alt-F8 adabuild

  4. A nice feature in Ada is genericity. They are simple to use and to read, they are amazingly robust. You can use it everywhere, for reuse of same things with several types or just to obtain optimised, inlined code with some parameters and I/O, callback procedures. You find large generic packages even generics in generics. Once an Ada generic passes compilation, the first phase of development is done even before the first instanciation: the compilation will work on every instanciation. A test with an instanciation, provided passed subprograms are meaningful (if there are any), will most of the time the job for all possible instanciations.
    It is very different from other similar things like templates or macros in other languages where a full testing for one instanciation won't guarantee the template or macro will build for another instanciation.
  5. Example of generic unit (specification)
    ------------------------------------------------------------------------------
    --  File:            bandmatr.ada
    --  Description:     Generic package for band matrices
    --
    --                   Symmetric and Asymmetric Lapack band matrix formats
    --
    --  Date / Version:  20-Apr-2000
    --  Author:          Gautier.deMontmollin@Maths.UniNe.CH
    ------------------------------------------------------------------------------
    
    generic
      type real is digits <>;
      type index is range <>;
      type vector is array(index range <>) of real;
      type matrix is array(index range <>, index range <>) of real;
    
    package BandMatr is
    
      --------------------------
      -- Define a band matrix --
      --------------------------
    
       type Band_matrix( max_size,    -- size of actual matrix
                         band,        -- bandwidth
                         multi_band   -- n-uple of bandwidth
                       : index ) is
       record
         val: matrix(1..max_size, 1..multi_band); -- transposed w/r Lapack due to Fortran
         symmetric: boolean;
         size: index:= max_size;
       end record;
    
       -- Lapack:
       -- minimal values for multi_band 1+3*band: asymmetric
       --                               1+  band:  symmetric
    
       type p_Band_matrix is access Band_matrix;
    
      ----------------------------------
      -- Matrix-vector multiplication --
      ----------------------------------
    
       -- w:= A*u
    
       procedure Mult( A: in out Band_matrix; u: vector; w: in out vector );
    
      ------------------------------------------
      -- Put/Add/Get data into/in/from matrix --
      ------------------------------------------
    
       procedure Put( A: in out Band_matrix; i,j: index; value: real );
       procedure Add( A: in out Band_matrix; i,j: index; value: real );
       function  Get( A: in     Band_matrix; i,j: index ) return real;
    
    end BandMatr;
    
    

More

Unless you are insisting, I stop here...
The best is to contemplate some Ada programs, read books, and program ! See resources and web links at bottom of this page.
OK, still a few examples, for the pleasure...
Example: generic matrix multiplication
  function "*"(A,B:matrix) return matrix is
    r: field_elt;
    AB: matrix(A'range(1),B'range(2));
  begin
    if A'length(2)/=B'length(1) then raise constraint_error; end if;
    for i in A'range(1) loop
      for j in B'range(2) loop
        r:= zero;
        for k in B'range(1) loop
          r:= r + A(i,k-B'first(1)+A'first(2)) * B(k,j);
        end loop;
        AB(i,j):= r;
      end loop;
    end loop;
    return AB;
  end "*";

Example: read a texture bitmap from a data stream
with SVGA.IO;

package body SVGA.Effects.IO is

   procedure Load_BMP_texture(S: Stream_Access; Texture: out p_Texture_map) is
     width: X_Loc; height: Y_Loc;

     function bits(n:natural) return natural is
       nn: natural:= n; b: natural:= 0;
       begin
         while nn/=0 loop b:= b+1; nn:= nn / 2; end loop;
         return b;
       end;

     begin
       SVGA.IO.Read_BMP_Header( S, width, height );
       declare
         B: Screen_Buffer( width, height );
         P: Color_Palette; -- unused here
       begin
         texture:= New Texture_map( bits(width-1), bits(height-1) );
         SVGA.IO.Load_BMP_Palette( S, P );
         SVGA.IO.Load_BMP_Image( S, width, height, B );
         Put_Buffer( B, Texture.all );
       end;
     end Load_BMP_texture;

end SVGA.Effects.IO;

To conclude, you can browse the following Ada sources originally translated from Pascal and developed further. GNAT provides a nice tool that automatically outputs a set of Web pages from an Ada unit (package or procedure) and its depending units!

  1. Zip-Ada, a library around for the Zip file format.
  2. Excel Writer - translated from Modula-2 via Pascal



2. Comparison Tables: benefits of the Ada standard even for using its own "extended Pascal" subset

The tables for this comparison are based on the " Apple and Borland Pascals Compared" document, by Neil A Six, who consented that I add an Ada column (It's here about standard Ada: OS-, target-, compiler- independent!). Also added a few rows (coloured). The Pascal compilers compared are Code Warrior for Macintosh and Borland (in fact, TMT) for PC.

Common Extensions to Pascal and their standard Ada counterpart
Pascal extensions Ada standard
UCSD-style unit (Borland) or
Modula-style module (ISO Pascal)
package
Can declare constants using expressions same - and you can use array/record
aggregates in any expression (of the right type)
not only to define constants!
Can mix the LABEL-CONST-TYPE-VAR-PROC declaration
order . (impossible in standard Pascal - a huge difference!)
same
Typeless files Streams, Stream_IO package
Objects (differences not yet verified) same - but not the same way
I'll document this...
@ prefix operator 'access and 'address attributes
Hex constants same - also: in any base, e.g. 2#0010001101#
Single, Double, Comp, Extended real types float, long_float and
"type my_real is digits 20"
for which the compiler finds the appropriate
FPU type for target machine
LongInt, MaxLongInt All signed and unsigned types with explicit names
like Integer_16, Unsigned_32.
Also Integer, that matches the "usual" integer
on the machine compiled to.
String type & its subroutines same and much more - but not the same way.
On this point the Ada fixed strings are harder to
manipulate - at least at beginning :-(. There are
also goodies: slices s(34..49):= s0(1..15) & '+',
80*'-' gives a line, etc.
That is for the type String. But you can define strings just like the Borland ones :-)
(you couldn't do it in Pascal itself !) :
  type BorString (maxlength : Positive) is record
    length : Natural := 0;
    s      : String (1 .. maxlength);
  end record;
Moreover, Ada provides Unbounded_String's which are unlimited and Bounded_String's which are jut like Borland's strings.
MemAvail function MemAvail-like is not in the Ada standard,
but is provided by compilers.
Eventual memory shortage is caught by the standard
Storage_Error exception. You can also use the 'storage_size attribute
IOResult function I/O exceptions (name_error, mode_error,...)
- works the same on an Alpha server as on a PC!
FillChar procedure Simply: s:= (others=> 'X')
Seek procedure Set_index
Sizeof function 'size attribute. Gives as result the number of bits
Variable typecasts none - and you really don't miss it! The implicit
conversions are a big source of errors and unefficiency
I,R,D directives I/O exceptions, pragma suppress(range_check)
pragma debug. Compilers also provide switches for
that, of course.



Trivial Differences in extensions of Pascal
Apple Borland Comment for Pascal extension Ada standard
otherwise else   when others
cycle continue Borland v. 7 predefined
ident
none
leave break Borland v. 7 predefined
ident
exit, exit when
PLFilePos FilePos   Index
PLFlush Flush   Flush
PLCrunch Truncate   none- is it really useful ?
Anyway, the 'append' mode is there.
MoveLeft
MoveRight
Move Borland handles overlapping
regions
slices:
a(1 .. 500_000):=
a(100_001 .. 600_000)
ord4 ord Apple ord yields Integer
unless paramalready pointer
or LongInt.Borland rejects
pointer parameter
'pos attribute
Huge integer consts considered real rejected Append ".0" to resolve universal floating-point or integer constants; compiler tries to make fit, or rejects.


Built-ins that can be emulated or should be replaced in extended Pascal
Apple Borland Solution in Pascal Ada standard
BSL,BSR infix shl,shr Define for Borland shift_left, shift_right
intrinsic functions
BAnd,BOr,BXor,BNot infix and,or,xor,not Define unique functions, since Apple integer params are zero-extended.
BNot(x) = -1 - x
same as Borland
HiWrd,LoWrd,Inf none Define for Borland none
none Upcase,Lo,Hi,Int,Frac Define for Apple [Ada.Characters.Handling.]To_Upper,
none for Lo,Hi,
attributes for Int,Frac
none Randomize,Random(int) Define for Apple (using
QuickDraw Random & qd
randSeed)
Reset (without initiator),
Random (issues value of the
desired range - it's generic)
Toolbox units none Define for Borland when possible
- e.g., SANE,TextUtils.
Ada.* packages



Nontrivial differences - best avoided or minimized in extended Pascal
Apple Borland Comment for Pascal Ada standard
none Unit initialization Best practice is to define initialization subroutine, even for trivial data structures. Package initialization
none Variable initializers   same
Leading hex zeroes significant insignificant E.g., $8000 = -32768 (Apple),32768 (Borland) insignificant
  predefined types ShortInt,Byte,Word Simulate or avoid altogether All signed and unsigned types with explicit names like Integer_16, Unsigned_32.
Can index a string literal can't E.g., 'ABCD'[3] = 'C' can't - is it really useful ?
Forwards need subprogram
prototype 1st time
both times
(I doubt it -GdM)
  both times
Packs to bit level byte level Borland ignores packed pragma pack,
precise representation
clauses
Pointer Ptr Pointer has a LongInt param,
yields 32-bit pointer.
Ptr has segment & offset integer
params, yields 20-bit pointer
access (pointer, short pointer, whatever the compiler wants to represent it)

address (the 32,64,... bits machine address)

NewPtr,DisposePtr New, Dispose,
GetMem,FreeMem
Apple: functions;
Borland: subroutines
new operator,
generic "Unchecked_deallocation" procedure, must be instanciated :-(
Mark/Release,Get/Put,
ScanEq/ScanNe
none Mark/Release supported in
Borland v. 7 predecessors
none - but you can do many more things on stack, e.g.
among the instructions:
...
declare
 t: vector(1..n1):=
    Calc_vect(n1);
begin
  -- manipulate t
  ...
end;
...
2040 max set elements 256 max set elements   unlimited: set=array of boolean. Set expressions are not as comfortable as in Pascal :-( but you have the implicit operators +,-, not, and, or, xor :-)
OV+ directive, -ov option Q+ directive, /$Q+ option Overflow-check enable
Borland v. 7 predecessors
lack Q directive
Storage_Error exception
Longint multiply always unchecked Checked based on Q directive   no problem (check if enabled, for all scalar types)
infix &,| or SC+ directive B- directive, /$B- option Having a compiler switch for distinguishing short-circuit from complete evaluation is a very poor design.
ISO Pascal did better on that point with and_then, or_else.
Ada provides and then, or else operators for short-circuit evaluation.
and, or represent the complete evaluation form.
Open,Rewrite,Reset with filename Assign Easier to port :
Open{Assign}(f,str);
Rewrite(f)
  or
Reset{Assign}(f,str);
Reset(f)
Open, Create procedures
BlockRead, BlockWrite functions procedures   'read, 'write attribute and Stream_IO
diagnostic none Diagnostic defined in unit IntEnv.
NT & Unix, but not DOS,
have stderr analogous to diagnostic
(DOS has stderr -GdM)
[Ada.Text_IO.]Standard_Error file
Unit IntEnv ArgC,ArgV ParamCount,ParamStr   [Ada.Command_Line.]Argument_Count, Argument(i)
IFC NOT UNDEFINED/ELSEC/ENDC IFDEF/ELSE/ENDIF Conditional compilation Fortunately, there is no conditional compilation in Ada!
Boolean constants, renames, separate, and having different bodies for the same package in specific directories do the job.
For "hard" cases, e.g. hardware-dependent libraries, a preprocessor like gnatprep may be useful, allowing to produce multiple Ada sources from a single one.



3. Web links

Powered by Ada          Awesome Ada


Parts (for Pascal) Copyright © 2000 Neil A Six. All Rights Reserved.
Ada part: Copyright © 2000-2021 Gautier de Montmollin, Switzerland.
From extended Pascals to Ada. Ada Programming.