Go to the first, previous, next, last section, table of contents.

GNU Pascal extensions

Extensions to ISO-7185 Pascal language

GPC contains a number of extensions to the ISO 7185 Pascal language.

Most of these extensions are written so that they should conform to the international standard ISO/IEC 10206 : 1991, Information technology -- Programming Languages -- Extended Pascal.

GPC is not yet fully compliant to the requirements of the Extended Pascal language.

The following Extended Pascal features are implemented:

GPC extensions not in Extended Pascal:

Extended Pascal features still missing from GPC

I/O to text files:

GPC implements "lazy" text file I/O, i.e. do a PUT as soon as you can and do GET as late as you can.

This should avoid most of the problems sometimes considered to be the most stupid feature of Pascal.

When passing a file buffer as parameter the buffer is validated when the parameter is passed. @@ Perhaps it would be nice to hack it to be validated when the VAR parameter is referenced...

When any lazy file is RESET, the file buffer state is set to undefined. It is validated on the first reference to it. Now this is also true for terminal devices.

Variable length strings in GPC:

Extended Pascal has a "type selector" feature called schema types.

GPC does not yet implement general schema types, but the STRING SCHEMA is now implemented.

(An example of a (unimplemented) schemata would be, e.g:

Matrix (N,M: Positive_int) = array [ 1..N, 1..M ] of integer;

Here the M and N are discriminant identifiers.)

A STRING SCHEMA is the only predefined schema type in Extended Pascal, with one required discriminant identifier "Capacity".

The string schema type, if explicitely defined, could look like:

TYPE string(capacity) = packed array [ 1..capacity ] of char;

Internally GPC implements STRING SCHEMA as follows:

The type representing the SCHEMA TYPE is a RECORD_TYPE node, with the following fields:

STRING  = RECORD
    Capacity : integer;
    length   : integer;
    string   : packed array [ 1..Capacity ] of char;
  END;

The "Capacity" field may be directly referenced by user,

"length" is referenced by a predefined string function LENGTH(str) and contains the current string length.

"string" contains the chars in the string.

The "string" and "length" fields can not be directly referenced by a user program.

References to the schema discriminants are allowed, and the WITH statement is also allowed, so one can say:

var str : string (80);
begin
   writeln (str.capacity),         (* writes 80 *)

   with str do
     writeln (capacity);           (* writes 80 *)
end;

When a new SCHEMA_TYPE is created, the discriminant identifier fields need to be initialized. GPC initializes the new schema type discriminant identifiers of every VAR_DECL node before it executes any instructions of the procedure, function or program where the string variable is declared.

If new internal schema types are created (for conversion of fixed-string or char type parameters to a string schema formal parameter), the discriminant identifiers are initialized immediately. The discriminant identifiers of PARM_DECL nodes are not initialized separately, they get their values from the actual parameters.

If a parameter is a SCHEMA_NAME (a schema with no discriminant identifiers), a proto string schema is used as the type of the parameter.

Variable length string parameters look like:

PROGRAM Zap (output);

TYPE
   stype = string (10);
   sptr  = ^string;

VAR
   str  : stype;
   str2 : string(100000);
   dstr : ^string;
   zstr : sptr;
   len  : integer value 256;

  (* "string" accepts any length of strings *)
  PROCEDURE foo(z: string);

  BEGIN
    writeln ('Capacity : ',z.capacity);
    writeln ('Length   : ',length (z));
    writeln ('Contents : ',z);
  END;

  (* Another way to use dynamic strings *)
  PROCEDURE bar(slen : integer);

  var
    lstring : string (slen);
    foostr  : type of lstring;

  BEGIN
    lstring := 'Hello World!';
    foo (lstring);
    foostr := 'Ent{ miksi juuri t{m{?';
    foo(foostr);
  END;

