comp.lang.ada
 help / color / mirror / Atom feed
* Re: Ada9X Features
@ 1994-09-12 15:12 Michael Hagerty
  1994-09-13 16:08 ` Michael Feldman
  0 siblings, 1 reply; 9+ messages in thread
From: Michael Hagerty @ 1994-09-12 15:12 UTC (permalink / raw)


On Sun, 11 Sep 1994, Michael Feldman <mfeldman@SEAS.GWU.EDU> wrote:

MF> This discussion of "creeping featurism" in Ada 9X points up just
  > how difficult a consensus process is. Everyone says "this language
  > is getting too big; we don't need all this junk; leave _my_
  > favorite stuff in, please."

Much, much, much horse trading goes on in building a consensus on a
standards committee.  I recall one instance on the Pascal committee
where, in order to get the set extensions I so dearly wanted, I went
along with adding complex numbers...  Even then, set complement was
whacked way down when the rest of the committee guessed what was
required in generating the complement of the null set!  Shucks...

Almost every language (he says qualifiedly) has parts that are unused
in common applications.  The goal is to build something like the
mid-scale swiss army knife: all of the things you need daily, some of
what you may need occasionally, but still small enough to carry in
your pocket, so that you will have it when you need it <everyday>.

I think of PL/I as the mega-swiss army knife; you know, the one in
the case that is so big that you could not imagine anyone schlepping
that puppy around...  Ada, in its current implementations, is more
like a ShopMate power tool.

Even Lincoln's comment about "pleasing all of the people" in mind,
there is the issue of timeliness and "hitting the market window".  I
recognize that standard Pascal's position in the market was harmed
by not having an extended language standard at the time the C weenies
were running amok.  Promises of a C standard right around the corner
were believed only by those who had never worked on a standard, but
it did have the effect of spreading FUD (fear, uncertainty and doubt).

Regards, Mikey <michael.hagerty@nitelog.com>



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: Ada9X Features
  1994-09-12 15:12 Ada9X Features Michael Hagerty
@ 1994-09-13 16:08 ` Michael Feldman
  1994-09-13 20:04   ` Robert Dewar
  1994-09-14  9:15   ` Richard A. O'Keefe
  0 siblings, 2 replies; 9+ messages in thread
From: Michael Feldman @ 1994-09-13 16:08 UTC (permalink / raw)


In article <9408127793.AA779382777@smtpgw.fnoc.navy.mil>,
Michael Hagerty  <mhagerty@FNOC.NAVY.MIL> wrote:
>On Sun, 11 Sep 1994, Michael Feldman <mfeldman@SEAS.GWU.EDU> wrote:
>
>MF> This discussion of "creeping featurism" in Ada 9X points up just
>  > how difficult a consensus process is. Everyone says "this language
>  > is getting too big; we don't need all this junk; leave _my_
>  > favorite stuff in, please."
>
>Much, much, much horse trading goes on in building a consensus on a
>standards committee.  I recall one instance on the Pascal committee
>where, in order to get the set extensions I so dearly wanted, I went
>along with adding complex numbers...  Even then, set complement was
>whacked way down when the rest of the committee guessed what was
>required in generating the complement of the null set!  Shucks...

Good anecdote. I was not on the Pascal committee but followed some of the 
discussions. I recall that the standard-making process stalled for some
time on the issue of "conformant array parameters", a seemingly obvious
idea in which array parameters to subprograms conform to the bounds of
the actual parameter (sort of a half-way "unconstrained array type paramter"
to use Ada's terms). This seemed natural to many, especially since
Fortran had it for years.

After all that, there are _two_ Pascal standards, one adopted by ISO
which includes conformant array parameters, and one adopted by ANSI,
which is the ISO one _minus_ conformant array parameters. The story
going around was that the US compiler vendors kept it out of the US 
standard.

And Pascal is a pretty simple language.:-)

