introduction to ada95 volume 6 of 7 cop 4232: software systems development i dr. david a. workman...

59
Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I © Dr. David A. Workman School of EE and CS University of Central Florida May 1996, Revised August 2000 Volume Contents Tagged Types Type Extension (Derived Tagged Types) Private Tagged Types OO Class Hierarchies Active Program Abstraction Active Data Abstraction

Upload: quentin-miller

Post on 18-Jan-2018

215 views

Category:

Documents


0 download

DESCRIPTION

August 2000(c) Dr. David A. Workman198 Tagged Type Classes Tagged Type: T (private or non-private) Tagged Type: T (private or non-private) Extension : T1 non-private Extension : T1 non-private Extension: T2 private Extension: T2 private Extension: T12 non-private Extension: T12 non-private Extension: T21 private Extension: T21 private Extension: T13 non-private Extension: T13 non-private Extension: T11 non-private Extension: T11 non-private Derivation Class Rooted at T type derivation mechanism type inheritance mechanism Inheritance: A mechanism whereby the properties of one type can be reused (inherited) and/or redefined and/or extended in defining properties of a new type.

TRANSCRIPT

Page 1: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

Introduction to Ada95Volume 6 of 7

COP 4232: Software Systems Development I© Dr. David A. Workman

School of EE and CSUniversity of Central Florida

May 1996, Revised August 2000

Volume Contents• Tagged Types• Type Extension (Derived Tagged Types) • Private Tagged Types• OO Class Hierarchies• Active Program Abstraction • Active Data Abstraction

Page 2: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

Introduction to Ada95Tagged Types

COP 4232: Software Systems Development I© Dr. David A. Workman

School of EE and CSUniversity of Central Florida

May 1996, Revised August 2000

Page 3: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 3

Tagged Type Classes

Tagged Type: T(private or non-private)

Extension : T1non-private

Extension: T2private

Extension: T12non-private

Extension: T21private

Extension: T13non-private

Extension: T11non-private

Derivation ClassDerivation ClassRooted at TRooted at T

type derivationmechanism

type inheritancemechanism

Inheritance: A mechanism whereby the properties of onetype can be reused (inherited) and/or redefined and/or extendedin defining properties of a new type.

Page 4: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 4

Class-Wide Programming

Derivation ClassDerivation ClassRooted at TRooted at T

T’CLASS

T2

T

T1

T11 T12 T13 T21

T2’CLASST1’CLASS

T11’CLASS

X: T’CLASS := Create(A,B,C);-- T’CLASS is an indefinite type-- called a class-wide type.Y: T; Z: T1;begin X := Y; -- sometimes OK X:= Z; -- sometimes OK Y:= X; -- sometimes OK Z := X; -- sometimes OK Y:= Z; -- never OK Z := Y; -- never OK

Page 5: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 5

Tagged Types: Motivation

• MOTIVATION

In Ada83 we used discriminated types to “simulate” type extension. Consider the class of Aircraft we might model using the following types:

type Wing_Type is (Fixed, Rotary); type Engine_Type is ( Piston, Jet, Rocket ); type Aircraft( W:Wing_Type; E: Engine_Type) is record -- components common to all aircraft (cockpit, navigation system, fuel, landing gear, … ) case W is when Fixed => -- components common to all fixed wing aircraft case E is when Piston => -- components specific to propeller-driven aircraft when Jet => -- components specific to jet-driven aircraft when Rocket => -- components specific to rocket-driven aircraft end case;

when Rotary => -- components common to all helicopter-type aircraft. ...

end case; end record;

Page 6: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 6

Tagged Types: Motivation

• MOTIVATION In Ada95 tagged types and tagged extensions would be used instead of a single discriminanted type.

type Aircraft_Type is tagged record -- components common to all aircraft

end record; -- type Fixed_Wing is new Aircraft_Type with -- inherits components of Aircraft_Type record -- components common to all fixed wing aircraft

end record; -- type Piston_Type is new Fixed_Wing with -- inherits components of Aircraft_Type & Fixed_Wing

record -- components specific to propeller-driven crafts end record;

Page 7: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 7

Tagged Types: Benefits• BENEFITS

– Type extension is incremental. It can be done as need arises and new requirements become known. Clients of all previous types remain unaffected by the change.

– Operations meaningful only to a given extension can be defined. In Ada83, operations specific to a given subclass would have to be defined for Aircraft_Type and exceptions raised if the specific instance did not have the right discriminant values.

– Each extension can be encapsulated in its own program unit enhancing maintainability and reuse potential.

Page 8: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 8

Tagged Type Declarations

• NON-DISCRIMINATED, NON-PRIVATE

type Type-Name is [abstract] tagged [limited] Record-Definition;

Record-Definition => record Component-Declarations end record => null record

Component-Declaration => Ident {, Ident }* : Component-Subtype [:= Expression]; => null ;

Component-Subtype => [ aliased ] Subtype_Mark [ Constraint ]

RULES:(1) All subtypes of a non-disciminated record type are both constrained and definite.

(2) Components of a record type cannot be indefinite; they must belong to a definite subtype, or else they must be declared with a constraint (range, index, or discriminant) or with an initial value expression.

[3] A tagged record type is limited if and only if the word limited appears in its definition; tagged types cannot be implicitly declared limited by having limited components.

Page 9: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 9

Tagged Type Declarations• NON-DISCRIMINATED, NON-PRIVATE

type Type-Name is [abstract] tagged [limited] Record-Definition;