BEGIN
  str   := 'KUKKUU';
  str2  := 'A longer string variable';

  new (dstr, 1000);     { Select the string Capacity with NEW }
  dstr^ := 'The max length of this is 1000 chars';
  new (zstr, len);
  zstr^ := 'This should fit here';

  foo(str);
  foo(str2);
  foo('This is a constant string');
  foo('R');             { A char parameter to string routine }
  foo(");              { An empty string }
  foo (dstr^);
  foo (zstr^);
  bar (10000);
END. (* Zap *)

In the above example, the required procedure NEW was used to select the capacity of the strings. Procedure "BAR" also has a string whose size depends of the parameter passed to it and another string whose type will be the same than the type of the first string ("type of" construct).

All string and char types are compatible as long as the destination string is long enough to hold the source in assignments. If the source string is shorter than the destination, the destination is automatically blank padded if the destination string is not of string schema type.

String routine (mostly in library):

S1 and S2 may be of string or char type. S is of string type.

WRITESTR (s, write-parameter-list)
READSTR (s, read-parameter-list)
Write to a string and read from a string. The parameter lists are identical to write/read from TEXT files. The semantics is closely modeled after file I/O.
INDEX(s1,s2)
If S2 is empty, return 1 else if S1 is empty return 0 else returns the position of s2 in s1 (an integer).
LENGTH (s1)
Return the length of S1 (an integer from 0..Capacity)
TRIM (s1)
Returns a new string with spaces stripped of the end of S.
SUBSTR (s1, i)
SUBSTR (s1, i, j)
If J is missing it is calculated as: J := LENGTH (S1) - I + 1; Return a new substring of S1 that contains J characters starting from I.
EQ (s1,s2)
NE (s1,s2)
LT (s1,s2)
LE (s1,s2)
GT (s1,s2)
GE (s1,s2)
Lexicographic comparisons of S1 and S2. Returns boolean result. Strings are not padded with spaces.
s1 = s2
s1 <> s2
s1 < s2
s1 <= s2
s1 > s2
s1 >= s2
Pascal string compare of S1 and S2. Returns boolean result. Shorter string is blank padded to length of the longer one.

No name space pollution with extensions:

In GPC you are free to re-define everything that is not a reserved word in ISO 7185 Pascal in your program.

All Extended Pascal additional "reserved words" may be redefined, so you do not have to modify your code for GPC if you have an identifier like RESTRICTED or VALUE or some such. @@ This violates Extended Pascal standard.

You may also redefine words like INTEGER and CHAR if you like.

@@ NOTE: The *only* exception to the redefinition rule currently is the word INLINE (to make routines inline compiled), because I added it in front of PROCEDURE or FUNCTION. But I think I will change the syntax later and make INLINE a directive instead of a reserved word.

Compile time switches:

to get info of possible clashes of keywords and other info of your program constructs that gpc thinks are "non-standard" use the switch "-pedantic" when compiling. See the GCC info files.

@@ I have not tested the switches like -Wall very much. If you do, @@ give me info of error messages that don't make sense in Pascal.

@@ As a rule, GPC implements most of the switches GCC implements, and a couple of more that can not currently be set.

Implemented directives:

FORWARD
Required by pascal standard.
EXTERNAL
External routine which starts with a capital letter. (e.g. calling external function "foo()" will actually call "Foo()")
EXTERN
Same as external
C
Calls external routine "foo()" as "foo()" (no capitalization of the first letter)
C_LANGUAGE
Same as C.
STATIC
Make a function static in C sense.

PROGRAM foo;
	
PROCEDURE gotoxy(x,y: Integer); C;
	
BEGIN
  gotoxy(10,10); (* Call external routine "gotoxy" *)
END.

Set operations:

GPC supports standard Pascal set operations. In addition it supports the extended Pascal set operation symmetric difference (set1 >< set2) operation (a XOR of the set elements).

It also has a function that counts the elements in the set: `a := card (set1)'

NOTE: the set operations are still under construction, e.g. the set code does not fully work in the 64 bit Alpha machines.

Initial values to type denoters:

A type (or variable) may be initialized to a value of expression when it is declared, as in:

program zap;

type
   int10   = integer value 10;
   footype = real;
   mytype  = char value pred('A');
   etype   = (a,b,c,d,e,f,g) value d;

var
   ii  : int10;                     (* Value of ii set to 10 *)
   ch  : mytype  value pred('z');
   aa  : integer value ii+10;
   foo : footype value sqrt(aa);
   e1  : etype;                     (* value set to d *)
   e2  : etype value g;             (* value set to g *)

begin
end.

Extended pascal requires the type initializers to be constant expressions. GPC allows any valid expression.

Note, however, that the expressions that affect the size of storage allocated for objects (e.g. the length of arrays) may contain variables only inside functions or procedures.

GPC evaluates the initial values used for the type when an identifier is declared for that type. If a variable is declared with a type-denoter that uses a type-name which already has an initial value the latter initialization has precedence.

@@ GPC does not know how to calculate constant values for math functions in the runtime library at compile time, e.g. `exp(sin(2.4567))', so you should not use these kind of expressions in object size expressions. (Extended Pascal allows this).

Date and time routines:

Predefined date and time routines:

procedure gettimestamp(VAR t: Timestamp);
function date(t: Timestamp) : packed array [ 1..DATE_LENGTH ] of char;
function time(t: Timestamp) : packed array [ 1..TIME_LENGTH ] of char;

DATE_LENGTH and TIME_LENGTH are implementation dependent constants. See E.20 and E.22 in chapter IMPLEMENTATION DEPENDENT FEATURES to find out these values for GPC.

GetTimeStamp(t) fills the record T with values. If they are valid, the boolean flags are set to TRUE.

TimeStamp is a required predefined type in extended pascal standard. (It may be extended in an implementation.)

The required part of the type looks like:

TimeStamp = PACKED RECORD
		     DateValid,
		     TimeValid : Boolean;
		     year      : integer;
		     month     : 1 .. 12;
		     day       : 1 .. 31;
		     hour      : 0 .. 23;
		     minute    : 0 .. 59;
		     second    : 0 .. 59;
		   END;

@@ NOTE: TimeStamp may be later extended in GPC to contain the following fields at the end of the TimeStamp record:

Dst_used   : Boolean;     (* If daylight savings are used *)
TimeZone   : Integer;     (* Positive if WEST, in minutes *)
Weekday    : 0..6;        (* 0 is Sunday *)
TimerValid : Boolean;     (* Is the following timer valid *)
us_Timer   : Integer;     (* A microsecond timer that is a 32 bit
                             modulus of the timer returned by the
                             system. *)

Fields Dst_used, TimeZone and WeekDay will be valid when DateValid is TRUE. Field us_Timer will be valid when TimerValid is TRUE.

Complex type and operations:

The following sample programs illustrates most of the COMPLEX type operations. In addition monadic + and - are supported and dyadic +,-,*,/ operations.

program complex_test(output);

var
   z1,z2       : complex;
   len, angle  : real;

begin
   z1 := cmplx (2,1);
   writeln;
   writeln ('Complex number Z1 is: (',re(z1):1,',',im(z1):1,')');
   writeln;

   z2 := conjugate(z1); { GPC extension }
   writeln ('Conjugate of Z1 is: (',re(z2):1,',',im(z2):1,')');
   writeln;
   len   := abs (z1);
   angle := arg (z1);
   writeln ('The polar representation of Z1 is LENGTH=',len:1,
            ' ANGLE=',angle:1);
   writeln;

   z2    := polar (len, angle);
   writeln ('Converting (LENGTH,ANGLE) back to (X,Y) gives: (',
             re(z2):1,',',im(z2):1,')');
   writeln;
   writeln ('The following operations operate on the complex number Z1');
   writeln;

   z2 := arctan (z1);
   writeln ('arctan:  R=',re(z2),', I=',im(z2));

   z2 := z1 ** 3.141;
   writeln ('**3.141: R=',re(z2),', I=',im(z2));
   { cos, ln, exp, sqrt and sqr exist also }

   z2 := sin(z1);
   writeln ('sin:     R=',re(z2),', I=',im(z2));

   z2 := z1 pow 8;
   writeln ('POW 8:   R=',re(z2),', I=',im(z2));

   z2 := z1 pow (-8);
   writeln ('POW (-8):  R=',re(z2),', I=',im(z2));
end.

Direct access files:

@@ Not tested. @@ Write a demo program.

type
  Dfile = file [ 1 .. 100 ] of integer;
var
  F : Dfile;
  P, N : 1..100;

Declares a type for a file that contains 100 integers.

The following direct access routines may be applied to a direct access file:

SeekRead (F, N); { Open file in Inspection mode, seek to record N }
SeekWrite (F, N); { Open file in Generation mode, seek to record N }
SeekUpdate (F, N); { Open file in Update mode, seek to record N }
Update (F); { Writes F^, position not changed. F^ kept. }
p := Position (F); { Return current record number }
p := LastPosition (F); { Return the last record number in file }

If the file is open for Inspection or Update, GET may be applied. If the file is open for Generation or Update, PUT may be applied.

@@ GPC acts like the file would always start at record number 0, and subtracts/adds the lower index from the record number. If you think this is incorrect, let me know.

Restricted types:

Extended Pascal defines restricted types as:

restricted-type = 'restricted' type-name .

A value of a restricted type may be passed as a value parameter to a formal parameter possessing its underlying type, or returned as the result of a function. A variable of a restricted type may be passed as a variable parameter to a formal parameter possessing the same type or its underlying type. No other operations, such as accessing a component of a restricted type value or performing arithmetic, are possible.

program zap;

type
   unres_rec =  record
                  a :  integer;
                end;

   res =  restricted unres_rec;

var
   r1 :  unres_rec;
   r2 :  res;

   i  :  restricted integer;       
   k  :  integer;       

  function zap(p : unres_rec) : res;
  var
     ures :  unres_rec;

  begin
     { The parameter is treated as unrestricted, even though the actual
       parameter may be a restricted object }
     ures.a := p.a;

     { Legal to assign a return value }
     zap := ures;
  end; { zap }

begin
   r1.a := 354;

   { Assigning a restricted return value to a restricted object }
   { @@ Verify if this should really be allowed????? }
   r2 := zap(r1);

   { Passing a restricted object to unrestericted formal parameter is ok }
   r2 := zap(r2);

   { *** The following are illegal *** }
   r2.a := 100;	    { field access }
   r1 := r2;        { := source is restricted type }
   r2 := r1;        { := target is restricted type }
   r1 := zap(r2);   { := a restricted return value to unrestricted object }
   i  := 16#ffff;   { := target is restricted type }
   k  := i + 2;     { Arithmetic with restricted type }
end.

Extended Pascal modules:

@@ Gpc does not yet support:

Gpc should be able to parse full Extended Pascal module syntax. But all the features are not implemented yet.

You may load one PROGRAM and several MODULEs to make up one pascal program. A single file may contain zero or more modules and/or zero or one programs.

Please NOTE: If you have many modules in the same file, the variable and function declarations are visible after the point they have been declared in the implementation even if the interface does not export them. But they do not become visible only by including the interface to another file and separate compiling that (so you do need to export them now). (@@ unfortunately, currently this applies only to variables and functions; all other things are visible after the interface has been compiled whether or not you exported them.)

The nicest way to handle the module interface in separate compilation environment is to use the non-standard

#include "module-interface.ph"

feature. You can collect your module interfaces to a single directory and include them from there by using the "-I DIR" switches to specify the include file search paths to the compiler. (See the GNU CPP manual for more info).

There is currently no attempt to avoid name clashes of separate compiled modules when they are linked together. (The exported variables and functions having the same name in different modules will clash!!!)

Sample module code with separate INTERFACE and IMPLEMENTATION parts follows:

MODULE foobar Interface;	(* INTERFACE *)
	
  EXPORT catch22 = (footype,setfoo,getfoo);

  TYPE footype = integer;

  PROCEDURE setfoo(f: footype);
  FUNCTION  getfoo: footype;

END. { module foobar interface }

MODULE foobar Implementation;	(* IMPLEMENTATION *)

  IMPORT StandardInput;
         StandardOutput;

  VAR foo : footype;

  { Note: the effect is the same as the Forward directive would have:
    parameter lists and return types are not "allowed" in the declaration
    of exported routines. }
  PROCEDURE setfoo;
  BEGIN
    foo := f;
  END;

  FUNCTION getfoo;
  BEGIN
    getfoo := foo;
  END;

  TO BEGIN DO
    BEGIN
      foo := 59;
      writeln ('Just an example of a module initializer. See comment below');
    END;

  TO END DO
   BEGIN
     foo := 0;
     writeln ('Goodbye');
   END;
	
END. { foobar implementation }

Alternatively the module interface and implementation may be combined as follows:

MODULE foobar;			(* ALTERNATIVE METHOD *)
	
  EXPORT catch22 = (footype,setfoo,getfoo);

  TYPE footype = integer;

  PROCEDURE setfoo(f: footype);
  FUNCTION getfoo: footype;

  END; { NOTE: this END is required here, even if the
         module-block below would be empty. }

  VAR foo : footype;

  PROCEDURE setfoo;
  BEGIN
    foo := f;
  END;

  FUNCTION getfoo;
  BEGIN
    getfoo := foo;
  END;

END. { module foobar }

Either one of the two methods may be used with:

PROGRAM what(output);

import catch22;
	
BEGIN
  setfoo (999);
  writeln (getfoo);
END.

The INTERFACE has to be in the same file as the program/module that uses it's exported names. Otherwise GPC does not know anything about it and fails to compile the file.

Somewhat simpler GPC modules are also supported:

Note: this is not supported in Extended Pascal standard.

This is a simpler module support that does not require exports, imports, module headers etc.

These non-standard simple Gpc modules look like (does not have an export part, does not have a separate module-block, does not use import/export features.)

MODULE foobar;
  TYPE footype = integer;
  VAR foo: footype;

  PROCEDURE setfoo(f: footype);
  BEGIN
    foo := f;
  END;

  FUNCTION getfoo: footype;
  BEGIN
    getfoo := foo;
  END;
END.

PROGRAM what(output);

  (* In case the module foobar is loaded from another file *)
  PROCEDURE setfoo(f: footype); External;
  FUNCTION  getfoo: footype;    External;

BEGIN
  setfoo (999);
  writeln (getfoo);
END.

Module initialization and finalization:

TO BEGIN DO module initialization and TO END DO module finalization constructs are supported if the GNU compiler supports constructors and destructors in your target machine. (It always does if you use the GNU Linker).

If the initialization and finalizations do not work by default, but you have the GNU Linker, use option -fgnu-linker when compiling the program.

I re-implemeted the standard I/O handling and now the input and output can also be used from the initialization and finalization parts.

@@ Try these, send me bug reports. These are not tested.

Binding of objects to external names:

GPC supports the extended pascal bind,unbind and binding operations when applied to files.

The compiler will currently reject binding of other object types (@@ Perhaps the run time system should do the rejection?)

GPC implements extensions to the required predefined record type BindingType:

BindingType = PACKED_RECORD
                Bound             : Boolean;
                Extensions_Valid  : Boolean;
                Writable          : Boolean;
                Readable          : Boolean;
                Existing          : Boolean;
                Error             : Integer;    { Unused currently }
                Size              : Integer;    { # of elements or -1 }
                Name              : String (BINDING_NAME_LENGTH);
              END;

The fields BOUND and NAME are required by the standard. All other fields are extensions.

The meaning of the extensions to the BindingType record type, and the value of BINDING_NAME_LENGTH is defined in this document, section IMPLEMENTATION DEFINED FEATURES (E.14). It is a compiler constant, the run time system accepts any length.

The Size field is a latest addition to BindingType; I added that because the direct access files actually require that the file is not bigger that the definition; and lastposition(file) does not work before the file is opened. The "Size" field can then be used to determine the size before open, and if the upper bound of the direct access file is a variable one should be able to open files of any size without violating the standard.

The following is an example of the binding:

program z(input,output,f);

var
   f :  text;
   
procedure bindfile (varf :  text);
var
   b : BindingType;

begin
  unbind (f);
  b := binding (f);
  repeat
    write ('Enter file name:');
    readln (b.name);
    bind (f, b);
    b := binding (f);
    if not b.bound then
      writeln ('File not bound--try again');
  until b.bound;
end;

begin

  bindfile (f);

  (* Now the file F is bound to an external file.
   *
   * You can use the implementation defined fields
   * to check if the file is Readable, Writable and
   * if it Exists. These are valid if the.Extensions_Valid
   * field is TRUE.
   *)   
end.

Function pointers:

GPC suports also function pointers and calls through them. This is a non-standard feature.

program zap(output);

type
    proc_ptr = ^ procedure (integer);

var
    pvar : proc_ptr;

procedure write_int(i: integer);
begin
  writeln ('Integer: ',i:1);
end;

begin
  (* PVAR points to function WRITE_IT *)
  pvar := &write_int;

  (* Dereferencing a function pointer calls the function *)
  pvar^(12345);
end.

String catenation:

Gpc supports string catenation with the '+' operator. All string-types are compatible, so you may catenate any chars, fixed length strings and variable length strings with each other.

program scat (input, output);

var
   ch          : char;
   str         : string(100);
   str2	       : string(50);
   fstr        : packed array [ 1 .. 20 ] of char;

begin
   ch   := '$';
   fstr := 'demo';        { padded with blanks }
   write ('Give me some chars to play with: ');
   readln (str);
   str := '^' + 'prefix:' + str + ':suffix:' + fstr + ch;
   writeln ('Len' + 'gth = ', length (str));
   writeln (str);
end.

Type qualifiers:

@ New feature. @ Currently gpc runtime does not know anything about these. @ These may change/or get removed...

As an extension, GPC allows you to use type qualifiers:

__byte__
8 bit integer
__short__
Short integer (16 bits) or real type (32 bits)
__long__
Long integer or real type
__longlong__
long long integer type (64 bits)
__unsigned__
Unsigned INTEGER type

The __unsigned__ works for all integer types, also those that have been previously declared with some other type qualifier, like __short__. The other qualifiers do not accept types that have already been modified with a type qualifier.

The syntax to use the qualifiers:

type-denoter > TYPE-QUALIFIER type-name

(The metasymbol `>' means type-denoter has also other meanings)

Most of these should be done with subranges anyway. However, '__short__ real' can not be done like that, neither can '__unsigned__ integer' or '__longlong__ integer'.

program zap(output);

type
   byte     = __byte__     integer;
   longint  = __long__     integer;
   float    = __short__    real;
   u_long   = __unsigned__ longint;
   verylong = __longlong__ integer;

var
  i8  : byte;
  i16 : __short__ integer;
  foo : u_long;
  pi  : float;
  big : verylong;

begin
  pi  := 3.141592654;
  i16 := 1000;
  big := MaxInt * i16;
  i8  := 127;

  (*
   * Hmm, does not work because constant is treated as an integer,
   * and this is too large. Need a method to specify long constants.
   *
   * What is the syntax in other Pascal compilers? Suggestions, please!
   *

  foo := 16#deadbeef;

   *)
end.

Accessing command line arguments:

The following module accesses the command line with ParamStr and ParamCount functions.

These follow the Un*x semantics, so that

MODULE command_line interface;

EXPORT cmdline = (Max_length, Arg_type, ParamStr, ParamCount);

CONST
   Max_length = 255;     { Max length of each argument.
                           If some arg is longer, the run time system
                           traps it. }

TYPE
  Arg_type = String(Max_length);

  FUNCTION ParamCount: Integer;

  FUNCTION ParamStr (arg_num: integer): Arg_type;
END. { command_line interface }

MODULE command_line implementation;

  { These are in the GPC runtime library }
  FUNCTION _p_paramcount : Integer; C;
  FUNCTION _p_paramstr (num: Integer; VAR str: String): Boolean; C;

  FUNCTION ParamCount;
  BEGIN
     ParamCount := _p_paramcount;
  END; { ParamCount }

  FUNCTION ParamStr;
  
  VAR
   Str       : Arg_type;
   Success     : Boolean;

  BEGIN
     Success := _p_paramstr (arg_num, Str);

     (* Should perhaps do something else on failure.
      *
      * Now it returns the empty string, which is also a valid
      * parameter.
      *)
     IF Success THEN
        ParamStr := Str
     else
        ParamStr := ";
  END; { ParamStr }
END. { command_line implementation }

{ The program below, when compiled with the interface module and
  linked with the implementation module, accesses the command
  line arguments. }	

program zap (output);

import cmdline;

var
   counter : integer;

begin
   writeln ('Program fetches command line arguments and outputs one per line');
   writeln ('Max length of each argument is ',Max_Length:1,' characters');

   for counter := 0 to ParamCount-1 do
      writeln ('Command line arg ',counter:1,' is "',paramstr(counter),'"');
end.

Borland Extensions in GNU Pascal

GNU Pascal implements these Borland extensions to the ISO Pascal language:


Go to the first, previous, next, last section, table of contents.