Mike Feldman
------------------------------------------------------------------------
Michael B. Feldman -  chair, SIGAda Education Working Group
Professor, Dept. of Electrical Engineering and Computer Science
The George Washington University -  Washington, DC 20052 USA
202-994-5919 (voice) - 202-994-0227 (fax) - mfeldman@seas.gwu.edu (Internet)
NOTE NEW PHONE NUMBER.
"Pork is all that stuff the government gives the other guys."
------------------------------------------------------------------------



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: Ada9X Features
  1994-09-13 16:08 ` Michael Feldman
@ 1994-09-13 20:04   ` Robert Dewar
  1994-09-14 13:06     ` Fortran 90 arrays (was: Re: Ada9X Features) Norman H. Cohen
  1994-09-16  1:39     ` Ada9X Features Michael Feldman
  1994-09-14  9:15   ` Richard A. O'Keefe
  1 sibling, 2 replies; 9+ messages in thread
From: Robert Dewar @ 1994-09-13 20:04 UTC (permalink / raw)


Mike, you are wrong about Fortran and conformant arrays, Fortran does
NOT have this feature, at least not in anything like the form of ISO
Pascal. Arrays in Fortran are passed by address only, and bounds information
is not passed (note I am talking up through 77 here, who knows what they
have wrought in 90 -- well probbaly some reader of this group does :-)




^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: Ada9X Features
  1994-09-13 16:08 ` Michael Feldman
  1994-09-13 20:04   ` Robert Dewar
@ 1994-09-14  9:15   ` Richard A. O'Keefe
  1994-09-14 14:26     ` Michael Feldman
  1 sibling, 1 reply; 9+ messages in thread
From: Richard A. O'Keefe @ 1994-09-14  9:15 UTC (permalink / raw)


mfeldman@seas.gwu.edu (Michael Feldman) writes:

>After all that, there are _two_ Pascal standards, one adopted by ISO
>which includes conformant array parameters, and one adopted by ANSI,
>which is the ISO one _minus_ conformant array parameters. The story
>going around was that the US compiler vendors kept it out of the US 
>standard.

There is a new standard.  ISO Pascal Extended.  It has _two_ mechanisms
for varying-size arrays:  the old conformant array parameters, and a
parametric type mechanism that looks uncannily like Ada.  The story I
heard was that the people who voted to keep conformant array parameters
out wanted to avoid conflicts with a possible future _better_ method,
which eventually arrived, but by then the perception of Pascal as too
crippled to use had sunk in.  I am aware of one ISO Pascal Extended
compiler in progress, but have not been able to locate any commercial
ones or plans for commercial ones, despite the "new" standard having
been out for years.

For what it's worth, the easiest way I can think of to implement "modern"
Pascal would be to build it on top of GNAT.  I'm not sure whether this
says more about Pascal Extended or about Ada.

-- 
The party that took Australia into Vietnam wants to smash the inner-city
yacht school and put a Grand Prix in its place.  They don't change.



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Fortran 90 arrays (was: Re: Ada9X Features)
  1994-09-13 20:04   ` Robert Dewar
@ 1994-09-14 13:06     ` Norman H. Cohen
  1994-09-16  1:39     ` Ada9X Features Michael Feldman
  1 sibling, 0 replies; 9+ messages in thread
From: Norman H. Cohen @ 1994-09-14 13:06 UTC (permalink / raw)


In article <3550l2$8o7@schonberg.cs.nyu.edu>, dewar@cs.nyu.edu (Robert Dewar)
writes: 

|>         Arrays in Fortran are passed by address only, and bounds information
|> is not passed (note I am talking up through 77 here, who knows what they
|> have wrought in 90 -- well probbaly some reader of this group does :-)
|>

Fortran 90 has "assumed shape arrays".  If a dummy argument (that's
Fortranese for formal parameter) named A is declared

       dimension(:,:)::A

for example, it's a two dimensional assumed-shape array that gets its
bounds from the actual argument.  A subroutine with such an argument must
be declared in an interface block--roughly analogous to an Ada subprogram
or package declaration.  That alerts the compiler to pass a descriptor
for the array, containing bounds information, rather than just the
address of the array.  This preserves upward compatibility, because
arrays can be passed to old-style subroutines by address, allowing the
conventional Fortran overlay tricks to be used within those subroutines.
There are intrinsic functions analogous to the Ada 'First(n) and 'Last(n)
attributes.