Record-Definition => record Component-Declarations end record => null record

Component-Declaration => Ident {, Ident }* : Component-Subtype [:= Expression]; => null ;

Component-Subtype => [ aliased ] Subtype_Mark [ Constraint ]

RULES:(4) Limited components of a record type cannot specify default value expressions.

(5) The value of a record type can be specified by an aggregate unless the record type is limited.

(6) Record components declared aliased can be designated by the ‘ACCESS attribute to produce an access value of the class General-Variable-Access (or General-access-to-variable).

[7] An abstract record type must also be tagged; no objects can be created for abstract types.

[8] Tagged types can be extended with additional discriminants and/or components through type derivation.

Page 10: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 10

Tagged Types: Examples• NON-DISCRIMINATED

type Personnel is tagged limited -- A record type can be declared limited without having limited components. The converse is not true -- for tagged types. Assignment to non-limited components of a limited type is permitted!

record Name: STRING(1..25) := (others => ‘ ’); Salary: Money range 0.0..250_000.0 := 0.0;

end record;

type Object_Name is abstract tagged null record;

--Type extension is accomplished through type derivation. Although derived types will be addressed in -- detail later, the example below illustrates how this would be accomplished.

type Manager is new Personnel with record Department: Department_Type; end record;

-- This declares a new tagged type, Manager, to be derived from Personnel with an additional -- component, Department. Manager inherits components Name and Salary from Personnel as well as -- any of its primitive operations. type Ceo_Type is new Manager with null record; -- Every type derived from a tagged type must have a record extension part.

Page 11: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 11

Tagged Type Declarations

• DISCIMINATED, NON-PRIVATE

type Type-Name ( Descriminant-Part ) is [ abstract ] tagged [ limited ] Record-Definition;

Discriminant-Part => Discrminant-Decl {; Discrminant-Decl }* -- Known Discriminants (KD)

Discrminant-Decl => Ident {, Ident }*: Subtype-Mark -- normal definition => Ident {, Ident }*: access Subtype-Mark -- access definition

Record-Definition => record Component-List end record

Component-List => Component-Item { Component-Item }* => { Component-Item }* Variant-Part => null ;

Component-Item => Component-Decl | Representation-Clause

Variant-Part => case Discriminant-Name is Variant { Variant }* end case;Variant => when Choice ( | Choice }* => Component-ListChoice => Discrete-Expression | Discrete-Range | others

Page 12: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 12

Tagged Type Declarations• DISCRIMINATED, NON-PRIVATE

RULES:(1) Normal discriminants must belong to a named discrete or named access subtype.

(2) Access discriminants belong to an anonymous general access-to-variable subtype, where the

Subtype-Mark can denote any subtype.

(3) Access discriminants are permitted only if the record type itself is declared limited, or if an ancestor type is limited (derived types only).

[4] For non-tagged types, discriminants can be initialized by default, but if one is initialized by default, they all must be; the first subtype of such a type is then said to be a definite subtype. For tagged types, discriminants cannot have defaults. Thus their first subtype is indefinite.

Page 13: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 13

Tagged Types: Examples

-- RULES (1,2,3)

subtype Option_Type is INTEGER range 1..3; -- A discrete subtype.type String_Ptr is access STRING; -- An unconstrained access type.type T( Option: Option_Type; -- ordinary discriminant Name : String_Ptr; -- ordinary discriminant Data : access STRING -- access discriminant (allowed only for limited types) ) is tagged limited record … end record;

-- RULE [4]: Discriminants for tagged types cannot be initialized by default. T is therefore-- an indefinite type.

My_Name : aliased STRING := “David A. Workman”;T_Object : T( Option => 2, Name := new STRING’(“OB1”), Data => My_Name’ACCESS );

-- T_Object is immutable - its discriminants can never be changed.

Page 14: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 14

Tagged Type Declarations• DISCRIMINATED, NON-PRIVATE

RULES:(5) The names of all components must be unique; this includes discriminants.

(6) Discriminants cannot appear in the default Expression of another discriminant. (Applies only to non-tagged types.)

(7) A discriminant can be used to govern a Variant, or as a bound in an index constraint, or as a discriminant value in a discriminant constraint that is part of a non-discriminant component declaration. In these contexts the discriminant must appear alone and not as part of a larger expression.

(8) A discriminant can be used in an initializer expression of another component not dependent upon that discriminant.

(9) Variables of a definite discriminated record type can be constrained (immutable) or uncon-strained (mutable), while variables of an indefinite subtype must be constrained (immutable). However, discriminants of an unconstrained (mutable) variable cannot be changed individually,they can only be changed by assigning a complete value to the variable where all components (including known discriminants) are given new values.

Page 15: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 15

Tagged Types: Examples• ABSTRACT & EXTENSIONS

type Operator_Type is (‘-’,’+’,’*’,’/’,’&’,’?’); type Arity is (Unary, Binary, Ternary); type Tree_Type is abstract tagged null record; -- Abstract tagged type type Tree_Ptr is access Tree_Type’Class; -- Class-Wide access type type Oper_Node(Mode: Arity) is new Tree_Type -- Extension to Tree_Type with record -- Non-private record extension with Discriminant Op: Operator_Type; case Mode is when Unary => Operand: Tree_Ptr;

when Binary => Left, Right: Tree_Ptr; when Trinary => First, Second, Third: Tree_Ptr; end case; end record; type Oprnd_Node is new Tree_Type with record -- Extension with no Discriminant Data: FLOAT := 0.0; end record;

