CS 334
Programming Languages
Spring 2002

Lecture 14


Procedures and functions as parameters and return values (Section 8.4.3)

Already seen how to pass functional (& procedural) parameters in our interpreter using closures.

When pass function (or procedure) parameters in stack-based languages, must also pass the equivalent of a closure. In particular must pass the environment in which the function was defined. This is accomplished by passing the appropriate static pointer with the function so that can find non-local variables. Usually pass the pair (ep,ip) of environment pointer and instruction pointer as the "closure" of a procedure, when it is passed as a parameter.

Returning functions from functions is harder since defining environment may go away:

program ret;

function a(): function (integer): integer;
        var m: integer;
        
        function addm (n: integer): integer;
                begin
                        return (n + m)
                end;

        begin (* a *)
                m := 5;
                return addm
        end; (* a *)

procedure b (g: function(integer): integer);
        begin (* b *)
                writeln(g(2))
        end (* b *)

begin (* main *)
        b(a())          (* note that a() returns a function, which is                                   
                       then passed to b *)
end.
When b(a()) is called, a() returns a function which depends on the non-local variable m, but m has gone away by the time the function is actually applied. Hence languages (like ML) which allow functions to return functions cannot use the simple stack discipline - must keep around activation records even after their associated function or procedure has returned.

Problems with writing large programs:

Wulf and Shaw: Global Variables Considered Harmful (1973)
  1. Side effects - hidden access

  2. Indiscriminant access - can't prevent access - may be difficult to make changes later

  3. Screening - may lose access via new declaration of vble

  4. Aliasing - control shared access to prevent more than one name for reference variables.

Characteristics of solution:

  1. No implicit inheritance of variables

  2. Right to access by mutual consent

  3. Access to structure not imply access to substructure

  4. Provide different types of access (e.g. read-only)

  5. Decouple declaration, name access, and allocation of space. (e.g. scope indep of where declared, similarly w/allocation of space - like Pascal new)

Abstract Data Types