Fortran 90 also has "deferred shape arrays," analogous to values in
access types designating unconstrained array subtypes.  Such arrays are
allocated dynamically by specifying their bounds in an Allocate
statement.  A conspicuous difference is that Fortran 90 pointers are
dereferenced implicitly, like C++ references.

Ada programmers will find a number of familiar terms and programming
mechanisms in Fortran 90.  Unfortunately, the correspondence between the
terms and the mechanisms is not the same as in Ada.  For example,
Fortran 90 has record types, but they're called derived types!  Fortran
90 has overloaded declarations, but they're called generic interfaces!

--
Norman H. Cohen    ncohen@watson.ibm.com



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: Ada9X Features
  1994-09-14  9:15   ` Richard A. O'Keefe
@ 1994-09-14 14:26     ` Michael Feldman
  1994-09-21  6:03       ` ISO Pascal Extended Richard A. O'Keefe
  0 siblings, 1 reply; 9+ messages in thread
From: Michael Feldman @ 1994-09-14 14:26 UTC (permalink / raw)


In article <356ev1$s8o@goanna.cs.rmit.oz.au>,
Richard A. O'Keefe <ok@goanna.cs.rmit.oz.au> wrote:

>There is a new standard.  ISO Pascal Extended.  It has _two_ mechanisms
>for varying-size arrays:  the old conformant array parameters, and a
>parametric type mechanism that looks uncannily like Ada.  The story I
>heard was that the people who voted to keep conformant array parameters
>out wanted to avoid conflicts with a possible future _better_ method,
>which eventually arrived, but by then the perception of Pascal as too
>crippled to use had sunk in.  I am aware of one ISO Pascal Extended
>compiler in progress, but have not been able to locate any commercial
>ones or plans for commercial ones, despite the "new" standard having
>been out for years.

Interesting. I had not heard of this, nor seen any books describing it.
(Or is the standard available by ftp somewhere?) Apparently the compiler
houses are not rushing to implement it either.

>For what it's worth, the easiest way I can think of to implement "modern"
>Pascal would be to build it on top of GNAT.  I'm not sure whether this
>says more about Pascal Extended or about Ada.

Even more interesting. Can you briefly describe how to build it on top
of GNAT? (Pascal-ish _sets_ are a CS2 exercise to build on Ada 83.)
Are there Pascal extended features that carry over easily into Ada?

Mike Feldman
------------------------------------------------------------------------
Michael B. Feldman -  chair, SIGAda Education Working Group
Professor, Dept. of Electrical Engineering and Computer Science
The George Washington University -  Washington, DC 20052 USA
202-994-5919 (voice) - 202-994-0227 (fax) - mfeldman@seas.gwu.edu (Internet)
NOTE NEW PHONE NUMBER.
"Pork is all that stuff the government gives the other guys."
------------------------------------------------------------------------



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: Ada9X Features
@ 1994-09-15 17:56 Michael Hagerty
  0 siblings, 0 replies; 9+ messages in thread
From: Michael Hagerty @ 1994-09-15 17:56 UTC (permalink / raw)


On 13 Sep 1994, Michael Feldman <mfeldman@SEAS.GWU.EDU> responded to my
earler post:

MF> Good anecdote. I was not on the Pascal committee but followed some
  > of the discussions. I recall that the standard-making process stalled
  > for some time on the issue of "conformant array parameters", a seemingly
  > obvious idea in which array parameters to subprograms conform to the
  > bounds of the actual parameter (sort of a half-way "unconstrained array
  > type paramter" to use Ada's terms). This seemed natural to many,
  > especially since Fortran had it for years.

The discussion of conformant arrays is long and tedious with the
sentinel issue being that the originator of the proposed standard tacked
on a feature which had never been tested, saying "take it or leave it".
Note that this was not the designer of the language, but someone who was
believed to be advancing a personal agenda.  The animosity and distrust
engendered in the American committee as a result of this high-handed
tactic doomed conformant arrays to second-class status independent of
the feature's perceived usefulness or uselessness.

Without arguing the reasonableness of such (childish) behavior, I can
say from first hand participation, that there were many of us who were
badly chafed by the whole experience.  I do not believe that this has
happened on Ada9X.

MF> After all that, there are _two_ Pascal standards, one adopted by ISO
  > which includes conformant array parameters, and one adopted by ANSI,
  > which is the ISO one _minus_ conformant array parameters. The story
  > going around was that the US compiler vendors kept it out of the US
  > standard.

Not true anymore.  There is one and only one Extended Pascal Standard.
It does, however, forever relegate conformant arrays to second-class
status, indicating that they will be phased out in a future standard.

MF> And Pascal is a pretty simple language.:-)

Looking more and more like Ada every day...

Regards, Mikey
---
Michael Patrick Hagerty, Computer Sciences Corp.    | mhagerty@fnoc.navy.mil
Fleet Numerical Meteorology and Oceanography Center | Phone:  (408) 656-4456
7 Grace Hopper Ave, Stop 1, Monterey, CA 93943-5501 | FAX:    (408) 656-4313

         "Outside of a dog, a book is man's best friend;
          inside a dog, it's too dark to read..."  Groucho Marx



^ permalink raw reply	[flat|nested] 9+ messages in thread

* Re: Ada9X Features
  1994-09-13 20:04   ` Robert Dewar
  1994-09-14 13:06     ` Fortran 90 arrays (was: Re: Ada9X Features) Norman H. Cohen
@ 1994-09-16  1:39     ` Michael Feldman
  1 sibling, 0 replies; 9+ messages in thread