Page 16: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 16

Tagged Types: ExampleContinued ...

Oprnd_Node

Tag

Data

Oper_Node

Tag

Op

Operand Left

Right

First

Second

Third

Tree_Node

Tag

Page 17: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

Introduction to Ada95Type Extensions

COP 4232: Software Systems Development I© Dr. David A. Workman

School of EE and CSUniversity of Central Florida

May 1996, Revised August 2000

Page 18: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 18

Type Extension: Declarations

• DEFINITION: NON-PRIVATE EXTENSIONS

type Derived-Type [( Known-Discriminants )] is [abstract] new Parent-Subtype with Record-Extension;

RULES:

(1a) A derived type defines a new type and its first subtype whose characteristics are derived from the Parent-Subtype. [1b] If the Parent-Subtype is a generic formal tagged type, the Derived-Type is an extension to the generic actual subtype.

(2) The Parent-Subtype shall be completely defined before its use in a derived type declaration; no incomplete parent types are permitted.

Page 19: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 19

Type Extension: Declarations• NON-PRIVATE EXTENSIONS( continued )

type Derived-Type [( Known-Discriminants )] is [abstract] new Parent-Subtype with Record-Extension ;

RULES:

[3a] A derived type is tagged (limited) if and only if the parent type is tagged (limited).

[3b] A Record-Extension and/or the word abstract can be specified only if the parent type is tagged. Furthermore, if the parent type is tagged, then every type derived from it must be declared with a (possibly null) record extension part; for private extensions, this rule applies to the full view of the derived type.

[4a] A type extension declaration cannot have an accessibility (nesting) level statically deeper than its parent.

[4b] Furthermore, a type declared in a generic package declaration cannot be extended in the body.

[5] Components of the Record-Extension (if any) must be of a definite subtype and cannot be limited unless the Parent-Subtype is limited.

Page 20: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 20

Type Extensions: Example• RULE [4a]: the type extension cannot be statically nested deeper than its

parent.

procedure Main is type Alpha is tagged null record; -- The parent type (has no components). type Alpha_Ptr is access Alpha’CLASS; P: Alpha_Ptr;

begin Nested; -- Sets P to a value of type Beta. … P ...end Main;

procedure Nested is type Beta is new Alpha with record ... end record; Declared-operations-on-Beta X: Beta := …; begin … P := new Alpha’CLASS’(X); -- global pointer to a value of type Beta end Nested;

In Main, after the call to Nested, P points to a value whose type is not visible, nor defined.

Page 21: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 21

Type Extension Declarations

RULES: (continued)

[6a] If Known-Discriminants are declared for the derived type, then the parent type must be constrained and cannot have unknown discriminants.

[6b] If the parent type has unknown discriminants, then so does the derived type.

Discriminants of the parent type can be constrained by specifying a discriminant constraint as part of the Parent-Subtype. Such a constraint must, for each parent discriminant, force it to correspondto a discriminant of the derived type or fix its value by an expression not involving discriminants.

[7] Known discriminants of the derived type may be new discriminants, or they may be made to correspond to discriminants of the parent type as described in [6].

DEFINITION: A discriminant of the derived type is said to correspond to itself, or toany discriminants of the parent type that it constrains, and to the same discriminant of the parent type if it is inherited. The “corresponds to” relation is an equivalence relation being reflexive, symetric and transitive.

[8] If Known-Discriminants are not declared for the derived type, then any discriminants (and other components ) defined for the parent type are inherited exactly.

Page 22: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 22

Type Extensions: Summary

Discriminant Properties of Parent SubtypeND KD UD

Extension defines new non-discriminant components.

Derived type inherits alldiscriminants of Parent;

extension defines new non-discriminant components.

Derived type hasunknown discriminants.

Derived type defines newdiscriminants to govern

non-discriminantcomponents defined by the

extension.

Discriminants of Derived typereplace and possibly extend the

discriminants of Parent;extension defines new non-discriminant components.

Discriminants of Parent must beconstrained to a fixed value ormade to correspond to some

discriminant of Derived type.

Not Permitted

NOTE: In all defined cases, the Derived type inherits all non-discriminant components of Parent.

Dis

crim

inan

t Opt

ions

of D

eriv

ed T

ype

K

D

N

D

Page 23: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 23

Type Extension: Examples-- From earlier example ..subtype Option_Type is INTEGER range 1..3; -- A discrete subtype.type String_Ptr is access STRING; -- An unconstrained access type.type T( Option: Option_Type; Name : String_Ptr; Data: access STRING ) is tagged limited record … end record;

type Switch_Type is (Off, On );type A( Opt : Option_Type; Id: String_Ptr; Info: access STRING; Sw: Switch_Type ) is new T(Option => Opt, Name => Id, Data => Info) with record … end record;-- A is an extension to T with known discriminants. By rules [6a] & [7] , all discriminants of T -- must correspond to a discriminant of the derived type. The derived type may, as in this case, -- define additional discriminants (e.g. Sw). A inherits the non-discriminant components of T-- (as determined by the discriminant constraint) and defines additional non-discriminant -- components in the record extension part. A is limited (and tagged) because T is (rule [3a]).

type B is new T with record … end record;-- B is an extension that inherits all discriminants of T, it inherits all non-discriminant components-- of T and defines additional non-discriminant components as well. Rule [8].