(Major thrust of programming language design in 70's)

Package data structure and its operations in same module - Encapsulation

Data type consists of set of objects plus set of operations on the objects of the type (constructors, inspectors, destructors).

Want mechanism to build new data types (extensible types). Should be treated same way as built-in types. Representation should be hidden from users (abstract). Users only have access via operations provided by the ADT.

Distinguish between specification and implementation.

Specification:

Book states language should provide:

Method for defining data type and the operations on that type (all in same place). The definitions should not depend on any implementation details. The definitions of the operations should include a specification of their semantics.

Provides user-interface with ADT.

Typically includes

  1. Data structures: constants, types, & variables accessible to user (although details may be hidden)

  2. Declarations of functions and procedures accessible to user (bodies not provided here).
May also include axioms specifying behavior "promised" by any implementation. The following is an algebraic specification of behavior (see text for details).

Ex:

        pop(push(S,x)) = S, 

if not empty(S) then push(pop(S), top(S)) = S

Data + Operations (+ possibly equations) = Algebra

Implementation (Representation):

Again from text:

Method for collecting the implementation details of the type and its operations (in one place), and of restricting access to these details by programs that use the data type. Provides details on all data structures (including some hidden to users) and bodies of all operations.

Note that ADT methodology is orthogonal to top-down design

How to represent ADT's in programming languages?

Three predominant concerns in language design:

Reusable modules to represent ADT's quite important.
Examine implementation in Simula 67, Ada, Modula 2, Clu, and ML..

Simula 67

Derived from Algol 60. Simulation language. The designers, Nygaard and Dahl, were just awarded the 2001 Turing Award in Computer Science.

Provided notion of class.

Ex.:
class vehicle(weight,maxload);
    real weight, maxload;
begin
    integer licenseno;      (* attributes of class instance *)
    real load;
    Boolean procedure tooheavy;
    tooheavy := weight + load > maxload;
    load := 0;      (* initialization code *)
end
Refer to objects through references:
    ref(vehicle) rv, pickup;
    rv1:- new vehicle(2000,2500);
    pickup:- rv1;       (* special assignment via sharing *)
    pickup.licenseno := 3747;
    pickup.load := pickup.load +150;
    if pickup.tooheavy then ...
Notice that attributes are available to all users.

Representation not hidden.

Come back to discuss subclasses later when discussing object-oriented languages.

Intermezzo: What are problems with defining a new type in terms of an old?

E.g., represent rationals as records (or ordered pairs) of integers.

  1. Representation might have several values that do not correspond to any values of the desired type (e.g., (3,0)).

  2. Representation might have multiple values corresponding to the same abstract value (e.g., (1,2), (2,4), etc.)

  3. Values of the new type can be confused with values of the representation type.

Abstract data type is one that is defined by group of operations (including constants) and (possibly) a set of equations. Set of values only defined indirectly as those values which can be generated by ops, starting from constructors or constants.

E.g., Stack defined by EmptyStack, push, pop, top, and empty operations and equations.

   pop(push(fst,rest)) = rest, 
   top(push(fst,rest)) = fst, 
   empty(EmptyStack) = true, 
   empty(push(fst,rest)) = false, 
   etc.
Key is representation is hidden.

Representing ADT's in programming languages

Ada (1980)

Designed via a U.S. DOD competition

Packages used to define abstract data types. Package together type, operations (& state) and hide rep. Provides support for parameterized packages (polymorphism)

package <package-name> is
    --  declarations of visible types, variables, constants, and subprograms
private
    --  complete definitions of private types and constants
end <package-name>;

package body <package-name> is
    -- definitions of local variables, types, and subprograms, and complete bodies for 
    -- subprograms declared in the specification part above.  Code for initialization
    -- and exception handlers
    end <package-name>;
Sample Program:

package VECT_PACKAGE is  -- declarations only
    type REAL_VECT is array (INTEGER range <>) of float;
    function SUM(V: in REAL_VECT) return FLOAT;
    procedure VECT_PRODUCT(V1,V2 : in REAL_VECT) return FLOAT;
    function MAX(V: in REAL_VECT) return FLOAT;
end VECT_PACKAGE ;

package body VECT_PACKAGE is  -- details of implementation
    function SUM(V: in REAL_VECT) return FLOAT is
        TEMP : FLOAT := 0.0;
    begin
        for I in V'FIRST..V'LAST loop
            TEMP:= TEMP + V(I);
        end loop;
        return TEMP;
    end;
        -- definitions of VECT_PRODUCT and MAX subprograms would appear here
end VECT_PACKAGE ;

with VECT_PACKAGE, TEXT_IO; -- used to make separately compiled package visible
procedure MAIN is
    use VECT_PACKAGE, TEXT_IO;  -- eliminates need for qualifiers
    package INT_IO is new INTEGER_IO(INTEGER); --instantiation of generic packages
    package REAL_IO is new FLOAT_IO(FLOAT);
    use INT_IO, REAL_IO;
    K: INTEGER range 0..99;
begin
    loop
        GET(K);
        exit when K<1;
        declare         -- start of block
            A : REAL_VECT(1..K);  -- provides subscript bounds
        begin
            for J in 1..K loop
                GET(A(J));
                PUT(A(J));
            end loop;
            PUT("SUM = ");
            PUT(SUM(A));      -- uses package function
        end; -- of block
    end loop;
end MAIN ;
SOPHISTICATED (generic) STACK EXAMPLE

Stack represented internally in package (closer to object-oriented than get w/ Modula 2 below)

generic
    length : Natural := 100;      -- generic parameters
    type element is private;
    -- only assignment and tests for = may be done on objects of "private" type 
    -- "limited private" is also available.
package stack is
    procedure push (X : in element);
    procedure pop (X: out element);
    function empty return boolean;
    stack_error : exception;
end stack;

package body stack is
    space   : array (1..length) of element;
    top : integer range 0..length := 0;

    procedure push (X : in element) is
    begin
        if full()  then 
            raise stack_error;
        else
            top := top + 1;
            space(top) := X;
        end if;
    end push;

    procedure pop (X: out element) is
    begin
        if empty() then 
            raise stack_error;
        else
            X := space(top);
            top := top - 1;
        end if;
    end pop;

    function empty return boolean is
    begin
        return (top = 0);
    end;

    function full return boolean is
    begin
        return (top = length);
    end;

	end stack;

Notice: Data structure of stack is entirely hidden from user - there is no object of type stack available to user.

How to use:

    package stack1 is new stack(20,integer);
    package stack2 is new stack(100, character);
        -- Note that this initializes length in both cases to 0
    use stack2;
    stack1.push(5)
    if not stack1.empty() then 
        stack1.pop(Z);
    endif;
    push('z');
Note: Package definition is very much like that of a record with procedures allowed as (non-updateable) fields. E.g.
        stack =  package
                         push : procedure (X : in element);
                         pop : procedure (X: out element);
                         empty : function return boolean;
                         stack_error : exception;
                     end package;

One of two key ideas behind object-oriented programming.

Can also have package where user can manipulate objects of type stack (external representation) like in Modula-2.

Advantage to external rep. is that can define array of stack, etc.

generic
	length : Natural := 100;
	type element is private; -- generic parameters
package stack is
	type stack is private;
	procedure make_empty (S : out stack);
	procedure push (S : in out stack; X : in element);
	procedure pop (S : in out stack; X: out element);
	function empty (S : stack)  return boolean;
	stack_error : exception;

private		
	type stack is record
		space	: array(1..length) of element;
		top	: integer range 0..length := 0;
	end record;
end stack;

package body stack is

	procedure make_empty (S : out stack);
	begin
		S.top := 0;
	end make_empty ;

	procedure push (S : in out stack; X : element) is
	begin
		if full(S)  then 
			raise stack_error;
		else
			S.top := S.top + 1;
			S.space(S.top) := X;
		end if;
	end push;

	procedure pop (S : in out stack; X: out element) is
	begin
		if empty(S) then 
			raise stack_error;
		else
			X := S.space(S.top);
			S.top := S.top - 1;
		end if;
	end pop;

	function empty(S : in out stack) return boolean is
	begin
		return (top = 0);
	end;

	function full(S : in out stack) return boolean is
	begin
		return (S.top = length);
	end;

	end stack;

Biggest problem is exposure of representation of ADT in private part of package spec.

Not available to user, but must recompile if change representation.

Important difference between the two definitions is that in the first, the ADT is accessible only via operations which belong to the object. Can think of the Stack as an "agent". In the second, there is a data type called stack, and the operations act upon the passive data. In the first one must ask the ADT nicely to perform an operation that it knows how to do. In the second, the operation is imposed on the passive data.

Modula-2

Modula (modular language) designed by Wirth in 1975 for programming small real-time control systems (no files, sets, or pointers)

Modula 2 is 1980 revision (influenced by Mesa at Xerox PARC) intended to synthesize systems programming with general purpose language supporting modern software engineering.

(operating system for Lilith microcomputer written in Modula 2)

  1. Minor changes to Pascal which simplify programming (reliability) and improve program readability and efficiency.

  2. Upward extension of Pascal to support large system design projects. (Modules which can be separately compiled and yet are type checked.)

  3. Downward extension to allow machine-level programming and supports coroutines.

Sample program

DEFINITION MODULE stackMod;
IMPORT element FROM elementMod;
	TYPE stack;
	PROCEDURE make_empty (VAR S : stack);
	PROCEDURE push (VAR S : stack; X : element);
	PROCEDURE pop (VAR S : stack; X: element);
	PROCEDURE empty (S : stack): BOOLEAN;

END stackMod.

IMPLEMENTATION MODULE stackMod;
	TYPE stack = POINTER TO RECORD
		space	: array[1..length] of element;
		top	: INTEGER;
	END;

	PROCEDURE make_empty (VAR S : stack);
	BEGIN
		S^.top := 0;
	END make_empty ;

	...
END stackMod;

Opaque types (those declared without definition in Definition module) must be pointers or take no more space than pointers.

Compare and contrast Modula-2 and Ada on supporting abstract data types.

Clu (1974)

Cluster is basis of support for abstract data types.

Provides both packaging and hiding of representation

(cvt used to go back and forth btn external abstract type and internal representation).

May have parameterized clusters where specify needed properties of type paramenter. E.g.,

	sorted_bag = cluster [t : type] is create, insert, ...
			where t has
				lt, equal : proctype (t,t) returns (bool);
Abstraction facilities described in Liskov et al. paper in collection on reserve shelf.

Biggest difference from Ada and Modula-2 is that cluster is a type. Therefore can create multiple copies. Elements of cluster types are held as implicit references.

ML

ADT supported in very straightforward way in ML.

Provides for encapsulation and information hiding

Example:

abstype intstack = mkstack of (int list)
  with exception stackUnderflow
    val emptyStk = mkstack []
    fun push (e:int) (mkstack(s):intstack) = mkstack(e::s)
    fun pop (mkstack([])) = raise stackUnderflow
      | pop (mkstack(e::s)) = mkstack(s)
    fun top (mkstack([])) = raise stackUnderflow
      | top (mkstack(e::s)) = e
    fun IsEmpty (mkstack([])) = true
      | IsEmpty (mkstack(e::s)) = false
    end;

Generic stacks ADT:

abstype 'a stack = mkstack of ('a list)
  with exception stackUnderflow
    val emptyStk : 'a stack = mkstack []
    fun push (e:'a) (mkstack(s):'a stack) = mkstack(e::s)
    fun pop (mkstack([]):'a stack) = raise stackUnderflow
      | pop (mkstack(e::s):'a stack) = mkstack(s):'a stack
    fun top (mkstack([]):'a stack) = raise stackUnderflow
      | top (mkstack(e::s):'a stack) = e
    fun IsEmpty (mkstack([]):'a stack) = true
      | IsEmpty (mkstack(e::s):'a stack) = false
   end;

Cannot get at representation of stack

Reference to mkstack(l) will generate an error message.

Only access through constants and op's.

More sophisticated support through modules, which also support separate compilation. See Ullman's text for more details.


Back to:
  • CS 334 home page
  • Kim Bruce's home page
  • CS Department home page
  • kim@cs.williams.edu