From: Michael Feldman @ 1994-09-16  1:39 UTC (permalink / raw)


In article <3550l2$8o7@schonberg.cs.nyu.edu>,
Robert Dewar <dewar@cs.nyu.edu> wrote:
>Mike, you are wrong about Fortran and conformant arrays, Fortran does
>NOT have this feature, at least not in anything like the form of ISO
>Pascal. Arrays in Fortran are passed by address only, and bounds information
>is not passed (note I am talking up through 77 here, who knows what they
>have wrought in 90 -- well probbaly some reader of this group does :-)
>
Yes, I was speaking in rather general terms. The point was that because
Fortran arrays are passed by address, one could write array declarations
in subprograms using (if my syntax is right) asterisks in place of
the dimensions. You're right that the bounds are not passed, and
must therefore be passed as extra parameters. 

Excuse the looseness; I didn't mean to get the discussion off track.
The point was that - even with Pascal, a relatively simple language,
it was rather difficult to reach a consensus in certain areas, and
in the end there were _two_ consensuses (consensi?), not one.

This was in response to the thread on "Ada 9X is too big - but please
don't take _my_ features out." People speak about standards as though
they could be handed down from Olympus, and often don't understand
just how much horse-trading and how many constituencies have to be
satisfied.

Mike Feldman
------------------------------------------------------------------------
Michael B. Feldman -  chair, SIGAda Education Working Group
Professor, Dept. of Electrical Engineering and Computer Science
The George Washington University -  Washington, DC 20052 USA
202-994-5919 (voice) - 202-994-0227 (fax) - mfeldman@seas.gwu.edu (Internet)
NOTE NEW PHONE NUMBER.
"Pork is all that stuff the government gives the other guys."
------------------------------------------------------------------------



^ permalink raw reply	[flat|nested] 9+ messages in thread

* ISO Pascal Extended
  1994-09-14 14:26     ` Michael Feldman
@ 1994-09-21  6:03       ` Richard A. O'Keefe
  0 siblings, 0 replies; 9+ messages in thread
From: Richard A. O'Keefe @ 1994-09-21  6:03 UTC (permalink / raw)


I commented in comp.lang.ada that
>There is a new (Pascal)standard.  ISO Pascal Extended.

mfeldman@seas.gwu.edu (Michael Feldman) replied:

>Interesting. I had not heard of this, nor seen any books describing it.
>(Or is the standard available by ftp somewhere?) Apparently the compiler
>houses are not rushing to implement it either.

For what it's worth, here is a brief sketch of ISO Pascal Extended.
Here's my summary:
(a) Any Ada 83 compiler vendor could easily support ISO Pascal Extended as well.
(b) If you were already using a language _other_ than Pascal, there is no
    reason to prefer Pascal Extended to Ada.
(c) If you were hoping for a standard that would make it easier to migrate
    non-trivial Pascal programs between Turbo Pascal and Unix or mainframe
    Pascals, tough luck.