type C is new T with null record;-- C is an extension of T that is an identical copy; it inherits all components (discriminants and non--- discriminants) of T exactly, and adds no additional components of either kind. The record -- extension part is required syntax (rule [3b]).

Page 24: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 24

Type Extension: Examples

type T( L: POSITIVE; B: BOOLEAN) is tagged record Name: STRING(1..L) := (others => ‘ ‘); case B is when TRUE => X: FLOAT := 0.0; when FALSE => I: INTEGER := -1; end case; end record;

subtype Op_Type is CHARACTER range ‘A’..’C’;type D( Len: POSITIVE; Option: Op_Type ) is new T(L => Len; B => FALSE) with record Total: NATURAL := 0; case Option is when ‘A’ => Alpha: INTEGER := 6; when others => null; end case; end record;

Len : POSITIVE; -- Corresponds to L of TB: BOOLEAN := FALSE; -- inherited from T but constrainedName: STRING(1..Len) := (others => ‘ ‘); -- inherited from TI: INTEGER := -1; -- Inherited from TOption: Op_Type; -- new discriminantTotal: NATURAL := 0; -- new component [ Alpha: INTEGER := 6; ] -- new component depends on Option

Structure of type D

Page 25: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 25

Type Extension: Examples

type T ( <> ) is tagged private;-- NOTE that T is non-limited private type.

type D is new T with record A,B : INTEGER := 0; end record;-- type D is an extension of T with unknown discriminants. All objects of type D must-- be initialized when they are created, but none of the components or discriminants inherited-- from T can be directly referenced after the object is creaated, only those declared in the-- extension part can be referenced.

X: T := … ;Y: T := … ;I : D := (X with A => 5, B => -4); -- extension aggregateJ: D := (Y with A => -10, B => 0 ); -- extension aggregatebegin I.A := J.B + I.B;

NOTE: types with unknown discriminants are of little, if any, valueunless they are limited private types.

Page 26: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 26

Type Extension DeclarationsRULES: (continued)

(9) For every predefined operator of the parent type, there is a corresponding operator of the derived type.

(10) The profile of an inherited primitive subprogram or enumeration literal is obtained by replacing each

subtype of parent type occurring in the profile of the operation by the corresponding derived subtype. (see ARM 3.4(18-22))

[11] For each user-defined primitive subprogram (other than “=“) of the parent type, there is a corresponding inherited primitive subprogram of the derived type whose profile is obtained according to (10).

[12] Conformant equality operators (“=“ and “/=“) are inherited except when the derived type defines a non-limited Record-Extension. In this case, the equality operators of the parent type are used to implement the predefined equality operators of the derived type in the following way:(a) for the subset of components corresponding to components of the parent type, the primitive equality operators of the parent type are used,(b) for all components of the record extension, on a component-by-component basis, the primitive equality operators associated with each component type are used, (c) for all other components of the derived type (e.g. new discriminants), the predefined equality operators determined by the component type are used.

Page 27: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 27

Type Extensions: Example

type Choice_Type is ( One, Two, Three );type Prize( Choice: Choice_Type) is tagged record -- full type of a tagged private type case Choice is when One => Jewels: Gem_Type := Pearl_Necklace; when Two => Money: Money_Type := Fifty; when Three => null; end case; end record;function “=“(X,Y: Prize) return BOOLEAN isbegin if X.Choice = Y.Choice then return TRUE; else return FALSE; end if;end “=“;---------------type Second_Prize (First_Choice, Second_Choice: Choice_Type ) is new Prize( Choice => First_Choice) with record case Second_Choice is when One => Food: Grocery_Type := Make_Grocery(“T_Bone_Steak”); when Two => Tickets: Ticket_Type := Disney_World; when Three => Cash: Money_Type := Bus_Fare; end case; end record;

X: Second_Prize( Three, One );Y: Second_Prize( Three, One);beginX.Food := Make_Grocery(“Caviar”);if X = Y then … end if;

Page 28: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

Introduction to Ada95Private Tagged Types

COP 4232: Software Systems Development I© Dr. David A. Workman

School of EE and CSUniversity of Central Florida

May 1996, Revised August 2000

Page 29: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 29

Private Tagged Types

• DEFINITIONS (a) type Type-Name [( Discriminant-part )] is Private-defn; -- new base type (b) type Type-Name [( Known-discriminants )] is Private-extn; -- private extension

Discriminant-part => Known-discriminants | <>Private-defn => [ abstract ] tagged [ limited ] privatePrivate-extn => [abstract] new Ancestor-Subtype with private

RULES:(1) The declaration of a private type gives a partial view of the type (the client’s view); it requires

completion by a full type declaration ( full view) in the private section of the declaring package. (2) Before the full view is completed, variables of the partial view cannot be declared or dynamically

allocated, nor can they be used in a generic instantiation.(3) If limited is used in (a), then all derived decendants of this partial view are also limited; a derived

private type declared in (b) is limited if its Ancestor-Subtype is limited.[4] If the partial view is non-limited, the full view must be non-limited. If the partial view is limited and

tagged, then the full view must be also. However, if the partial view is untagged and limited, the full view can be either limited or non-limited.

[5] If the partial view is tagged, the full view must also be tagged. However, if the partial view is not tagged, then the full view can be either tagged or untagged.

Page 30: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 30

Private Tagged Types

Partial ViewAttributes

Full ViewAttributes

~ L ~ L

L *L

T T

~ T *T

~T & L *T & *L

T & L T & L

Partial ViewAttributes

Full ViewAttributes

ND, D, C D, *C, KD or ND

KD, ~D, ~C(1)

KD (identical)~D, ~C

UD, ~D, ~C *D, *C, ND or KD

(1) Discriminants must be declared without defaults.

LegendLegendT (Tagged), L(Limited), D(Definite), C( Constrained),

ND (No Discriminants), KD( Known Discriminants), UD( Unknown Discriminants)

(a) Private Definitions

Page 31: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 31

Private ExtensionsRULES (Continued)

RULES (Continued)[6] The ancestor type shall be a specific tagged type.[7] The parent type of the extension (full view) shall be derived directly or indirectly from the ancestor

type. The parent type belongs to the derivation class of the ancestor type, but need not be the same as the parent type.

package Scope_Example is ... type T [( D )] is [ abstract ] new Ancestor-Subtype with private; -- partial view

...private … type T [( D )] is [ abstract ] new Parent-Subtype with record New-Components end record; -- full view ...end Scope_Example;

Immediate scopeof partial view.

Page 32: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 32

Private Extensions: Example

package One is type Alpha is tagged private; function “+”(X,Y: Alpha) return Alpha; …private type Alpha is tagged record A: INTEGER; end record;end One;

with One; use One;package Two is type Beta is new Alpha with private; function “-”(X,Y: Beta) return Beta; function “<“(X,Y: Beta) return BOOLEAN; …private type Beta is new Alpha with record B: INTEGER; end record;end Two;

with One, Two; use One, Two;package Three is type Gamma is new Alpha with private; function “-”(X,Y: Gamma) return Gamma; …private type Gamma is new Beta with record C: INTEGER; end record;end Threee;

package body Three isfunction “-”(X,Y: Gamma) return Gamma isbegin if Beta(Y) < Beta(X) then return Beta(X) - Beta(Y); else return Beta(Y) - Beta(X); end if;end “-”;end Threee;

Page 33: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 33

Private Extensions

RULES (Continued)

[8] If the Ancestor-Subtype imposes a discriminant constraint, then the Parent-Subtype shall impose a statically matching constraint.

[9] If the partial view of a tagged private extension has known discriminants, then (a) the full view shall have a fully conformant discriminant part, (b) the parent type must be constrained as described in rule [6] for non-private extensions, and (c) the ancestor type need not be constrained, but shall not have unknown discriminants.

[10] If the partial view of a tagged private extension has no discriminants, then: (a) the full view shall inherit any discriminants defined for the ancestor type, (b) the parent type shall be constrained if and only if the ancestor type is constrained, and (c) the full view shall define a definite subtype.

[11] The partial view of a private extension is treated as a composite type within its extended scope.

OPERATIONS(12) Operations defined for tagged private extensions follow the same rules that apply to non-tagged

private extensions.

Page 34: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 34

Private Extensions

Private Extension(Partial View)

Parent Subtype(Full View)

Ancestor Subtype(Partial View)

Inherits Propertiesand Operations ofAncestor [6]

Descendant of Ancestor (notnecessarily the same type) [7]

A Specific TaggedType [6]

If ND, it inheritsdiscriminants andconstraint of Ancestorsubtype.If KD, Ancestordiscriminants must bemade to correspond tothose defined in KD orthey must be constrainedby an expression.

Imposes a constraint thatstatically matches that ofAncestor subtype. [8]

Imposes a discriminantconstraint.

Page 35: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 35

Private Extensions

Private Extension(Partial View)

Parent Subtype(Full View)

Ancestor Subtype(Partial View)

KD [9]Discriminants eithergovern extension orcorrespond to discrimin-ants of AncestorT, *L(Ancestor), ~C, ~D,KD

Constraint staticallymatches that of AncestorT, {*L, *C, *D, ND or KD}of Ancestor

If ND, then C and D.If KD, then C and eachdiscriminant must eithercorrespond to a discrimin-ant of the partial view, ormust be specified by anexpression.T, *L, *C, *D, ND or KD

ND [10]

T, {*L, *C, *D , ND or KDor UD} of Ancestor

Inherits discriminants, ifany, from the Ancestor type.Is C if and only if Ancestoris C and has a staticallymatching constraint. [9b]T, {*L, *C, *D, ND or KDor UD} of Ancestor

T, *L, *C, *D, ND or KD orUD

Page 36: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

Introduction to Ada95OO Class Hierarchies

COP 4232: Software Systems Development I© Dr. David A. Workman

School of EE and CSUniversity of Central Florida

May 1996, Revised August 2000

Page 37: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 37

Class Hierarchies• PRINCIPLES

For passive class hierarchies:

– (1) The root class of an OO hierarchy should be implemented by a package that exports a tagged private type, optionally with discriminants, optionally limited, optionally abstract.

– (2) When possible, the Figurative method of data abstraction should be used implying that the private section should contain all details of the full type, rather than an access type designating a type hidden in the package body.

– (3) Descendant subclasses of the root class should be implemented as private extensions encapsulated by child packages. The ancestor of an extension should be the private type declared in the parent package.

– (4) Private extensions should declare discriminants if the ancestor does, and each discriminant of the ancestor should correspond to a discriminant of the extension (ancestor discriminants should not be inherited).

Page 38: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 38

Class Hierarchies• ROOT CLASS

package Collection_Pkg is type Class-name [ ( Discriminant-part ) ] is [ abstract ] tagged [limited] private;

private