(d) If you were hoping for a standard that would fix some of the nastier
    problems in Pascal (no error recovery in read(), forward procedure
    parameters _must_ be widely separated from the corresponding blocks,
    numeric labels, and/or precedence botch, &c), tough luck.
In short, too little, too different, too late.


Some brief notes in ISO/IEC 10206: 1991, Extended Pascal.

1.  Identifiers any length, not case sensitive, can contain [_A-Za-z0-9].
    All names can be qualified by an <interface> <dot> prefix.

    New special symbols '><' (sym.diff.), '=>' (renaming), '**' (power),
    'pow' (power), 'and_then' (conditional and), 'or_else' (conditional or),
    'import, 'export', 'module', 'qualified' (module-related), 'bindable'
    (interface to external objects like files), 'otherwise' (in case stmts),
    'protected', 'restricted' (type modifier), 'value' (initial value).

    Integers can be written as base#extendedDigits.  Note to Ada lovers:
    no closing #, no underscores in numbers, no radix point among the
    extendedDigits.

2.  One of the most popular and most requested extensions and easiest to
    provide, namely alphanumeric labels, is NOT present.

3.  The sections of a block can occur more than once and in any order
    (except that the new 'import' section can only occur once and at the
    beginning).  Constants can be of structured types.  Types and
    variables can be given initial values:
	VAR id1,...,idn : type VALUE expr;
    The initial value is actually a property of the _type_ and thus all
    the identifiers get copies of the _same_ value evaluated _once_.  I
    prefer this to the Ada rule (where the expr is evaluated n times).
    It is not only fields that can be given default initial values (as in
    Ada), any type identifier can be associated with an initial value.

4.  Variable syntax is extended:  <var>[<lower> .. <upper>] is a substring,
    functions can return structured values, and those values can be treated
    as variables, so that
	f(x)[i]  f(x)[L..U]  f(x).foo  f(x)^
    are all legal provided f has appropriate result type.  As structured
    constants now exist, such constants can also be indexed &c.