type Class-name [ ( Discriminant-part ) ] is [ abstract ] tagged [limited] record ... end record;end Collection_Pkg;

OPTIONAL Context Clause. Declares reusableData Abstractions needed for Service parameters.

Exception declarations for Services.

OPTIONAL hidden declarations necessary todeclare the FULL Type.

FULL Type declaration is a tagged record type.

Subprogram and overloaded operator declarationsdenoting Service for the Collection_Type. Functionswith no parameters are used to represent constants of the Collection_Type.

OPTIONAL Abstraction-specific, non-private types and subtypes needed for Service parameters.

Page 39: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 39

Class Hierarchies• SUBCLASSES

package Parent.Child is type Class-name [ ( Discriminant-part ) ] is [ abstract ] new Parent-subtype with private;

private

type Class-name [ ( Discriminant-part ) ] is [ abstract ] new Parent-subtype with record ... end record;end Parent.Child;

OPTIONAL Context Clause. Declares reusableData Abstractions needed for Service parameters.

Exception declarations for Services.

OPTIONAL hidden declarations necessary todeclare the FULL Type.

FULL Type declaration is a record extension.

Subprogram and overloaded operator declarationsdenoting Service for the Collection_Type. Functionswith no parameters are used to represent constants of the Collection_Type.

OPTIONAL Abstraction-specific, non-private types and subtypes needed for Service parameters.

Page 40: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 40

Class Hierarchies: Example

package Ckout_Pkg is type Ckout_Type is abstract tagged private; type Item_Ptr is access Ckout_Type'CLASS;private type Ckout_Type is tagged null record;end Ckout_Pkg;

package Ckout_Pkg.Bars is type Bar_Type is new Ckout_Type with private;private type Bar_Type is new Ckout_Type with null record;end Ckout_Pkg.Bars;

next slide

Page 41: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 41

Class Hierarchies: Example

with Ada.Text_Io, Name_Pkg, Price_Pkg;package Ckout_Pkg.Groceries is type Grocery_Type is new Ckout_Type with private; ----------- Services function Make_Grocery( Name: in String; Price: in Price_Pkg.Price_Type) return Grocery_Type; function Name_Is (Grocery: in Grocery_Type ) return Name_Pkg.Name_Type; function Price_Is (Grocery: in Grocery_Type ) return Price_Pkg.Price_Type; procedure Get( File: in Ada.Text_Io.File_Type; Data: out Grocery_Type); procedure Get( Data: out Grocery_Type); procedure Put( File: in Ada.Text_Io.File_Type; Data: in Grocery_Type); procedure Put( Data: in Grocery_Type); ----------- Error Handling Grocery_Data_Error, Grocery_File_Error : exception;private type Grocery_Type is new Ckout_Type with record Name: Name_Pkg.Name_Type; Price: Price_Pkg.Price_Type; end record;end Ckout_Pkg.Groceries;

next slide

Page 42: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 42

Class Hierarchies: Example

with Price_Pkg;package Ckout_Pkg.Groceries.Produce is type Produce_Type is new Grocery_Type with private; type Ounces_Type is range 0..500; function Weight_Is( Item: Produce_Type) return Ounces_Type; function Price_Per_Lb( Item: Produce_Type) return Price_Pkg.Price_Type; function Make_Produce( Name: in String; Price: in Price_Pkg.Price_Type; -- per unit weight Weight:in Ounces_Type ) return Produce_Type; procedure Get( File: in Ada.Text_Io.File_Type; Data: out Produce_Type); procedure Get( Data: out Produce_Type); procedure Put( File: in Ada.Text_Io.File_Type; Data: in Produce_Type); procedure Put( Data: in Produce_Type); ----------- Error Handling Produce_Data_Error, Produce_File_Error : exception;private type Produce_Type is new Grocery_Type with record Weight: Ounces_Type; end record;end Ckout_Pkg.Groceries.Produce;

Page 43: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

Introduction to Ada95Active Data Abstractions(Protected & Task Types)

COP 4232: Software Systems Development I© Dr. David A. Workman

School of EE and CSUniversity of Central Florida

May 1996, Revised August 2000

Page 44: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 44

Active Program Abstractions• DESCRIPTION