5.  Basic types:

    integer : no change except for new based literals
	      +, -, *, /, div, mod, as before.
	      New (X pow N) raises X to integer power N, where X is
	      integer, real, or complex.

    real    : still not usable in portable code.  The standard is VERY
	      clear that 'real' =/= 'float'.  maxreal need not be the
	      largest representable "real" number.  The text says that
	      "The value of EPSREAL shall be the result of subtracting
	      1.0 from the smallest value of real-type that is greater
	      than 1.0".  It is not clear whether the subtraction is to
	      be _mathematical_ subtraction or real-type subtraction;
	      if the latter it is entirely possible for EPSREAL to be 0.0,
	      which does not seem very useful.
	      +, -, *, /, as before.
	      New (X ** P) raises X to real power P, where X is
	      integer (-> real), real, or complex.

    Boolean : no change
	      New operators (P and_then Q), (P or_else Q) evaluate P
	      first, then evaluate Q only if needed.  This was a wonderful
	      opportunity to do something about the Great Pascal Operator
	      Disaster, and give these new operators wider scope than the
	      relational operators.  That opportunity was spurned; they
	      have the same b****y stupid precedence as 'and' and 'or'.

    char    : no change (and still no BCPL-style escapes like *T or \t).
	      One thing to note:  the language needs *no* change to deal
	      with 16-bit characters.

    complex : "The complex-type shall be a simple-type."  What a sense
	      of humour, eh?  Pretty good, actually, except that it is
	      built on top of an excessively fuzzy specification of "real".
	      There is no "raise to complex power".
	      cmplx(X, Y) and polar(R, T) construct complex numbers.

    enums   : no change.  *STILL* no enumeration read/write, and no tools
	      to build it with.  The built-in operations succ() and pred()
	      have been extended:
		succ(X, N) -> return ord(X)+N with same type as X
		pred(X, N) -> return ord(X)-N with same type as X
	      This also applies to Boolean, char, and integer.  Note that
	      it isn't quite good enough.  Many people wanted an inverse
	      of ord.  Given
		type T = (C1, ..., Cn); var X: T;
	      then X := succ(C1, K) is almost the same as X := T(K), but
	      it breaks horribly if you add a new enum literal before C1.

    ranges  : CAN BE DYNAMIC.	      
	      Many Pascals have something like min(T) or first_of(T); to
	      get that you can do pred(X, ord(X)) provided X is initialised.
	      So the inverse of ord is
		X := succ(pred(X, ord(X)), K);   {X := T(K)}
	      Many Pascals have something like max(T) or last_of(T); I can
	      discover no way to do that using what Pascal Extended provides.
	      In Ada you can ask whether a variable would fit in a subrange:
		if X in T then ...
	      In many Pascals you can also ask that:
		if X in [first_of(T) .. last_of(T)] then ...
	      and that will work even when the bounds of T are changed.
	      You can _not_ do that in Pascal Extended.

  restricted: T = representation; restricted T = abstraction (sort of).

    arrays  : CAN BE DYNAMIC, because ranges can be dynamic.  But Pascal
	      still doesn't believe in zero.  Both
		var x : array[1:0] of real;  (*and*)
	            y : array[n:n-1] of real;
	      are illegal (the first is an error that must be reported at
	      compile time, the second an error that must be reported at
	      run time).  Ada-like array constructors now exist.
	      Functions can return arrays.  Constructors exist.  They
	      begin with a type name, then resemble a case statement
	      body with '[' ']' for 'of' 'end'.  For example, consider
		type A = array [1..10] of integer;
		case I of 1..3,5: X := 135; 6..8: X := 68;
			otherwise: X := 4910 end;
	      and the array-valued expression
		     A [  1..3,5:      135; 6..8:      68;
			otherwise:      4910 ]
	      Note especially that element values are separated by
	      SEMICOLONS, not commas.

    strings : If L is a static expression yielding 1, and R is either
	      literally L..E or a type name for L..E, then
		packed array [R] of char
	      is a fixed string type.  (E can be dynamic.)  string(E) is
	      a "varying" string type (0 <= length <= E).
	      Functions can return strings.

	      readstr(StringSource{, variable}...);
	      writestr(StringDestination{, output_parameter}...);
	      do the obvious things.  Built in functions length (current
	      dynamic length), index (find substring), substr, trim, and
	      two sets of comparisons; "+" is concatenation.
	      
    records : no change except that OTHERWISE is allowed in a variant part
	      and fields can be given initial values (because types can).
	      Trap for young players: initial values in variant parts are
	      allowed but basically useless (except when the case constant
	      is specified in a call to new() or a constructor).
	      Functions can return records.  There are constructors.
	      Put the type name, then what follows looks like a record
	      type, with '[' for 'record', ']' for 'end', and only one
	      branch in each variant.  E.g. from
		type R = record A, B: integer; case C: Boolean of
				false: (D: char); true: (E: real) end;
	      we get expressions like
		R[A, B: 2; case C: true of [E: 3.0]]
	      Note in particular that SEMICOLONS are used as separators,
	      not commas, which wrecks "panic mode" syntax error recovery.

  new types : there are two new predefined record types:
		TimeStamp has fields
		    DateValid, year, month, day,
		    TimeValid, hour, minute, second
		and possibly others, so you cannot write TimeStamp[...].
		GetTimeStamp(t) stores the local date & time in t.
		date(t) returns a locale-dependent string from the date bits
		time(t) returns a locale-dependent string from the time bits
		There are no built-in operations for comparing TimeStamps or
		for doing arithmetic on them.

		BindingType has fields
		    bound : Boolean
		    name  : implementation-defined string type
	        and possibly others.  See note 10.

    sets    : no change, except that
	      Functions can return sets.
	      card() was in Jensen & Wirth, but not in the standard.
	      Now it is in the standard.  S1 >< S2 is symmetric difference.
	      There are still no proper subset/superset comparisons.
	      Set constructors can have the type name in front, but they
	      still use COMMAS, not semicolons.  So given
		type S = set of [1..10];
	      both [5,2] and S[5,2] are allowed.

    files   : can be given an index, file [IndexRange] of Type, which
	      allows random access.
	      Functions cannot return files.

	      rewrite(f)	-- as before
	      extend(f)		-- preserves old contents; new writes at end
	      reset(f)		-- as before
	      get(f)		-- as before
	      update(f)		-- replace existing record
	      put(f)		-- as before
	      SeekRead(f, n)	-- random position for reading
	      SeekUpdate(f, n)	-- random position for update
	      SeekWrite(f, n)	-- random position for writing
	      empty(f)		-- true if f empty; f must be indexed!
	      LastPosition(f)	-- index of last record in f (may not be
				   defined if f is empty!)
	      position(f)	-- index of currend record in f (may not
				   be defined if f is empty!)

	      The point about the positions is that if you do
		type FooIndex = (A, B, C);
		     FooType = file [FooIndex] of char;
		var  Foo: FooType;
		rewrite(Foo);
	      then at that point LastPosition(Foo) and position(Foo)
	      would have to be succ(A, 0-1), which does not exist.

	      SeekUpdate sets the buffer variable, SeekWrite doesn't.
	      For file names, see note 10.

    pointers: no change (still can't point to ordinary variables).

    schemas : TYPE id( {id*,:ordinaltype}*; ) = type.  Example:
	      type vector(n: integer) = array [1..n] of real;

  enquiries : TYPE OF <variable> can be used as a type; this is useful
	      with conformant arrays and with schemas.

    Types can have initial values associated with them.
	type int0 = integer value 0;
	     int1 = integer value 1;
	var x: int0; y: int1;
    x will be initialised to 0, y to 1.


6.  Procedures and functions.

    The single worst mistake in Pascal was that when you declare a
    procedure or function forward, you are *forbidden* to repeat the
    parameter list at the actual declaration site.  It would have taken
    about 4 lines of text written twice to *allow* duplication of the
    parameter list and thus let people avoid this error prone bit of
    nastiness, and since a compiler must _already_ retain the parameter
    names and types, it would require _very_ little work in a compiler
    to support this extension.  BUT THE WRETCHED COMMITTEE DID NOT ADD
    THIS EXTENSION!

    Assignment to the function identifier was always a rather error-
    prone method of returning a result; a 'return' statement as in PL/I
    or C is far easier to get right.  The only change here is that you
    can now give an alias for the function result:
	function foo(...) = bar: T; ...
    within the body of foo() you can use 'bar' as a variable and you _can't_
    use 'foo' that way; the final value of 'bar' is the function result.

    Value and VAR parameters can now be declared PROTECTED which means
    that the routine is not allowed to change them.  There is no exact
    equivalent of Ada's "in" mode; PROTECTED VAR still requires a
    variable actual parameter, not an expression, and it is still a
    by-reference method, so the value _may_ change as a result of
    aliasing.  PROTECTED {value} still implies a copy.

    Conformant array parameters are _still_ an optional (level 1) feature,
    despite the fact that the standard _demands_ a more powerful method
    whose underlying machine can necessarily support conformants as well.

7.  A form of error handling was proposed and described in SigPlan Notices,
    but is NOT in the standard.  There is NO form of error handling in the
    standard.  In particular, there is no way to recover from errors in
    data processed by read() or readln(), which means that anyone trying
    to cope with real data has to roll her or his own.  Speaking of errors,
    I _think_ the standard in effect forbids the use of IEEE 754/854
    arithmetic.

8.  Statements.

    Case statements can have 'otherwise' (it must be last) and case labels
    can be ranges (so basically a case label is now a set literal missing
    its brackets).

    For statements have an additional form:
	for Identifier in SetExpression do Statement
    (the order in which elements are processed is implementation dependent).

    No error recovery for input/output.  No enumeration input/output.
    Strings can be read and written.

9.  Modules.

    Years ago, UCSD Pascal introduced "units".  Much of UCSD Pascal was
    carried over to Borland's spectactularly successful "Turbo Pascal",
    which today is _the_ practical Pascal system.  The mechanism is
    simple, demonstrably implementable on small machines, useful, and
    the de facto standard.  No single change to the Pascal standard would
    have been more useful than "blessing" this established practice.

    So the standardisers invented something new.  It is necessary to
    distinguish between MODULES and INTERFACES.  An interface is a named
    collection of constant,type,variable,procedure, and/or function
    identifiers.  Modules import identifiers _from_ interfaces (not from
    other modules), and they export one OR MORE entire interfaces, not
    identifiers.  Apart from the distinction between modules and
    interfaces, and the ability of a module to export more than one
    interface, the module system is pretty much like Modula-2.

    The extra generality is more apparent than real.  Anything that can
    be done using Pascal Extended modules can be done using UCSD Pascal
    units, with one UCSD unit for each Extended module AND for each
    Extended interface.  Almost anything:  Pascal Extended allows
    circular dependencies, but initialisation doesn't work if you do that.

    This one area of the standard, more than anything else, makes me feel
    that the Pascal Extended committee were out of touch.

10. One widely implemented extension is
	reset(FileVariable, FileNameString[, ... Status]);
	rewrite(FileVariable, FileNameString[, ... Status]);
    and if you have extend,
	extend(FileVariable, FileNameString[, ... Status]);
    would make a lot of sense.  The idea is that these extensions let
    you specify the file name as a string, and optionally get a "status"
    result instead of aborting if the file cannot be opened.  Turbo Pascal
    does something different and clumsier, but has the machinery to support
    these if that were the standard.

    The standard has adopted neither the extension above (which was in use
    even before the first Pascal standard) nor the Turbo Pascal equivalent.
    Instead, there is a whole new major concept of "bindable" types and
    variables, and a BindingType.  What you have to do is explicitly say

	var
	    b: BindingType;
	    f: bindable file of ... ;

	begin
	    b := binding(f);	{ initialise hidden fields }
	    b.name := FileNameString;
	    bind(f, b);		{ this does not change b }
	    b := binding(f);	
	    if b.bound then { all went well }
	    else { the file could not be opened };
	
	This can be abbreviated to
	    b := binding(f);	{ initialise hidden fields }
	    b.name := FileNameString;
	    bind(f, b);		{ this does not change b }
	    if binding(f).bound then { all went well }

    What does it mean to have a bindable variable that is not a file?
    It would make a very nice typed interface to memory-mapped I/O:
    'bind' could open the file and map it into memory, and set the
    variable to point to the area of memory, 'unbind' could close the
    file.  On the other hand, the standard doesn't _require_ bind &
    unbind to work with anything except files.

    I really do _not_ want to have to use
	b := binding(f);
	b.name := FileNameString;
	bind(f, b);
	if binding(f).bound then begin
	    reset(f);
    when existing dialects would let me say
	reset(f, FileNameString, status);
	if status = IO_OK then begin ... 
    I can program my way around this for any specific file type, but
    as Pascal Extended still lacks generic procedures, I'd have to do
    it over and over again.  Note in particular that the predefined
    type 'text' is NOT bindable!


Summary:
    The standard is 220 printed pages.  Compared with Ada 83, it lacks
    nested packages, tasks, generics, *portable* floating point, any
    kind of exception handling, and pleasant I/O, but it does have
    dynamic ranges, type schemas with discriminants, record and array
    expressions, and strings.

    The new features of the standard tend not to be compatible with the
    dialects that already had them.  There is no detectable influence
    from Object Pascal.


-- 
"The complex-type shall be a simple-type."  ISO 10206:1991 (Extended Pascal)
Richard A. O'Keefe; http://www.cs.rmit.edu.au/~ok; RMIT Comp.Sci.



^ permalink raw reply	[flat|nested] 9+ messages in thread

end of thread, other threads:[~1994-09-21  6:03 UTC | newest]

Thread overview: 9+ messages (download: mbox.gz / follow: Atom feed)
-- links below jump to the message on this page --
1994-09-12 15:12 Ada9X Features Michael Hagerty
1994-09-13 16:08 ` Michael Feldman
1994-09-13 20:04   ` Robert Dewar
1994-09-14 13:06     ` Fortran 90 arrays (was: Re: Ada9X Features) Norman H. Cohen
1994-09-16  1:39     ` Ada9X Features Michael Feldman
1994-09-14  9:15   ` Richard A. O'Keefe
1994-09-14 14:26     ` Michael Feldman
1994-09-21  6:03       ` ISO Pascal Extended Richard A. O'Keefe
  -- strict thread matches above, loose matches on Subject: below --
1994-09-15 17:56 Ada9X Features Michael Hagerty

This is a public inbox, see mirroring instructions
for how to clone and mirror all data and code used for this inbox