The interface template for active abstractions is the same as their corresponding passive abstraction (see Methods #1,#4-#8). The implementation template (package body) for active program abstractions is different. The essential difference is that the object state is encapsulated by a protected object or by a task.

Protected Object: use this approach for modeling shared resources that behave as servers, that is, they only respond to requests from other system components, they never originate a processing action independently.

Task Object: use this approach for modeling agents or actors. These types of objects must, on occasion, initiate some processing activity in the system and consequently have oversight responsibility for seeing that it is completed. Agents may also provide services to other objects in addition to playing a management role within the system.

Methods #2 and #3

Page 45: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 45

Active Program Abstraction• IMPLEMENTATION TEMPLATE (Protected Unit Model)

Public Interface

Implementation Body

procedure

entry

function

protected unit

Encapsulated State

Method #2

Page 46: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 46

Method 2 Example• BAGGING BIN(Interface)

Method #2

with Bag_Pkg, Grocery_Pkg;package Store.Checkout_Station.Bagging_Bin is function Item_Count return NATURAL; function Bag_Count return NATURAL; procedure Add_Item( Item: in Grocery_Pkg.Item_Type ); procedure Remove_Item( Item: out Grocery_Pkg.Item_Type ); procedure New_Bag( Bag: out Bag_Pkg.Bag_Ptr ); procedure Add_To_Bag( Bag: in Bag_Pkg.Bag_Ptr; Item: in Grocery_Pkg.Item_Type ); procedure Remove_Bag( Bag: out Bag_Pkg.Bag_Type ); -- Error interface Bin_Underflow_Error : exception; -- raised by Remove_Item and Remove_Bagend Store.Checkout_Station.Bagging_Bin;

The Baggin_Bin is shared by the clerk and bagger. The clerk may be adding items concurrentlywith access by the bagger who is adding empty bags, removing items, additng items to bags, and removing bags.

Page 47: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 47

Method 2 Example• BAGGING BIN (Implementation)

Method #2

with Item_List_Pkg, BagPtr_List_Pkg;package body Store.Checkout_Station.Bagging_Bin is protected Bin is function Item_Count return NATURAL; function Bag_Count return NATURAL; procedure Add_Item( Item: in Grocery_Pkg.Item_Type ); procedure Remove_Item( Item: out Grocery_Pkg.Item_Type ); procedure New_Bag( Bag: out Bag_Pkg.Bag_Ptr ); procedure Add_To_Bag( Bag: in Bag_Pkg.Bag_Ptr; Item: in Grocery_Pkg.Item_Type ); procedure Remove_Bag( Bag: out Bag_Pkg.Bag_Type );

private -- The encapsulated state of the protected object ! Item_List: Item_List_Pkg.List_Type; Bag_List : BagPtr_List_Pkg.List_Type; end Bin;

protected body Bin is separate; -- see next slide + 1

… Renames declarations for object services (see next slide)end Store.Checkout_Station.Bagging_Bin;

note!

Page 48: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 48

Method 2 Example• BAGGING BIN (Implementation)

Method #2

with Item_List_Pkg, BagPtr_List_Pkg;package body Store.Checkout_Station.Bagging_Bin is … see previous slide function Item_Count return NATURAL renames Bin.Item_Count; function Bag_Count return NATURAL renames Bin. Bag_Count; procedure Add_Item( Item: in Grocery_Pkg.Item_Type ) renames Bin.Add_Item; procedure Remove_Item( Item: out Grocery_Pkg.Item_Type ) renames Bin.Remove_Item; procedure New_Bag( Bag: out Bag_Pkg.Bag_Ptr ) renames Bin.New_Bag; procedure Add_To_Bag( Bag: in Bag_Pkg.Bag_Ptr; Item: in Grocery_Pkg.Item_Type )

renames Bin.Add_To_Bag; procedure Remove_Bag( Bag: out Bag_Pkg.Bag_Type ) renames Bin.Remove_Bag;end Store.Checkout_Station.Bagging_Bin;

Page 49: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 49

Method 2 Example• BAGGING BIN (Implementation)

Method #2

separate (Store.Checkout_Station.Bagging_Bin )protected body Bin is function Item_Count return NATURAL is begin return Item_List_Pkg.List_Size( Item_List ); -- reference to the protected component (Item_List) end Item_Count; ----------- function Bag_Count return NATURAL is … end Bag_Count; procedure Add_Item( Item: in Grocery_Pkg.Item_Type ) is … end Add_Item; procedure Remove_Item( Item: out Grocery_Pkg.Item_Type ) is ... end Remove_Item; ------------- procedure New_Bag( Bag: out Bag_Pkg.Bag_Ptr ) is begin BagPtr_List_Pkg.Add_Last(Bag_List, new BagPtr_List_Pkg.List_Type); end New_Bag; ------------- procedure Add_To_Bag( Bag: in Bag_Pkg.Bag_Ptr; Item: in Grocery_Pkg.Item_Type )

is ... end Add_To_Bag; procedure Remove_Bag( Bag: out Bag_Pkg.Bag_Type ) is ... end Remove_Bag;end Bin;

Page 50: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 50

Active Program Abstraction• IMPLEMENTATION TEMPLATE (Task Model)

Public Interface

Implementation(Body)

procedure

entry

function

task

encapsulated state

Method #3

Page 51: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 51

Active Data Abstraction• IMPLEMENTATION TEMPLATE (Task Model)

procedure

entry

function

encapsulated state

Public Interface

Implementation(Body)

private task type

task instance

Page 52: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 52

Active Data Abstraction:Example• TALK SHOW

Consider the familiar experience of a talk radio program. Radio listeners call in to the program and compete for dedicated access to the program host. Listeners can be modeled by a class of active objects, while the host is modeled as a single active object, a shared resource among callers. Active abstractions must be used both for the host as well as the listener, since both parties play the role of “actor” at different times.

Our solution, then, is to use an active program abstraction to implement the host, and and active data abstraction to implement the listeners.

The next series of slides illustrates the Ada95 solution.

Page 53: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 53

Active Abstractions: Example

package Listener_Pkg is type Listener_Type is limited private; type Listener_Ptr is access all Listener_Type; procedure Create(Person: in out Listener_Ptr ); -- In CLIENT write: -- X: aliased Listener_Type; -- Create(X'Access); -- OR -- X: Listener_Ptr := new Listener_Type; -- Create(X); procedure Speak (Person: in Listener_Type; Msg: in STRING); Protocol_Error: exception;private -- FIGURATIVE METHOD! type Controller; type Controller_Ptr is access Controller; -- function Create return Controller_Ptr; type Listener_Type is limited record Name: Controller_Ptr; -- Name: Controller_Ptr := Create(Listener_Type'ACCESS); end record;end Listener_Pkg;

Page 54: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 54

Active Abstractions: Example

with Listener_Pkg; use Listener_Pkg;package Host is type Pass_Type is limited private; procedure Call_In( Person: in Listener_Ptr; Pass: out Pass_Type); procedure Speak ( Pass: in Pass_Type; Msg: in STRING ); procedure Hang_Up( Pass: in Pass_Type ); Protocol_Error: exception;private type Pass_Type is MOD 2**16;end Host;

Page 55: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 55

Active Abstractions: Example

with Host, Text_Io, Ada.Exceptions; use Host, Text_Io, Ada.Exceptions;package body Listener_Pkg is task type Controller is entry Initialize( Person: in Listener_Ptr ); entry Speak ( Msg : in STRING ); end Controller; type String_Ptr is access STRING; ------------------------------------------ task body Controller is separate; --------- Methods ------------- procedure Create( Person: in out Listener_Ptr ) is begin if Person.Name /= NULL then raise Protocol_Error; end if; Person.Name := new Controller; Person.Name.Initialize( Person ); end Create; procedure Speak(Person: in Listener_Type; Msg: in STRING) is begin if Person.Name = NULL then raise Protocol_Error; end if; Person.Name.Speak(Msg); end Speak;end Listener_Pkg;

Page 56: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 56

Active Abstractions: Example

separate( Listener_Pkg )task body Controller is Self : Listener_Ptr; My_Name : STRING(1..10) := (others => ' '); N : NATURAL; In_Msg : String_Ptr; Password : Host.Pass_Type; begin

Put("What is my name? "); Get_Line(My_Name,N); -- From interactive user loop -- until the Host accepts the call. begin Host.Call_In(Self, Password); exit; exception when E: others => Ada.Text_Io.Put_Line(My_Name(1..N) & " Call_In failure:" & Exception_Message(E)); end; end loop;

Host.Speak(Password, My_Name(1..N) & ": Question 1"); Put_Line(In_Msg.ALL); -- Host’s response to my question. Host.Hang_Up(Password); Put_Line(My_Name & " TERMINATING!"); end Controller;

accept Initialize( Person: in Listener_Ptr ) do Self := Person; end Initialize;

accept Speak(Msg: in STRING ) do In_Msg := new STRING'(Msg); end Speak;

Page 57: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 57

Active Abstractions: Example

with Ada.Exceptions,Ada.Numerics.Float_Random, Ada.Text_Io; use Ada.Exceptions,Ada.Numerics.Float_Random;package body Host is task Controller is entry Call_In ( Person: in Listener_Ptr; Pass: out Pass_Type ); entry Speak ( Pass: in Pass_Type; Msg: in STRING ); entry Hang_Up( Pass: in Pass_Type); end Controller; -------------------- task body Controller is separate; -- Methods -------------------------- end Host;

procedure Call_In ( Person: in Listener_Ptr; Pass: out Pass_Type) isbegin Controller.Call_In (Person, Pass); end Call_In;

procedure Speak ( Pass: in Pass_Type; Msg: in STRING ) is begin Controller.Speak(Pass,Msg); end Speak;

procedure Hang_Up( Pass: in Pass_Type ) is begin Controller.Hang_Up(Pass); end Hang_Up;

Cannot define using renames declaration for

a body. Entries and subprograms are not

calling-convention conformant.

Page 58: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 58

Active Abstractions: Example

separate( Host )task body Controller is type String_Ptr is access constant STRING; type State_Type is (One, Two); begin Ada.Text_Io.Put_Line("HOST CONTROL is ON-LINE!"); loop select when Current_State = One => -- accept Call_In or -- accept Speak or -- accept Hang_up or delay 10.0; exit; end select; end loop; Ada.Text_Io.Put_Line("CENTRAL CONTROL is TERMINATING."); Ada.Text_Io.Flush; end Controller;

Current_State : State_Type := One;Current_Pass : Pass_Type := 0;Current_Person: Listener_Ptr;In_Msg,Out_Msg: String_Ptr;Brain : Generator;X : String_Ptr;YES : aliased constant STRING := "YES!"; NO : aliased constant STRING := "NO!";

if Random(Brain) > 0.5 then X := YES'Access; else X := NO'Access; end if;Out_Msg := new STRING'("ANSWER TO, """ & In_Msg.ALL & """, is " & X.ALL);Listener_Pkg.Speak(Current_Person.ALL,Out_Msg.ALL);

stateinfo

Page 59: Introduction to Ada95 Volume 6 of 7 COP 4232: Software Systems Development I  Dr. David A. Workman School of EE and CS University of Central Florida May

August 2000 (c) Dr. David A. Workman 59

Active Abstractions: Example

accept Call_In ( Person: in Listener_Ptr; Pass : out Pass_Type) do Current_Person := Person; Current_Pass := Current_Pass + 1; Pass := Current_Pass; Current_State := Two;end Sign_On;

accept Hang_Up( Pass: in Pass_Type) do if Pass = Current_Pass then Current_State := One; else Raise_Exception(Protocol_Error'IDENTITY, "Invalid Password! Please Sign ON."); end if;end Hang_Up;

accept Speak( Pass: in Pass_Type; Msg: in STRING ) do if Pass = Current_Pass then In_Msg := new STRING'(Msg); else Raise_Exception(Protocol_Error'IDENTITY, "Invalid Password! Please Sign ON."); end if;end Speak;